{-# LANGUAGE BangPatterns #-} import Control.Monad import Text.Printf import Data.Array import qualified Data.IntMap as IM type Pos = Int type Table = Array Pos (Pos, Integer) f :: Int -> Int -> Int -> [Integer] -> Integer f r k n gs = snd $ g r ! 0 where table1 :: Table table1 = mkTable k n gs g :: Int -> Table g 1 = table1 g r | even r = let t2 = g (r `div` 2) in compose t2 t2 | otherwise = compose (g (r - 1)) table1 mkTable :: Int -> Int -> [Integer] -> Table mkTable k n gs = array (0,n-1) [(pos, f pos) | pos <-[0..n-1]] where f :: Pos -> (Pos, Integer) f pos = ((pos+j) `mod` n, s) where (j,s) = case splitAt pos gs of (xs,ys) -> h 0 0 (ys ++ xs) h !j !s [] = (j,s) h !j !s (x:xs) | fromIntegral k < s + x = (j,s) | otherwise = h (j+1) (s + x) xs compose :: Table -> Table -> Table compose t1 t2 = array b $ do pos <- range b case t1 ! pos of (pos', s1) -> case t2 ! pos' of (pos'', s2) -> return (pos, (pos'', s1+s2)) where b = bounds t1 main :: IO () main = do t <- readLn forM_ [(1::Int)..t] $ \i -> do [r, k, n] <- liftM (map read . words) $ getLine gs <- liftM (map read . words) $ getLine printf "Case #%d: %d\n" i (f r k n gs)