Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-23 Thread Ryan Ingram
Haha, not exactly.

You can replace

sj - get
let (a, sk) = runState something sj
put sk

with

a - something

Also, you don't need do notation for single statements; do return x is
just return x


On Wed, Dec 22, 2010 at 7:21 PM, michael rice nowg...@yahoo.com wrote:

 Thanks for the tip, Ozgur. It worked for me. Is this what you had in mind,
 Ryan?

 Michael

 ==

 import Control.Monad.State.Lazy

 import Control.Monad
 import System.Random

 type GeneratorState = State StdGen
 data Craps a = Roll a | Win a | Lose a deriving (Show)

 genRandomR :: Random a = (a,a) - GeneratorState a
 genRandomR = state . randomR

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

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

 f :: Craps [Int] - GeneratorState (Craps [Int])
 f (Roll []) = do g0 - get
  let (throw1,g1) = runState roll2Dice g0
  put g1
  case throw1 of
 2 - return (Lose [throw1])
 3 - return (Lose [throw1])
 7 - return (Win [throw1])
 11 - return (Win [throw1])
 _ - do g1 - get
 let (throw2,g2) = runState roll2Dice g1
 put g2
 if throw2 == throw1
   then do return (Win [throw1,throw2])
   else
 if throw2 == 7
   then do return (Lose [throw1,throw2])
   else do f (Roll [throw1,throw2])
 f (Roll z@(throw1:throws)) = do g0 - get
 let (throw,g1) = runState roll2Dice g0
 put g1
 if throw == throw1
   then do return (Win (z ++ [throw]))
   else
 if throw == 7
   then do return (Lose (z ++ [throw]))
   else do f (Roll (z ++ [throw]))



 --- On *Wed, 12/22/10, Ozgur Akgun ozgurak...@gmail.com* wrote:


 From: Ozgur Akgun ozgurak...@gmail.com

 Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
 To: Ryan Ingram ryani.s...@gmail.com
 Cc: haskell-cafe@haskell.org, Daniel Fischer 
 daniel.is.fisc...@googlemail.com
 Date: Wednesday, December 22, 2010, 7:37 PM


 see also:
 http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Monad-State-Lazy.html#v:state

 On 22 December 2010 20:02, Ryan Ingram 
 ryani.s...@gmail.comhttp://mc/compose?to=ryani.s...@gmail.com
  wrote:

 Interesting.  In that case,

 state f = StateT $ \s - Identity (f s)

 allows state to replace State in that code.


 Ozgur

 -Inline Attachment Follows-


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org http://mc/compose?to=haskell-c...@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-22 Thread Ryan Ingram
Huh, that's weird, I just copy and pasted this into a new file and it worked
for me.

I did prepend the line

module RandTest where

  -- ryan

