
Hi, I am using the System.Random method randomRIO. How can I convert its output to an Int? Thanks... -- View this message in context: http://www.nabble.com/Convert-IO-Int-to-Int-tp23940249p23940249.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

You can not convert an IO Int to Int, or at least, you shouldn't.
However, you can do as follows:
test :: IO ()
test = do
int <- randomRIO -- or whatever it is called
print $ useInt int
useInt :: Int -> Int
useInt x = x+10
//Tobias
2009/6/9 ptrash
Hi,
I am using the System.Random method randomRIO. How can I convert its output to an Int?
Thanks... -- View this message in context: http://www.nabble.com/Convert-IO-Int-to-Int-tp23940249p23940249.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Tobias Olausson tobsan@gmail.com

On 2009/06/09, at 19:33, Tobias Olausson wrote:
You can not convert an IO Int to Int, or at least, you shouldn't. However, you can do as follows:
test :: IO () test = do int <- randomRIO -- or whatever it is called print $ useInt int
useInt :: Int -> Int useInt x = x+10
Or, you can lift pure function into IO. the below test' function almost same as above test function. (But I used randomIO instead of randomRIO because it seemed to be a typo :-) test' = print =<< fmap useInt randomIO I think it is more handy than using do notation, when you want to do something simple with monads. And converting IO Int to IO anything is much easier and safer than converting IO Int to Int. ghci> :m +System.Random Data.Char ghci> :t fmap (+1) randomIO fmap (+1) randomIO :: (Num a, Random a) => IO a ghci> :t fmap show randomIO fmap show randomIO :: IO String ghci> :t fmap chr randomIO fmap Data.Char.chr randomIO :: IO Char ghci> :t fmap (+) randomIO fmap (+) randomIO :: (Num a, Random a) => IO (a -> a) Thanks, Hashimoto
//Tobias
2009/6/9 ptrash
: Hi,
I am using the System.Random method randomRIO. How can I convert its output to an Int?
Thanks... -- View this message in context: http://www.nabble.com/Convert-IO-Int- to-Int-tp23940249p23940249.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Tobias Olausson tobsan@gmail.com _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

ptrash wrote:
Hi,
I am using the System.Random method randomRIO. How can I convert its output to an Int?
Thanks...
You cannot [1], you should read up on monads and I/O in Haskell, for example http://haskell.org/haskellwiki/IO_inside [1] Yes, you can, but no, you don't want to. Regards, -- Jochem Berndsen | jochem@functor.nl GPG: 0xE6FABFAB

