Simple program. Simple problem?

What is going wrong here? Michael ======= import System.Random coinToss :: StdGen -> IO () coinToss gen = putStrLn "What's your guess, heads or tails ('h' or 't')?" >> getChar >>= \c -> let (randInt, _) = randomR(0,1) gen :: (Int, StdGen) in if c == ((!!) "ht" randInt) then putStrLn "You win!" else putStrLn "You lose!" main = do gen <- getStdGen coinToss gen gen <- newStdGen main ======= [michael@localhost ~]$ runhaskell cointoss.hs What's your guess, heads or tails ('h' or 't')? h You win! What's your guess, heads or tails ('h' or 't')? You lose! What's your guess, heads or tails ('h' or 't')? h You lose! What's your guess, heads or tails ('h' or 't')? You lose! What's your guess, heads or tails ('h' or 't')? ^Ccointoss.hs: cointoss.hs: interrupted [michael@localhost ~]$

It always helps to put a Debug.Trace.trace:
in if trace (show (fromEnum c)) $ c == ((!!) "ht"
randInt) then p
What's your guess, heads or tails ('h' or 't')?
h
104
You win!
What's your guess, heads or tails ('h' or 't')?
*10*
You lose!
What's your guess, heads or tails ('h' or 't')?
So getChar also receives the linefeed character.
An easy way to get around this, is to use getLine instead and just use the
first character, as in
>> fmap head getLine
But of course we're hacking away here :-)
On Mon, Oct 12, 2009 at 12:10 AM, michael rice
What is going wrong here?
Michael
=======
import System.Random
coinToss :: StdGen -> IO () coinToss gen = putStrLn "What's your guess, heads or tails ('h' or 't')?" >> getChar >>= \c -> let (randInt, _) = randomR(0,1) gen :: (Int, StdGen) in if c == ((!!) "ht" randInt) then putStrLn "You win!" else putStrLn "You lose!"
main = do gen <- getStdGen coinToss gen gen <- newStdGen main
=======
[michael@localhost ~]$ runhaskell cointoss.hs What's your guess, heads or tails ('h' or 't')? h You win! What's your guess, heads or tails ('h' or 't')? You lose! What's your guess, heads or tails ('h' or 't')? h You lose! What's your guess, heads or tails ('h' or 't')? You lose! What's your guess, heads or tails ('h' or 't')? ^Ccointoss.hs: cointoss.hs: interrupted [michael@localhost ~]$
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

btw I always find it amusing to play with interact and lazy IO:
guess :: [Char] -> [String] -> [String]
guess (c:cs) ~(i:is) =
"What's your guess, heads or tails ('h' or 't')?" :
(if [c]==i then "You win!" else "You lose!") :
guess cs is
main = do
gen <- getStdGen
let rs = randomRs (0,1::Int) gen
cs = map ("ht"!!) rs
interact $ unlines . guess cs . lines
On Mon, Oct 12, 2009 at 12:24 AM, Peter Verswyvelen
It always helps to put a Debug.Trace.trace: in if trace (show (fromEnum c)) $ c == ((!!) "ht" randInt) then p
What's your guess, heads or tails ('h' or 't')? h 104 You win! What's your guess, heads or tails ('h' or 't')? *10* You lose! What's your guess, heads or tails ('h' or 't')?
So getChar also receives the linefeed character.
An easy way to get around this, is to use getLine instead and just use the first character, as in
>> fmap head getLine
But of course we're hacking away here :-)
On Mon, Oct 12, 2009 at 12:10 AM, michael rice
wrote: What is going wrong here?
Michael
=======
import System.Random
coinToss :: StdGen -> IO () coinToss gen = putStrLn "What's your guess, heads or tails ('h' or 't')?" >> getChar >>= \c -> let (randInt, _) = randomR(0,1) gen :: (Int, StdGen) in if c == ((!!) "ht" randInt) then putStrLn "You win!" else putStrLn "You lose!"
main = do gen <- getStdGen coinToss gen gen <- newStdGen main
=======
[michael@localhost ~]$ runhaskell cointoss.hs What's your guess, heads or tails ('h' or 't')? h You win! What's your guess, heads or tails ('h' or 't')? You lose! What's your guess, heads or tails ('h' or 't')? h You lose! What's your guess, heads or tails ('h' or 't')? You lose! What's your guess, heads or tails ('h' or 't')? ^Ccointoss.hs: cointoss.hs: interrupted [michael@localhost ~]$
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thanks for the tip, and the lazy example.
I think I'm finally beginning to "get" monads, so I decided to test my
understanding with this small example. So far so good, except for that
little bump in the road.
Onward and upward.
Michael
--- On Sun, 10/11/09, Peter Verswyvelen

