Commit 958e7551 by Stuart Kurtz

Day 21, with major part a cleanups and improved comments.

parent 22bed7cf
Showing with 17 additions and 28 deletions
module Main where
diracGame :: Int -> Int -> IO Int
diracGame startA startB = iter (1,0) 1 (startA,0) (startB,0) where
iter :: (Int,Int) -> Int -> (Int,Int) -> (Int,Int) -> IO Int
iter (die,dieRolls) currentPlayer (posA,scoreA) (posB,scoreB) = do
let r1 = roll die
r2 = roll r1
r3 = roll r2
nDieRolls = dieRolls + 3
let nPosA = ((posA + die + r1 + r2 - 1) `mod` 10) + 1
nScoreA = scoreA + nPosA
putStrLn $ "Player " ++ show currentPlayer ++ " rolls "
++ show die ++"+" ++ show r1 ++ "+" ++ show r2 ++
" and moves to space " ++ show nPosA ++
" for a total score of " ++ show nScoreA ++ "."
if nScoreA >= 1000
then do
let result = scoreB * nDieRolls
putStrLn $ "Result: " ++ show scoreB ++ " * " ++ show nDieRolls ++ " = " ++ show result
pure result
else
iter (r3,nDieRolls) (3-currentPlayer) (posB,scoreB) (nPosA,nScoreA)
roll :: Int -> Int
roll = (+1)
diracGame :: Int -> Int -> Int
diracGame startA startB = iter (1,0) (startA,0) (startB,0) where
iter (die,dieRolls) (posA,scoreA) (posB,scoreB)
| nScoreA >= 1000 = scoreB * nDieRolls
| otherwise = iter (die + 3,nDieRolls) (posB,scoreB) (nPosA,nScoreA)
where
dieSum = 3 * die + 3
nDieRolls = dieRolls + 3
nPosA = ((posA + dieSum- 1) `mod` 10) + 1
nScoreA = scoreA + nPosA
main :: IO ()
main = do
r <- diracGame 4 6
print r
main = print $ diracGame 4 6
......@@ -3,13 +3,18 @@ module Main where
import Data.Array ( Ix(range), Array, (!), array )
import qualified Data.Map as M
-- This is Pascal's triangle, mutatis mutandis.
-- Each entry has the form (value,n), where after three
-- die rolls, there will be n universes in which the sume
-- of the pips is value.
splits :: [(Int,Integer)]
splits = M.assocs $ roll 3 (M.singleton 0 1) where
roll :: Int -> M.Map Int Integer -> M.Map Int Integer
roll 0 m = m
roll n m = roll (n-1) . M.unionsWith (+) . map ((`M.mapKeys` m) . (+)) $ [1,2,3]
-- universes xScore xPos yScore yPos = (losers,winners)
-- universes (xScore,xPos,yScore,yPos) = (losers,winners)
-- where player X will make the next move.
universes :: Array (Int,Int,Int,Int) (Integer,Integer)
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or sign in to comment