so how does one convert an IO a into an a ?

Hi Thanks for your help so far, but I am still not getting this IO stuff. After reading your previous help and reading several articles on it I still cant phathom how you convert the IO Int into an Int. One person mentioned how random just returns an interative program which when eveluated returns the Int. Also from the school of expression book he says " The right way to think of (>>=) above is simply this: It "Executes" e1 ..." in relation to "do pat <- e1 ...". so I have this: <code> rollDice :: IO Int rollDice = getStdRandom (randomR (1,6)) rl :: [Int] rl = [ (getRndNum x) | x <- [1..] ] getRndNum :: Int -> Int getRndNum x = do n <- rollDice return n </code> *PS Pretend return is correctly aligned under n. dont what ahppens in copy and paste* now my understanding therefore is that "do n <- rollDice" should execute the the itererative program returned by rollDice. So now n should be my Int since IO Int was a program which when evaluted returns an Int ? However this is what haskell thinks of my thoery: *** Term : getRndNum *** Type : Int -> IO (Maybe Int) *** Does not match : Int -> Int So I am still in IO Int land despite having used the >>= in the do syntax. Worse Still I am in IO (Maybe Int) land. Monads within Monads. In yours, and many other examples I found online, the results are always passed to print which seems to know how to deal with an IO Int. Is this specially coded or overloaded or something ? There are plenty of examples which use return like so: do k <- getKey w return k which is what I tried above to no avail. It seems awefully complicated just to get hold a simple Int, but naturally complicity is directly related to ones understanding. Mine is sumewhat lacking ... any help would be appreciated. Thanks, S _________________________________________________________________ Tired of spam? Get advanced junk mail protection with MSN 8. http://join.msn.com/?page=features/junkmail

Crypt Master, CM> Thanks for your help so far, but I am still not CM> getting this IO stuff. After reading your CM> previous help and reading several articles on CM> it I still cant phathom how you convert the IO CM> Int into an Int. Welcome to pure functional programming! :) Well, since you qualify as a beginner to Haskell, the only good answer one can give you is "you *cannot* convert from IO Int to Int. Until you're familiar enough with functional programming in general and Haskell, I'd recommend not to go with any suggestions people will give you on how to achieve this. Trust me. So, first try to ask yourself if it is really needed to get from IO Int to Int. If you're really convinced that it is and that is for nothing but good reasons, then ask again and we might carefully point you to a function that is called unsafePerformIO. (Note: it is called unsafe for a reason.) Now, think about this for a minute. Consider this a function foo :: Int -> Int. In Haskell, I can be sure that whenever I call this function with the same Int argument, I get the same Int result. This observation makes it quite easy for me to reason about this function, e.g. derive some theorems for it. So, I know foo 5 == foo 5 will *always* be True as will foo 6 == foo 6. Then, consider a function bar :: Int -> IO Int. That reads a number from some file, increments the number by argument value, writes the new number back to the file, and produces the new number as the result of the function. (The interaction with the file system makes that the result is included in an IO value.) So, consecutive calls to this function with the same argument will produce different values, won't they? But now imagine now you could somehow convert from IO Int to Int. Then you could use this mechanism to derive a function bar' :: String -> Int that does the same as bar but unwraps the IO Int value to produce an Int. Since consecutive calls to bar' with the same argument are not guaranteed to produce the same values, we cannot rely on bar' 5 == bar' 5 and bar' 6 == bar' 6. Can you see that this troubles reasoning about functions and programs? So, to keep the language 'pure' all stuff inside the IO monad should stay within the IO monad. At first, you might think of this as a limitation, but if you open yourself for it and think about it for a while, and---even better---work with it for a while, I'm sure you will start to appreciate it and start consider it a feature. Well, I might have simplified things here, and perhaps haven't explained in a very clear way: I'm sorry for that. However, I think this is more or less the main reason why the answer to your question should be 'you can't'. HTH, Stefan

Most of my imperative pieces of software find their answers by touching around in some space of solutions and my favourite approximation algorithms use random distributions. Is it haskell the wrong languages for those, as I'm obliged to code them inside Monads loosing the benefits of lazyness? grazie Paolino

