結果
| 問題 |
No.50 おもちゃ箱
|
| コンテスト | |
| ユーザー |
|
| 提出日時 | 2021-08-21 15:19:12 |
| 言語 | Haskell (9.10.1) |
| 結果 |
WA
|
| 実行時間 | - |
| コード長 | 2,333 bytes |
| コンパイル時間 | 6,965 ms |
| コンパイル使用メモリ | 246,684 KB |
| 実行使用メモリ | 6,824 KB |
| 最終ジャッジ日時 | 2024-10-15 06:15:33 |
| 合計ジャッジ時間 | 8,124 ms |
|
ジャッジサーバーID (参考情報) |
judge3 / judge2 |
(要ログイン)
| ファイルパターン | 結果 |
|---|---|
| sample | AC * 1 WA * 3 |
| other | AC * 1 WA * 37 |
コンパイルメッセージ
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 #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
import Control.Monad
import Control.Monad.State
import Data.Bits
import qualified Data.ByteString.Char8 as BSC8
import Data.Char
import Data.Coerce
import qualified Data.Vector.Fusion.Stream.Monadic as VFSM
import qualified Data.Vector.Unboxed as VU
import qualified Data.Vector.Unboxed.Mutable as VUM
inf :: Int
inf = 1234567890
{-# INLINE inf #-}
main :: IO ()
main = do
n <- readLn :: IO Int
as <- seqInput n
m <- readLn :: IO Int
bs <- VU.reverse . bucketSort <$> seqInput m
dp <- VUM.unsafeNew ((1 :: Int) `unsafeShiftL` n) :: IO (VUM.IOVector (Int, Int))
VUM.unsafeWrite dp 0 (0, 0)
forM_ [0 .. ((1 :: Int) `unsafeShiftL` n - 1)] $ \s -> forM_ [0 .. (n - 1)] $ \i -> when (s .&. ((1 :: Int) `unsafeShiftL` i) == 0) $ do
(j, a) <- VUM.unsafeRead dp s
if (j < m) && (a + as VU.! i <= bs VU.! j)
then VUM.unsafeModify dp (min (j, a + as VU.! i)) (s + ((1 :: Int) `unsafeShiftL` i))
else when ((j + 1 < m) && (as VU.! i <= bs VU.! (j + 1))) $ VUM.unsafeModify dp (min (j + 1, as VU.! i)) (s + ((1 :: Int) `unsafeShiftL` i))
(ans, _) <- VUM.unsafeRead dp ((1 :: Int) `unsafeShiftL` n - 1)
if ans < m
then print $ ans + 1
else putStrLn "-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 #-}
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 #-}
bucketSort :: VU.Vector Int -> VU.Vector Int
bucketSort = VU.concatMap (uncurry $ flip VU.replicate) . VU.indexed . VU.unsafeAccumulate (+) (VU.replicate 21 0) . VU.map (,1)
{-# INLINE bucketSort #-}