There's still something screwy going on here with the random generation or passing the gen to cointoss. Shouldn't newStdGen be updating getStdGen?
I've been running it and entering 'h' four (4) times, then aborting with CNTL-C.
Each time I either get
You lose!
You lose!
You win!
You lose!
or
You win!
You win!
You lose!
You win!
That's all, should be getting some variation.
Michael
======================
import System.Random
coinToss :: StdGen -> IO ()
coinToss gen = putStrLn "What's your guess, heads or tails ('h' or 't')?"
>> fmap head getLine
>>= \c -> let (randInt, _) = randomR(0,1) gen :: (Int, StdGen)
in if c == ((!!) "ht" randInt) then putStrLn "You win!" else putStrLn "You lose!"
main = do
gen <- getStdGen
coinToss gen
gen <- newStdGen
main
--- On Sun, 10/11/09, Felipe Lessa
btw I always find it amusing to play with interact and lazy IO:
I always find it frightening to play with lazy IO :). -- Felipe. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

It seems that the definition of split in System.Random is not really satisfactory. Imagine a tree-like computation of the form f gen = {- some expression using b, g1, g2 -} where b = fst (random gen) :: Bool (gen1, gen2) = split gen g1 = f gen1 g2 = f gen2 Let's look at the first 30 values of b produced along the right side of the tree: GHCi> length $ nub [ take 30 . map (fst . random) . iterate (snd . split) $ mkStdGen i :: [Bool] | i <- take 10000 . randoms $ mkStdGen 0 ] 10000 Great, we tried 10000 different initial gens and got 10000 different sequences. Now let's look at the left side: GHCi> length $ nub [ take 30 . map (fst . random) . iterate (fst . split) $ mkStdGen i :: [Bool] | i <- take 10000 . randoms $ mkStdGen 0 ] 8 This doesn't seem good. Michael's code (below) is effectively doing iterate (fst . split). Regards, Reid Barton On Sun, Oct 11, 2009 at 04:24:55PM -0700, michael rice wrote:
main = do gen <- getStdGen coinToss gen gen <- newStdGen main

On Sun, Oct 11, 2009 at 08:17:48PM -0400, Reid Barton wrote:
It seems that the definition of split in System.Random is not really satisfactory.
For the curious, the reason for the asymmetry between fst . split and snd . split is that the RNG states produced by mkStdGen have varying first component but second component (virtually) always equal to 1. For full details see http://hackage.haskell.org/trac/ghc/ticket/3575 Regards, Reid Barton

For the code below, if I CNTL-C after the list is printed, and run it again, I get a different list of colors, each time. This doesn't seem to be happening with my earlier example.
Michael
=============
import System.Random
import Data.Ord
data Color
= Red
| Blue
| Green
| Yellow
| Orange
| Brown
deriving (Show, Read, Eq, Enum, Ord, Bounded)
main = do
gen <- getStdGen
let code = map toEnum $ take 4 $ randomRs (0,5) gen :: [Color]
putStrLn $ "List is " ++ show code
guessString <- getLine
newGen <- newStdGen
main
--- On Sun, 10/11/09, Felipe Lessa
btw I always find it amusing to play with interact and lazy IO:
I always find it frightening to play with lazy IO :). -- Felipe. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mon, Oct 12, 2009 at 1:08 AM, Felipe Lessa
On Mon, Oct 12, 2009 at 12:42:16AM +0200, Peter Verswyvelen wrote:
btw I always find it amusing to play with interact and lazy IO:
I always find it frightening to play with lazy IO :).
yes, I guess that's why I like it, because I'm still an imperative / OO programmer ;-)
-- Felipe. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (4)
-
Felipe Lessa
-
michael rice
-
Peter Verswyvelen
-
Reid Barton