[Haskell] Random matrices

Scherrer, Chad Chad.Scherrer at pnl.gov
Fri Aug 19 16:31:39 EDT 2005


I'm doing some statistical calculations, and I decided to try this out
in Haskell to see how it goes. I'm really enjoying using the language,
so I hope I can straighten this out so I can keep using it at work.

I keep getting stack overflows, so I think my code must be too lazy
somewhere (that's what that means, right?) Here is my code to build
random vectors and matrices.
------------------------------------------------------------------------
--------
type Vector = UArray Int Float
type Matrix = DiffArray Int Vector

-- Generate a random number from the unit interval
randomEntry :: State StdGen Float
randomEntry = do g <- get
                 (x, g') <- return $ randomR (0,1) g
                 put g'
                 return x

-- Build an array of n random things
randomArray :: (IArray arr a) => Int -> State StdGen a -> State StdGen
(arr Int a)
randomArray n x = mapState arr . sequence $ replicate n x
    where
    arr (a,s) = (array (1,n) $ zip [1..n] a, s)

-- A random vector is an array of random entries
randomVector :: Int -> State StdGen Vector
randomVector n = randomArray n randomEntry

-- a random matrix is an array of random vectors.
randomMatrix :: Int -> Int -> State StdGen Matrix
randomMatrix i j = randomArray i $ randomVector j
------------------------------------------------------------------------
--------

I decided to write a tester function to see whether building the random
matrices is the root of my problem.

tester :: Int -> [Matrix]
tester n = fst $ runState vals $ mkStdGen 1
    where 
    vals = sequence . repeat $ randomMatrix n n 

Then if I do

main = print $ ((tester 10)!!10000)!5

with ghc -O, I get a stack overflow. So all main is trying to do is
build an infinite list of 10x10 random matrices, extract the 10000th
one, and then look at row 5.

Stack overflows like this have given me trouble before. I thought using
unboxed arrays might help, since they're forced to be strict, but I
haven't had any luck with them. Are there any general guidelines I'm
overlooking? I think Haskell can be very useful in my work, but I have
to get beyond this hurdle. I just figured out the State monad yesterday,
so maybe I'm not using it as it's intended? I dunno.

Thanks,
Chad Scherrer
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org//pipermail/haskell/attachments/20050819/a48806ff/attachment.htm


More information about the Haskell mailing list