
I'm looking for a hint to write the following code with less redundancy. I have a constructor called BoxBounds, and I want to make one with random values. randomBox :: IO BoxBounds randomBox = do x <- getStdRandom (randomR (-10,10)) y <- getStdRandom (randomR (-70,70)) t <- getStdRandom (randomR (5,10)) b <- getStdRandom (randomR (5,10)) l <- getStdRandom (randomR (5,10)) r <- getStdRandom (randomR (5,10)) return (BoxBounds x y l r t b)

[x,y,t,b,l,r] <- mapM (getStdRandom . randomR) [(-10,10), (-70,70), ...]
return (BoxBounds ...)
2009/10/4 Michael Mossey
I'm looking for a hint to write the following code with less redundancy. I have a constructor called BoxBounds, and I want to make one with random values.
randomBox :: IO BoxBounds randomBox = do x <- getStdRandom (randomR (-10,10)) y <- getStdRandom (randomR (-70,70)) t <- getStdRandom (randomR (5,10)) b <- getStdRandom (randomR (5,10)) l <- getStdRandom (randomR (5,10)) r <- getStdRandom (randomR (5,10)) return (BoxBounds x y l r t b)
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Eugene Kirpichov Web IR developer, market.yandex.ru

On Sun, Oct 04, 2009 at 01:55:11PM +0400, Eugene Kirpichov wrote:
[x,y,t,b,l,r] <- mapM (getStdRandom . randomR) [(-10,10), (-70,70), ...] return (BoxBounds ...)
import Control.Applicative let f = getStdRandom . randomR g1 = \x -> f (-x,x) g2 = f (5,10) in BoxBounds <$> g1 10 <*> g1 70 <*> g2 <*> g2 <*> g2 <*> g2 -- Felipe.

If I understand correctly, this works because IO is an instance of Applicative, correct? I wonder if any of the random monads are instances of Applicative. Felipe Lessa wrote:
On Sun, Oct 04, 2009 at 01:55:11PM +0400, Eugene Kirpichov wrote:
[x,y,t,b,l,r] <- mapM (getStdRandom . randomR) [(-10,10), (-70,70), ...] return (BoxBounds ...)
import Control.Applicative
let f = getStdRandom . randomR g1 = \x -> f (-x,x) g2 = f (5,10) in BoxBounds <$> g1 10 <*> g1 70 <*> g2 <*> g2 <*> g2 <*> g2
-- Felipe. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mon, Oct 05, 2009 at 07:24:00AM -0700, Michael Mossey wrote:
If I understand correctly, this works because IO is an instance of Applicative, correct?
I wonder if any of the random monads are instances of Applicative.
If they aren't then that's a bug in the library :). Every monad can be made an instance of Applicative; given any monad M, instance Functor M where fmap = liftM -- from Control.Monad instance Applicative M where pure = return (<*>) = ap -- from Control.Applicative -- Felipe.

Eugene Kirpichov wrote:
[x,y,t,b,l,r] <- mapM (getStdRandom . randomR) [(-10,10), (-70,70), ...] return (BoxBounds ...)
Thanks. I'm curious about the idea of "pattern matching in do-statements that can fail." This particular pattern cannot fail. I read that the "fail" function was introduced to Monad in order to handle pattern matches that fail, and that most members of haskell-cafe seem to think that was a mistake---that MonadZero should have been used instead. I.e., any do-block with a pattern that can fail should explicitly have a MonadZero class constraint. This leads to my question about detecting pattern matches that could fail. We can easily prove the above pattern will never fail. I'm wondering if the compiler infers this. And if a future version of Haskell dumps "fail" and used MonadZero to replace it, would that future Haskell compiler need to infer, in all cases, whether a pattern can fail? Is it simple enough to make that correct inference? Thanks, Mike

2009/10/5 Michael Mossey
Eugene Kirpichov wrote:
[x,y,t,b,l,r] <- mapM (getStdRandom . randomR) [(-10,10), (-70,70), ...] return (BoxBounds ...)
Thanks.
I'm curious about the idea of "pattern matching in do-statements that can fail." This particular pattern cannot fail. I read that the "fail" function was introduced to Monad in order to handle pattern matches that fail, and that most members of haskell-cafe seem to think that was a mistake---that MonadZero should have been used instead. I.e., any do-block with a pattern that can fail should explicitly have a MonadZero class constraint.
This leads to my question about detecting pattern matches that could fail. We can easily prove the above pattern will never fail. I'm wondering if the compiler infers this.
Try proving it by hand and judge the result with respect to whether it could have been done by the compiler.
And if a future version of Haskell dumps "fail" and used MonadZero to replace it, would that future Haskell compiler need to infer, in all cases, whether a pattern can fail? Is it simple enough to make that correct inference?
Thanks, Mike _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Eugene Kirpichov Web IR developer, market.yandex.ru

