trees with pointers to parents & memory gobbling
Hal Daume III
hdaume@ISI.EDU
Fri, 14 Jun 2002 11:04:30 -0700 (PDT)
Hi all,
I have a datatype which (simplified) looks like:
data FBTree a = FBLeaf (Maybe (FBTree a)) a | FBBranch (Maybe (FBTree
a)) (FBTree a) (FBTree a)
is basically a tree with Maybe a parent node. however, unlike the nice
non-haskell equivalent, they tend to eat up memory as you traverse
them. for instance, given the conversion functions and helper functions:
data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving (Eq, Show)
data FBTree a = FBLeaf (Maybe (FBTree a)) a | FBBranch (Maybe (FBTree
a)) (FBTree a) (FBTree a)
instance Eq a => Eq (FBTree a) where a == b = unFBTree a == unFBTree b
instance Show a => Show (FBTree a) where showsPrec i = showsPrec i
. unFBTree
mkFBTree = mkFBTree' Nothing
where mkFBTree' par (Leaf a) = FBLeaf par a
mkFBTree' par (Branch l r) = this
where this = FBBranch par (mkFBTree' (Just
this) l) (mkFBTree' (Just this) r)
unFBTree (FBLeaf _ a) = Leaf a
unFBTree (FBBranch _ l r) = Branch (unFBTree l) (unFBTree r)
findRoot (FBLeaf (Just par) _) = findRoot par
findRoot (FBBranch (Just par) _ _) = findRoot par
findRoot t = t
findLeftMostChild (FBBranch _ l _) = findLeftMostChild l
findLeftMostChild t = t
if we just walk up and down a tree a bunch of time, heap profiling reports
huge amounts of memory usage. witness:
tree = Branch (Branch (Branch (Branch (Branch (Leaf 'h') (Branch (Leaf
'a') (Leaf 's'))) (Leaf 'k')) (Branch (Leaf 'e') (Leaf 'l'))) (Leaf
'l')) (Leaf '!')
fbtree = mkFBTree tree
main = print $ last $ take 100000 $ iterate (findLeftMostChild
. findRoot) fbtree
even if i put an appropriate call to seq in the iteration, i still get
lots of memory eaten up, can someone say how i can fix this?
- Hal
--
Hal Daume III
"Computer science is no more about computers | hdaume@isi.edu
than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume