|
|
Line 1: |
Line 1: |
− | __TOC__
| |
| | | |
− | == The problem ==
| |
− |
| |
− | Convert a list of number of pins knocked over by each ball into a final score for a game of ten pin bowling.
| |
− |
| |
− | == Solution by Eric Kidd ==
| |
− |
| |
− | [http://www.randomhacks.net/articles/2007/04/28/bowling-in-haskell On his blog]. This is a recursive solution.
| |
− |
| |
− | == Short Solution by Chris Kuklewicz ==
| |
− |
| |
− | <haskell>
| |
− | import Control.Monad.State
| |
− |
| |
− | score = sum . evalState (replicateM 10 (State scoreFrame))
| |
− | where scoreFrame (10:rest@(a:b:_)) = (10+a+b,rest)
| |
− | scoreFrame (x:y:rest) | x+y < 10 = (x+y,rest)
| |
− | | otherwise = (10+head rest,rest)
| |
− |
| |
− | score2 = fst . (!!10) . iterate addFrame . (,) 0
| |
− | where addFrame (total,10:rest@(a:b:_)) = (total+10+a+b ,rest)
| |
− | addFrame (total,x:y:rest) | x+y < 10 = (total+x+y ,rest)
| |
− | | otherwise = (total+x+y+head rest,rest)
| |
− | </haskell>
| |
− |
| |
− | == Solution by Chris Kuklewicz ==
| |
− |
| |
− | Listed here. This has a monad-using parser with inferred type:
| |
− | <haskell>StateT [Int] (Error String) Frame</haskell>
| |
− | The constraint that there are 10 frames is declared by using (replicateM 10). All invalid input lists should be recognized.
| |
− |
| |
− | <haskell>
| |
− | module Bowling(Frame(..),Game(..),toGame,toBalls,score) where
| |
− |
| |
− | import Control.Monad(replicateM,when)
| |
− | import Control.Monad.State(get,put,evalStateT,StateT(..))
| |
− | import Control.Monad.Error(throwError)
| |
− | import Data.Array.IArray(Array,(!),elems,listArray,inRange)
| |
− |
| |
− | -- | Representation of a finished Game of bowling
| |
− | data Game = Game { gameScore :: Int
| |
− | , tenFrames :: Array Int Frame }
| |
− | deriving (Show,Eq)
| |
− |
| |
− | -- | Compact representation of a Frame from a finished Game
| |
− | data Frame = Normal { frameScore, first, second :: Int}
| |
− | | Spare { frameScore, first :: Int}
| |
− | | Strike { frameScore, next :: Int}
| |
− | deriving (Show,Eq)
| |
− |
| |
− | -- | Convert a list of pins to a final score
| |
− | score :: [Int] -> Int
| |
− | score balls = case toGame balls of
| |
− | Left msg -> error msg
| |
− | Right g -> gameScore g
| |
− |
| |
− | -- | Convert a Game to a list of (list of pins) for each frame
| |
− | toBalls :: Game -> [[Int]]
| |
− | toBalls (Game {tenFrames = frames}) = map decode (elems frames) ++ final
| |
− | where decode (Normal {first=x,second=y}) = [x,y]
| |
− | decode (Spare {first=x}) = [x,10-x]
| |
− | decode (Strike {}) = [10]
| |
− | final = case (frames ! 10) of
| |
− | Normal {} -> []
| |
− | Spare {frameScore=s} -> [[s-10]]
| |
− | Strike {frameScore=s,next=10} -> [[10],[s-20]]
| |
− | Strike {frameScore=s,next=a} -> [[a,s-a-10]]
| |
− |
| |
− | -- | Try to convert a list of pins to a Game
| |
− | toGame :: [Int] -> Either String Game
| |
− | toGame balls = do
| |
− | frames <- parseFrames balls
| |
− | return $ Game { gameScore = sum (map frameScore frames)
| |
− | , tenFrames = listArray (1,10) frames
| |
− | }
| |
− |
| |
− | -- This will only return an error or a list of precisely 10 frames
| |
− | parseFrames balls = flip evalStateT balls $ do
| |
− | frames <- replicateM 10 (StateT parseFrame)
| |
− | remaining <- get
| |
− | case (last frames,remaining) of
| |
− | (Normal {} , []) -> return frames
| |
− | (Spare {} , _:[]) -> return frames
| |
− | (Strike {} , _:_:[]) -> return frames
| |
− | _ -> err balls "Too many balls"
| |
− |
| |
− | parseFrame balls@(10:rest) = do
| |
− | case rest of
| |
− | (a:b:_) -> do
| |
− | checkBalls [a,b]
| |
− | when ((a /= 10) && (a+b > 10)) $
| |
− | err balls "More than 10 pins in frame after a strike"
| |
− | return (Strike (10+a+b) a,rest)
| |
− | _ -> err balls "Too few balls after a strike"
| |
− |
| |
− | parseFrame balls@(x:y:rest) = do
| |
− | checkBalls [x,y]
| |
− | case compare (x+y) 10 of
| |
− | GT -> err balls "More than 10 pins in a frame"
| |
− | LT -> return (Normal (x+y) x y,rest)
| |
− | EQ -> case rest of
| |
− | [] -> err balls "No ball after a spare"
| |
− | (a:_) -> do checkBall a
| |
− | return (Spare (10+a) x,rest)
| |
− |
| |
− | parseFrame balls = err balls "Not enough balls"
| |
− |
| |
− | err balls s = throwError (s ++ " : " ++ show (take 23 balls))
| |
− | checkBalls = mapM_ checkBall
| |
− | checkBall x = when (not (inRange (0,10) x))
| |
− | (throwError $ "Number of pins is of out range (0,10) : " ++ show x)
| |
− | </haskell>
| |
− |
| |
− | [[Category:Code]]
| |