Am Montag 05 Oktober 2009 16:22:15 schrieb Michael Mossey:
Eugene Kirpichov wrote:
[x,y,t,b,l,r] <- mapM (getStdRandom . randomR) [(-10,10), (-70,70), ...] return (BoxBounds ...)
Thanks.
I'm curious about the idea of "pattern matching in do-statements that can fail." This particular pattern cannot fail.
It can. It won't fail in this particular context, but it's a refutable pattern, that's what counts. Whether or not a pattern matching in a do-block can fail is intrinsic to the pattern.
I read that the "fail" function was introduced to Monad in order to handle pattern matches that fail, and that most members of haskell-cafe seem to think that was a mistake---that MonadZero should have been used instead. I.e., any do-block with a pattern that can fail should explicitly have a MonadZero class constraint.
This leads to my question about detecting pattern matches that could fail. We can easily prove the above pattern will never fail.
We can. And we could make the compiler able to prove it, too.
I'm wondering if the compiler infers this.
Not worth the hassle. One could make the compiler infer any finite number of special cases, but you can't have an algorithm that can for an arbitrary refutable pattern and an arbitrary monadic action (of appropriate type) decide whether the pattern match in pat <- act will always succeed.
And if a future version of Haskell dumps "fail" and used MonadZero to replace it, would that future Haskell compiler need to infer, in all cases, whether a pattern can fail? Is it simple enough to make that correct inference?
Using a refutable pattern would add the MonadZero constraint, while do-blocks with only irrefutable patterns can be had in any Monad. Whether a pattern is refutable or irrefutable is easy to decide (cf. http://haskell.org/onlinereport/exps.html#sect3.17).
Thanks, Mike

On Sun, 2009-10-04 at 02:52 -0700, Michael Mossey wrote:
I'm looking for a hint to write the following code with less redundancy. I have a constructor called BoxBounds, and I want to make one with random values.
randomBox :: IO BoxBounds randomBox = do x <- getStdRandom (randomR (-10,10)) y <- getStdRandom (randomR (-70,70)) t <- getStdRandom (randomR (5,10)) b <- getStdRandom (randomR (5,10)) l <- getStdRandom (randomR (5,10)) r <- getStdRandom (randomR (5,10)) return (BoxBounds x y l r t b)
Others have already answered but I'd like to suggest that you avoid using IO here. There's no need for this to be impure. The getStdRandom function is one that should be avoided IMHO (and indeed removed from the Random module). A much nicer way to do the above is using some random monad, for example from the MonadRandom package. The suggestions from Felipe and Eugene will work just as well using Rand monad as the IO monad. Duncan

Duncan Coutts wrote:
On Sun, 2009-10-04 at 02:52 -0700, Michael Mossey wrote:
I'm looking for a hint to write the following code with less redundancy. I have a constructor called BoxBounds, and I want to make one with random values.
randomBox :: IO BoxBounds randomBox = do x <- getStdRandom (randomR (-10,10)) y <- getStdRandom (randomR (-70,70)) t <- getStdRandom (randomR (5,10)) b <- getStdRandom (randomR (5,10)) l <- getStdRandom (randomR (5,10)) r <- getStdRandom (randomR (5,10)) return (BoxBounds x y l r t b)
Others have already answered but I'd like to suggest that you avoid using IO here. There's no need for this to be impure. The getStdRandom function is one that should be avoided IMHO (and indeed removed from the Random module).
A much nicer way to do the above is using some random monad, for example from the MonadRandom package. The suggestions from Felipe and Eugene will work just as well using Rand monad as the IO monad.
Duncan
Hi Duncan, Can you point me to a tutorial that covers the basics of randomness in Hasell? I find it very confusing. Mike

On Sun, 2009-10-04 at 05:11 -0700, Michael Mossey wrote:
Duncan Coutts wrote:
Others have already answered but I'd like to suggest that you avoid using IO here. There's no need for this to be impure.
Can you point me to a tutorial that covers the basics of randomness in Hasell? I find it very confusing.
http://en.wikibooks.org/wiki/Haskell/Hierarchical_libraries/Randoms http://learnyouahaskell.com/input-and-output#randomness The main thing to realise is that random number generators are pure and predictable. Given the state of a random number generator, if you ask for a random number, it always gives the same answer. It has to, because it is pure. Let's make one, and seed it with the starting state 12345 ghci> :module System.Random ghci> let g0 = mkStdGen 12345 Now we can ask for the next random number in the sequence: ghci> let (n1, g1) = next g0 ghci> n1 493972152 Now of course if we asked for the random number from g0 again then we must get the same result. But notice that when we use 'next' it also gives us back g1 which is the next state of the random number generator. ghci> let (n2, g2) = next g1 ghci> n2 335387100 So this is the basic way that random number generators work in a pure language. The generator has to be passed around the pure function, for example from one recursion to the next. So you end up with pure functions like: shuffle :: RandomGen g => g -> [x] -> [x] Another approach is to hide the 'g' inside a monad. That's what MonadRandom is all about. eg: shuffle :: [x] -> Rand [x] The tutorials above explain about the other random functions, for getting values of different types (not just Int) and restricted ranges of number etc. Of course at some point you want to seed the random number generator with some initial genuinely random value (not like the 12345 we used above). That is the only place in your random-handling code that needs to do IO. All the rest of it can be pure. Duncan

And, to go further, once you embrace "determinism" in your randomness, you can do all sorts of really cool things.
From the perspective of a games programmer:
You can run the same simulation code on two different network nodes, and
reliably get the same result, allowing you to just transfer user inputs
between the nodes instead of game state. This has applications in reducing
latency as well, as you only need to transfer the input one way across the
network.
You can save off the user inputs and initial into a tiny "replay" buffer,
allowing you to re-run the game from the beginning without much memory
cost. This is not only a cool end-user feature, but it aids *tremendously*
in debugging. When something goes wrong, you can always just rewind as many
times as you want while you narrow down the cause of the problem.
However, we always had problems with determinism failures, where somebody
would use the wrong random-number generator, or forget that they aren't
allowed to have the simulation depend on something that came from the
graphics RNG. In Haskell you can encode the purity of the simulation into
its type and it won't break!
-- ryan
On Sun, Oct 4, 2009 at 6:20 AM, Duncan Coutts
On Sun, 2009-10-04 at 05:11 -0700, Michael Mossey wrote:
Duncan Coutts wrote:
Others have already answered but I'd like to suggest that you avoid using IO here. There's no need for this to be impure.
Can you point me to a tutorial that covers the basics of randomness in Hasell? I find it very confusing.
http://en.wikibooks.org/wiki/Haskell/Hierarchical_libraries/Randoms
http://learnyouahaskell.com/input-and-output#randomness
The main thing to realise is that random number generators are pure and predictable. Given the state of a random number generator, if you ask for a random number, it always gives the same answer. It has to, because it is pure.
Let's make one, and seed it with the starting state 12345
ghci> :module System.Random ghci> let g0 = mkStdGen 12345
Now we can ask for the next random number in the sequence:
ghci> let (n1, g1) = next g0 ghci> n1 493972152
Now of course if we asked for the random number from g0 again then we must get the same result. But notice that when we use 'next' it also gives us back g1 which is the next state of the random number generator.
ghci> let (n2, g2) = next g1 ghci> n2 335387100
So this is the basic way that random number generators work in a pure language. The generator has to be passed around the pure function, for example from one recursion to the next.
So you end up with pure functions like:
shuffle :: RandomGen g => g -> [x] -> [x]
Another approach is to hide the 'g' inside a monad. That's what MonadRandom is all about. eg:
shuffle :: [x] -> Rand [x]
The tutorials above explain about the other random functions, for getting values of different types (not just Int) and restricted ranges of number etc.
Of course at some point you want to seed the random number generator with some initial genuinely random value (not like the 12345 we used above). That is the only place in your random-handling code that needs to do IO. All the rest of it can be pure.
Duncan
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

--- BEGIN NOSTALGIA ---
Well, I have to add to this, that when I coded my first games in assembler
in the eighties, I did exactly the same thing: just recording the input of
the joystick was enough to get full replays and make auto playing demos.
But on the old computers, this was all so easy, since you had full control
over every bit of the system (it was even easy to count exactly how many
cycles a routine would take :-), so it was just a matter of starting the
system in the same initial state, which was very easy.
As Ryan says, this was a blessing for debugging; after a bug was found (but
of course when writing in assembler one did not make bugs ;-), the testers
just returned a small log file of the input and version number, and this
allowed reproducing the problem *before* the bug occurred (aka known as
reverse debugging?).
Also since the mutable part of the game was just a couple of kilobytes (most
of the memory was used for immutable graphics, sounds and code), taking a
snapshot at regular intervals and embedding this into the log-file made it
easy to quickly go backwards and forwards in time.
To me, that was the joy of imperative programming: I could reason about
those systems as a whole, they behaved in a very predictable way, and since
all home computers (and game console) where basically identical, you knew
that if it behaved correctly on your system, it would also work on the
millions of other systems out there. Now IMO imperative programming is more
like playing Russian roulette...
--- END NOSTALGIA ---
But I find it so much harder or impossible on modern systems to do this, or
as Ryan says, it requires a high discipline from coders...
So yes, without using IO, Haskell forces you into this safe spot (there's of
course the unsafePerformIO function as backdoor to break all that :). But we
still need to see the first commercial games written in Haskell; hope to see
those soon, without using IO everywhere of course :)
Actually, it might be interesting to make a special mailing list for Haskell
and games? Or even a broader list for applying FP to games and simulations?
Or maybe that already exists?
On Sun, Oct 4, 2009 at 7:16 PM, Ryan Ingram
And, to go further, once you embrace "determinism" in your randomness, you can do all sorts of really cool things.
From the perspective of a games programmer:
You can run the same simulation code on two different network nodes, and reliably get the same result, allowing you to just transfer user inputs between the nodes instead of game state. This has applications in reducing latency as well, as you only need to transfer the input one way across the network.
You can save off the user inputs and initial into a tiny "replay" buffer, allowing you to re-run the game from the beginning without much memory cost. This is not only a cool end-user feature, but it aids *tremendously* in debugging. When something goes wrong, you can always just rewind as many times as you want while you narrow down the cause of the problem.
However, we always had problems with determinism failures, where somebody would use the wrong random-number generator, or forget that they aren't allowed to have the simulation depend on something that came from the graphics RNG. In Haskell you can encode the purity of the simulation into its type and it won't break!
-- ryan
On Sun, Oct 4, 2009 at 6:20 AM, Duncan Coutts < duncan.coutts@googlemail.com> wrote:
On Sun, 2009-10-04 at 05:11 -0700, Michael Mossey wrote:
Duncan Coutts wrote:
Others have already answered but I'd like to suggest that you avoid using IO here. There's no need for this to be impure.
Can you point me to a tutorial that covers the basics of randomness in Hasell? I find it very confusing.
http://en.wikibooks.org/wiki/Haskell/Hierarchical_libraries/Randoms
http://learnyouahaskell.com/input-and-output#randomness
The main thing to realise is that random number generators are pure and predictable. Given the state of a random number generator, if you ask for a random number, it always gives the same answer. It has to, because it is pure.
Let's make one, and seed it with the starting state 12345
ghci> :module System.Random ghci> let g0 = mkStdGen 12345
Now we can ask for the next random number in the sequence:
ghci> let (n1, g1) = next g0 ghci> n1 493972152
Now of course if we asked for the random number from g0 again then we must get the same result. But notice that when we use 'next' it also gives us back g1 which is the next state of the random number generator.
ghci> let (n2, g2) = next g1 ghci> n2 335387100
So this is the basic way that random number generators work in a pure language. The generator has to be passed around the pure function, for example from one recursion to the next.
So you end up with pure functions like:
shuffle :: RandomGen g => g -> [x] -> [x]
Another approach is to hide the 'g' inside a monad. That's what MonadRandom is all about. eg:
shuffle :: [x] -> Rand [x]
The tutorials above explain about the other random functions, for getting values of different types (not just Int) and restricted ranges of number etc.
Of course at some point you want to seed the random number generator with some initial genuinely random value (not like the 12345 we used above). That is the only place in your random-handling code that needs to do IO. All the rest of it can be pure.
Duncan
_______________________________________________ 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

