Skip to content

Instantly share code, notes, and snippets.

@serafo27
Last active August 2, 2019 16:37
Show Gist options
  • Save serafo27/8759c9b8d7ba334e3028833c16c3ed5b to your computer and use it in GitHub Desktop.
Save serafo27/8759c9b8d7ba334e3028833c16c3ed5b to your computer and use it in GitHub Desktop.
Bowling kata haskell
module Bowling where
import Data.Char (digitToInt)
import Data.List.Split (splitOn)
toInt = digitToInt
data Score = Strike | Points Int Int | None | Spare Int
deriving (Eq, Show)
type Frame = (Int, Score)
parse :: String -> [Frame]
parse s = (zip [1..]) . (map toScore) $ framesString s
framesString :: String -> [String]
framesString = splitOn " "
toScore :: String -> Score
toScore "X" = Strike
toScore (x:"/") = Spare (toInt x)
toScore (x:"-") = Points (toInt x) 0
toScore ('-':xs) = Points 0 (toInt (head xs))
toScore s
| length s == 2 = Points (toInt (head s)) (toInt (last s))
| otherwise = None
calculate :: [Frame] -> Int
calculate [] = 0
calculate ((n, Strike):rest@((_, Strike):(_, Strike):xs))
| n <= 10 = 30 + calculate rest
| otherwise = 0
calculate ((n, Strike):xs)
| n <= 10 = 10 + calculate xs
calculate ((_, Points a b):xs) = (a+b) + calculate xs
calculate ((n, Spare _):rest@((_, Spare k):xs)) = (10+k) + calculate rest
calculate ((_, Spare k):rest@((_, Strike):xs)) = (10+10) + calculate rest
calculate ((_, Spare k):rest@((_, Points n _):xs)) = (10+n) + calculate rest
calculate _ = 0
module BowlingSpec where
import Test.Hspec
import Bowling
spec :: Spec
spec = do
describe "shoud split string in array of strings" $ do
it "parse only strike" $
parse "X X X" `shouldBe` [(1, Strike), (2, Strike), (3, Strike)]
it "only points" $
parse "91 64 12" `shouldBe` [(1, Points 9 1), (2, Points 6 4), (3, Points 1 2)]
it "points incomplete" $
parse "9- -4 1-" `shouldBe` [(1, Points 9 0), (2, Points 0 4), (3, Points 1 0)]
it "points with spare" $
parse "9/ 4/ 1/" `shouldBe` [(1, Spare 9), (2, Spare 4), (3, Spare 1)]
describe "calculate correct point from scores" $ do
it "only strike" $
calculate (allStrike 12) `shouldBe` 300
it "all miss" $
calculate (allNineMiss 10) `shouldBe` 90
it "all miss" $
calculate (allSpare 11) `shouldBe` 150
it "points incomplete" $
calculate [(1, Points 9 0), (2, Points 0 4), (3, Points 1 0)] `shouldBe` 14
it "mix" $
calculate [(1, Strike), (2, Points 0 4), (3, Points 1 0)] `shouldBe` 15
allStrike :: Int -> [Frame]
allStrike n = [(n, Strike) | n <- [1..n]]
allNineMiss :: Int -> [Frame]
allNineMiss n = [(n, Points 9 0) | n <- [1..n]]
allSpare :: Int -> [Frame]
allSpare n = [(n, Spare 5) | n <- [1..n]]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment