[Haskell-cafe] How do I avoid stack overflows?

oleg at pobox.com oleg at pobox.com
Fri Mar 16 02:52:28 EDT 2007


DavidA wrote:
> I'm trying to write some code which involves lots of matrix multiplications,
> but whenever I do too many, I get stack overflows (in both GHCi 6.4.2, and
> Hugs May 2006).

By placing a couple of strictness annotations, your test' gives the
expected answer (given some time) on Hugs. GHCi unfortunately runs
into some kind of bug (it says so itself), an unimplemented opcode.
The test'' below gives that bug instantly...


import List (transpose)

-- not needed here
-- foldl' f z [] = z
-- foldl' f z (h:t) = (foldl' f $! f h z) t
-- sum' l = foldl' (+) 0 l

map' f [] = []
map' f (h:t) = scons (f h) (map f t)

-- strict cons. Could be associated with an infix op, e.g., :$
scons :: a -> [a] -> [a]
scons x l | x `seq` l `seq` False = undefined
scons x l = x:l


u <.> v = sum $ zipWith (*) u v

a <<*>> b = multMx a (transpose b)
        where
                multMx [] _ = []
                multMx (u:us) bT = scons (map' (u <.>) bT) (multMx us bT)

id3 = [[1,0,0],[0,1,0],[0,0,1]]

-- test = iterate (<<*>> id3) id3 !! 1000000

iterate' f x = x : seq x' (iterate' f x') where x' = f x
test' = iterate' (<<*>> id3) id3 !! 1000000

test'' = head $ drop 1000000 $ iterate' (<<*>> id3) id3


More information about the Haskell-Cafe mailing list