Skip to content

Commit

Permalink
Improve definition of forever (#5205)
Browse files Browse the repository at this point in the history
The previous implementation was:

    forever a = a >> forever a

which can create a space leak in some cases, even with optimizations.
The current implementation:

    forever a = let a' = a >> a' in a'

prevents repeated thunk allocations by creating a single thunk for the
final result, even without optimizations.
  • Loading branch information
pcapriotti committed Aug 20, 2012
1 parent 53ed79a commit f55f557
Show file tree
Hide file tree
Showing 2 changed files with 4 additions and 23 deletions.
23 changes: 4 additions & 19 deletions Control/Monad.hs
Expand Up @@ -190,25 +190,10 @@ f >=> g = \x -> f x >>= g

-- | @'forever' act@ repeats the action infinitely.
forever :: (Monad m) => m a -> m b
{-# INLINABLE forever #-} -- See Note [Make forever INLINABLE]
forever a = a >> forever a

{- Note [Make forever INLINABLE]
If you say x = forever a
you'll get x = a >> a >> a >> a >> ... etc ...
and that can make a massive space leak (see Trac #5205)
In some monads, where (>>) is expensive, this might be the right
thing, but not in the IO monad. We want to specialise 'forever' for
the IO monad, so that eta expansion happens and there's no space leak.
To achieve this we must make forever INLINABLE, so that it'll get
specialised at call sites.
Still delicate, though, because it depends on optimisation. But there
really is a space/time tradeoff here, and only optimisation reveals
the "right" answer.
-}
{-# INLINE forever #-}
forever a = let a' = a >> a' in a'
-- Use explicit sharing here, as it is prevents a space leak regardless of
-- optimizations.

-- | @'void' value@ discards or ignores the result of evaluation, such as the return value of an 'IO' action.
void :: Functor f => f a -> f ()
Expand Down
4 changes: 0 additions & 4 deletions GHC/ST.lhs
Expand Up @@ -27,7 +27,6 @@ module GHC.ST (
import GHC.Base
import GHC.Show
import Control.Monad( forever )
default ()
\end{code}
Expand Down Expand Up @@ -82,9 +81,6 @@ instance Monad (ST s) where
data STret s a = STret (State# s) a
{-# SPECIALISE forever :: ST s a -> ST s b #-}
-- See Note [Make forever INLINABLE] in Control.Monad
-- liftST is useful when we want a lifted result from an ST computation. See
-- fixST below.
liftST :: ST s a -> State# s -> STret s a
Expand Down

0 comments on commit f55f557

Please sign in to comment.