On Tue, Dec 21, 2010 at 6:43 PM, michael rice nowg...@yahoo.com wrote:

 I changed your die function to rollDie in function roll2Dice (I assume
 that's what you meant) but get the errors listed below.

 Michael

 

 import Control.Monad.State
 import Control.Monad

 import System.Random

 type GeneratorState = State 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 (+) rollDie rollDie

 ===

 Prelude :l craps7
 [1 of 1] Compiling Main ( craps7.hs, interpreted )

 craps7.hs:7:12: Not in scope: data constructor `State'

 craps7.hs:11:13: Not in scope: data constructor `State'

 Failed, modules loaded: none.
 Prelude


 --- On *Tue, 12/21/10, Ryan Ingram ryani.s...@gmail.com* wrote:


 From: Ryan Ingram ryani.s...@gmail.com

 Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
 To: michael rice nowg...@yahoo.com
 Cc: David Leimbach leim...@gmail.com, Daniel Fischer 
 daniel.is.fisc...@googlemail.com, haskell-cafe@haskell.org
 Date: Tuesday, December 21, 2010, 7:00 PM

 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 
 nowg...@yahoo.comhttp://mc/compose?to=nowg...@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

Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-22 Thread Daniel Fischer
On Wednesday 22 December 2010 12:03:01, Ryan Ingram wrote:
 Huh, that's weird, I just copy and pasted this into a new file and it
 worked for me.

As a guess, you have mtl-1.*?
In mtl-2.*, State s is made a type synonym for StateT s Identity, so 
there's no longer a data constructor State.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-22 Thread Ryan Ingram
Interesting.  In that case,

state f = StateT $ \s - Identity (f s)

allows state to replace State in that code.

On Wed, Dec 22, 2010 at 4:56 AM, Daniel Fischer
daniel.is.fisc...@googlemail.com wrote:
 On Wednesday 22 December 2010 12:03:01, Ryan Ingram wrote:
 Huh, that's weird, I just copy and pasted this into a new file and it
 worked for me.

 As a guess, you have mtl-1.*?
 In mtl-2.*, State s is made a type synonym for StateT s Identity, so
 there's no longer a data constructor State.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-22 Thread Ozgur Akgun
see also:
http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Monad-State-Lazy.html#v:state

On 22 December 2010 20:02, Ryan Ingram ryani.s...@gmail.com wrote:

 Interesting.  In that case,

 state f = StateT $ \s - Identity (f s)

 allows state to replace State in that code.


Ozgur
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-22 Thread michael rice
Thanks for the tip, Ozgur. It worked for me. Is this what you had in mind, Ryan?

Michael

==

import Control.Monad.State.Lazy
import Control.Monad
import System.Random

type GeneratorState = State StdGen
data Craps a = Roll a | Win a | Lose a deriving (Show)

genRandomR :: Random a = (a,a) - GeneratorState a
genRandomR = state . randomR

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

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

f :: Craps [Int] - GeneratorState (Craps [Int])
f (Roll []) = do g0 - get
 let (throw1,g1) = runState roll2Dice g0
 put g1
 case throw1 of
    2 - return (Lose [throw1])
    3 - return (Lose [throw1])
    7 - return (Win [throw1])
    11 - return (Win [throw1])
    _ - do g1 - get
    let (throw2,g2) = runState roll2Dice g1
    put g2
    if throw2 == throw1
  then do return (Win [throw1,throw2])
  else
    if throw2 == 7
  then do return (Lose [throw1,throw2])
  else do f (Roll [throw1,throw2])
f (Roll z@(throw1:throws)) = do g0 - get
    let (throw,g1) = runState roll2Dice g0
    put g1
    if throw == throw1
  then do return (Win (z ++ [throw]))
  else
    if throw == 7
  then do return (Lose (z ++ [throw]))
  else do f (Roll (z ++ [throw]))



--- On Wed, 12/22/10, Ozgur Akgun ozgurak...@gmail.com wrote:

From: Ozgur Akgun ozgurak...@gmail.com
Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
To: Ryan Ingram ryani.s...@gmail.com
Cc: haskell-cafe@haskell.org, Daniel Fischer 
daniel.is.fisc...@googlemail.com
Date: Wednesday, December 22, 2010, 7:37 PM

see 
also: http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Monad-State-Lazy.html#v:state


On 22 December 2010 20:02, Ryan Ingram ryani.s...@gmail.com wrote:

Interesting.  In that case,



state f = StateT $ \s - Identity (f s)



allows state to replace State in that code.
Ozgur

-Inline Attachment Follows-

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-21 Thread Ryan Ingram
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 nowg...@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 leim...@gmail.com* wrote:


 From: David Leimbach leim...@gmail.com

 Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
 To: michael rice nowg...@yahoo.com
 Cc: haskell-cafe@haskell.org, Daniel Fischer 
 daniel.is.fisc...@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 
 nowg...@yahoo.comhttp://mc/compose?to=nowg...@yahoo.com
  wrote:

 Hi, all.

 Plenty of answers. Thank you.

 Putting the list in the IO monad was deliberate. Another one I was looking

Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-21 Thread michael rice
Thanks, Ryan.

I rewrote it yesterday. Here's my updated version.

Better?

Michael

==

import Data.Functor (($))
import System.Random

data Craps a = Roll a | Win a | Lose a deriving (Show)

-- Returns an infinite list of die throws
rollDice :: IO [Int]
rollDice =  randomRs (1,6) $ newStdGen

-- fmap g rollDice - an infinite list of double dice throws.

g :: [Int] - [Int]
g (x:y:rest) = (x+y) : (g rest)

h :: Craps [Int] - [Int] - [Craps [Int]]
h (Roll []) (2:ys) = (Lose [2]) : (h (Roll []) ys)
h (Roll []) (3:ys) = (Lose [3]) : (h (Roll []) ys)
h (Roll []) (7:ys) = (Win [7]) : (h (Roll []) ys)
h (Roll []) (11:ys) = (Win [11]) : (h (Roll []) ys)
h (Roll []) (y:ys) = h (Roll [y]) ys 
h (Roll z@(x:xs)) (y:ys) = if y == 7
   then (Lose (z ++ [y])) : (h (Roll []) ys)
   else
 if x == y
   then (Win (z ++ [y])) : (h (Roll []) ys)
   else h (Roll (z ++ [y])) ys

progressive ((x:xs),won) (Win _) = let bet = x + (last xs)
   in (init xs,won+bet) 
progressive (z@(x:xs),won) (Lose _) = let bet = x + (last xs)
  in (z ++ [bet],won-bet) 
martingale (won,lost) (Win _) = let bet = max 1 (2*lost)
    in (won+bet,0)
martingale (won,lost) (Lose _) = let bet = max 1 (2*lost)
 in (won,lost+bet)

-- Play
 -- n : throw cycles
 -- f : betting system
 -- x : starting condition
playCraps n f x = let r = fmap ((take n) . (h (Roll [])) . g) rollDice
  in fmap (foldl f x) r

{-
*Main playCraps 5 progressive ([1..10],0)
([5,6,7],37)
*Main playCraps 5 martingale (0,0)
(7,1)
-}


--- On Tue, 12/21/10, Ryan Ingram ryani.s...@gmail.com wrote:

From: Ryan Ingram ryani.s...@gmail.com
Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
To: michael rice nowg...@yahoo.com
Cc: David Leimbach leim...@gmail.com, Daniel Fischer 
daniel.is.fisc...@googlemail.com, haskell-cafe@haskell.org
Date: Tuesday, December 21, 2010, 7:00 PM

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 nowg...@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

Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-21 Thread michael rice
I changed your die function to rollDie in function roll2Dice (I assume that's 
what you meant) but get the errors listed below.

Michael



import Control.Monad.State
import Control.Monad
import System.Random

type GeneratorState = State 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 (+) rollDie rollDie

===

Prelude :l craps7
[1 of 1] Compiling Main ( craps7.hs, interpreted )

craps7.hs:7:12: Not in scope: data constructor `State'

craps7.hs:11:13: Not in scope: data constructor `State'
Failed, modules loaded: none.
Prelude


--- On Tue, 12/21/10, Ryan Ingram ryani.s...@gmail.com wrote:

From: Ryan Ingram ryani.s...@gmail.com
Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
To: michael rice nowg...@yahoo.com
Cc: David Leimbach leim...@gmail.com, Daniel Fischer 
daniel.is.fisc...@googlemail.com, haskell-cafe@haskell.org
Date: Tuesday, December 21, 2010, 7:00 PM

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 nowg...@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

Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-18 Thread Christopher Wilson
On Fri, Dec 17, 2010 at 11:04 AM, michael rice nowg...@yahoo.com 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

 ===

 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


Excuse any inaccuracies, I'm somewhat new at Haskell myself, but what it
looks like is happening is that at the point in main where you've bound
lst, it will have type of IO [Int].  The signature for fmap is:

fmap :: (Functor f) = (a - b) - f a - f b

if you call fmap (+1) the next argument that fmap expects is something
that is in just one functor, for example, this

fmap (+1) [1,2,3,4,5]

works fine, but, something that is IO [Int] won't.  You can compose two
'fmap's to solve this:

:t (fmap.fmap)
(fmap.fmap)
  :: (Functor f, Functor f1) = (a - b) - f (f1 a) - f (f1 b)

which means that 'main' looks like:


main = do let lst = f [1, 2, 3, 4, 5]
  (fmap.fmap) (+1) lst


-- 
Chris Wilson christopher.j.wil...@gmail.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-18 Thread aditya siram
I think it is giving you the error because you the fmap in your code is
operating on the IO monad and not the List monad. In order to get it to
work, you can remove the IO layer with = as below:

f :: [Int] - IO [Int]
f lst = do return lst

main = do let lst = f [1,2,3,4,5]
  lst = return . fmap (+1)

Or you can not wrap the list in IO to begin with, my guess is that you wrote
'f' to make the compiler happy at some point in development:
main = do let lst = [1,2,3,4,5]
  return $ fmap (+1) lst

-deech

On Fri, Dec 17, 2010 at 11:04 AM, michael rice nowg...@yahoo.com 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

 ===

 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


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-18 Thread Antoine Latter
This is a bit tricky.

The type of 'f' is '[Int] - IO [Int]', which means that the type of 'lst'
is 'IO [Int]'.

So fmap (+1) tries to add one to the [Int] underneath the 'IO' type
constructor.

You can either use two 'fmap's, the first to lift up to IO and the second to
lift into the list, or you can use monad notation:

 do
   lst - f [1,2,3,4]
   return $ fmap (+1) lst

Does that make sense?

Take care,
Antoine

On Fri, Dec 17, 2010 at 11:04 AM, michael rice nowg...@yahoo.com 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

 ===

 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


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-18 Thread Mads Lindstrøm
Hi Michael

The type of lst is IO [Int] and therefore fmap (+1) applies (+1) to
the hole lists of integers, and not to each member of the list. That is:

fmap (+1) lst   =
fmap (+1) (return [1,2,3,4,5])  =
return ([1,2,3,4,5] + 1)

and you cannot say [1,2,3,4,5] + 1.

Does that make sense?

Maybe you want to say:

main = do let lst = [1,2,3,4,5]
  print $ map (+1) lst

/Mads

On Fri, 2010-12-17 at 09:04 -0800, 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
 
 ===
 
 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


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-18 Thread aditya siram
To make that a little clearer, here is code that uses two calls to fmap to
drill through two monadic layers:
f :: [Int] - IO [Int]
f lst = do return lst

main = do let lst = f [1,2,3,4,5]
  fmap (fmap (+1)) lst

So the order of operations is :
1. The first fmap converts an IO [Int] to [Int] and hands it off to the
second fmap
2. The second fmap applies the (+1) function to every element of the list.
3. The second fmap re-wraps the elements back into a [Int]
4. The first fmap re-wraps and returns the transformed [Int] into an IO
[Int].

-deech


On Fri, Dec 17, 2010 at 3:27 PM, aditya siram aditya.si...@gmail.comwrote:

 I think it is giving you the error because you the fmap in your code is
 operating on the IO monad and not the List monad. In order to get it to
 work, you can remove the IO layer with = as below:


 f :: [Int] - IO [Int]
 f lst = do return lst

 main = do let lst = f [1,2,3,4,5]
   lst = return . fmap (+1)

 Or you can not wrap the list in IO to begin with, my guess is that you
 wrote 'f' to make the compiler happy at some point in development:
 main = do let lst = [1,2,3,4,5]
   return $ fmap (+1) lst

 -deech

 On Fri, Dec 17, 2010 at 11:04 AM, michael rice nowg...@yahoo.com 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

 ===

 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



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-18 Thread David Leimbach
On Fri, Dec 17, 2010 at 9:04 AM, michael rice nowg...@yahoo.com 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


f takes [Int] and returns IO [Int]

fmap is

fmap :: (Functor f) = (a - b) - f a - f b

That is it takes a function of a's to b's, a functor of a, and returns you a
functor of b.

So when you fmap (+1) to an IO [Int], it's trying to add 1 to a [Int], and
[Int] is not an instance of Num, so the + does not work.

Luckily you can use function composition here

(fmap . fmap) (+1) $ f [1..10]
[2,3,4,5,6,7,8,9,10,11]

fmap . fmap is the type I think you wanted:

Prelude :t fmap . fmap
fmap . fmap
  :: (Functor f, Functor f1) = (a - b) - f (f1 a) - f (f1 b)


With IO as the f Functor, and [] as the f1 Functor.




 ===

 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


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-18 Thread Daniel Peebles
Write out more types and it'll get more clear.

f is [Int] - IO [Int]

lst is f applied to Num a = [a], so it is of type IO [Int]

fmap is applied to lst, which means it's stepping inside the IO. That
means it's applying +1 to [1,2,3,4,5], which doesn't make much sense unless
you have a Num instance for [Int]. That's what the error was saying.

What you probably want is fmap (fmap (+1)) lst.

Not sure why you're doing this stuff in the first place though, since the
return into IO is only restricting what you can do with it. Also, the do in
both cases is unnecessary (in the second case you can replace the let with a
let..in)

Hope this helps,
Dan

On Fri, Dec 17, 2010 at 12:04 PM, michael rice nowg...@yahoo.com 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

 ===

 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


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-18 Thread Christopher Done
On 17 December 2010 18:04, michael rice nowg...@yahoo.com wrote:

 ===

 f :: [Int] - IO [Int]
 f lst = do return lst

 main = do let lst = f [1,2,3,4,5]
   fmap (+1) lst


The problem is that you are applying fmap to a type IO a.

fmap (+1) (return [1,2,3])

But to achieve the behaviour you expect, you need another fmap:

fmap (fmap (+1)) (return [1,2,3])
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-18 Thread Thomas Davie

On 17 Dec 2010, at 21:44, Christopher Done wrote:

 On 17 December 2010 18:04, michael rice nowg...@yahoo.com wrote:
 ===
 
 f :: [Int] - IO [Int]
 f lst = do return lst
 
 main = do let lst = f [1,2,3,4,5]
   fmap (+1) lst
  
 The problem is that you are applying fmap to a type IO a.
 
 fmap (+1) (return [1,2,3])
 
 But to achieve the behaviour you expect, you need another fmap:
 
 fmap (fmap (+1)) (return [1,2,3])

Which can be more neatly written with Conal's semantic editor cominators as

(fmap . fmap) (+1) (return [1,2,3])

Of course, I question why the list is put in the IO monad at all here... surely 
this would be much better

return $ fmap (+1) [1,2,3]

Finally, that has the wrong type for main... perhaps you meant to print it out?

main :: IO ()
main = print $ fmap (+1) [1,2,3]

Bob___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-18 Thread David Leimbach
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 nowg...@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.fisc...@googlemail.com
 wrote:


 From: Daniel Fischer daniel.is.fisc...@googlemail.com
 Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
 To: haskell-cafe@haskell.org
 Cc: michael rice nowg...@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.fisc...@googlemail.com*wrote:


 From: Daniel Fischer daniel.is.fisc...@googlemail.com
 Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
 To: haskell-cafe@haskell.org
 Cc: michael rice nowg...@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@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-17 Thread Darrin Chandler
On Fri, Dec 17, 2010 at 09:04:20AM -0800, 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

'f' operates on '[Int]', but '(+1)' operates on 'Int'... Does the
following do what you want?

main = do let lst = f [1,2,3,4,5] in
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


-- 
You've been warned.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-17 Thread Miguel Mitrofanov

On 17 Dec 2010, at 20:04, michael rice wrote:

 I don't understand this error message. Haskell appears not to understand that 
 1 is a Num.

As it clearly states in the error message, it doesn't understand that [Int] is 
a Num - and it's not.

No instance for Num something usually indicates that you're trying to use an 
integer literal - in this case, 1 - as this something.

The problem is that your lst has the type IO [Int] (which is the same as 
IO ([] Int)). fmap has the type (a - b) - f a - f b, so, it tries to 
unify the type of (+1) with [Int] - something - which, probably, isn't 
what you've meant. In fact, I'm pretty sure you wanted lst to have the type 
[Int] (= [] Int), without IO. You can do that using - instead of let:

main =
   do lst - fst [1,2,3,4,5]
  return (fmap (+1) lst)

 
 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
 
 ===
 
 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


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-17 Thread michael rice
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.fisc...@googlemail.com wrote:


    From: Daniel Fischer daniel.is.fisc...@googlemail.com
    Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
    To: haskell-cafe@haskell.org
    Cc: michael rice nowg...@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.fisc...@googlemail.com wrote:

From: Daniel Fischer daniel.is.fisc...@googlemail.com
Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
To: haskell-cafe@haskell.org
Cc: michael rice nowg...@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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-17 Thread michael rice
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 leim...@gmail.com wrote:

From: David Leimbach leim...@gmail.com
Subject: Re: [Haskell-cafe] Why is Haskell flagging this?
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org, Daniel Fischer 
daniel.is.fisc...@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 nowg...@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.fisc...@googlemail.com wrote:


    From: Daniel Fischer daniel.is.fisc...@googlemail.com

    Subject: Re

Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-17 Thread Daniel Fischer
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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe