[Haskell-cafe] Why is Haskell flagging this?

Ryan Ingram ryani.spam at gmail.com
Wed Dec 22 01:00:00 CET 2010


First, let's make some useful operations in your GeneratorState monad:

-- State :: (s -> (a,s)) -> State s a
-- random :: Random a => StdGen -> (a, StdGen)
genRandom :: Random a => GeneratorState a
genRandom = State random

-- similar
genRandomR :: Random a => (a,a) -> GeneratorState a
genRandomR = State . randomR

rollDie :: GeneratorState Int
rollDie = genRandomR (1,6)

roll2Dice :: GeneratorState Int
roll2Dice = liftM2 (+) die die

These can be used to simplify a lot of the code here.

  -- ryan


On Fri, Dec 17, 2010 at 5:55 PM, michael rice <nowgate at yahoo.com> wrote:

> 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 <leimy2k at gmail.com>* wrote:
>
>
> From: David Leimbach <leimy2k at gmail.com>
>
> Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
> To: "michael rice" <nowgate at yahoo.com>
> Cc: haskell-cafe at haskell.org, "Daniel Fischer" <
> daniel.is.fischer at googlemail.com>
> Date: Friday, December 17, 2010, 7:45 PM
>
>
> No problem.  Haskell is a different animal than even other functional
> languages in my experience, and it takes time to get used to the coolness in
> the type system, the lazy evaluation, the point free style, functional
> composition and all the other interesting techniques you now have at your
> fingertips for writing very expressive code :-).
>
> Do that for a while then go back to algol based languages, and wonder why
> the heck anyone uses those on purpose :-).  (yeah there's good reasons to
> use them, but it starts to feel confining)
>
> Dave
>
> On Fri, Dec 17, 2010 at 4:28 PM, michael rice <nowgate at yahoo.com<http://mc/compose?to=nowgate@yahoo.com>
> > wrote:
>
> Hi, all.
>
> Plenty of answers. Thank you.
>
> Putting the list in the IO monad was deliberate. Another one I was looking
> at was
>
> f :: String -> IO String
> f s = do return s
>
> main = do ios <- f "hello"
>           fmap tail ios
>
> which worked fine
>
> So, the big error was trying to add  1 + [1,2,3,4,5].
>
> I considered that I needed an additional fmap and thought I had tried
>
> fmap (fmap (1+)) iol
>
> but must have messed it up, because I got an error. I guess I was on the
> right track.
>
> I like to try various combinations to test my understanding. It's kind of
> embarrassing when I get stumped by something simple like this, but that's
> how one learns.
>
> Thanks again,
>
> Michael
>
> --- On Fri, 12/17/10, Daniel Fischer <daniel.is.fischer at googlemail.com<http://mc/compose?to=daniel.is.fischer@googlemail.com>>
> wrote:
>
>
>     From: Daniel Fischer <daniel.is.fischer at googlemail.com<http://mc/compose?to=daniel.is.fischer@googlemail.com>
> >
>     Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
>     To: haskell-cafe at haskell.org<http://mc/compose?to=haskell-cafe@haskell.org>
>     Cc: "michael rice" <nowgate at yahoo.com<http://mc/compose?to=nowgate@yahoo.com>
> >
>     Date: Friday, December 17, 2010, 4:24 PM
>
>
>     On Friday 17 December 2010 18:04:20, michael rice wrote:
>     > 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>
>
>
> --- On *Fri, 12/17/10, Daniel Fischer <daniel.is.fischer at googlemail.com<http://mc/compose?to=daniel.is.fischer@googlemail.com>
> >* wrote:
>
>
> From: Daniel Fischer <daniel.is.fischer at googlemail.com<http://mc/compose?to=daniel.is.fischer@googlemail.com>
> >
> Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
> To: haskell-cafe at haskell.org<http://mc/compose?to=haskell-cafe@haskell.org>
> Cc: "michael rice" <nowgate at yahoo.com<http://mc/compose?to=nowgate@yahoo.com>
> >
> Date: Friday, December 17, 2010, 4:24 PM
>
> On Friday 17 December 2010 18:04:20, michael rice wrote:
> > 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 at haskell.org <http://mc/compose?to=Haskell-Cafe@haskell.org>
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20101221/fdf285fb/attachment.htm>


More information about the Haskell-Cafe mailing list