
The problem here is actually in the rmat function, not the forpaintbdry or whatever. The problem is that, afaik, the listArray function doesn't deforest the list argument (someone can correct me here, though). That is, you write: rmat n = listArray ... [a big list] and then this list is first built, then the array is filled in. You can see that this is a problem by replacing your main with: main = print (m ! snd (bounds m)) where m = rmat 800 This will stack overflow too. Solution: use mutable arrays and fill them in by hand :). -- Hal Daume III | hdaume@isi.edu "Arrest this man, he talks in maths." | www.isi.edu/~hdaume
-----Original Message----- From: Koji Nakahara [mailto:yu-@div.club.ne.jp] Sent: Wednesday, June 18, 2003 7:41 PM To: Hal Daume; haskell-cafe@haskell.org Subject: Re: Help: Stack-overflow and tail-recursive functions
On Wed, 18 Jun 2003 17:36:28 -0700 "Hal Daume"
wrote: Note that there is essentially no difference between f1 and f2. When you $! in f2, all it does is ensure that the argument isn't undefined. It doesn't evaluate any of the list. Try $!! from the DeepSeq module or write your own list-forcing function.
Thank you very much. I understand.
However my original program still (or maybe from the beginning) stack-overflows at another point, in the middle of the evaluation of "forpaintbdry".
Please give me some advice. ----------- -- snippet of the program for painting a random matrix from its boundary. module Main where import System import Random import Array import Ix import List
main = putStrLn $ show $ forpaintbdry $ rmat 200
forpaintbdry m = [(pos, Live) | pos <- (uncurry bdryidxlist) $ bounds m , isUnknown $ m ! pos ]
bdryidxlist :: (Int, Int) -> (Int, Int) -> [(Int, Int)] bdryidxlist (a1, a2) (b1, b2) = nub $ [(ab, j) | ab <- [a1, b1], j <- [a2..b2]] ++ [(i, ab) | ab <- [a2, b2], i <- [a1..b1]]
rmat n = listArray ((1,1),(n,n)) $ map ct (randoms (mkStdGen 1) ::[Bool]) where ct True = Unknown ct False = Dead
data CellColor = Live | Unknown | Dead
isUnknown Unknown = True isUnknown _ = False
instance Show CellColor where show Live = "Live" show Unknown = "Unknown" show Dead = "Dead"