Running out of memory in a simple monad

Magnus Lindberg f98mali@dd.chalmers.se
Thu, 28 Nov 2002 18:26:46 +0100


{- Hi!
I have problems with monads and memory. I have a monad through which
I thread output. If I do the concatenation of the output-strings in
one way Hugs runs out of memory, but if I do it in another way
everything works. I can't see why the first way doesn't work but the
second is OK. I woudl appreciate if someone could tell me what I am
doing wrong.
  Here is the non-working monad:   -}

data M a  = M (String -> (a, String))

instance Monad M where
  return x   = M $ \o -> (x, o)
  M io >>= fio = M $ \o0 ->
    let (r1, o1)  = o0 `seq` io o0
        M io2     = r1 `seq` fio r1
    in io2 o1

putCharM c  = M $ \o  -> ((), o ++ [c]) -- Is this stupid in some way?

runM       :: M a -> IO()
runM (M io) = let (r, outp) = io ""
              in putStr outp

crashHugs 0 = return ()
crashHugs n = do putCharM 'x'; crashHugs (n-1)

r = runM (crashHugs 50000)

{-  Besides, the output generated when one runs `r' (with a smaller
number, for example r = 4000) above is in the beginning written in a
very slow pace but then the delay between each char decreases and
finally everything is written very fast (but not for the working
monad below)
  Well, here is the working monad:   -}
{-
data M a  = M (a, String)

instance Monad M where
  return x   = M (x, "")
  M f >>= k  = M $
    let (x, o)   = f
        M f2     = k x
        (x', o') = f2
    in (x', o ++ o')

putCharM c  = M ((), [c])

runM       :: M a -> IO()
runM (M f) = let (r, outp) = f
             in putStr outp

thisIsOk 0 = return ()
thisIsOk n = do putCharM 'x'; thisIsOk (n-1)

r = runM (thisIsOk 50000)
-}

{- So, it works when I concatenate the output in `>>=' but not (as in
the first monad) in putChar... I can't see why :(

Keen regards,
    Magnus Lidnberg
-}