Re: newbie:: getting random Ints

2002-04-04 Thread Jon Cast


This may, in places, be somewhat pedantic --- I'm paid to be far more
concerned with formal proofs of correctness than any sane person
should be :) However, it should ultimately make sense if you'll read
the entire thing through.

Peter Rooney <[EMAIL PROTECTED]> wrote:

> in my case, it was not OK to have arbitrary data, i needed (pseudo-)
> random numbers for different runs of the program.

Normally, if you want program behavior to vary between runs of the
program, you want to use the IO monad.  This is a feature.

See, Haskell expressions usually satisfy the following property (call
it Axiom 1):

Assuming t is a point in the computation of the program (say, after t
machine-language instructions have been executed), let x(t) be the
value of x at point t.  Now, for all points t, t', x(t) = x(t').  In
other words, the value of a variable/program fragment is invariant
during computation.

This guarantees things like map f xn = map f xn, i.e., (=) (as used in
reasoning about Haskell programs) is an equivalence relation in the
mathematical sense.  (This is not true for languages like C, nor is it
necessarily true for Haskell in the presence of unsafePerformIO, a
point I'll return to later.)

This allows you to use normal equational reasoning to reason about
Haskell programs, which is of course both the most common and most
powerful form of reasoning about Haskell programming.

Axiom 1 has a consequence that's important here: Haskell program
phrases have a value that is invariant across runs of the program.
So, if you want a value of type [Int] whose value varies across
program invocations, that's not possible (well, as you know, you can
get it using unsafePerformIO, but that violates the implicit rules of
the language).

The IO monad allows you to use side-effects and have values that are
not invariant between runs of the program.  Basically, it works like
this: you should think of (IO a) as being equivalent to (State -> (a,
State)), where the argument is the state of the computer (mutable
variables, files, etc.) before the action executes and the result is
the state of the computer after the action executes, together with the
resultant value.  Because values inside the IO monad are within the
evaluation of a function with a particular value, you actually have
separate variables across runs, so their values can differ.

Now then, unsafePerformIO ``more or less'' has type (State -> (a,
State)) -> a.  In other words, it promises to deliver you the result
of the function /without knowing what that function's argument is/.
That's why it's ``unsafe'' --- you have to prove yourself that the
result satisfies Axiom 1.  If it doesn't, the program's results are
undefined, since any results depend on Axiom 1.  Basically, if you
know C, treat arbitrary unsafePerformIOs like you would treat:

x++ = x;

In other words, like the plague.

So how do you re-write your program without unsafePerformIO?

> i want to:

> -generate random Ints

As you know, this can be done in the IO monad.  Let your generator
have type IO [Int].

> -do some arbitrary computations on them to generate a [[Int]]

If you can do these computations outside the IO monad, do that.  Then,
use liftM (in the Monad module, I believe) to get a computation over
IO values.

In other words, let your computations be in a function f :: [Int] ->
[[Int]].  Then, liftM f :: IO [Int] -> IO [[Int]].  This function can
be applied to your random [Int] generator (remember, IO [Int] is a
function), generated above.

> -compare each [Int] in the list with a list of [Int] known at
> compile time

Again, do this outside the IO monad, then use liftM.

You can revise your code to do this like such:

> > import Random

> > rollDice :: IO Int
> > rollDice = getStdRandom (randomR (1,6))

This part is fine.
 
> > getRandomSeed :: IO Int
> > getRandomSeed = do
> > retval <- rollDice
> > return retval

Again, this is fine.  But, an orthogonal note about style:

>   do
>retval <- rollDice
>return retval

As you may or may not know, this is simply syntax sugar for:

> = rollDice >>= \retval -> return retval

Eta-contracting, we get:

> = rollDice >>= return

And, finally, applying the monad laws (in the Haskell Report, under
the Monad class specification), we get:

> = rollDice

So, all you've done is rename rollDice as getRandomSeed.
 
> > getRandomSeedInt :: IO Int -> Int
> > getRandomSeedInt x = unsafePerformIO x

Again, eta-contracting, we get:

> getRandomSeedInt = unsafePerformIO

So, another re-naming.
 
> > getARange :: Int -> Int -> [Int]
> > getARange x y  = randomRs (x,y) (mkStdGen (getRandomSeedInt getRandomSeed))
 
The simplest way to eliminate the (getRandomSeedInt = unsafePerformIO)
is to re-type it as:

> getARange :: Int -> Int -> IO [Int]

And re-write the definition as:

> getARange x y  = liftM randomRs (x,y) (liftM mkStdGen getRandomSeed)

Or, equivalently, as:

> getARange x y = do
>   seed <- getRandomSeed
>   

Re: newbie:: getting random Ints

2002-04-02 Thread Peter Rooney


[EMAIL PROTECTED] (Ketil Z. Malde) writes:


> 
> Depending on why you need random numbers, you might want to consider
> using a fixed seed, i.e. 
> 
> a = randoms (mkStdGen 4711)
> 
> will get you a sequence of "random" numbers.  Of course, it will be
> the same sequence for every run of your program, but in some cases,
> (when you only want arbitrary data, and not necessarily random) this
> won't matter much.
> 
> The advantage is, of course, that you get rid of the IO monad.  I've
> toyed with the idea of using unsafePerformIO (at least to get the
> seed), but haven't quite dared (or needed) to yet. :-)
> 

well, thanks to all for the help. in my case, it was not OK to have
arbitrary data, i needed (pseudo-) random numbers for different runs
of the program.  i want to:

