結果
| 問題 |
No.40 多項式の割り算
|
| コンテスト | |
| ユーザー |
|
| 提出日時 | 2021-08-21 13:50:15 |
| 言語 | Haskell (9.10.1) |
| 結果 |
AC
|
| 実行時間 | 3 ms / 5,000 ms |
| コード長 | 2,174 bytes |
| コンパイル時間 | 10,697 ms |
| コンパイル使用メモリ | 215,236 KB |
| 実行使用メモリ | 6,820 KB |
| 最終ジャッジ日時 | 2024-10-15 05:04:10 |
| 合計ジャッジ時間 | 11,863 ms |
|
ジャッジサーバーID (参考情報) |
judge3 / judge2 |
(要ログイン)
| ファイルパターン | 結果 |
|---|---|
| sample | AC * 3 |
| other | AC * 32 |
コンパイルメッセージ
Loaded package environment from /home/judge/.ghc/x86_64-linux-9.8.2/environments/default [1 of 2] Compiling Main ( Main.hs, Main.o ) [2 of 2] Linking a.out
ソースコード
{-# LANGUAGE BangPatterns #-}
import Control.Monad (when)
import Control.Monad.State (StateT (..))
import qualified Data.ByteString.Char8 as BSC8
import Data.Char (isSpace)
import Data.Coerce (coerce)
import qualified Data.List as L
import qualified Data.Vector.Fusion.Stream.Monadic as VFSM
import qualified Data.Vector.Unboxed as VU
import qualified Data.Vector.Unboxed.Mutable as VUM
main :: IO ()
main = do
d <- readLn :: IO Int
xs <- seqInput (d + 1)
a <- VU.unsafeThaw xs
rev' (d - 3) $ \i -> do
ai3 <- VUM.unsafeRead a (i + 3)
VUM.unsafeModify a (+ ai3) (i + 1)
VUM.unsafeWrite a (i + 3) 0
b <- VUM.unsafeNew 1 :: IO (VUM.IOVector Int)
rep' d $ \i -> do
ai <- VUM.unsafeRead a i
when (ai /= 0) $ VUM.unsafeWrite b 0 i
n <- VUM.unsafeRead b 0
print n
VU.unsafeFreeze a >>= putStrLn . L.unwords . L.map show . VU.toList . VU.take (n + 1)
return ()
type Parser a = StateT BSC8.ByteString Maybe a
runParser :: Parser a -> BSC8.ByteString -> Maybe (a, BSC8.ByteString)
runParser = runStateT
{-# INLINE runParser #-}
int :: Parser Int
int = coerce $ BSC8.readInt . BSC8.dropWhile isSpace
{-# INLINE int #-}
seqInput :: Int -> IO (VU.Vector Int)
seqInput n = VU.unfoldrN n (runParser int) <$> BSC8.getLine
{-# INLINE seqInput #-}
rep' :: Monad m => Int -> (Int -> m ()) -> m ()
rep' n = flip VFSM.mapM_ (stream 0 (n + 1))
{-# INLINE rep' #-}
stream :: Monad m => Int -> Int -> VFSM.Stream m Int
stream !l !r = VFSM.Stream step l
where
step x
| x < r = return $ VFSM.Yield x (x + 1)
| otherwise = return VFSM.Done
{-# INLINE [0] step #-}
{-# INLINE [1] stream #-}
rev' :: Monad m => Int -> (Int -> m ()) -> m ()
rev' n = flip VFSM.mapM_ (streamR 0 (n + 1))
{-# INLINE rev' #-}
streamR :: Monad m => Int -> Int -> VFSM.Stream m Int
streamR !l !r = VFSM.Stream step (r - 1)
where
step x
| x >= l = return $ VFSM.Yield x (x - 1)
| otherwise = return VFSM.Done
{-# INLINE [0] step #-}
{-# INLINE [1] streamR #-}