Hola Manolo,

What you are trying to do is very easy in Haskell, but you'd better change the approach. In short, you are trying to use b as if it was a mutable variable, which it is not!
One could rewrite your program using mutable variables, as below:

import Data.IORef
import Random
import Control.Monad

main1 = do
        b <- newIORef 0
        let loop = do
               c <- randomRIO (1,2)
               unless (c == 1) (modifyIORef b increment >> loop)
        loop
        readIORef b

Ugh, that's ugly (I have changed 'until' for 'unless', which is much more widely used).
But as I said, this is not the right approach.

What one would do in Haskell is to simply generate an infinite list of random numbers, and then operate on that, e.g. counting the number of consecutive heads of the coin.

main2 = do
        gen <- newStdGen
        let tosses = randomRs (1::Int,2) gen
            b      = takeWhile ( /= 1) tosses
        return (length b)



Hope that was of help. You can find more material on Haskell in the wiki :)
http://haskell.org/haskellwiki/Learning_Haskell

pepe "otaku!"

PS: Puedo preguntarme qué hace este hombre aprendiendo Haskell? Viva!


On 27/11/2007, at 14:27, [EMAIL PROTECTED] wrote:

Hello,

I'm trying to program an implementation of the St. Petersburg game in
Haskell. There is a coin toss implied, and the random-number generation is
driving me quite mad. So far, I've tried this:

import Random

increment :: Int -> Int
increment b = b + 1


main =  do      let b = 0
                let c = randomRIO (1,2)
                until (c == 1)  increment b
                return b

This is intended to print the number of consecutive heads (i.e., 2) before
the first tail, but I get the following error:

ERROR "StPetersburg.hs":8 - Type error in application
*** Expression     : until (c == 1) increment b
*** Term           : c == 1
*** Type           : Bool
*** Does not match : Int -> Bool

I don't really see what's going on, so any help will be more than welcome.
I hope this is a suitable question for the Haskell Café list.

I'm using Hugs in an Ubuntu box, in case that should be useful.

Thanks,
Manolo

_______________________________________________
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

Reply via email to