-generate random Ints
-do some arbitrary computations on them to generate a [[Int]]
-compare each [Int] in the list with a list of [Int] known at compile time

the functions below seem to be doing what i need; i'm posting the code
in case it helps other newbies get there a bit faster than i did. any
constructive criticism / pointing out of errors most welcome.

code:

> import Random

> rollDice :: IO Int
> rollDice = getStdRandom (randomR (1,6))
 
> getRandomSeed :: IO Int
> getRandomSeed = do
> retval <- rollDice
> return retval
 
> getRandomSeedInt :: IO Int -> Int
> getRandomSeedInt x = unsafePerformIO x
 
> getARange :: Int -> Int -> [Int]
> getARange x y  = randomRs (x,y) (mkStdGen (getRandomSeedInt getRandomSeed))
 
> getRandomInt :: Int -> Int
> getRandomInt x = head (take 1 (getARange 0 x ))

output:

Main> take 20 (getARange 0 10)
[5,8,1,8,2,8,9,7,1,4,6,2,5,8,6,2,10,0,7,10]
Main> take 20 (getARange 0 10)
[9,8,9,9,7,2,4,5,1,7,2,2,8,2,5,10,5,3,1,8]


thanks and regards,
peter



___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: newbie:: getting random Ints

2002-04-02 Thread Ketil Z. Malde

Peter Rooney <[EMAIL PROTECTED]> writes:

> I can't seem to generate random numbers.

Depending on why you need random numbers, you might want to consider
using a fixed seed, i.e. 

a = randoms (mkStdGen 4711)

will get you a sequence of "random" numbers.  Of course, it will be
the same sequence for every run of your program, but in some cases,
(when you only want arbitrary data, and not necessarily random) this
won't matter much.

The advantage is, of course, that you get rid of the IO monad.  I've
toyed with the idea of using unsafePerformIO (at least to get the
seed), but haven't quite dared (or needed) to yet. :-)

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



Re: newbie:: getting random Ints

2002-03-29 Thread Andre W B Furtado

the function
randomRIO :: (a,a) -> IO a
defined in module Random gives you a random number between the two input
parameters (including themselves).

-- Andre

- Original Message -
From: Peter Rooney <[EMAIL PROTECTED]>
To: <[EMAIL PROTECTED]>
Sent: Thursday, March 28, 2002 3:05 AM
Subject: newbie:: getting random Ints


>
> hello all,
>
> total newbie to haskell, armed with "the craft of functional
> programming".
>
> i can't seem to generate random numbers. i have read this:
>
> http://www.haskell.org/onlinelibrary/random.html
>
> and searched the web and archives, and read thru Random.hs (mostly
> over my head), but have been unable to get any combination of
> getStdRandom randomR, etc. to work. even the example in the 98 report,
>
> import Random
>
> rollDice :: IO Int
> rollDice = getStdRandom (randomR (1,6))
>
> gets me:
>
>
> Main> rollDice
>
> Main>
>
> after loading the file, which makes me think i'm missing something!
> TCFP has an example of how to do it yourself, but i can see that my
> needs are more than met by Random.hs.
>
> my various attempts all look a lot like this:
>
> Main> getStdGen (random 5)
> ERROR - Type error in application
> *** Expression : getStdGen (random 5)
> *** Term   : getStdGen
> *** Type   : IO StdGen
> *** Does not match : a -> b
>
> could someone post an example of how to generate random integers
> within a range?
>
> tia,
> peter
> ___
> Haskell-Cafe mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: newbie:: getting random Ints

2002-03-28 Thread Christian Sievers

Peter Rooney wrote:

> over my head), but have been unable to get any combination of
> getStdRandom randomR, etc. to work. even the example in the 98 report,
> 
> import Random
>  
> rollDice :: IO Int
> rollDice = getStdRandom (randomR (1,6))
> 
> gets me:
> 
> 
> Main> rollDice
>  
> Main>
> 
> after loading the file, which makes me think i'm missing something!


This looks like you are using Hugs.  Given an IO action, it will perform it.
That is different from giving it a non-IO expression, which it will evaluate
and print.
In this case, it will simply generate a random number - and throw it away!

You can try

  do dice <- rollDice; print dice

or

  rollDice >>= print

(which is essentially the same) instead, which is an IO action that, when
performed, will generate a random number and print it.

If your problem was not knowing what Hugs does when given an IO action, that's
it. But if you don't yet know who to handle IO, you have still some way to go.


HTH
Christian Sievers



___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



newbie:: getting random Ints

2002-03-27 Thread Peter Rooney


hello all,

total newbie to haskell, armed with "the craft of functional
programming".

i can't seem to generate random numbers. i have read this:

http://www.haskell.org/onlinelibrary/random.html

and searched the web and archives, and read thru Random.hs (mostly
over my head), but have been unable to get any combination of
getStdRandom randomR, etc. to work. even the example in the 98 report,

import Random
 
rollDice :: IO Int
rollDice = getStdRandom (randomR (1,6))

gets me:


Main> rollDice
 
Main>

after loading the file, which makes me think i'm missing something!
TCFP has an example of how to do it yourself, but i can see that my
needs are more than met by Random.hs.

my various attempts all look a lot like this:

Main> getStdGen (random 5)
ERROR - Type error in application
*** Expression : getStdGen (random 5)
*** Term   : getStdGen
*** Type   : IO StdGen
*** Does not match : a -> b
 
could someone post an example of how to generate random integers
within a range?

tia,
peter
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe