Refactor the FPTOOLS_CHECK_HTYPE macro
[ghc-base.git] / Control / Monad.hs
index 0650e7a..75b9d0b 100644 (file)
@@ -1,4 +1,5 @@
-{-# OPTIONS_GHC -XNoImplicitPrelude #-}
+{-# LANGUAGE CPP, NoImplicitPrelude #-}
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Control.Monad
@@ -46,6 +47,7 @@ module Control.Monad
 
     , join          -- :: (Monad m) => m (m a) -> m a
     , msum          -- :: (MonadPlus m) => [m a] -> m a
+    , mfilter       -- :: (MonadPlus m) => (a -> Bool) -> m a -> m a
     , filterM       -- :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
     , mapAndUnzipM  -- :: (Monad m) => (a -> m (b,c)) -> [a] -> m ([b], [c])
     , zipWithM      -- :: (Monad m) => (a -> b -> m c) -> [a] -> [b] -> m [c]
@@ -127,8 +129,6 @@ class Monad m => MonadPlus m where
    -- > mzero >>= f  =  mzero
    -- > v >> mzero   =  mzero
    --
-   -- (but the instance for 'System.IO.IO' defined in Control.Monad.Error
-   -- in the mtl package does not satisfy the second one).
    mzero :: m a 
    -- | an associative operation
    mplus :: m a -> m a -> m a
@@ -189,8 +189,26 @@ 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.
+-}
+
 -- | @'void' value@ discards or ignores the result of evaluation, such as the return value of an 'IO' action.
 void :: Functor f => f a -> f ()
 void = fmap (const ())
@@ -313,6 +331,20 @@ ap                :: (Monad m) => m (a -> b) -> m a -> m b
 ap                =  liftM2 id
 
 
+-- -----------------------------------------------------------------------------
+-- Other MonadPlus functions
+
+-- | Direct 'MonadPlus' equivalent of 'filter'
+-- @'filter'@ = @(mfilter:: (a -> Bool) -> [a] -> [a]@
+-- applicable to any 'MonadPlus', for example
+-- @mfilter odd (Just 1) == Just 1@
+-- @mfilter odd (Just 2) == Nothing@
+
+mfilter :: (MonadPlus m) => (a -> Bool) -> m a -> m a
+mfilter p ma = do
+  a <- ma
+  if p a then return a else mzero
+
 {- $naming
 
 The functions in this library use the following naming conventions: