{-# LANGUAGE BangPatterns #-} import Data.Array import qualified Data.IntMap as IM import qualified Data.IntSet as IS import Control.Monad (liftM, filterM, forM_) import Control.Monad.State import Text.Printf import System.IO digits :: Int -> Int -> [Int] digits !base = go where go 0 = [] go n = case n `divMod` base of (x,y) -> y : go x happyNumbers :: Int -> [Int] happyNumbers !base = evalState (filterM (f IS.empty) [2..]) (IM.singleton 1 True) where f :: IS.IntSet -> Int -> State (IM.IntMap Bool) Bool f s !n | IS.member n s = g s False >> return False | otherwise = do m <- get case IM.lookup n m of Just r -> g (IS.insert n s) r >> return r Nothing -> f (IS.insert n s) (sum [d*d | d <- digits base n]) g :: IS.IntSet -> Bool -> State (IM.IntMap Bool) () g s !b = modify $ \m -> IM.union m (IM.fromAscList [(x,b) | x <- IS.toAscList s, x <= 1000]) intersectAscList :: Ord a => [a] -> [a] -> [a] intersectAscList [] _ = [] intersectAscList _ [] = [] intersectAscList xxs@(x:xs) yys@(y:ys) = case x `compare` y of EQ -> x : intersectAscList xs ys LT -> intersectAscList xs yys GT -> intersectAscList xxs ys hss :: Array Int [Int] hss = array (2,10) [(i, happyNumbers i) | i<-[2..10]] findMinHappyNumber :: [Int] -> Int findMinHappyNumber bases = head $ foldr1 intersectAscList [hss!b | b<-bases] main :: IO () main = do n <- liftM read getLine forM_ [(1::Int)..n] $ \n -> do bs <- liftM (map read . words) getLine printf "Case #%d: %d\n" n (findMinHappyNumber bs) hFlush stdout