At 21:40 08/07/04 +0200, paolo veronelli wrote:
Most of my imperative pieces of software find their answers by touching around in some space of solutions and my favourite approximation algorithms use random distributions.
Is it haskell the wrong languages for those, as I'm obliged to code them inside Monads loosing the benefits of lazyness?
I don't see any reason to sacrifice the benefits of laziness. I can imagine a program that uses internally a random sequence of values. Given a suitable pseudo-random value generator, it would be quite possible to write a pure function that accepts as one its parameters a seed for the P-R generator. For many randomized algorithms, I think this should work fine, though I don't recommend this approach for cryptographic work. #g ------------ Graham Klyne For email: http://www.ninebynine.org/#Contact

On Thursday 08 July 2004 20:40, paolo veronelli wrote:
Most of my imperative pieces of software find their answers by touching around in some space of solutions and my favourite approximation algorithms use random distributions.
Is it haskell the wrong languages for those, as I'm obliged to code them inside Monads loosing the benefits of lazyness?
No, no reason to lose laziness. First off, suppose your algorithm is a loop that needs one random number per iteration. An obvious structure would be: loop :: Solution -> IO Solution loop old_solution = do a <- randomIO let new_solution = next a old_solution if goodEnough new_solution then return new_solution else loop new_solution With this structure, the loop is strict and imperative but the 'next' function which improves the solution is pure, lazy code. Except in trivial cases, the next function will be where all the action is so you still get most of the benefit of laziness. We can do better though. Using two functions in System.Random, it's easy to get an infinite list of random numbers: randomRsIO :: IO [Int] randomRsIO = do g <- getStdGen return (randoms g) Let's rewrite the above code to use a list of random numbers and an initial solution to search for a better solution: genSolutions :: [Int] -> Solution -> [Solution] genSolutions (r:rs) s0 = s0 : genSolutions (next r s0) -- slightly more cryptic implementation using foldl and map possible -- and probably preferable findGoodSolution :: [Int] -> Solution -> Solution findGoodSolution rs s0 = head (dropWhile (not . goodEnough) solutions) where solutions = genSolutions rs s0 main = do rs <- randomRsIO print (findGoodSolution rs initial_solution) Hope this helps, -- Alastair Reid

On Thu, Jul 08, 2004 at 11:44:38PM +0100, Alastair Reid wrote: [snip]
We can do better though. Using two functions in System.Random, it's easy to get an infinite list of random numbers:
randomRsIO :: IO [Int] randomRsIO = do g <- getStdGen return (randoms g) [snip]
Except that AFAICS, getStdGen gives you _the_ standard PRNG which means that you shouldn't use it (the standard PRNG) anymore afterwards, or you'll get repeated numbers: (getStdGen returns the current state without changing it) -- Return the current state and use it Prelude Random> getStdGen >>= print . take 10 . randomRs (0,9::Int) [4,5,9,0,9,5,6,3,5,3] -- Return & use it again and you'll get the _same answers_ Prelude Random> getStdGen >>= print . take 10 . randomRs (0,9::Int) [4,5,9,0,9,5,6,3,5,3] -- getStdRandom is a special use-and-consume function Prelude Random> (sequence $ replicate 10 $ getStdRandom $ randomR (0,9::Int)) >>= print [4,5,9,0,9,5,6,3,5,3] -- Finally: the last getStdRandom _did_ change the PRNG state Prelude Random> (sequence $ replicate 10 $ getStdRandom $ randomR (0,9::Int)) >>= print [1,5,0,7,8,6,6,4,4,1] newStdGen splits the current state (using one as the new stdGen and returning the other), which probably _is_ what you want. Except that I have no idea what hidden costs splitting random number generators have :) (anyone?) Prelude Random> newStdGen >>= print . take 10 . randomRs (0,9::Int) [4,9,9,2,3,2,9,6,9,3] Prelude Random> newStdGen >>= print . take 10 . randomRs (0,9::Int) [5,1,5,5,9,0,8,6,2,1] Prelude Random> (sequence $ replicate 10 $ getStdRandom $ randomR (0,9::Int)) >>= print [2,0,1,5,2,5,6,0,4,7] Prelude Random> (sequence $ replicate 10 $ getStdRandom $ randomR (0,9::Int)) >>= print [9,9,2,7,2,5,3,4,0,0] Prelude Random> Groeten, Remi -- Nobody can be exactly like me. Even I have trouble doing it.