Yep. Commodore 64, Amiga. I really loved those machined, especially the
Amiga (mmm, maybe someone should port a Haskell compiler to the Amiga. ha,
how "nerdy" can one get? ;-)
On Wed, Oct 7, 2009 at 10:50 AM, David Virebayre
wrote:
On Wed, Oct 7, 2009 at 10:05 AM, Peter Verswyvelen
wrote: over every bit of the system (it was even easy to count exactly how many cycles a routine would take :-), so it was just a matter of starting the
You sound like you used to code on the Commodore 64 :)
David.

Hello Peter, Wednesday, October 7, 2009, 2:04:49 PM, you wrote: afair, nhc was started there. it was a small compiler exactly because Amiga was a rather small computer (comapred to RISC stations)
Yep. Commodore 64, Amiga. I really loved those machined, especially the Amiga (mmm, maybe someone should port a Haskell compiler to the Amiga. ha, how "nerdy" can one get? ;-)
On Wed, Oct 7, 2009 at 10:50 AM, David Virebayre
wrote: On Wed, Oct 7, 2009 at 10:05 AM, Peter Verswyvelen
wrote: over every bit of the system (it was even easy to count exactly how many cycles a routine would take :-), so it was just a matter of starting the
You sound like you used to code on the Commodore 64 :)
David.
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

