One time I needed to do use a random number in some places of a completly pure program so I made a infinite list of random numbers and passed it around all the time in the functions as they where called, using the head of the list I passed to the function whenever I needed a random number and returning a tuple which it's second element was the tail of the random numbers list e.g.

f:: [int] -> (a,[Int])
f randomList =
    let usedRandomNumber = g $ head randomList
    in (usedRandomNumber,(tail randomList))

or even something like:
f:: [int] -> (a,[Int])
f randomList =
    let (usedRandomNumber,newRandomList) = g randomList
    in (usedRandomNumber,newRandomList)

where g:: [int] -> (a,[Int])


The actuall code for doing this is: (Warning, it uses unsafePerformIO, just for the seed of the random Generator, I really don't think it would do any harm)

rand :: (RandomGen g, Random a) => (a,a) -> g -> [a]
rand range gen = as
     where  (a,b) = split gen      -- create two separate generators
            as = randomRs range a  -- one infinite list of randoms

seed :: Int
seed = fromInteger (unsafePerformIO getCPUTime)

mygen  = mkStdGen seed

infinito:: (Num t,Random t) => [t]
infinito = [ x | x <- rand (1,1000000) mygen]


infinito is the function that you need to call in your code that will give you the infinite list of random numbers which will be evaluated lazyly...

Hope you can use this...

About the prompt thing, that you'll have to wait for another answer or use what they have already told you,


Greetings,

Hector Guilarte




On Mon, Nov 30, 2009 at 8:13 PM, Eric Dedieu <papa.eric@free.fr> wrote:
> > Still more importantly to me, I understand that anyhow  if I intend
> > to use IO or random numbers, I must design my strategy from the
> > beginning as "encapsulated in a monad". Something like:
> >
> > class (Monad m) => Strategy m a where ...
> >
> That's not true at all, you can always pass this data to your strategy
> entry points and let haskell get it lazily, though it is not as
> intuitive as other aproaches,

That seems exactly what I had tried to do (and
failed) in my original code.

The Fixed type was to provide the list of moves:

> data Fixed = Fixed [Move] deriving Show

and instanciate a strategy that ignores the game to
make decisions, just return the provided moves, then zeroes if ever
exhausted:

> instance Strategy Fixed where
>     proposeNext game s = case s of
>                            Fixed [] -> (0, Fixed [])
>                            Fixed (x:xs) -> (x, Fixed xs)

but when using an IO Fixed, the questions were not repeated lazily as
needed, as if the list of moves was entirely evaluated; so this failed:

> askUntil :: String -> IO Fixed
> askUntil name = liftM Fixed (sequence $ repeat askio)
>     where askio = putStr (name ++ ", pick a number: ") >> readLn

I thought that sequencing [IO Move] to IO [Move] was what breaked
lazyness, so I tried other ways to turn an [IO Move] into a IO
Strategy, and failed.

If I did not interpret correctly why this was not lazy, or if it is
indeed possible to do otherwise can you please show me how?

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