Submission #210390


Source Code Expand

{-# LANGUAGE MultiParamTypeClasses,FlexibleContexts,FlexibleInstances,TypeSynonymInstances,BangPatterns,RankNTypes,TupleSections #-}
import Control.Monad
import Control.Monad.ST
import Control.Applicative
import Control.Arrow
import Debug.Trace
import Text.Printf

import Data.List
import Data.Int
import Data.Bits
import Data.Maybe
import Data.Array.Unboxed
import Data.Array.ST
import qualified Data.Map as M
import qualified Data.Set as S
import qualified Data.ByteString.Char8 as B

readInt = fromJust . fmap fst . B.readInt
readInts = map readInt . B.words <$> B.getLine
readIntPair = l2p . map readInt . take 2 . B.words <$> B.getLine
readLns :: Read a => IO [a]
readLns = map read . words <$> getLine
cmpFst (a,_) (b,_) = compare a b
cmpSnd (_,a) (_,b) = compare a b
cmpLen a b = length a `compare` length b
swap (a,b) = (b,a)
l2p (a:b:_) = (a,b)
p2l (a,b) = [a,b]
itof :: Int -> Double
itof = fromIntegral
defaultArray :: (IArray a e,Ix i) => e -> (i,i) -> [(i,e)] -> a i e
defaultArray = accumArray $ curry snd
flatten :: [(a,[(b,c)])] -> [((a,b),c)]
flatten = (=<<) $ uncurry $ fmap . first . (,)
stepM_ :: Monad m => a -> (a -> Bool) -> (a -> a) -> (a -> m ()) -> m ()
stepM_ i judge incr step = sub i where 
    sub i | judge i = step i >> sub (incr i) | otherwise = return ()
inf = maxBound `div` 2 :: Int

main = do
    s <- getLine
    print $ solve s

data Game = Game { combo :: Int
                 , kaburin :: Int
                 , score :: Integer
                 , tame  :: Int
                 , future :: [(Int,Int)] }deriving(Show)



solve :: String -> Integer
solve = step game
game = Game 0 5 0 0 []
step (Game c k s t f) [] = s
step g@(Game !c !k !s !t !f) (ch:cs) = step nxt2 cs where
    nxt1 = case ch of 
            'N' | k >= 1 && t == 0 -> Game c (k-1) (s + 10 + fromIntegral (div c 10))     0 ((7,1):f) 
            'C' | k >= 3 && t == 0 -> Game c (k-3) (s + 50 + 5 * fromIntegral (div c 10)) 3 ((9,3):f)
            _ -> Game c k s t f
    nxt2 = nxt1 { combo = c + length (filter ((==6).fst) f)
                , tame = max 0 (tame nxt1 - 1)
                , future = [(x-1,n) | (x,n) <- future nxt1, x > 1 ]
                , kaburin = kaburin nxt1 + sum (map snd (filter ((==1).fst) f)) }

Submission Info

Submission Time
Task B - かぶりん!
User autotaker
Language Haskell (GHC 7.4.1)
Score 50
Code Size 2299 Byte
Status AC
Exec Time 652 ms
Memory 49824 KB

Judge Result

Set Name All
Score / Max Score 50 / 50
Status
AC × 97
Set Name Test Cases
All 00_sample00.txt, 00_sample01.txt, 00_sample02.txt, 00_small00.txt, 00_small01.txt, 00_small02.txt, 00_small03.txt, 00_small04.txt, 00_small05.txt, 00_small06.txt, 00_small07.txt, 00_small08.txt, 00_small09.txt, 00_small10.txt, 00_small11.txt, 00_small12.txt, 00_small13.txt, 00_small14.txt, 00_small15.txt, 00_small16.txt, 00_small17.txt, 00_small18.txt, 00_small19.txt, 00_small20.txt, 00_small21.txt, 00_small22.txt, 00_small23.txt, 00_small24.txt, 00_small25.txt, 00_small26.txt, 00_small27.txt, 00_small28.txt, 00_small29.txt, 01_medium00.txt, 01_medium01.txt, 01_medium02.txt, 01_medium03.txt, 01_medium04.txt, 01_medium05.txt, 01_medium06.txt, 01_medium07.txt, 01_medium08.txt, 01_medium09.txt, 01_medium10.txt, 01_medium11.txt, 01_medium12.txt, 01_medium13.txt, 01_medium14.txt, 01_medium15.txt, 01_medium16.txt, 01_medium17.txt, 01_medium18.txt, 01_medium19.txt, 01_medium20.txt, 01_medium21.txt, 01_medium22.txt, 01_medium23.txt, 01_medium24.txt, 01_medium25.txt, 01_medium26.txt, 01_medium27.txt, 01_medium28.txt, 01_medium29.txt, 02_large00.txt, 02_large01.txt, 02_large02.txt, 02_large03.txt, 02_large04.txt, 02_large05.txt, 02_large06.txt, 02_large07.txt, 02_large08.txt, 02_large09.txt, 02_large10.txt, 02_large11.txt, 02_large12.txt, 02_large13.txt, 02_large14.txt, 02_large15.txt, 02_large16.txt, 02_large17.txt, 02_large18.txt, 02_large19.txt, 02_large20.txt, 02_large21.txt, 02_large22.txt, 02_large23.txt, 02_large24.txt, 02_large25.txt, 02_large26.txt, 02_large27.txt, 02_large28.txt, 02_large29.txt, 03_manual00.txt, 03_manual01.txt, 03_manual02.txt, 03_manual03.txt
Case Name Status Exec Time Memory
00_sample00.txt AC 30 ms 1312 KB
00_sample01.txt AC 29 ms 1308 KB
00_sample02.txt AC 26 ms 1260 KB
00_small00.txt AC 29 ms 1308 KB
00_small01.txt AC 28 ms 1320 KB
00_small02.txt AC 26 ms 1312 KB
00_small03.txt AC 28 ms 1260 KB
00_small04.txt AC 28 ms 1308 KB
00_small05.txt AC 27 ms 1264 KB
00_small06.txt AC 26 ms 1308 KB
00_small07.txt AC 26 ms 1312 KB
00_small08.txt AC 27 ms 1308 KB
00_small09.txt AC 25 ms 1312 KB
00_small10.txt AC 26 ms 1308 KB
00_small11.txt AC 26 ms 1308 KB
00_small12.txt AC 27 ms 1308 KB
00_small13.txt AC 27 ms 1320 KB
00_small14.txt AC 27 ms 1432 KB
00_small15.txt AC 26 ms 1380 KB
00_small16.txt AC 25 ms 1312 KB
00_small17.txt AC 27 ms 1308 KB
00_small18.txt AC 27 ms 1268 KB
00_small19.txt AC 24 ms 1432 KB
00_small20.txt AC 25 ms 1316 KB
00_small21.txt AC 27 ms 1304 KB
00_small22.txt AC 27 ms 1308 KB
00_small23.txt AC 27 ms 1432 KB
00_small24.txt AC 27 ms 1308 KB
00_small25.txt AC 25 ms 1436 KB
00_small26.txt AC 25 ms 1308 KB
00_small27.txt AC 29 ms 1252 KB
00_small28.txt AC 26 ms 1312 KB
00_small29.txt AC 26 ms 1304 KB
01_medium00.txt AC 28 ms 1688 KB
01_medium01.txt AC 26 ms 1308 KB
01_medium02.txt AC 27 ms 1432 KB
01_medium03.txt AC 28 ms 1432 KB
01_medium04.txt AC 28 ms 1820 KB
01_medium05.txt AC 28 ms 1812 KB
01_medium06.txt AC 26 ms 1436 KB
01_medium07.txt AC 26 ms 1688 KB
01_medium08.txt AC 29 ms 1692 KB
01_medium09.txt AC 27 ms 1304 KB
01_medium10.txt AC 26 ms 1560 KB
01_medium11.txt AC 27 ms 1496 KB
01_medium12.txt AC 27 ms 1628 KB
01_medium13.txt AC 26 ms 1308 KB
01_medium14.txt AC 27 ms 1392 KB
01_medium15.txt AC 28 ms 1304 KB
01_medium16.txt AC 26 ms 1944 KB
01_medium17.txt AC 28 ms 1816 KB
01_medium18.txt AC 29 ms 1428 KB
01_medium19.txt AC 27 ms 1516 KB
01_medium20.txt AC 37 ms 1560 KB
01_medium21.txt AC 25 ms 1312 KB
01_medium22.txt AC 28 ms 1436 KB
01_medium23.txt AC 26 ms 1572 KB
01_medium24.txt AC 27 ms 1692 KB
01_medium25.txt AC 26 ms 1312 KB
01_medium26.txt AC 26 ms 1632 KB
01_medium27.txt AC 26 ms 1568 KB
01_medium28.txt AC 25 ms 1432 KB
01_medium29.txt AC 27 ms 1496 KB
02_large00.txt AC 370 ms 35032 KB
02_large01.txt AC 285 ms 27292 KB
02_large02.txt AC 160 ms 14360 KB
02_large03.txt AC 496 ms 47908 KB
02_large04.txt AC 274 ms 24984 KB
02_large05.txt AC 304 ms 29856 KB
02_large06.txt AC 103 ms 9692 KB
02_large07.txt AC 420 ms 39072 KB
02_large08.txt AC 314 ms 30880 KB
02_large09.txt AC 206 ms 19608 KB
02_large10.txt AC 505 ms 46496 KB
02_large11.txt AC 37 ms 2500 KB
02_large12.txt AC 70 ms 6300 KB
02_large13.txt AC 170 ms 15512 KB
02_large14.txt AC 272 ms 25756 KB
02_large15.txt AC 279 ms 27292 KB
02_large16.txt AC 338 ms 30876 KB
02_large17.txt AC 83 ms 7320 KB
02_large18.txt AC 184 ms 17564 KB
02_large19.txt AC 480 ms 45808 KB
02_large20.txt AC 36 ms 2720 KB
02_large21.txt AC 141 ms 13600 KB
02_large22.txt AC 54 ms 4764 KB
02_large23.txt AC 363 ms 36000 KB
02_large24.txt AC 162 ms 16540 KB
02_large25.txt AC 187 ms 17564 KB
02_large26.txt AC 82 ms 7324 KB
02_large27.txt AC 371 ms 35996 KB
02_large28.txt AC 252 ms 24348 KB
02_large29.txt AC 384 ms 37976 KB
03_manual00.txt AC 652 ms 49824 KB
03_manual01.txt AC 460 ms 49820 KB
03_manual02.txt AC 325 ms 44188 KB
03_manual03.txt AC 24 ms 1308 KB