[Warning: this message is going to talk about 'splitting supplies' and 'splitting random number generators'. The two sound quite similar and can be used to accomplish similar goals but are quite different in the way you write your code, in how repeatable the results, etc. so try not to confuse the two.]
Except that AFAICS, getStdGen gives you _the_ standard PRNG which means that you shouldn't use it (the standard PRNG) anymore afterwards, or you'll get repeated numbers: [...] newStdGen splits the current state (using one as the new stdGen and returning the other), which probably _is_ what you want.
Yes, you're quite right - use newStdGen instead of getStdGen. Also consider use of a 'splittable supply'. This is a generic mechanism for splitting infinite lists of values into trees of lists in situations where the values are regarded as 'equivalent' in the sense that they are all equally good. For example, the fresh names used inside a compiler to name temporary variables are all equally good (as long as you don't reuse them), and random numbers are all equally good. One Supply implementation is documented here: http://www.csg.lcs.mit.edu/~earwig/haskell-lib/ but I think another was mentioned recently on one of the Haskell mailing lists.
Except that I have no idea what hidden costs splitting random number generators have :) (anyone?)
A quick glance at the source suggests that the standard generator type is a pair of Ints and that the cost of splitting is a few arithmetic instructions - no big deal. -- Alastair Reid

The root problem is that random number generation is inherently stateful, and so the familiar imperative idioms don't translate directly into a pure functional language. In a C-like language, each invocation of "rand()" mutates a secret piece of state lurking off-stage; pure functional code doesn't have the option of doing this. What you should probably be using is an infinite list of random numbers (see "randoms" in "Random"). With regard to your IO question, note that "return" "puts the IO back on", as it were; all this is carefully organised so you *can't* quietly file the IO's off values. The trick is to write almost everything in pure functions, then have a little bit of monad-y glue which connects all these ethereal abstractions (what might happen) to the merely contingent (what actually does). Disclaimer: I'm no haskell expert. John P.S. Sorry, but I can't resist this. With apologies to Allen Ginsberg: IO Howl ------- Monad! Monad! Nightmare of Monad! Monad the loveless! Mental Monad! Monad the heavy judger of men! Monad the incomprehensible prison! Monad the crossbone soulless jailhouse and Congress of sorrows! Monad whose buildings are judgement! Monad the vast stone of war! Monad the stunned governments! Monad whose mind is pure machinery! Monad whose blood is running money! Monad whose fingers are ten armies! Monad whose breast is a cannibal dynamo! Monad whose ear is a smoking tomb!

On Thu, 8 Jul 2004, John Kozak wrote:
The root problem is that random number generation is inherently stateful, and so the familiar imperative idioms don't translate directly into a pure functional language. In a C-like language, each invocation of "rand()" mutates a secret piece of state lurking off-stage; pure functional code doesn't have the option of doing this.
Another way of thinking about/implementing it is to thread through the relevant state, eg: rand :: RandState -> (Int, RandState) where RandState is the state from which numbers are generated. Then, you must be careful to avoid reusing any particular RandState if you don't want to have repetitions. You can do pure I/O in this way too, where the threaded state is "the state of the world". Mercury does this; Hello World looks something like this: :- pred main(io:state, io:state). :- mode main(di, uo) is det. main(S1, S2) :- io:write_string("Hello, World!\n", S1, S2). Here io:state is the type of "the state of the world". It's really important that you don't reuse an old "state of the world" because it would rip holes in timespace. That's the point of the "mode" declaration... the "di" is short for "destructive input" and the "uo" for "unique output". They are "linear modes", which basically means the compiler won't let you reuse an io:state. If you have multiple I/O actions you have to thread the states correctly, viz: main(S1, S3) :- io:write_string("Hello, ", S1, S2). io:write_string("World!\n", S2, S3). If you write this: main(S1, S2) :- io:write_string("Hello, ", S1, S2). io:write_string("World!\n", S1, S2). the compiler will scream at you for trying to rip timespace by reusing S1. It's conceptually straightforward, but a bit fiddly, so Mercury has a couple of bits of syntactic sugar to make it nicer, which means you can write: main --> :- io:write_string("Hello, "). io:write_string("World!\n"). or main(!S) :- io:write_string("Hello, ", !S), io:write_string("World\n", !S). and the threading gets done automatically. And of course, the compiled code doesn't really thread any states-of-the-world around, it all disappears inside the compiler once the modes have been checked. I think Clean does a similar thing for I/O with its linear types. So it's similar to Haskell's IO monad, in that you end up with an "I/O shell" with side-effects around a pure program. It's different in that monads are a bit more powerful in general, and a zillion times harder to understand. Perhaps it's helpful to think about the IO monad as just a way of doing this state threading, or perhaps it just confuses things further. N ps: I might have got the module separator ':' wrong above -- "__" is a (horrible) alternative, '.' might be accepted now.

[...] So I am still in IO Int land despite having used the >>= in the do syntax. [...]
The idea of the IO type is that it marks code that can behave differently each time it is called. For this reason, the IO monad 'infects' everything above it in the call chain and, for this reason, the entire program (i.e., Main.main) has type IO (). Rather than trying to extract an Int from the IO monad, you should look at how you can use an Int inside the IO monad. Many programs have a structure like this: read a value, compute a result, display the result. Let's suppose we have a function to do each of these three parts: readValue :: IO Int compute :: Int -> String display :: String -> IO () Note that reading and displaying have side effects and/or depend on the environment so they involve the IO monad. Since they involve a monad, let's use the do notation. Obviously, we start by reading a value: main = do x <- readValue .... The next thing to do is to compute a result. From the types, we know that x has type Int so obviously we want something involving 'compute x'. compute is not in the IO monad so we'll use a let binding instead of '<-': main = do x <- readValue let y = compute x ... Now we want to display y. We know that y has type String so we can apply display to it. 'display y' has type 'IO ()' so we use a monadic binding (<-) instead of a let binding: main = do x <- readValue let y = compute x z <- display y .... Hmmm, what to do with z. It's type is just () so we don't really need to bind it to anything so let's drop the binding to get the complete program: main = do x <- readValue let y = compute x display y Let me summarise what went on here: 1) If something has monadic type (i.e., has side effects or depends on the environment it is run in), use '<-' to bind the (non-monadic) result to a variable. 2) If something is not monadic (i.e., doesn't affect the world and doesn't depend on the world), use 'let' to bind the (non-monadic) result to a variable. 3) If something has a monadic type but we don't care about the result (so, presumably, it has an interesting side effect) you can drop the 'blah <-' part. [This last rule makes more sense if you use >>= and >> instead of the do notation. >>= corresponds to binding a result using '<-' while
corresponds to not binding a result.]
Another way of looking at it is that the IO monad infects the type of everything _above_ it in the call chain but doesn't infect the type of things _below_ it. So if you have a pure function like 'compute', you just call it from within the IO monad rather than trying to get out of the IO monad, call compute and then go back into the IO monad when you want to display the result. I hope this helps, -- Alastair Reid