afair, nhc was started there. it was a small compiler exactly because Amiga was a rather small computer (comapred to RISC stations)
nhc12 (for Haskell 1.2) was first developed on an Acorn Archimedes with 2Mb of RAM, under RiscOS. Regards, Malcolm

Peter Verswyvelen
So yes, without using IO, Haskell forces you into this safe spot
One could argue that IO should be broken down into a set of "sub-monads" encapsulating various subsets of the functionality - file system, network access, randomness, and so on. This could extend the "safe spot" to cover much more computational real estate, and effectively sandbox programs in various ways. So instead of 'main :: IO ()', a text processing program using stdin and stdout could have type 'main :: MonadStdIO m => m ()'. For testing, you could then define your own monad implementing 'putStrLn' and 'readLn' etc, and a function 'runStdIO :: MonadStdIO m => m () -> String' that you are free to use in your quickcheck properties. (ObAttribution: I think it was a posting by Lennart Augustsson on unique names that brought this to my mind, but a quick googling didn't find that exact mail.) -k -- If I haven't seen further, it is by standing in the footprints of giants

Or you can use an effect system (however that doesn't give you the
opportunity of overriding IO functions, but I think that providing
such an opportunity with the means you suggest (splitting IO into many
sub-monads) is not going to be usable in the large scale)
By the way, I am surprised that there seems to not exist any
non-purely-academic language at all that supports effect systems!
(except for Java's checked exceptions being a poor analogue). The only
language with an effect system *and* a compiler that I know of is DDC,
but it seems to be purely experimental.
2009/10/7 Ketil Malde
Peter Verswyvelen
writes: So yes, without using IO, Haskell forces you into this safe spot
One could argue that IO should be broken down into a set of "sub-monads" encapsulating various subsets of the functionality - file system, network access, randomness, and so on. This could extend the "safe spot" to cover much more computational real estate, and effectively sandbox programs in various ways.
So instead of 'main :: IO ()', a text processing program using stdin and stdout could have type 'main :: MonadStdIO m => m ()'. For testing, you could then define your own monad implementing 'putStrLn' and 'readLn' etc, and a function 'runStdIO :: MonadStdIO m => m () -> String' that you are free to use in your quickcheck properties.
(ObAttribution: I think it was a posting by Lennart Augustsson on unique names that brought this to my mind, but a quick googling didn't find that exact mail.)
-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
-- Eugene Kirpichov Web IR developer, market.yandex.ru

It's a complex area not a lot of people are working in. Similar (actually worse than) dependent typing. Regards, John A. De Goes N-Brain, Inc. The Evolution of Collaboration http://www.n-brain.net | 877-376-2724 x 101 On Oct 7, 2009, at 3:32 AM, Eugene Kirpichov wrote:
Or you can use an effect system (however that doesn't give you the opportunity of overriding IO functions, but I think that providing such an opportunity with the means you suggest (splitting IO into many sub-monads) is not going to be usable in the large scale)
By the way, I am surprised that there seems to not exist any non-purely-academic language at all that supports effect systems! (except for Java's checked exceptions being a poor analogue). The only language with an effect system *and* a compiler that I know of is DDC, but it seems to be purely experimental.
2009/10/7 Ketil Malde
: Peter Verswyvelen
writes: So yes, without using IO, Haskell forces you into this safe spot
One could argue that IO should be broken down into a set of "sub- monads" encapsulating various subsets of the functionality - file system, network access, randomness, and so on. This could extend the "safe spot" to cover much more computational real estate, and effectively sandbox programs in various ways.
So instead of 'main :: IO ()', a text processing program using stdin and stdout could have type 'main :: MonadStdIO m => m ()'. For testing, you could then define your own monad implementing 'putStrLn' and 'readLn' etc, and a function 'runStdIO :: MonadStdIO m => m () -> String' that you are free to use in your quickcheck properties.
(ObAttribution: I think it was a posting by Lennart Augustsson on unique names that brought this to my mind, but a quick googling didn't find that exact mail.)
-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
-- Eugene Kirpichov Web IR developer, market.yandex.ru _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Eugene Kirpichov wrote:
Or you can use an effect system (however that doesn't give you the opportunity of overriding IO functions, but I think that providing such an opportunity with the means you suggest (splitting IO into many sub-monads) is not going to be usable in the large scale)
By the way, I am surprised that there seems to not exist any non-purely-academic language at all that supports effect systems! (except for Java's checked exceptions being a poor analogue). The only language with an effect system *and* a compiler that I know of is DDC, but it seems to be purely experimental.
What about ATS (http://www.ats-lang.org/)? Ben

On Wed, Oct 7, 2009 at 11:13 AM, Ketil Malde
One could argue that IO should be broken down into a set of "sub-monads" encapsulating various subsets of the functionality - file system, network access, randomness, and so on. This could extend the "safe spot" to cover much more computational real estate, and effectively sandbox programs in various ways.
Yes, a similar and very long thread I unintentionally started (sorry for that :p) was: DDC compiler and effects; better than Haskell? http://thread.gmane.org/gmane.comp.lang.haskell.cafe/62205

On Oct 7, 2009, at 3:13 AM, Ketil Malde wrote:
Peter Verswyvelen
writes: So yes, without using IO, Haskell forces you into this safe spot
One could argue that IO should be broken down into a set of "sub- monads" encapsulating various subsets of the functionality - file system, network access, randomness, and so on. This could extend the "safe spot" to cover much more computational real estate, and effectively sandbox programs in various ways.
Good idea in theory, in practice I suspect it would lead to unmanageable boilerplate. Regards, John A. De Goes N-Brain, Inc. The Evolution of Collaboration http://www.n-brain.net | 877-376-2724 x 101

On 7 Oct 2009, at 15:04, John A. De Goes wrote:
On Oct 7, 2009, at 3:13 AM, Ketil Malde wrote:
Peter Verswyvelen
writes: So yes, without using IO, Haskell forces you into this safe spot
One could argue that IO should be broken down into a set of "sub- monads" encapsulating various subsets of the functionality - file system, network access, randomness, and so on. This could extend the "safe spot" to cover much more computational real estate, and effectively sandbox programs in various ways.
Good idea in theory, in practice I suspect it would lead to unmanageable boilerplate.
Aye, but today's boilerplate is tomorrow's language design. Cheers Conor

Excerpts from Ketil Malde's message of Wed Oct 07 05:13:19 -0400 2009:
One could argue that IO should be broken down into a set of "sub-monads" encapsulating various subsets of the functionality - file system, network access, randomness, and so on. This could extend the "safe spot" to cover much more computational real estate, and effectively sandbox programs in various ways.
You can approximate this using the Prompt monad. http://hackage.haskell.org/packages/archive/MonadPrompt/1.0.0.1/doc/html/Con... Cheers, Edward

Duncan Coutts wrote:
So you end up with pure functions like:
shuffle :: RandomGen g => g -> [x] -> [x]
Thanks for the help, Duncan. I'm confused on one point. Don't you always need the new state of the generator back? So wouldn't this need to be: shuffle :: RandomGen g => g -> [x] -> (g,[x])
Another approach is to hide the 'g' inside a monad. That's what MonadRandom is all about. eg:
shuffle :: [x] -> Rand [x]
One tutorial mentions the class Gen in the Test.QuickCheck module. Is "Rand" a different class defined somewhere else?
The tutorials above explain about the other random functions, for getting values of different types (not just Int) and restricted ranges of number etc.
Of course at some point you want to seed the random number generator with some initial genuinely random value (not like the 12345 we used above). That is the only place in your random-handling code that needs to do IO. All the rest of it can be pure.
What function gives you that initial random seed? (Grabs it from the system clock?) Thanks, Mike

I think I've answered part of my question. There is a function that lives in the IO monad, newStdGen. This gives you a new generator with random initial state. That's the first part of the story. Then, I'm not sure, but perhaps you can call newStdGen many times during a program and get good pseudorandom behavior. For example: shuffle :: RandomGen g, Random a => g -> [a] -> [a] shuffle = ... main = do g1 <- newStdGen print (shuffle g1 [1,2,3,4,5] :: [Int]) g2 <- newStdGen print (shuffle g2 [6,7,8,9,0] :: [Int]) Does calling newStdGen twice in a row give good behavior? Is it a bad idea? Is it system-dependent? Also note that I added the Random class constraint to 'shuffle'. I haven't tested this but it might be necessary. Or not? Thanks, Mike Michael P Mossey wrote:
Duncan Coutts wrote:
So you end up with pure functions like:
shuffle :: RandomGen g => g -> [x] -> [x]
Thanks for the help, Duncan. I'm confused on one point. Don't you always need the new state of the generator back? So wouldn't this need to be:
shuffle :: RandomGen g => g -> [x] -> (g,[x])
Another approach is to hide the 'g' inside a monad. That's what MonadRandom is all about. eg:
shuffle :: [x] -> Rand [x]
One tutorial mentions the class Gen in the Test.QuickCheck module. Is "Rand" a different class defined somewhere else?
The tutorials above explain about the other random functions, for getting values of different types (not just Int) and restricted ranges of number etc.
Of course at some point you want to seed the random number generator with some initial genuinely random value (not like the 12345 we used above). That is the only place in your random-handling code that needs to do IO. All the rest of it can be pure.
What function gives you that initial random seed? (Grabs it from the system clock?)
Thanks, Mike _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Michael P Mossey wrote:
Also note that I added the Random class constraint to 'shuffle'. I haven't tested this but it might be necessary. Or not?
Okay I figured this part out too. The members of the list you are shuffling have no class constraint on them because the 'shuffle' function is not generating or computing with them... only moving them around.

On Tue, 2009-10-06 at 13:22 -0700, Michael P Mossey wrote:
Duncan Coutts wrote:
So you end up with pure functions like:
shuffle :: RandomGen g => g -> [x] -> [x]
Thanks for the help, Duncan. I'm confused on one point. Don't you always need the new state of the generator back? So wouldn't this need to be:
shuffle :: RandomGen g => g -> [x] -> (g,[x])
Yes if you want it back at the end. This is actually an interesting case for split, which is another member of the RandomGen class. Having the luxury to discard the tail of the sequence relies on us being able to split the RNG first so that we don't end up loosing the RNG completely. Why might we want to be able to discard the tail? In the shuffle case above we can actually do the shuffle lazily. If we use the right algorithm we can use a single random number per element returned, and only have to compute each random number when each element of the result is demanded. But if we had to return the final state of the RNG then that would force us to have used all the random numbers we might eventually need, which would defeat the lazy shuffle.
Another approach is to hide the 'g' inside a monad. That's what MonadRandom is all about. eg:
shuffle :: [x] -> Rand [x]
One tutorial mentions the class Gen in the Test.QuickCheck module. Is "Rand" a different class defined somewhere else?
It's a monad type from the MonadRandom package. Essentially it deals with passing the RNG in and returning the new one at the end. It's similar to QC's Gen monad, but not specialised to the task of generating random elements of various types.
The tutorials above explain about the other random functions, for getting values of different types (not just Int) and restricted ranges of number etc.
Of course at some point you want to seed the random number generator with some initial genuinely random value (not like the 12345 we used above). That is the only place in your random-handling code that needs to do IO. All the rest of it can be pure.
What function gives you that initial random seed? (Grabs it from the system clock?)
System.Random doesn't have an explicit "initialise from the system" action. It has a global StdGen that is always available and gets initialised once from the system. To get a new, independent StdGen use newStdGen :: IO StdGen which works just by applying 'split' to the global StdGen. Duncan
participants (16)
-
Ben Franksen
-
Bulat Ziganshin
-
Conor McBride
-
Daniel Fischer
-
David Virebayre
-
Duncan Coutts
-
Edward Z. Yang
-
Eugene Kirpichov
-
Felipe Lessa
-
John A. De Goes
-
Ketil Malde
-
Malcolm Wallace
-
Michael Mossey
-
Michael P Mossey
-
Peter Verswyvelen
-
Ryan Ingram