Ok, thanks for the information. -- View this message in context: http://www.nabble.com/Convert-IO-Int-to-Int-tp23940249p23942344.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Hmm...it am not getting through it. I just want to generate a random number and then compare it with other numbers. Something like r = randomRIO (1, 10) if (r > 5) then... else ... -- View this message in context: http://www.nabble.com/Convert-IO-Int-to-Int-tp23940249p23943301.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On Tue, Jun 9, 2009 at 2:52 PM, ptrash
Hmm...it am not getting through it. I just want to generate a random number and then compare it with other numbers. Something like
r = randomRIO (1, 10) if (r > 5) then... else ...
You have to do it inside the IO monad, something like myFunc = do r <- randomRIO (1, 10 if r > 5 then ... else ... /M -- Magnus Therning (OpenPGP: 0xAB4DFBA4) magnus@therning.org Jabber: magnus@therning.org http://therning.org/magnus identi.ca|twitter: magthe

Am Dienstag 09 Juni 2009 15:57:24 schrieb Magnus Therning:
On Tue, Jun 9, 2009 at 2:52 PM, ptrash
wrote: Hmm...it am not getting through it. I just want to generate a random number and then compare it with other numbers. Something like
r = randomRIO (1, 10) if (r > 5) then... else ...
You have to do it inside the IO monad, something like
myFunc = do r <- randomRIO (1, 10 if r > 5 then ... else ...
/M
Or make the source of the pseudo-random numbers explicit: import System.Random function :: (RandomGen g, Random a) => g -> other args -> result function gen whatever | r > 5 = blah newgen something | r < 3 = blub newgen somethingElse | otherwise = bling where (r,newgen) = randomR (lo,hi) gen and finally, when the programme is run: main = do args <- getArgs sg <- getStdGen foo <- thisNThat print $ function sg foo If you're doing much with random generators, wrap it in a State monad.

On Tue, Jun 9, 2009 at 16:14, Daniel Fischer
Am Dienstag 09 Juni 2009 15:57:24 schrieb Magnus Therning:
On Tue, Jun 9, 2009 at 2:52 PM, ptrash
wrote: Hmm...it am not getting through it. I just want to generate a random number and then compare it with other numbers. Something like
r = randomRIO (1, 10) if (r > 5) then... else ...
You have to do it inside the IO monad, something like
myFunc = do r <- randomRIO (1, 10 if r > 5 then ... else ...
/M
Or make the source of the pseudo-random numbers explicit:
import System.Random
function :: (RandomGen g, Random a) => g -> other args -> result function gen whatever | r > 5 = blah newgen something | r < 3 = blub newgen somethingElse | otherwise = bling where (r,newgen) = randomR (lo,hi) gen
and finally, when the programme is run:
main = do args <- getArgs sg <- getStdGen foo <- thisNThat print $ function sg foo
If you're doing much with random generators, wrap it in a State monad.
To avoid reinventing the wheel one can use excellent package available on Hackage: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/MonadRandom
The die function simulates the roll of a die, picking a number between 1 and 6, inclusive, and returning it in the Rand monad. Notice that this code will work with any source of random numbers g.
die :: (RandomGen g) => Rand g Int die = getRandomR (1,6)
The dice function uses replicate and sequence to simulate the roll of n dice.
dice :: (RandomGen g) => Int -> Rand g [Int] dice n = sequence (replicate n die)
To extract a value from the Rand monad, we can can use evalRandIO.
main = do values <- evalRandIO (dice 2) putStrLn (show values)
Best regards Krzysztof Skrzętnicki

2009/6/9 Krzysztof Skrzętnicki
On Tue, Jun 9, 2009 at 16:14, Daniel Fischer
wrote: If you're doing much with random generators, wrap it in a State monad.
To avoid reinventing the wheel one can use excellent package available on Hackage: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/MonadRandom
Please do! Prefer MonadRandom to explicit generator passing: http://lukepalmer.wordpress.com/2009/01/17/use-monadrandom/. Keep computations in MonadRandom, and pull them out with evalRandomIO at the last second. Luke
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/MonadRandom
The die function simulates the roll of a die, picking a number between 1 and 6, inclusive, and returning it in the Rand monad. Notice that this code will work with any source of random numbers g.
die :: (RandomGen g) => Rand g Int die = getRandomR (1,6)
The dice function uses replicate and sequence to simulate the roll of n dice.
dice :: (RandomGen g) => Int -> Rand g [Int] dice n = sequence (replicate n die)
To extract a value from the Rand monad, we can can use evalRandIO.
main = do values <- evalRandIO (dice 2) putStrLn (show values)
Best regards
Krzysztof Skrzętnicki _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Magnus Therning writes:
ptrash wrote:
...am not getting through it. I just want to generate a random number and then compare it with other numbers. Something like
r = randomRIO (1, 10) if (r > 5) then... else ...
You have to do it inside the IO monad, something like
myFunc = do r <- randomRIO (1, 10
This may continue forever... With nice references to monads, to Unsafe@#*!, etc. ... We may say, as many tutorials do : "this is not what you want!" (which I hate ; you are not my conscience, whoever you are...), or just give some code, not always readable... Perhaps I belong to a minority here, but I strongly believe that at THIS level, the first thing to do - unless I am dead wrong - is to explain to our friend ptrash (who could find a less gothic pseudo) that in a pure functional programming, the construction r = whatEver(par1,par2) being a function call, cannot give "just a random number", something which is not (intuitively) determined, and changes with every call, despite the constancy of the arguments. For most of us, acquainted with the stuff, it becomes trivial, but if somebody doesn't know that a classical pseudo-random generator modifies a "seed", and in such a way involves a "side effect", then sending him to the monadic heaven is dangerous. Please, tell him first about random streams, which he can handle without IO. Or, about ergodic functions (hashing contraptions which transform ANY parameter into something unrecognizable). When he says : "I know all that", THEN hurt him badly with monads. Jerzy Karczmarczuk

Hello jerzy, Tuesday, June 9, 2009, 8:23:04 PM, you wrote:
Please, tell him first about random streams, which he can handle without IO. Or, about ergodic functions (hashing contraptions which transform ANY parameter into something unrecognizable). When he says : "I know all that", THEN hurt him badly with monads.
i think that for someone coming from imperative programming teeling about IO monad is the easiest way. and then he will learn how to do it FP way -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello jerzy,
Tuesday, June 9, 2009, 8:23:04 PM, you wrote:
Please, tell him first about random streams, which he can handle without IO. Or, about ergodic functions (hashing contraptions which transform ANY parameter into something unrecognizable). When he says : "I know all that", THEN hurt him badly with monads.
i think that for someone coming from imperative programming teeling about IO monad is the easiest way. and then he will learn how to do it FP way
I came from a imperative programming background. I didn't feel like this help me at all back then. At least in the beginning you want to detach yourself from an imperative style, not try to simulate it with some weird structure that you don't really understand. More generally I really wish IO hadn't been the first Monad I played with. It's so close to a Functor, yet in my mind Functors were simple, just structures that could be mapped, and Monads were these mysterious things that allowed you to get away with side effects and that once you were inside you could never get out. Jorge

On Tue, 9 Jun 2009, Bulat Ziganshin wrote:
Hello jerzy,
Tuesday, June 9, 2009, 8:23:04 PM, you wrote:
Please, tell him first about random streams, which he can handle without IO. Or, about ergodic functions (hashing contraptions which transform ANY parameter into something unrecognizable). When he says : "I know all that", THEN hurt him badly with monads.
i think that for someone coming from imperative programming teeling about IO monad is the easiest way. and then he will learn how to do it FP way
I came from imperative programming and never wanted to use randomIO, because it forces you to IO and randomsIO is not lazy.

On Tue, 9 Jun 2009, ptrash wrote:
I am using the System.Random method randomRIO. How can I convert its output to an Int?
in general: http://haskell.org/haskellwiki/How_to_get_rid_of_IO about randomIO: http://haskell.org/haskellwiki/Avoiding_IO#State_monad

Hi, I have tried on the console to write x <- randomRIO(1,10) :t x Everythings fine and the type of x is x :: Integer Now I have tried to write a Method which gives me a Number of random numbers the same way but it doesn't work. randomList :: Int -> [Integer] randomList 0 = [] randomList n = do r <- randomRIO (1, 10) r:randomList(n-1) It says Couldn't match expected type `IO t' against inferred type `[t]' r <- randomRIO (1,10) causes an error. But why does it work on the console? Is there a way to solve it another way? -- View this message in context: http://www.nabble.com/Convert-IO-Int-to-Int-tp23940249p23960652.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

"r <- randomRIO (1,10)" is NOT the source of error. Why do you think it is? ptrash wrote on 10.06.2009 15:55:
Hi,
I have tried on the console to write
x <- randomRIO(1,10) :t x
Everythings fine and the type of x is x :: Integer
Now I have tried to write a Method which gives me a Number of random numbers the same way but it doesn't work.
randomList :: Int -> [Integer] randomList 0 = [] randomList n = do r <- randomRIO (1, 10) r:randomList(n-1)
It says Couldn't match expected type `IO t' against inferred type `[t]' r <- randomRIO (1,10) causes an error. But why does it work on the console? Is there a way to solve it another way?

Hmm...I use the Eclipse Plugin. And this row is marked as error. Then where is the error? -- View this message in context: http://www.nabble.com/Convert-IO-Int-to-Int-tp23940249p23960827.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On 10 Jun 2009, at 12:55 pm, ptrash wrote:
Now I have tried to write a Method which gives me a Number of random numbers the same way but it doesn't work.
randomList :: Int -> [Integer] randomList 0 = [] randomList n = do r <- randomRIO (1, 10) r:randomList(n-1)
It says Couldn't match expected type `IO t' against inferred type `[t]' r <- randomRIO (1,10) causes an error. But why does it work on the console? Is there a way to solve it another way?
I had the same problem a while back, the thread is here http://www.mail-archive.com/haskell-cafe@haskell.org/msg46194.html the console uses IO already, so it's not a problem there. I ended up learning about the >>= operator, and that helped a lot. Anyway, lots of helpful links in that mail thread. Iain

On Wed, Jun 10, 2009 at 12:55 PM, ptrash
Hi,
I have tried on the console to write
x <- randomRIO(1,10) :t x
Everythings fine and the type of x is x :: Integer
The type of x *in the context of an IO computation* is Integer. GHCi is basically an IO computation. Another example: foo :: Integer -> Integer foo x = x+1 main :: IO () main = do x <- randomRIO (1,10) print (foo x) This is fine. In the context of the IO computation "main", x is bound to the result of "randomRIO (1,10)", and you can pass it to functions expecting Integer values (not IO Integer!). So in this way, and this way only, you can access the Integer returned by an IO action. You can *not* access the Integer returned by an IO action from within a normal function, *only* by by binding it to a variable (with "<-") inside *another IO action*. I'm not sure what text you're using to learn Haskell, but a very basic and fundamental property of Haskell (and indeed 99% of why it's cool, IMO) is that code which does side effects (like reading from a global random number seed), and code which does not do side effects (i.e. functions which always return the same result given the same input) are kept extremely separate. This appears to be the source of your confusion. It's simply not possible to do side effect inside a normal function, just like it's not possible to cast an arbitrary integer to a pointer in Java - the language is designed to not require it, and the benefits of being able to trust that your program obeys certain properties are worth it.
randomList :: Int -> [Integer] randomList 0 = [] randomList n = do r <- randomRIO (1, 10) r:randomList(n-1)
In this code you're trying to do side effects from within a pure function. This is *not* allowed. You must either make randomList an IO action (i.e returning IO [Integer]), or remove any impurities from its implementation. For example you can make randomList take a randon number generator and use the random number generator to produce random values: randomList :: (RandomGen g) -> Int -> g -> [Integer] randomList 0 _ = [] randomList n generator = r : randomList (n-1) newGenerator where (r, newGenerator) = randomR (1,10) generator This is totally pure, since if you pass in the same random number generator multiple times, you'll get the exact same result. Note that randomR returns a random values and a new random number generator (you wouldn't want to pass along the same one in the recursive call to randomList as that would give you an identical random number each time you use it!). So where do you get the random number generator from? Well one way is to make your own using "mkStdGen", which produces one from a seed (it will give you an identical one given an identical seed). Another way is to use "newStdGen" to generate one from within an IO action: main :: IO () main = do generator <- newStdGen print ( randomList 10 generator ) The point, though, is that things having side effects (such as newStdGen) can only be used in the context of something else having side effects. So the "IO" type is "contagious", as soon as you use it in a function, then that function must also return IO, and so on for anything using *that* function and son. -- Sebastian Sylvan +44(0)7857-300802 UIN: 44640862

On Wed, Jun 10, 2009 at 2:08 PM, Sebastian Sylvan < sebastian.sylvan@gmail.com> wrote:
randomList :: (RandomGen g) -> Int -> g -> [Integer]
Just spotted this typo, it should be: randomList :: (RandomGen g) = Int -> g -> [Integer] There may be other minor typos as I don't have a compiler handy. -- Sebastian Sylvan +44(0)7857-300802 UIN: 44640862

On Wed, Jun 10, 2009 at 2:10 PM, Sebastian Sylvan < sebastian.sylvan@gmail.com> wrote:
On Wed, Jun 10, 2009 at 2:08 PM, Sebastian Sylvan < sebastian.sylvan@gmail.com> wrote:
randomList :: (RandomGen g) -> Int -> g -> [Integer]
Just spotted this typo, it should be:
randomList :: (RandomGen g) = Int -> g -> [Integer]
There may be other minor typos as I don't have a compiler handy.
Oh come on! randomList :: (RandomGen g) => Int -> g -> [Integer] -- Sebastian Sylvan +44(0)7857-300802 UIN: 44640862

Thanks a lot. I have put now everything into the main method and it works. -- View this message in context: http://www.nabble.com/Convert-IO-Int-to-Int-tp23940249p23964365.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

This stuff is tricky for most newcomers I suspect (it was for me)
x <- randomRIO(1,10)
is "temporarilly" pulling the Integer you've named "x" out of the IO Integer
it came from.
You can think of the console as being an input/output stream inside the IO
monad, which is why it is allowed there.
The fact is these are equivalent
do
x <- randomRIO(1,10)
x : <expression>
and
randomRIO(1,10) >>= (\x -> x:
Hi,
I have tried on the console to write
x <- randomRIO(1,10) :t x
Everythings fine and the type of x is x :: Integer
Now I have tried to write a Method which gives me a Number of random numbers the same way but it doesn't work.
randomList :: Int -> [Integer] randomList 0 = [] randomList n = do r <- randomRIO (1, 10) r:randomList(n-1)
It says Couldn't match expected type `IO t' against inferred type `[t]' r <- randomRIO (1,10) causes an error. But why does it work on the console? Is there a way to solve it another way? -- View this message in context: http://www.nabble.com/Convert-IO-Int-to-Int-tp23940249p23960652.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (16)
-
Bulat Ziganshin
-
Daniel Fischer
-
David Leimbach
-
Henning Thielemann
-
Iain Barnett
-
jerzy.karczmarczuk@info.unicaen.fr
-
Jochem Berndsen
-
Jorge Branco Branco Aires
-
Krzysztof Skrzętnicki
-
Luke Palmer
-
Magnus Therning
-
Miguel Mitrofanov
-
ptrash
-
Sebastian Sylvan
-
Tobias Olausson
-
Yusaku Hashimoto