Adjust behaviour of gcd
[ghc-base.git] / Control / Monad.hs
index b7785dd..75b9d0b 100644 (file)
@@ -1,4 +1,5 @@
-{-# OPTIONS_GHC -fno-implicit-prelude #-}
+{-# LANGUAGE CPP, NoImplicitPrelude #-}
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Control.Monad
@@ -20,15 +21,15 @@ module Control.Monad
     , Monad((>>=), (>>), return, fail)
 
     , MonadPlus (   -- class context: Monad
-         mzero     -- :: (MonadPlus m) => m a
-       , mplus     -- :: (MonadPlus m) => m a -> m a -> m a
-       )
+          mzero     -- :: (MonadPlus m) => m a
+        , mplus     -- :: (MonadPlus m) => m a -> m a -> m a
+        )
     -- * Functions
 
     -- ** Naming conventions
     -- $naming
 
-    -- ** Basic functions from the "Prelude"
+    -- ** Basic @Monad@ functions
 
     , mapM          -- :: (Monad m) => (a -> m b) -> [a] -> m [b]
     , mapM_         -- :: (Monad m) => (a -> m b) -> [a] -> m ()
@@ -39,12 +40,14 @@ module Control.Monad
     , (=<<)         -- :: (Monad m) => (a -> m b) -> m a -> m b
     , (>=>)         -- :: (Monad m) => (a -> m b) -> (b -> m c) -> (a -> m c)
     , (<=<)         -- :: (Monad m) => (b -> m c) -> (a -> m b) -> (a -> m c)
-    , forever       -- :: (Monad m) => m a -> m ()
+    , forever       -- :: (Monad m) => m a -> m b
+    , void
 
     -- ** Generalisations of list functions
 
     , 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]
@@ -88,15 +91,15 @@ infixr 1 =<<
 -- | Same as '>>=', but with the arguments interchanged.
 {-# SPECIALISE (=<<) :: (a -> [b]) -> [a] -> [b] #-}
 (=<<)           :: Monad m => (a -> m b) -> m a -> m b
-f =<< x                = x >>= f
+f =<< x         = x >>= f
 
 -- | Evaluate each action in the sequence from left to right,
 -- and collect the results.
 sequence       :: Monad m => [m a] -> m [a] 
 {-# INLINE sequence #-}
 sequence ms = foldr k (return []) ms
-           where
-             k m m' = do { x <- m; xs <- m'; return (x:xs) }
+            where
+              k m m' = do { x <- m; xs <- m'; return (x:xs) }
 
 -- | Evaluate each action in the sequence from left to right,
 -- and ignore the results.
@@ -126,9 +129,7 @@ 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        
+   mzero :: m a 
    -- | an associative operation
    mplus :: m a -> m a -> m a
 
@@ -182,14 +183,36 @@ infixr 1 <=<, >=>
 (>=>)       :: Monad m => (a -> m b) -> (b -> m c) -> (a -> m c)
 f >=> g     = \x -> f x >>= g
 
--- | Right-to-left Kleisli composition of monads. '(>=>)', with the arguments flipped
+-- | Right-to-left Kleisli composition of monads. @('>=>')@, with the arguments flipped
 (<=<)       :: Monad m => (b -> m c) -> (a -> m b) -> (a -> m c)
 (<=<)       = flip (>=>)
 
 -- | @'forever' act@ repeats the action infinitely.
-forever     :: (Monad m) => m a -> m ()
+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 ())
+
 -- -----------------------------------------------------------------------------
 -- Other monad functions
 
@@ -215,19 +238,19 @@ zipWithM_ f xs ys =  sequence_ (zipWith f xs ys)
 
 {- | The 'foldM' function is analogous to 'foldl', except that its result is
 encapsulated in a monad. Note that 'foldM' works from left-to-right over
-the list arguments. This could be an issue where '(>>)' and the `folded
+the list arguments. This could be an issue where @('>>')@ and the `folded
 function' are not commutative.
 
 
->      foldM f a1 [x1, x2, ..., xm ]
+>       foldM f a1 [x1, x2, ..., xm]
 
 ==  
 
->      do
->        a2 <- f a1 x1
->        a3 <- f a2 x2
->        ...
->        f am xm
+>       do
+>         a2 <- f a1 x1
+>         a3 <- f a2 x2
+>         ...
+>         f am xm
 
 If right-to-left evaluation is required, the input list should be reversed.
 -}
@@ -251,7 +274,7 @@ replicateM_ n x   = sequence_ (replicate n x)
 
 {- | Conditional execution of monadic expressions. For example, 
 
->      when debug (putStr "Debugging\n")
+>       when debug (putStr "Debugging\n")
 
 will output the string @Debugging\\n@ if the Boolean value @debug@ is 'True',
 and otherwise do nothing.
@@ -272,8 +295,8 @@ liftM f m1              = do { x1 <- m1; return (f x1) }
 -- | Promote a function to a monad, scanning the monadic arguments from
 -- left to right.  For example,
 --
--- >   liftM2 (+) [0,1] [0,2] = [0,2,1,3]
--- >   liftM2 (+) (Just 1) Nothing = Nothing
+-- >    liftM2 (+) [0,1] [0,2] = [0,2,1,3]
+-- >    liftM2 (+) (Just 1) Nothing = Nothing
 --
 liftM2  :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
 liftM2 f m1 m2          = do { x1 <- m1; x2 <- m2; return (f x1 x2) }
@@ -296,11 +319,11 @@ liftM5 f m1 m2 m3 m4 m5 = do { x1 <- m1; x2 <- m2; x3 <- m3; x4 <- m4; x5 <- m5;
 {- | In many situations, the 'liftM' operations can be replaced by uses of
 'ap', which promotes function application. 
 
->      return f `ap` x1 `ap` ... `ap` xn
+>       return f `ap` x1 `ap` ... `ap` xn
 
 is equivalent to 
 
->      liftMn f x1 x2 ... xn
+>       liftMn f x1 x2 ... xn
 
 -}
 
@@ -308,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: