Difference between revisions of "Google Code Jam/Ugly Numbers"

From HaskellWiki
Jump to navigation Jump to search
Line 83: Line 83:
 
type Cache = Map String RCache -- memoized number counts for strings
 
type Cache = Map String RCache -- memoized number counts for strings
   
date :: (Integer -> Integer) -> Cache -> String -> Cache
+
date :: (Integer -> Integer) -> String -> Cache -> Cache
date comp cache ct@(c:cs) = insert ct (unionsWith (+) ns) cache where
+
date comp ct@(c:cs) cache = insert ct (unionsWith (+) ns) cache where
 
ns = do
 
ns = do
 
(t,i) <- uncurry zip $ (tails &&& inits) cs
 
(t,i) <- uncurry zip $ (tails &&& inits) cs
Line 94: Line 94:
 
solution :: String -> Integer
 
solution :: String -> Integer
 
solution x = sum . elems . filterWithKey (const . ugly) $ cache x ! x where
 
solution x = sum . elems . filterWithKey (const . ugly) $ cache x ! x where
cache = foldl (date compress) empty . tail . reverse . tails
+
cache = foldr (date compress) empty . inits . tails
   
 
main = enumFromTo (1::Int) <$> readLn >>= mapM_ doCase where
 
main = enumFromTo (1::Int) <$> readLn >>= mapM_ doCase where

Revision as of 08:57, 30 July 2008

Problem

Once upon a time in a strange situation, people called a number ugly if it was divisible by any of the one-digit primes (2, 3, 5 or 7). Thus, 14 is ugly, but 13 is fine. 39 is ugly, but 121 is not. Note that 0 is ugly. Also note that negative numbers can also be ugly; -14 and -39 are examples of such numbers.

One day on your free time, you are gazing at a string of digits, something like:

123456

You are amused by how many possibilities there are if you are allowed to insert plus or minus signs between the digits. For example you can make

1 + 234 - 5 + 6 = 236

which is ugly. Or

123 + 4 - 56 = 71

which is not ugly.

It is easy to count the number of different ways you can play with the digits: Between each two adjacent digits you may choose put a plus sign, a minus sign, or nothing. Therefore, if you start with D digits there are 3 ** (D-1) expressions you can make.

Note that it is fine to have leading zeros for a number. If the string is "01023", then "01023", "0+1-02+3" and "01-023" are legal expressions.

Your task is simple: Among the 3 ** (D-1) expressions, count how many of them evaluate to an ugly number.

Input

The first line of the input file contains the number of cases, N. Each test case will be a single line containing a non-empty string of decimal digits.

Output

For each test case, you should output a line

Case #X: Y

where X is the case number, starting from 1, and Y is the number of expressions that evaluate to an ugly number.

Limits

0 <= N <= 100.

The string in each test case will be non-empty and will contain only characters '0' through '9'.

Small dataset

Each string is no more than 13 characters long.

Large dataset

Each string is no more than 40 characters long.

Sample

Input

  • 4
  • 1
  • 9
  • 011
  • 12345

Output

  • Case #1: 0
  • Case #2: 1
  • Case #3: 6
  • Case #4: 64


import Prelude hiding (lookup) import Data.Map hiding (map) import Control.Arrow ((&&&)) import Data.List hiding (insert,lookup) import Text.Printf import Control.Applicative hiding (empty) uglys = [2,3,5,7] :: [Integer] compress = flip mod $ product uglys ugly x = any ((==0) . mod x) $ uglys type RCache = Map Integer Integer -- use a Map to have a nice unionsWith, when summarizing number counts type Cache = Map String RCache -- memoized number counts for strings date :: (Integer -> Integer) -> String -> Cache -> Cache date comp ct@(c:cs) cache = insert ct (unionsWith (+) ns) cache where ns = do (t,i) <- uncurry zip $ (tails &&& inits) cs let n = read $ c:i case lookup t cache of Nothing -> [singleton (comp n) 1] Just r -> map (\f -> mapKeys (comp . f n) r) [(-),(+)] solution :: String -> Integer solution x = sum . elems . filterWithKey (const . ugly) $ cache x ! x where cache = foldr (date compress) empty . inits . tails main = enumFromTo (1::Int) <$> readLn >>= mapM_ doCase where doCase i = getLine >>= putStrLn . printf "Case #%d: %d" i . solution