Running out of memory in a simple program
Magnus Lindberg
f98mali@dd.chalmers.se
Fri, 15 Nov 2002 11:51:09 +0100
{-
Hi!
I have a problem with monads. When a monadic function calls itself
many times (see below) Hugs and GHCi runs out of memory/stack,
and I can't see why.
This is my program (well, I've kind of sipmlified it a lot :):
-}
newtype M a = M (Int -> (a,Int))
instance Monad M where
return x = M $ \i -> (x,i)
M f >>= k = M $ \i -> let (x,i2) = f i
M f2 = k x
in f2 i2
inc 0 = return ()
inc n = do inc'; inc (n-1)
where inc' = M $ \i -> ((), i+1)
runM :: M () -> IO ()
runM (M m) =
print (m 0)
-- in print i
run n = runM (inc n) -- crashes for large n !!
{-
Shouldn't `run n' work for any n? But if I use n over 20 000 (or
something) Hugs says "error: couldn't retreive enough
memory when garabae-collecting" (or something), and other times
Windows 2000 says "unknown software exception 0xc000000fd at
0x00040ec01".
I tested to add "continuation passing style" (I don't really know
what I should do) but that didn't work either. Does anyone have an
idea of what the error is and what I should do / not do?
Best regards,
Magnus Lindberg
-}