
Paul Graham refers to all those features as "orthogonality" ("On Lisp", pg. 63) and you're right, Haskell has it in spades, but it takes time to understand all of it and even more time to use it effectively. One almost needs a checklist.
But I think I'm catching on. I programmed this craps simulation last week. It's a problem from "Problems For Computer Solution", Gruenberger & Jaffray, 1965, The RAND Corp.
import Control.Monad.State
import System.Random
type GeneratorState = State StdGen
data Craps a = Roll a | Win a | Lose a deriving (Show)
f :: Craps [Int] -> GeneratorState (Craps [Int])
f (Roll []) = do g0 <- get
let (d1,g1) = randomR (1,6) g0
(d2,g2) = randomR (1,6) g1
t1 = d1+d2
put g2
case t1 of
2 -> return (Lose [t1])
3 -> return (Lose [t1])
7 -> return (Win [t1])
11 -> return (Win [t1])
_ -> do g2 <- get
let (d3,g3) = randomR (1,6) g2
(d4,g4) = randomR (1,6) g3
t2 = d3+d4
put g4
if t2 == t1
then do
return (Win [t1,t2])
else
if t2 == 7
then do
return (Lose [t1,t2])
else
f (Roll [t2,t1])
f (Roll l) = do g0 <- get
let (d1,g1) = randomR (1,6) g0
(d2,g2) = randomR (1,6) g1
t = d1+d2
if t == (last l)
then do
put g2
return (Win (reverse (t:l)))
else
if t == 7
then do
put g2
return (Lose (reverse (t:l)))
else do
put g2
f (Roll (t:l))
progressive (z@(x:xs),n) (Win _) = let b = x + (last xs)
in (init xs,n+b)
progressive (z@(x:xs),n) (Lose _) = let b = x + (last xs)
in (z ++ [b],n-b)
*Main> let r = evalState (sequence $ replicate 6 (f (Roll []))) (mkStdGen 987)
*Main> r
[Win [8,12,10,3,8],Win [5,9,10,11,12,11,8,9,5],Win [7],Lose [9,7],Win [5,5],Win [5,2,6,4,6,8,5]]
*Main> foldl progressive ([1..10],0) r
([6],49)
Function f generates the roll cycle outcomes which are then folded with the progressive betting system.
In the final answer, the [6] is what's left of the original betting list [1..10]. The betting list is used to determine the bet: always bet the (first + last) of betting list. If a win, delete the first and last. If a loss, add loss to end of betting list. The 49 is winnings, initially 0.
There's no explanation in the book of what should happen if the betting list becomes empty, or a singleton, but that could be fixed by making it longer.
Comments, criticism, and better ways of doing it are welcome.
Michael
--- On Fri, 12/17/10, David Leimbach
I don't understand this error message. Haskell appears not to understand that 1 is a Num.
Prelude> :t 1 1 :: (Num t) => t Prelude> :t [1,2,3,4,5]
[1,2,3,4,5] :: (Num t) => [t]
Prelude>
Michael
===================
f :: [Int] -> IO [Int] f lst = do return lst
main = do let lst = f [1,2,3,4,5]
fmap (+1) lst
The fmap is relative to IO, your code is equivalent to do let lst = (return [1,2,3,4,5]) fmap (+1) lst ~> fmap (+1) (return [1,2,3,4,5]) ~> do lst <- return [1,2,3,4,5] return $ (+1) lst but there's no instance Num [Int] in scope You probably meant do let lst = f [1,2,3,4,5] fmap (map (+1)) lst
===============================
Prelude> :l test [1 of 1] Compiling Main ( test.hs, interpreted
)
test.hs:5:17: No instance for (Num [Int]) arising from the literal `1' at test.hs:5:17 Possible fix: add an instance declaration for (Num [Int]) In the second argument of `(+)', namely `1'
In the first argument of `fmap', namely `(+ 1)' In the expression: fmap (+ 1) lst Failed, modules loaded: none. Prelude>
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe