Re: [Haskell-cafe] St. Petersburg Game

2007-11-27 Thread Ketil Malde
[EMAIL PROTECTED] writes:

 increment b = b + 1

This is also called 'succ' (for successor).

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

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

  Prelude :t until
  until :: (a - Bool) - (a - a) - a - a

So until wants a function from a something to a boolean, but you are
giving it (c==1) which is just a boolean.

More generally, I think you should solve this in a more functional
style, perhaps using randomRs to get a list of coin tosses, and take
what you need from that.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] St. Petersburg Game

2007-11-27 Thread Lutz Donnerhacke
* [EMAIL PROTECTED] wrote:
 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

import System.Random  -- time goes on, interfaces change

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


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

In Haskell you take it the other side around:
  - Given a random number generator
System.Random.newStdGen :: IO StdGen

  - you generate an infinite list of coin flip results
System.Random.randoms  :: (RandomGen g) =  g - [a]
System.Random.randomRs :: (RandomGen g) = (a,a) - g - [a]
  
  - you are interested in the the first elements of a given value
takeWhile :: (a - Bool) - [a] - [a]
  
  - and need to compute the length of this list
length :: [a] - Int
  

To model the result of a coin flip, you need two possible values.
Your choice [1,2] is possible, but the boolean values are much easier.
Let's choose True for number up and False otherwise.

Put it together:

main :: IO ()
main = do
  rnd - newStdGen
  let result = computeResult rnd
  print result

computeResult :: (RandomGen g) = g - Int
computeResult = length . takeWhile not . randoms

Or in short:

main = print . length . takeWhile not . randoms = newStdGen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] St. Petersburg Game

2007-11-27 Thread Thomas Davie

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 not familiar with the problem, so I won't comment on how I would  
implement it.  However what you appear to be doing is trying to write  
something in an imperative style.


If you want to generate random coin tosses and count how many are  
heads, I suggest you write a function that returns an infinite list of  
coin toss results.  Something like


tosses :: IO ([Int])
tosses = do ts - tosses
return (randomRIO (1,2):ts)

Then your main function merely needs to count them:

main = do ts - tosses
  return $ countHeads ts

countHeads = if (head fg == 1) then 0 else length fg where fg = head $  
group ts


Your immediate error is caused by a misunderstanding of how until works.

Until essentially is a restricted while loop implemented with  
recursion.  It takes three things:

1) A condition for stopping looping
2) A thing to do in the loop
3) A value to start with.

Because there's no mutable state, a while loop can't alter the program  
state, so we must do something else instead.  What we do is we have a  
function for computing whether we're done looping or not, and we pass  
a value into it. ___

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


Re: [Haskell-cafe] St. Petersburg Game

2007-11-27 Thread Luke Palmer
On Nov 27, 2007 1:27 PM,  [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:

Yeah, random number generation is one of those things in Haskell that
can be tricky.  But it looks like you're struggling more with the idea
of monadic programming.  That is expected :-)

 import Random

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

This is unnecessary; it can just be written (+1).  (I.e. wherever you
said increment you could write (+1) instead)

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

You can think of this block as four statements, one after the other.
 the do-until thing doesn't delimit anything, i.e. doesn't work the
way you think it does.   Let me rewrite this so it's clearer what's
going on:


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

In particular, until is a function, and you've given it three
arguments: c == 1 (which is False), increment, and b.

To solve this problem you'll probably want to use recursion, since it
is a loop.  There are higher-order ways to loop, but they all boil
down to recursion in the end.

So let's write a function which does this, call it count:

count :: Int - IO Int

That is the type.  It takes an integer representing the current count,
does some IO and returns an integer.  Specifically, it should take the
current count and flip a coin.  If the coin comes up tails, it should
just return the current count.  It it comes up heads, it should call
itself again with 1 + the current count as an argument.  I'll get you
started

count currentCount = do
coin - randomRIO (1,2)
...

We use - to run an action and get its result; we use let .. = to
define the meaning of a symbol (but nothing is run).  Using let just
gives a shorter name for an expression.

Why don't you try to write the rest?  main will look like:

main = do
flips - count 0
print flips

I also recommend going through a tutorial which others will doubtless
recommend to you until you get to monads (or skip ahead to monads and
see if you understand).

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


Re: [Haskell-cafe] St. Petersburg Game

2007-11-27 Thread pepe

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


Re: [Haskell-cafe] St. Petersburg Game

2007-11-27 Thread Henning Thielemann

On Tue, 27 Nov 2007 [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 =  dolet b = 0
   let c = randomRIO (1,2)
   until (c == 1)  increment b
   return b

http://www.haskell.org/pipermail/haskell-cafe/2006-December/020005.html

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