doc wibbles
[ghc-base.git] / Control / Monad.hs
index 721c445..7d43db9 100644 (file)
@@ -1,4 +1,4 @@
-{-# OPTIONS_GHC -fno-implicit-prelude #-}
+{-# OPTIONS_GHC -XNoImplicitPrelude #-}
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Control.Monad
@@ -20,21 +20,27 @@ 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 ()
+    , forM          -- :: (Monad m) => [a] -> (a -> m b) -> m [b]
+    , forM_         -- :: (Monad m) => [a] -> (a -> m b) -> m ()
     , sequence      -- :: (Monad m) => [m a] -> m [a]
     , sequence_     -- :: (Monad m) => [m a] -> m ()
     , (=<<)         -- :: (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 b
+    , void
 
     -- ** Generalisations of list functions
 
@@ -83,15 +89,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.
@@ -108,6 +114,7 @@ mapM f as       =  sequence (map f as)
 mapM_           :: Monad m => (a -> m b) -> [a] -> m ()
 {-# INLINE mapM_ #-}
 mapM_ f as      =  sequence_ (map f as)
+
 #endif  /* __GLASGOW_HASKELL__ */
 
 -- -----------------------------------------------------------------------------
@@ -120,9 +127,9 @@ class Monad m => MonadPlus m where
    -- > mzero >>= f  =  mzero
    -- > v >> mzero   =  mzero
    --
-   -- (but the instance for 'System.IO.IO' defined in "Control.Monad.Error"
-   -- does not satisfy the second one).
-   mzero :: m a        
+   -- (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
 
@@ -154,12 +161,40 @@ filterM p (x:xs) =  do
    ys  <- filterM p xs
    return (if flg then x:ys else ys)
 
+-- | 'forM' is 'mapM' with its arguments flipped
+forM            :: Monad m => [a] -> (a -> m b) -> m [b]
+{-# INLINE forM #-}
+forM            = flip mapM
+
+-- | 'forM_' is 'mapM_' with its arguments flipped
+forM_           :: Monad m => [a] -> (a -> m b) -> m ()
+{-# INLINE forM_ #-}
+forM_           = flip mapM_
+
 -- | This generalizes the list-based 'concat' function.
 
 msum        :: MonadPlus m => [m a] -> m a
 {-# INLINE msum #-}
 msum        =  foldr mplus mzero
 
+infixr 1 <=<, >=>
+
+-- | Left-to-right Kleisli composition of monads.
+(>=>)       :: 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
+(<=<)       :: Monad m => (b -> m c) -> (a -> m b) -> (a -> m c)
+(<=<)       = flip (>=>)
+
+-- | @'forever' act@ repeats the action infinitely.
+forever     :: (Monad m) => m a -> m b
+forever a   = a >> forever a
+
+-- | @'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
 
@@ -185,19 +220,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.
 -}
@@ -221,7 +256,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.
@@ -242,8 +277,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) }
@@ -266,17 +301,18 @@ 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
 
 -}
 
 ap                :: (Monad m) => m (a -> b) -> m a -> m b
 ap                =  liftM2 id
 
+
 {- $naming
 
 The functions in this library use the following naming conventions: