[Haskell-cafe] memory leak when using "forever"

Tom Ellis tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk
Tue Oct 4 17:56:48 UTC 2016


On Tue, Oct 04, 2016 at 06:19:52PM +0100, Tom Ellis wrote:
> On Tue, Oct 04, 2016 at 01:51:04PM +0200, Zoran Bosnjak wrote:
> > can you please explain why does this simple program leak memory.
> >
> > But, if I replace loop2 with loop1 (that is: without using "forever"),
> > then it does not leak.
> >
> > import Control.Concurrent
> > import Control.Monad
> > import Control.Monad.Trans
> > import Control.Monad.Trans.Reader
> > import Control.Monad.Trans.State
> > 
> > main :: IO ()
> > main = do
> >     --let loop1 = (liftIO $ threadDelay 1) >> loop1
> >     let loop2 = forever (liftIO $ threadDelay 1)
> > 
> >     _ <- runStateT (runReaderT loop2 'a') 'b'
> >     return ()
> 
> My results below.  Looks like there's something wrong with *> for ReaderT
> and StateT.

This seems to be how it executes

    let loop = return () *> loop in loop
    in runReaderT loop ()

    let loop = return () *> loop in loop
    in loop ()

    let loop = (id <$ return ()) <*> loop in loop
    in loop ()

    -- <*> for ReaderT in terms of <*> for m
    let loop = \r -> (id <$ return ()) r <*> loop r in loop
    in loop ()

    let loop = \r -> (id <$ return ()) r <*> loop r in loop
    in (id <$ return ()) () <*> loop ()

    let loop = \r -> (id <$ return ()) r <*> loop r in loop
    in ((fmap . const) id (return ())) () (loop ())

    let loop = \r -> (id <$ return ()) r <*> loop r in loop
    in (fmap (const id) (return ())) () <*> loop ()

    -- fmap for ReaderT m in terms of fmap for m
    let loop = \r -> (id <$ return ()) r <*> loop r in loop
    in (fmap (const id) . (return ())) () <*> loop ()

    let loop = \r -> (id <$ return ()) r <*> loop r in loop
    in (\x -> fmap (const id) (return () x)) () <*> loop ()

    let loop = \r -> (id <$ return ()) r <*> loop r in loop
    in fmap (const id) (return () ()) <*> loop ()

    -- return for ReaderT in terms of return for m
    let loop = \r -> (id <$ return ()) r <*> loop r in loop
    in fmap (const id) (return ()) <*> loop ()

which then in IO I think becomes

    fmap (const id ()) (loop ())

so each time round the loop we add a redundant

    fmap (const id ())

on the front.  Oh dear.  Something needs fixing.  I'm not sure what.

We don't see the space leak in the Identity Applictave because

    fmap (const id) (return ()) <*> loop ()

is

    const id (return ()) (loop ())

which evaluates as

    (\x y -> x) id (return ()) (loop ())

    id (loop ())

    loop ()

Anyone who is at Haskell eXchange on Thursday and who is interested in
working out how the above code executes can come to my talk!

Tom


More information about the Haskell-Cafe mailing list