Monte Carlo Pi calculation (newbie learnings)
 
            Hi all,
I'm new to Haskell, and don't quite understand how IO and lazy 
evaluation work together yet.  In order to improve my understanding, I 
thought I'd try to knock together a translation of a fairly simple 
problem I can code up in C, that of calculating pi by throwing random 
numbers about.  The C code I started with is as follows:
//////////////////////////////////////////////////
#include 
 
            On 11/5/07, Alex Young 
randList :: Int -> [IO Int] randList n = randListTail [] n
randPairs :: Int -> [(IO Int, IO Int)] randPairs n = zip (randList n) (randList n)
[snip]
doCountPair :: (IO Int, IO Int) -> IO Int doCountPair (a, b) = do x <- a y <- b return (pairIsInside x y)
fSumListTail :: Int -> [(IO Int, IO Int)] -> IO Int fSumListTail total [] = do return total fSumListTail total (x:xs) = do y <- doCountPair x fSumListTail (total+y) xs
fSumList :: [(IO Int, IO Int)] -> IO Int fSumList l = fSumListTail 0 l
It's unusual to return a list of IO actions or to take a list of pairs of IO actions as an argument. You should think about whether there's a reason you're doing this. For example, why not rewrite randList as: randList :: Int -> IO [Int] randList n = sequence $ randListTail [] n (for example)?
piAsDouble :: Int -> Int -> Double piAsDouble a b = (fromInteger (toInteger a)) / (fromInteger (toInteger b))
This can be rewritten as: fromIntegral a / fromIntegral b (I think -- not tested. The above isn't tested either.) Those are just a couple things that jump out at me. fSumListTail looks like it should be expressible using a foldM as well. In fact, fSumListTail looks like it ought to be a pure function. Think about how you can isolate the parts of the code that do IO so that most functions are pure. Cheers, Tim -- Tim Chevalier * catamorphism.org * Often in error, never in doubt "Faith, faith is an island in the setting sun / But proof, yes, proof is the bottom line for everyone."--Paul Simon
 
            Tim Chevalier wrote:
On 11/5/07, Alex Young
wrote: randList :: Int -> [IO Int] randList n = randListTail [] n
randPairs :: Int -> [(IO Int, IO Int)] randPairs n = zip (randList n) (randList n) [snip] doCountPair :: (IO Int, IO Int) -> IO Int doCountPair (a, b) = do x <- a y <- b return (pairIsInside x y)
fSumListTail :: Int -> [(IO Int, IO Int)] -> IO Int fSumListTail total [] = do return total fSumListTail total (x:xs) = do y <- doCountPair x fSumListTail (total+y) xs
fSumList :: [(IO Int, IO Int)] -> IO Int fSumList l = fSumListTail 0 l
It's unusual to return a list of IO actions or to take a list of pairs of IO actions as an argument. You should think about whether there's a reason you're doing this. For example, why not rewrite randList as:
randList :: Int -> IO [Int] randList n = sequence $ randListTail [] n
Wouldn't that force the list of Ints to be evaluated into memory all at once? I did have that (or a close approximation) in a previous version, but got rid of it because it wasn't clear to me how it could be lazily evaluated. The interesting thing about this specific problem (at least from my point of view) is that while random numbers happen in the IO monad, I explicitly don't care what order they are evaluated in - that's why I thought I'd be best off with a list of IO objects. Is this wrong?
(for example)?
piAsDouble :: Int -> Int -> Double piAsDouble a b = (fromInteger (toInteger a)) / (fromInteger (toInteger b))
This can be rewritten as: fromIntegral a / fromIntegral b (I think -- not tested. The above isn't tested either.)
Those are just a couple things that jump out at me. fSumListTail looks like it should be expressible using a foldM as well. I thought so, but couldn't quite figure it out. I'll have another stab at it.
(P.S. Sorry for the duplicate, Tim, I hadn't realised I replied off-list) Thanks, -- Alex
 
            On Mon, 2007-11-05 at 20:11 +0000, Alex Young wrote:
Hi all,
I'm new to Haskell, and don't quite understand how IO and lazy evaluation work together yet. In order to improve my understanding, I thought I'd try to knock together a translation of a fairly simple problem I can code up in C, that of calculating pi by throwing random numbers about. The C code I started with is as follows:
////////////////////////////////////////////////// #include
#include #include int main(int argc, char *argv[]) { if(argc != 2) { printf("usage: %s iteration_count", argv[0]); return 1; }
int total; if(sscanf(argv[1], "%d", &total) != 1) return 1;
int count = 0; int unit_radius = RAND_MAX * RAND_MAX; int i;
srand(time(NULL));
for(i = 0; i < total; i++) { int x, y; x = rand(); y = rand(); count += x*x + y*y < unit_radius; }
double pi = (count << 2) / (double)total;
printf("Count: %d\nTotal: %d\n", count, total); printf("%f", pi);
return 0; } ///////////////////////////////////////////////////
All very simple - the key is that I'm counting the result of a conditional evaluated inside a loop. Ignore whether it's correct, or accurate, for now; it happily runs and gives an accurate-looking result when run with an argument of 10000000. My (thoroughly ugly, not currently working) Haskell version looks like this:
{--------------------------------------------------} module Main where
import Random import System.Environment import List import Monad
randMax = 32767 unitRadius = randMax * randMax
rand :: IO Int rand = getStdRandom (randomR (0, randMax))
randListTail accum 0 = accum randListTail accum n = randListTail (rand : accum) (n - 1)
randList :: Int -> [IO Int] randList n = randListTail [] n
randPairs :: Int -> [(IO Int, IO Int)] randPairs n = zip (randList n) (randList n)
pairIsInside x y = if x*x + y*y < unitRadius then 1 else 0
doCountPair :: (IO Int, IO Int) -> IO Int doCountPair (a, b) = do x <- a y <- b return (pairIsInside x y)
fSumListTail :: Int -> [(IO Int, IO Int)] -> IO Int fSumListTail total [] = do return total fSumListTail total (x:xs) = do y <- doCountPair x fSumListTail (total+y) xs
fSumList :: [(IO Int, IO Int)] -> IO Int fSumList l = fSumListTail 0 l
piAsDouble :: Int -> Int -> Double piAsDouble a b = (fromInteger (toInteger a)) / (fromInteger (toInteger b))
calculatePi total = do count <- fSumList (randPairs total) return (piAsDouble (4*count) total)
main = do args <- getArgs (calculatePi (read (args !! 0))) >>= (putStr . show) {--------------------------------------------------}
Now, I have two questions. The easy question is, how can I make this more idiomatic?
main = do
Get two standard generators (one per dimension)
g0 <- newStdGen g1 <- newStdGen
Get an infinite list of pairs
let pairs = [ (x, y) | x <- randoms (-1, 1) g0, y <- randoms (-1, 1) g1 ]
Get a finite list
consideredPairs = take total pairs
Count how many are in the unit circle
circleArea = length $ filter (\ (x, y) -> x^2 + y^2 < 1) consideredPairs
Divide by total
ratio = fromInteger circleArea / fromIntegral total
Now, pi is approximated by ratio.
putStr $ show ratio
jcc
 
            On Nov 5, 2007 1:30 PM, Jonathan Cast 
main = do
Get two standard generators (one per dimension)
g0 <- newStdGen g1 <- newStdGen
Get an infinite list of pairs
let pairs = [ (x, y) | x <- randoms (-1, 1) g0, y <- randoms (-1, 1) g1 ]
This will return a list like [(a,b),(a,c),(a,d),(a,e),...]. This needs to be a parallel comprehension: let pairs = [ (x,y) | x <- randoms (-1,1) g0 | y <- randoms (-1,1) g1 ] (Did I remember that syntax right?) Luke
 
            On Mon, Nov 05, 2007 at 01:42:50PM -0700, Luke Palmer wrote:
On Nov 5, 2007 1:30 PM, Jonathan Cast
wrote: Get an infinite list of pairs
let pairs = [ (x, y) | x <- randoms (-1, 1) g0, y <- randoms (-1, 1) g1 ]
This will return a list like [(a,b),(a,c),(a,d),(a,e),...]. This needs to be a parallel comprehension:
let pairs = [ (x,y) | x <- randoms (-1,1) g0 | y <- randoms (-1,1) g1 ]
Or even better, just don't use list comprehensions, they're confusing: let pairs = zip (randoms (-1,1) g0) (randoms (-1,1) g1) Now you don't have to think backwards to figure out what the comprehension is doing. -- David Roundy Department of Physics Oregon State University
 
            On 11/5/07, David Roundy 
On Mon, Nov 05, 2007 at 01:42:50PM -0700, Luke Palmer wrote:
let pairs = [ (x,y) | x <- randoms (-1,1) g0 | y <- randoms (-1,1) g1 ]
Or even better, just don't use list comprehensions, they're confusing:
let pairs = zip (randoms (-1,1) g0) (randoms (-1,1) g1)
Or even better, have a declaration instance (Random a, Random b) => Random (a, b) then do let pairs = randomRs ((-1, -1), (1, 1)) g0 Wouldn't it be nice if System.Random had an instance declaration for pairs?
 
            Alex Young wrote:
rand :: IO Int rand = getStdRandom (randomR (0, randMax))
randListTail accum 0 = accum randListTail accum n = randListTail (rand : accum) (n - 1)
randList :: Int -> [IO Int] randList n = randListTail [] n
randPairs :: Int -> [(IO Int, IO Int)] randPairs n = zip (randList n) (randList n)
This looks entirely broken. How about this? randList :: Int -> IO [Int] randList n = mapM (\x -> randomRIO (0, randMax)) [1..n] (Sorry, I'm not very familiar with the Random module. However, I believe this works.) This then gives you an ordinary list of integers, which elides some of the stuff below...
pairIsInside x y = if x*x + y*y < unitRadius then 1 else 0
This is fairly atypical in Haskell. More likely you'd do something like pairIsInside :: (Int,Int) -> Bool pairIsInside x y = x*x + y*y < unitRadius and then later write length . filter pairIsInside instead of using "sum".
doCountPair :: (IO Int, IO Int) -> IO Int doCountPair (a, b) = do x <- a y <- b return (pairIsInside x y)
fSumListTail :: Int -> [(IO Int, IO Int)] -> IO Int fSumListTail total [] = do return total fSumListTail total (x:xs) = do y <- doCountPair x fSumListTail (total+y) xs
fSumList :: [(IO Int, IO Int)] -> IO Int fSumList l = fSumListTail 0 l
Most of this goes away if you use an "IO [Int]" rather than "[IO Int]".
piAsDouble :: Int -> Int -> Double piAsDouble a b = (fromInteger (toInteger a)) / (fromInteger (toInteger b))
I don't *think* you need the toInteger there - I may be wrong...
calculatePi total = do count <- fSumList (randPairs total) return (piAsDouble (4*count) total)
This looks OK.
main = do args <- getArgs (calculatePi (read (args !! 0))) >>= (putStr . show)
This looks OK too - if a little confusing. As a matter of style, I'd write main = do args <- getArgs case args of [size] -> print $ calculatePi $ read size _ -> putStrLn "Usage: CALCPI <size>" But that's just me...
 
            alex:
Hi all,
import Random import System.Environment import List import Monad
randMax = 32767 unitRadius = randMax * randMax
rand :: IO Int rand = getStdRandom (randomR (0, randMax))
randListTail accum 0 = accum randListTail accum n = randListTail (rand : accum) (n - 1)
randList :: Int -> [IO Int] randList n = randListTail [] n
randPairs :: Int -> [(IO Int, IO Int)] randPairs n = zip (randList n) (randList n)
pairIsInside x y = if x*x + y*y < unitRadius then 1 else 0
doCountPair :: (IO Int, IO Int) -> IO Int doCountPair (a, b) = do x <- a y <- b return (pairIsInside x y)
fSumListTail :: Int -> [(IO Int, IO Int)] -> IO Int fSumListTail total [] = do return total fSumListTail total (x:xs) = do y <- doCountPair x fSumListTail (total+y) xs
fSumList :: [(IO Int, IO Int)] -> IO Int fSumList l = fSumListTail 0 l
piAsDouble :: Int -> Int -> Double piAsDouble a b = (fromInteger (toInteger a)) / (fromInteger (toInteger b))
calculatePi total = do count <- fSumList (randPairs total) return (piAsDouble (4*count) total)
main = do args <- getArgs (calculatePi (read (args !! 0))) >>= (putStr . show) {--------------------------------------------------}
Now, I have two questions. The easy question is, how can I make this more idiomatic? I seem to be jumping through hoops rather a lot to achieve what should be rather simple operations. The piAsDouble and fSumListTail functions are perfect examples, but I'm not wildly keen on doCountPair either.
The second question is performance-related. The Haskell code above overflows the stack when run with an argument of 1000000, so either somewhere a list I'm intending to be lazily evaluated and chucked away is being retained, or one of my recursive functions isn't tail-optimising. Is it obvious to a more trained eye where the problem is? If not, how should I start to diagnose this? I'm not really sure where I should look for more information.
You can replace most of your loops with Data.List functions, and simplify the code overall by threading around a lazy list of randoms, rather than calling into IO all the time: import System.Random import System.Environment import Data.List import Control.Monad randMax = 32767 unitRadius = randMax * randMax countPair :: (Int, Int) -> Int countPair (x, y) = fromEnum (x*x + y*y < unitRadius) calculatePi total g = fromIntegral (4*count) / fromIntegral total where count = sum . map countPair . take total $ zip (randomRs (0,randMax) a) (randomRs (0,randMax) b) (a,b) = split g main = do [v] <- getArgs g <- newStdGen print $ calculatePi (read v) g Compiled like so: $ ghc -O2 A.hs -o A $ time ./A 100000 3.13548 ./A 100000 0.08s user 0.02s system 98% cpu 0.101 total We get no stack overflow. But note you're implementing a different algorithm to the C program, with different data structures, so expect different performance.
 
            Don Stewart wrote:
alex: <snip> You can replace most of your loops with Data.List functions, and simplify the code overall by threading around a lazy list of randoms, rather than calling into IO all the time:
import System.Random import System.Environment import Data.List import Control.Monad
randMax = 32767 unitRadius = randMax * randMax
countPair :: (Int, Int) -> Int countPair (x, y) = fromEnum (x*x + y*y < unitRadius)
calculatePi total g = fromIntegral (4*count) / fromIntegral total where count = sum . map countPair . take total $ zip (randomRs (0,randMax) a) I wish I'd known about randomRs a couple of hours ago :-)
(randomRs (0,randMax) b)
(a,b) = split g
main = do [v] <- getArgs g <- newStdGen print $ calculatePi (read v) g
Compiled like so:
$ ghc -O2 A.hs -o A
$ time ./A 100000 3.13548 ./A 100000 0.08s user 0.02s system 98% cpu 0.101 total
We get no stack overflow.
Not with -O2, but: C:\Users\Alex\Documents\HaskellLearning\MonteCarlo>ghc BetterPi.hs C:\Users\Alex\Documents\HaskellLearning\MonteCarlo>main.exe 1000000 Stack space overflow: current size 8388608 bytes. Use `+RTS -Ksize' to increase it. But: C:\Users\Alex\Documents\HaskellLearning\MonteCarlo>ghc -O2 BetterPi.hs C:\Users\Alex\Documents\HaskellLearning\MonteCarlo>main.exe 1000000 3.140636 This is a little confusing. Is there a simple explanation for this behaviour, or is it just a matter of "always use -O2 unless there's a reason not to?" Thanks - I really appreciate the explanations. (P.S. Again - sorry for the duplication. I really need to watch my mail client more closely :-) -- Alex
 
            On Nov 5, 2007, at 16:21 , Alex Young wrote:
C:\Users\Alex\Documents\HaskellLearning\MonteCarlo>ghc BetterPi.hs
C:\Users\Alex\Documents\HaskellLearning\MonteCarlo>main.exe 1000000 Stack space overflow: current size 8388608 bytes. Use `+RTS -Ksize' to increase it.
But:
C:\Users\Alex\Documents\HaskellLearning\MonteCarlo>ghc -O2 BetterPi.hs
C:\Users\Alex\Documents\HaskellLearning\MonteCarlo>main.exe 1000000 3.140636
This is a little confusing. Is there a simple explanation for this behaviour, or is it just a matter of "always use -O2 unless there's a reason not to?"
Basically, one of the optimizations enabled by -O2 causes ghc to notice that it doesn't need to collect a bunch of thunks on the stack, but instead can use them as they're generated. ("fusion" --- in this case probably some build/fold fusion) I would indeed say that in most cases you want to use -O2 just to get the smarter behavior, unless you're trying to learn how to write efficient code to start with; but on the other hand, it's nice to be able to write *readable* code and have the compiler figure out how to make it efficient. (Much the same goes for C, by the way; I can write code to the bare metal, or write comprehensible code and let cc work out how to make it fast. Unless I (a) absolutely need the performance and (b) know the optimizer's not smart enough to do it for me, I'll go for readable instead of e.g. Duff's Device.) -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH
 
            G'day all.
Quoting Don Stewart 
calculatePi total g = fromIntegral (4*count) / fromIntegral total
This is slightly more robust in cases where the multiplication would overflow an Int: calculatePi total g = fromRational ((4*fromIntegral count) % fromIntegral total) Cheers, Andrew Bromage
 
            Hi Alex, You wrote:
I'm new to Haskell, and don't quite understand how IO and lazy evaluation work together yet. In order to improve my understanding, I thought I'd try to knock together a translation of a fairly simple problem I can code up in C... Now, I have two questions. The easy question is, how can I make this more idiomatic? ...The second question is performance-related. The Haskell code above overflows the stack when run with an argument of 1000000
These are great questions, and a really fun example! Let me focus back on your original two questions. When you are just playing around with an algorithm, it is not so idiomatic in Haskell to write a program that takes a command-line argument and prints to stdout like in C. Instead, you would more likely write a small module containing some functions. Then you load them into GHCi or Hugs and play with them, and reload as you make changes. So I might write something simple like this into RandomPi.hs: module RandomPi where import System.Random randMax, unitRadius :: Int randMax = floor $ sqrt $ fromIntegral (maxBound `div` 2 :: Int) unitRadius = randMax * randMax calcPi :: RandomGen g => g -> Int -> (Int, Double) calcPi g total = (count, fromIntegral count / fromIntegral total * 4) where count = length $ filter isInCircle randPairs isInCircle (x, y) = x*x + y*y < unitRadius randPairs = take total $ pairs $ randomRs (0, randMax) g -- Group a list into pairs pairs :: [a] -> [(a,a)] pairs (x:x':xs) = (x, x') : pairs xs pairs _ = [] I think this pretty faithfully translates your ideas from C into Haskell. (I was a little more careful than you were regarding MAX_RAND, but that has nothing to do with Haskell. In fact, I'm not sure your C code would work using GNU libc, because you'd get unit_radius = 1 I think due to int overflow.) If you really, really, want a command-line/stdout thing, you would then add in stuff like this to do the required plumbing work: import System.Environment import System.Exit randomPiMain :: IO () randomPiMain = do args <- getArgs when (length args /= 2) $ usage args let total = read $ args !! 1 :: Int g <- newStdGen let (count, myPi) = calcPi g total putStrLn $ "Count: " ++ show count putStrLn $ "Total: " ++ show total putStrLn $ show myPi usage :: [String] -> IO () usage (progname:_) = do putStrLn $ concat ["usage: ", progname, " iteration_count"] exitWith $ ExitFailure 1 Then you would create a separate file containing only two lines, and compile it: import RandomPi main = RandomPiMain So the answer to your first question is that you isolate out the IO stuff - usually not very much - and write the rest of your program entirely pure. Then the IO stuff you either do by hand at the prompt, or you write separate functions for it. In this case, the only IO is: o Reading 'total' o Printing the answer o Giving the usage message o Getting an initial random generator You second question, about blowing the stack, is settled in the above the same way that the previous posters suggested. Represent your big iteration as a list. Try to stick to fairly simple operations on the list. Then the compiler will figure out how to keep things lazy and also release memory as it goes along. Another point (where I disagree a bit with some previous posters): I think that it is not very idiomatic to use split on the random generator here. For several reasons, I think split should usually be avoided, except for things like sharing a generator across multiple threads. Instead, I just pull pairs of random numbers off of a single stream. There is still a problem here - my code (and also all of the previous posters, I think) clobbers the random generator, rendering it unusable for future calculations. In this case that is probably not a problem, but it is a bad habit to get into, and not very polite. But now we become entangled with your second question. Because it is tricky to generate a huge list of random numbers lazily, while still keeping track of the last value of the generator, without blowing the stack. I will leave others to post a traditional solution to that. I avoid that problem entirely by using yet another Haskell idiom - I *always* (OK, almost always) do random calculations inside a lazy State monad. You don't need to understand the theory of monads to understand the following code. You can see that it just generates a big list of random pairs and uses it. The type says to quietly keep the current value of the random generator as state in the background. The idiom "State $ randomR range" is a trick that makes this possible. module RandomPi where import System.Random import Control.Monad.State randMax, unitRadius :: Int randMax = floor $ sqrt $ fromIntegral (maxBound `div` 2 :: Int) unitRadius = randMax * randMax calcPiM :: RandomGen g => Int -> State g (Int, Double) calcPiM total = do randPairs <- replicateM total $ randPairM (0, randMax) let count = length $ filter isInCircle randPairs return (count, fromIntegral count / fromIntegral total * 4) where isInCircle (x, y) = x*x + y*y < unitRadius -- Generate a pair of random numbers randPairM :: (RandomGen g, Random a) => (a, a) -> State g (a, a) randPairM range = do x <- State $ randomR range y <- State $ randomR range return (x, y) To use this at the GHCi or Hugs command prompt, or in randomPiMain, you write: g <- newStdGen evalState (calcPiM 100000) g Hope this helps, Yitz
 
            On 6 Nov 2007, at 6:00 AM, Yitzchak Gale wrote: <snip>
There is still a problem here - my code (and also all of the previous posters, I think) clobbers the random generator, rendering it unusable for future calculations. In this case that is probably not a problem, but it is a bad habit to get into, and not very polite.
Nope. newStdGen is specified in terms of split, which means it leaves the random generator in a state independent of the generator it returns. Perfectly safe. (I think you think you used getStdGen). jcc
 
            I wrote:
There is still a problem here - my code (and also all of the previous posters, I think) clobbers the random generator, rendering it unusable for future calculations. In this case that is probably not a problem, but it is a bad habit to get into, and not very polite.
Jonathan Cast wrote:
Nope. newStdGen is specified in terms of split, which means it leaves the random generator in a state independent of the generator it returns. Perfectly safe. (I think you think you used getStdGen).
I was referring to randoms and randomRs. They clobber the generator. You can then get a new one using newStdGen, but that forces you back into the IO monad. Regards, Yitz
 
            On 6 Nov 2007, at 3:56 PM, Yitzchak Gale wrote:
I wrote:
There is still a problem here - my code (and also all of the previous posters, I think) clobbers the random generator, rendering it unusable for future calculations. In this case that is probably not a problem, but it is a bad habit to get into, and not very polite.
Jonathan Cast wrote:
Nope. newStdGen is specified in terms of split, which means it leaves the random generator in a state independent of the generator it returns. Perfectly safe. (I think you think you used getStdGen).
I was referring to randoms and randomRs. They clobber the generator. You can then get a new one using newStdGen, but that forces you back into the IO monad.
Oh, of course. Or call split first. jcc
 
            On Nov 5, 2007 8:11 PM, Alex Young 
{--------------------------------------------------} module Main where
import Random import System.Environment import List import Monad
randMax = 32767 unitRadius = randMax * randMax
rand :: IO Int rand = getStdRandom (randomR (0, randMax))
randListTail accum 0 = accum randListTail accum n = randListTail (rand : accum) (n - 1)
I can't believe that nobody has pointed this out yet. I think we were all focused on your weird usage of the IO monad... Anyway, you do not want to use tail recursion in this case. Here you have to evaluate everything before you can return the first element, because we don't know that you're going to return accum when you get down to zero... you might return 1:accum or something. When you're returning a list, it's best not to use tail recursion because we can get the initial elements of the list lazily. randList 0 = [] randList n = rand : randList (n-1) Is a much better implementation in Haskell. But that's usually just spelled "replicate n rand". :-) Luke
 
            lrpalmer:
On Nov 5, 2007 8:11 PM, Alex Young
wrote: {--------------------------------------------------} module Main where
import Random import System.Environment import List import Monad
randMax = 32767 unitRadius = randMax * randMax
rand :: IO Int rand = getStdRandom (randomR (0, randMax))
randListTail accum 0 = accum randListTail accum n = randListTail (rand : accum) (n - 1)
I can't believe that nobody has pointed this out yet. I think we were all focused on your weird usage of the IO monad...
Anyway, you do not want to use tail recursion in this case. Here you have to evaluate everything before you can return the first element, because we don't know that you're going to return accum when you get down to zero... you might return 1:accum or something. When you're returning a list, it's best not to use tail recursion because we can get the initial elements of the list lazily.
randList 0 = [] randList n = rand : randList (n-1)
Is a much better implementation in Haskell.
But that's usually just spelled "replicate n rand". :-)
I did suggest: take n randomrRs :) -- Don
participants (12)
- 
                 ajb@spamcop.net ajb@spamcop.net
- 
                 Alex Young Alex Young
- 
                 Andrew Coppin Andrew Coppin
- 
                 Brandon S. Allbery KF8NH Brandon S. Allbery KF8NH
- 
                 David Benbennick David Benbennick
- 
                 David Roundy David Roundy
- 
                 Don Stewart Don Stewart
- 
                 Henning Thielemann Henning Thielemann
- 
                 Jonathan Cast Jonathan Cast
- 
                 Luke Palmer Luke Palmer
- 
                 Tim Chevalier Tim Chevalier
- 
                 Yitzchak Gale Yitzchak Gale