On 09/07/2004, at 4:50 AM, Crypt Master wrote:
One person mentioned how random just returns an interative program which when eveluated returns the Int. Also from the school of expression book he says " The right way to think of (>>=) above is simply this: It "Executes" e1 ..." in relation to "do pat <- e1 ...".
so I have this:
<code> rollDice :: IO Int rollDice = getStdRandom (randomR (1,6))
rl :: [Int] rl = [ (getRndNum x) | x <- [1..] ]
getRndNum :: Int -> Int getRndNum x = do n <- rollDice return n </code> *PS Pretend return is correctly aligned under n. dont what ahppens in copy and paste*
Other people have covered a lot about IO, but for your particular problem of random numbers, here's a reasonably simple solution: module RandomList where import Random seed :: Int seed = 69 randomList :: [Int] randomList = randomRs (1,6) (mkStdGen seed) Usage: RandomList> :t randomList randomList :: [Int] RandomList> take 10 randomList [6,2,6,2,6,2,1,3,2,3] RandomList> The key to figuring out how on earth to use the combinations of randomRs and generators is having good documentation on the Random module, which I found here: http://www.haskell.org/ghc/docs/latest/html/libraries/base/ System.Random.html#t%3ARandom I'm guessing you're using hugs, which does give you the Random module, but it's not exactly easy to figure out from reading the source code (especially if you're a Haskell beginner)! -- % Andre Pang : trust.in.love.to.save

Judging from a previous message I'm not sure if you're still using SOE, but one of the things I tried to do is introduce IO without mentioning monads at all, and if you read chapter 3 (especially section 3.1) you will see that that's the case. To those who have had imperative programming experience, I think that section 3.1 should not present any problems. But it sounds as if you've gotten past that, since you quoted something from chapter 18, where the "mysteries" of IO are revealed in gory detail. It looks like lots of people have given you good advice, but I'll throw in one more idea about how to "convert an IO Int into an Int". Although, as many have pointed out, you can't really do this in a technical sense, you can get the effect that you want as follows: Suppose you have a function foo of type IO Int, and you wish to apply a function bar of type Int -> T to the value you get from foo (T is some result type). Then all you have to do is this:
do i <- foo return (bar i)
This is what people meant by "writing a little monadic scaffolding" to achieve what you want. The function bar is a pure function that does not involve IO at all. It may involve dozens of page of code, but you need the two lines of "scaffolding" above in order to invoke it. Now, in the end, you might say that we haven't achieved much, because the above expression has type IO T, so all we've really done is convert an IO Int into an IO T. Quite true! That's why most of the people who responded to your email eventually wrote something like:
do i <- foo putStr (show (bar i))
or whatever, in order to actually generate some useful output. Indeed, that useful output might also include writing to a file, displaying some graphics, etc. I hope this helps, -Paul Crypt Master wrote:
Hi
Thanks for your help so far, but I am still not getting this IO stuff. After reading your previous help and reading several articles on it I still cant phathom how you convert the IO Int into an Int.
One person mentioned how random just returns an interative program which when eveluated returns the Int. Also from the school of expression book he says " The right way to think of (>>=) above is simply this: It "Executes" e1 ..." in relation to "do pat <- e1 ...".
so I have this:
<code> rollDice :: IO Int rollDice = getStdRandom (randomR (1,6))
rl :: [Int] rl = [ (getRndNum x) | x <- [1..] ]
getRndNum :: Int -> Int getRndNum x = do n <- rollDice return n </code> *PS Pretend return is correctly aligned under n. dont what ahppens in copy and paste*
now my understanding therefore is that "do n <- rollDice" should execute the the itererative program returned by rollDice. So now n should be my Int since IO Int was a program which when evaluted returns an Int ?
However this is what haskell thinks of my thoery:
*** Term : getRndNum *** Type : Int -> IO (Maybe Int) *** Does not match : Int -> Int
So I am still in IO Int land despite having used the >>= in the do syntax. Worse Still I am in IO (Maybe Int) land. Monads within Monads.
In yours, and many other examples I found online, the results are always passed to print which seems to know how to deal with an IO Int. Is this specially coded or overloaded or something ?
There are plenty of examples which use return like so:
do k <- getKey w return k
which is what I tried above to no avail.
It seems awefully complicated just to get hold a simple Int, but naturally complicity is directly related to ones understanding. Mine is sumewhat lacking ... any help would be appreciated.
Thanks,
S
participants (10)
-
Alastair Reid
-
André Pang
-
Crypt Master
-
Graham Klyne
-
John Kozak
-
Nicholas Nethercote
-
paolo veronelli
-
Paul Hudak
-
Remi Turk
-
Stefan Holdermans