
I'm just starting out with Haskell, and I could use some help. I'm trying to create a random list and print it out, which seems simple enough, but has been giving me problems. Here's what I have: module Main where import IO import Random randomList :: Random a => a -> a-> [IO a] randomList lbound ubound = randomRIO(lbound, ubound) : randomList lbound ubound main = do myRandomList <- sequence(randomList(0::Int 255)) putStrLn(show(take(10 myRandomList))) ----- So, I have tried to make a randomList action which defines an infinite random list, bounded by lbound and ubound. It seems that to print this, I need to convert between randomList, which is of type [IO a] to something like IO [a], which is what sequence should do for me. Then I just want to print out the first 10 elements. I'm currently getting the error "Only unit numeric type pattern is valid", pointing to 0::Int 255 in the code. I'm not sure what this means. I'm sure I'm looking at this the wrong way, since I'm new to Haskell and haven't quite wrapped my head around it yet. Maybe you can fix the problem by showing me a more Haskell approach to creating a random list and printing it... =) Thanks! - bryan catanzaro

catanzar:
I'm just starting out with Haskell, and I could use some help. I'm trying to create a random list and print it out, which seems simple enough, but has been giving me problems. Here's what I have:
module Main where import IO import Random
randomList :: Random a => a -> a-> [IO a] randomList lbound ubound = randomRIO(lbound, ubound) : randomList lbound ubound
main = do myRandomList <- sequence(randomList(0::Int 255)) putStrLn(show(take(10 myRandomList)))
-----
So, I have tried to make a randomList action which defines an infinite random list, bounded by lbound and ubound. It seems that to print this, I need to convert between randomList, which is of type [IO a] to something like IO [a], which is what sequence should do for me. Then I just want to print out the first 10 elements.
I'm currently getting the error "Only unit numeric type pattern is valid", pointing to 0::Int 255 in the code. I'm not sure what this means.
Missing parenthesis around the (0 :: Int) type annotation.
I'm sure I'm looking at this the wrong way, since I'm new to Haskell and haven't quite wrapped my head around it yet. Maybe you can fix the problem by showing me a more Haskell approach to creating a random list and printing it... =)
For lists, best to use the randomRs function, import System.Random main = do g <- newStdGen print (take 10 (randomRs (0,255) g :: [Int])) Running it: $ runhaskell A.hs [11,90,187,119,240,57,241,52,143,86] Cheers, Don

Thanks for the response, it does compile after I juggled some parentheses around. And also I appreciate the pointer to the better way of making a random list. So that problem is solved. However, when I ran my random list generator, the interpreter had a stack overflow. Here's my code again: --- module Main where import IO import Random randomList :: Random a => a -> a-> [IO a] randomList lbound ubound = randomRIO(lbound, ubound) : randomList lbound ubound main = do myRandomList <- sequence(randomList (0::Int) 255) putStrLn(show(take 10 myRandomList)) --- It seems that this code somehow tries to evaluate every element of the infinite list defined by randomList. Can you tell me why it is not lazily evaluating this list? I can get around this by changing main to do this instead: --- main = do myRandomList <- sequence(take 10 (randomList (0::Int) 255)) putStrLn(show(myRandomList)) --- But I don't understand why sequence(randomList (0::Int) 255) actually tries to evaluate the entire infinite list, instead of just lazily defining a list with the proper types, that I evaluate later when I take elements from it. Thanks for your help! - bryan On Jun 8, 2008, at 4:33 PM, Don Stewart wrote:
catanzar:
I'm just starting out with Haskell, and I could use some help. I'm trying to create a random list and print it out, which seems simple enough, but has been giving me problems. Here's what I have:
module Main where import IO import Random
randomList :: Random a => a -> a-> [IO a] randomList lbound ubound = randomRIO(lbound, ubound) : randomList lbound ubound
main = do myRandomList <- sequence(randomList(0::Int 255)) putStrLn(show(take(10 myRandomList)))
-----
So, I have tried to make a randomList action which defines an infinite random list, bounded by lbound and ubound. It seems that to print this, I need to convert between randomList, which is of type [IO a] to something like IO [a], which is what sequence should do for me. Then I just want to print out the first 10 elements.
I'm currently getting the error "Only unit numeric type pattern is valid", pointing to 0::Int 255 in the code. I'm not sure what this means.
Missing parenthesis around the (0 :: Int) type annotation.
I'm sure I'm looking at this the wrong way, since I'm new to Haskell and haven't quite wrapped my head around it yet. Maybe you can fix the problem by showing me a more Haskell approach to creating a random list and printing it... =)
For lists, best to use the randomRs function,
import System.Random
main = do g <- newStdGen print (take 10 (randomRs (0,255) g :: [Int]))
Running it:
$ runhaskell A.hs [11,90,187,119,240,57,241,52,143,86]
Cheers, Don

Bryan Catanzaro wrote:
However, when I ran my random list generator, the interpreter had a stack overflow. Here's my code again: --- module Main where import IO import Random
randomList :: Random a => a -> a-> [IO a] randomList lbound ubound = randomRIO(lbound, ubound) : randomList lbound ubound
main = do myRandomList <- sequence(randomList (0::Int) 255) putStrLn(show(take 10 myRandomList)) ---
It seems that this code somehow tries to evaluate every element of the infinite list defined by randomList.
You are correct.
Can you tell me why it is not lazily evaluating this list?
Whenever you use IO, there is a baton being passed along behind the scenes. The baton is called "RealWorld#" and it represents the fact that interactions with global state and the outside world have to be serialized. In particular, whenever you use the global random number generator, a global state variable has to be updated. This has to be serialized, thus the baton has to be passed along from one action to the next. When you "sequence" a list of IO actions, you are effectively sending the baton along that list, and you don't get it back until the end of the list is reached. Your code is sending the baton into an infinite list of actions, never to be returned.
I can get around this by changing main to do this instead:
--- main = do myRandomList <- sequence(take 10 (randomList (0::Int) 255)) putStrLn(show(myRandomList)) ---
Now you are sending the baton into a list of only 10 actions. The baton comes back, and the program goes on. If you don't know in advance how many random numbers you need, and if you are satisfied with the global random number generator, then Don Stewart's solution is a better approach. Don Stewart wrote:
main = do g <- newStdGen print (take 10 (randomRs (0,255) g :: [Int]))
If you want to be able to reproduce the same sequence of random numbers, for example for testing and debugging purposes, then you can use mkStdGen to create your own random number generator, independent of the global one. The catch is that you will have to thread the state of the random number generator through your code. Once you learn about monads (if you haven't already), you'll recognize that you can use the State monad for your random number generator.
participants (3)
-
Bryan Catanzaro
-
Don Stewart
-
Ronald Guida