
Hi, I don't understand why the following code always result in a Stack space overflow error. I'm using foldl' and think the main algorithm is tail recursive. Am I wrong ? I've read the http://www.haskell.org/haskellwiki/Stack_overflow Any help would be greatly appreciated. Thanks module Main where import Data.List -- Data structures data Point = Point { x::Double, y::Double, z::Double } deriving(Eq, Show) data Triangle = Triangle { p1::Point, p2::Point, p3::Point } deriving(Eq, Show) data BBox = BBox { bbmax::Point, bbmin::Point } deriving(Eq,Show) -- Construct a default triangle newTriangle :: Triangle newTriangle = Triangle (Point 1 0 0) (Point 0 1 0) (Point 0 0 1) -- Construct a default BBox newBBox = BBox (Point 0 0 0) (Point 0 0 0) -- Defines min and max for Point instance Ord Point where max a b = Point ( max (x a ) (x b) ) ( max (y a) (y b) ) ( max (z a) (z b) ) min a b = Point ( min (x a ) (x b) ) ( min (y a) (y b) ) ( min (z a) (z b) ) -- Create a list of triangles makeTriangles :: Double -> [Triangle] makeTriangles 0 = [] makeTriangles n = [ Triangle (Point v 0 0) (Point 0 v 0) (Point 0 0 v) | v <- [1..n] ] -- Compute the bounding box of a triangle boundingBox :: Triangle -> BBox boundingBox t = BBox pmax pmin where pmax = max (p3 t) (max (p1 t) (p2 t)) pmin = min (p3 t) (min (p1 t) (p2 t)) -- Compute the bounding box of two bounding boxes bboxAddb :: BBox -> BBox -> BBox bboxAddb (BBox bb1max bb1min) (BBox bb2max bb2min) = BBox (max bb1max bb2max) (min bb1min bb2min) -- Compute the bounding box of a triangle and a bounding box bboxAddt :: BBox -> Triangle -> BBox bboxAddt b t = bboxAddb b (boundingBox t) main = do print $ foldl' bboxAddt newBBox triangles; where triangles = makeTriangles 610000 error returned : Stack space overflow: current size 8388608 bytes. Use `+RTS -Ksize' to increase it. ghc version 6.10.3 on MacOsX Snow Leopard

Am Samstag 23 Januar 2010 14:05:42 schrieb Cyril Pichard:
Hi,
I don't understand why the following code always result in a Stack space overflow error. I'm using foldl' and think the main algorithm is tail recursive. Am I wrong ? I've read the http://www.haskell.org/haskellwiki/Stack_overflow Any help would be greatly appreciated.
Thanks
Because the 'seq' in foldl' evaluates its argument only to the outermost constructor. So in foldl' bboxAddt bb triangles@(t1:tail), it starts evaluating bboxAddt bb t1 ~> bboxAddb bb (boundingBox t) now bb must be matched against (BBox mxb mnb) and boundingBox t must be matched against (BBox mxt mnt) if the first match succeeds (which it does). Now boundingBox t = BBox calculatelater1 calculatelater2, so that match succeeds too. Then the definition of bboxAddb says the result of bboxAddt bb t1 is z' = BBox (max mxb calculatelater1) (min mnb calculatelater2) The next step in foldl' is z' `seq` foldl' bboxAddt z' tail but z' `seq` something only evaluates z' far enough to see it's a (BBox _ _), the components remain happily unevaluated. And so on. At the end of the list, you have the result BBox hugeThunk1 hugeThunk2 When you try to evaluate one of these thunks, the stack overflows. You need to force the evaluation of the components in each step. The easiest way is to make the data structures strict. For this case, it is sufficient to make BBox and Point strict: data Point = Point { x, y, z :: !Double } deriving (Eq, Show) data BBox = BBox { bbmax, bbmin :: !Point } deriving (Eq, Show) though it's probably a good idea to make Triangle strict, too. Then BBox can't have undefined components, evaluating a BBox to the outermost constructor (weak head normal form) forces the evaluation of its component Points to their outermost constructor, which in turn forces the evaluation of their respective components; those are Doubles and thus evaluating them to their outerost constructor evaluates them completely. Now bb`seq` something evaluates bb completely (to normal form) when something is demanded, no huge thunks, no stack overflow anymore :) Of course, if you need the possibility to have (BBox undefined undefined) without the programme aborting, you can't make the datatypes strict and have to make the folding function stricter, e.g. import Control.DeepSeq -- from package deepseq instance NFData Point where rnf (Point x y z) = x `seq` y `seq` z `seq` () instance NFData BBox where rnf (BBox mx mn) = rnf mx `seq` rnf mn bbAddt' bb t = bb `deepseq` bbAddt bb t foldl' bbAddt' newBBox triangles
module Main where
import Data.List
-- Data structures data Point = Point { x::Double, y::Double, z::Double } deriving(Eq, Show) data Triangle = Triangle { p1::Point, p2::Point, p3::Point } deriving(Eq, Show) data BBox = BBox { bbmax::Point, bbmin::Point } deriving(Eq,Show)
-- Construct a default triangle newTriangle :: Triangle newTriangle = Triangle (Point 1 0 0) (Point 0 1 0) (Point 0 0 1)
-- Construct a default BBox newBBox = BBox (Point 0 0 0) (Point 0 0 0)
-- Defines min and max for Point instance Ord Point where max a b = Point ( max (x a ) (x b) ) ( max (y a) (y b) ) ( max (z a) (z b) ) min a b = Point ( min (x a ) (x b) ) ( min (y a) (y b) ) ( min (z a) (z b) )
-- Create a list of triangles makeTriangles :: Double -> [Triangle] makeTriangles 0 = [] makeTriangles n = [ Triangle (Point v 0 0) (Point 0 v 0) (Point 0 0 v) | v <- [1..n] ]
-- Compute the bounding box of a triangle boundingBox :: Triangle -> BBox boundingBox t = BBox pmax pmin where pmax = max (p3 t) (max (p1 t) (p2 t)) pmin = min (p3 t) (min (p1 t) (p2 t))
-- Compute the bounding box of two bounding boxes bboxAddb :: BBox -> BBox -> BBox bboxAddb (BBox bb1max bb1min) (BBox bb2max bb2min) = BBox (max bb1max bb2max) (min bb1min bb2min)
-- Compute the bounding box of a triangle and a bounding box bboxAddt :: BBox -> Triangle -> BBox bboxAddt b t = bboxAddb b (boundingBox t)
main = do print $ foldl' bboxAddt newBBox triangles; where triangles = makeTriangles 610000
error returned : Stack space overflow: current size 8388608 bytes. Use `+RTS -Ksize' to increase it.
ghc version 6.10.3 on MacOsX Snow Leopard
participants (2)
-
Cyril Pichard
-
Daniel Fischer