[project @ 2005-02-24 09:58:23 by simonmar]
[ghc-base.git] / Control / Monad.hs
1 {-# OPTIONS_GHC -fno-implicit-prelude #-}
2 -----------------------------------------------------------------------------
3 -- |
4 -- Module      :  Control.Monad
5 -- Copyright   :  (c) The University of Glasgow 2001
6 -- License     :  BSD-style (see the file libraries/base/LICENSE)
7 -- 
8 -- Maintainer  :  libraries@haskell.org
9 -- Stability   :  provisional
10 -- Portability :  portable
11 --
12 -- The 'Functor', 'Monad' and 'MonadPlus' classes,
13 -- with some useful operations on monads.
14
15 module Control.Monad
16     (
17     -- * Functor and monad classes
18
19       Functor(fmap)
20     , Monad((>>=), (>>), return, fail)
21
22     , MonadPlus (   -- class context: Monad
23           mzero     -- :: (MonadPlus m) => m a
24         , mplus     -- :: (MonadPlus m) => m a -> m a -> m a
25         )
26     -- * Functions
27
28     -- ** Naming conventions
29     -- $naming
30
31     -- ** Basic functions from the "Prelude"
32
33     , mapM          -- :: (Monad m) => (a -> m b) -> [a] -> m [b]
34     , mapM_         -- :: (Monad m) => (a -> m b) -> [a] -> m ()
35     , sequence      -- :: (Monad m) => [m a] -> m [a]
36     , sequence_     -- :: (Monad m) => [m a] -> m ()
37     , (=<<)         -- :: (Monad m) => (a -> m b) -> m a -> m b
38
39     -- ** Generalisations of list functions
40
41     , join          -- :: (Monad m) => m (m a) -> m a
42     , msum          -- :: (MonadPlus m) => [m a] -> m a
43     , filterM       -- :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
44     , mapAndUnzipM  -- :: (Monad m) => (a -> m (b,c)) -> [a] -> m ([b], [c])
45     , zipWithM      -- :: (Monad m) => (a -> b -> m c) -> [a] -> [b] -> m [c]
46     , zipWithM_     -- :: (Monad m) => (a -> b -> m c) -> [a] -> [b] -> m ()
47     , foldM         -- :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m a 
48     , foldM_        -- :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m ()
49     , replicateM    -- :: (Monad m) => Int -> m a -> m [a]
50     , replicateM_   -- :: (Monad m) => Int -> m a -> m ()
51
52     -- ** Conditional execution of monadic expressions
53
54     , guard         -- :: (MonadPlus m) => Bool -> m ()
55     , when          -- :: (Monad m) => Bool -> m () -> m ()
56     , unless        -- :: (Monad m) => Bool -> m () -> m ()
57
58     -- ** Monadic lifting operators
59
60     , liftM         -- :: (Monad m) => (a -> b) -> (m a -> m b)
61     , liftM2        -- :: (Monad m) => (a -> b -> c) -> (m a -> m b -> m c)
62     , liftM3        -- :: ...
63     , liftM4        -- :: ...
64     , liftM5        -- :: ...
65
66     , ap            -- :: (Monad m) => m (a -> b) -> m a -> m b
67
68     ) where
69
70 import Data.Maybe
71
72 #ifdef __GLASGOW_HASKELL__
73 import GHC.List
74 import GHC.Base
75 #endif
76
77 #ifdef __GLASGOW_HASKELL__
78 infixr 1 =<<
79
80 -- -----------------------------------------------------------------------------
81 -- Prelude monad functions
82
83 -- | Same as '>>=', but with the arguments interchanged.
84 {-# SPECIALISE (=<<) :: (a -> [b]) -> [a] -> [b] #-}
85 (=<<)           :: Monad m => (a -> m b) -> m a -> m b
86 f =<< x         = x >>= f
87
88 -- | Evaluate each action in the sequence from left to right,
89 -- and collect the results.
90 sequence       :: Monad m => [m a] -> m [a] 
91 {-# INLINE sequence #-}
92 sequence ms = foldr k (return []) ms
93             where
94               k m m' = do { x <- m; xs <- m'; return (x:xs) }
95
96 -- | Evaluate each action in the sequence from left to right,
97 -- and ignore the results.
98 sequence_        :: Monad m => [m a] -> m () 
99 {-# INLINE sequence_ #-}
100 sequence_ ms     =  foldr (>>) (return ()) ms
101
102 -- | @'mapM' f@ is equivalent to @'sequence' . 'map' f@.
103 mapM            :: Monad m => (a -> m b) -> [a] -> m [b]
104 {-# INLINE mapM #-}
105 mapM f as       =  sequence (map f as)
106
107 -- | @'mapM_' f@ is equivalent to @'sequence_' . 'map' f@.
108 mapM_           :: Monad m => (a -> m b) -> [a] -> m ()
109 {-# INLINE mapM_ #-}
110 mapM_ f as      =  sequence_ (map f as)
111 #endif  /* __GLASGOW_HASKELL__ */
112
113 -- -----------------------------------------------------------------------------
114 -- The MonadPlus class definition
115
116 -- | Monads that also support choice and failure.
117 class Monad m => MonadPlus m where
118    -- | the identity of 'mplus'.  It should also satisfy the equations
119    --
120    -- > mzero >>= f  =  mzero
121    -- > v >> mzero   =  mzero
122    --
123    -- (but the instance for 'System.IO.IO' defined in "Control.Monad.Error"
124    -- does not satisfy the second one).
125    mzero :: m a 
126    -- | an associative operation
127    mplus :: m a -> m a -> m a
128
129 instance MonadPlus [] where
130    mzero = []
131    mplus = (++)
132
133 instance MonadPlus Maybe where
134    mzero = Nothing
135
136    Nothing `mplus` ys  = ys
137    xs      `mplus` _ys = xs
138
139 -- -----------------------------------------------------------------------------
140 -- Functions mandated by the Prelude
141
142 -- | @'guard' b@ is @'return' ()@ if @b@ is 'True',
143 -- and 'mzero' if @b@ is 'False'.
144 guard           :: (MonadPlus m) => Bool -> m ()
145 guard True      =  return ()
146 guard False     =  mzero
147
148 -- | This generalizes the list-based 'filter' function.
149
150 filterM          :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
151 filterM _ []     =  return []
152 filterM p (x:xs) =  do
153    flg <- p x
154    ys  <- filterM p xs
155    return (if flg then x:ys else ys)
156
157 -- | This generalizes the list-based 'concat' function.
158
159 msum        :: MonadPlus m => [m a] -> m a
160 {-# INLINE msum #-}
161 msum        =  foldr mplus mzero
162
163 -- -----------------------------------------------------------------------------
164 -- Other monad functions
165
166 -- | The 'join' function is the conventional monad join operator. It is used to
167 -- remove one level of monadic structure, projecting its bound argument into the
168 -- outer level.
169 join              :: (Monad m) => m (m a) -> m a
170 join x            =  x >>= id
171
172 -- | The 'mapAndUnzipM' function maps its first argument over a list, returning
173 -- the result as a pair of lists. This function is mainly used with complicated
174 -- data structures or a state-transforming monad.
175 mapAndUnzipM      :: (Monad m) => (a -> m (b,c)) -> [a] -> m ([b], [c])
176 mapAndUnzipM f xs =  sequence (map f xs) >>= return . unzip
177
178 -- | The 'zipWithM' function generalizes 'zipWith' to arbitrary monads.
179 zipWithM          :: (Monad m) => (a -> b -> m c) -> [a] -> [b] -> m [c]
180 zipWithM f xs ys  =  sequence (zipWith f xs ys)
181
182 -- | 'zipWithM_' is the extension of 'zipWithM' which ignores the final result.
183 zipWithM_         :: (Monad m) => (a -> b -> m c) -> [a] -> [b] -> m ()
184 zipWithM_ f xs ys =  sequence_ (zipWith f xs ys)
185
186 {- | The 'foldM' function is analogous to 'foldl', except that its result is
187 encapsulated in a monad. Note that 'foldM' works from left-to-right over
188 the list arguments. This could be an issue where '(>>)' and the `folded
189 function' are not commutative.
190
191
192 >       foldM f a1 [x1, x2, ..., xm ]
193
194 ==  
195
196 >       do
197 >         a2 <- f a1 x1
198 >         a3 <- f a2 x2
199 >         ...
200 >         f am xm
201
202 If right-to-left evaluation is required, the input list should be reversed.
203 -}
204
205 foldM             :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m a
206 foldM _ a []      =  return a
207 foldM f a (x:xs)  =  f a x >>= \fax -> foldM f fax xs
208
209 -- | Like 'foldM', but discards the result.
210 foldM_            :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m ()
211 foldM_ f a xs     = foldM f a xs >> return ()
212
213 -- | @'replicateM' n act@ performs the action @n@ times,
214 -- gathering the results.
215 replicateM        :: (Monad m) => Int -> m a -> m [a]
216 replicateM n x    = sequence (replicate n x)
217
218 -- | Like 'replicateM', but discards the result.
219 replicateM_       :: (Monad m) => Int -> m a -> m ()
220 replicateM_ n x   = sequence_ (replicate n x)
221
222 {- | Conditional execution of monadic expressions. For example, 
223
224 >       when debug (putStr "Debugging\n")
225
226 will output the string @Debugging\\n@ if the Boolean value @debug@ is 'True',
227 and otherwise do nothing.
228 -}
229
230 when              :: (Monad m) => Bool -> m () -> m ()
231 when p s          =  if p then s else return ()
232
233 -- | The reverse of 'when'.
234
235 unless            :: (Monad m) => Bool -> m () -> m ()
236 unless p s        =  if p then return () else s
237
238 -- | Promote a function to a monad.
239 liftM   :: (Monad m) => (a1 -> r) -> m a1 -> m r
240 liftM f m1              = do { x1 <- m1; return (f x1) }
241
242 -- | Promote a function to a monad, scanning the monadic arguments from
243 -- left to right.  For example,
244 --
245 -- >    liftM2 (+) [0,1] [0,2] = [0,2,1,3]
246 -- >    liftM2 (+) (Just 1) Nothing = Nothing
247 --
248 liftM2  :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
249 liftM2 f m1 m2          = do { x1 <- m1; x2 <- m2; return (f x1 x2) }
250
251 -- | Promote a function to a monad, scanning the monadic arguments from
252 -- left to right (cf. 'liftM2').
253 liftM3  :: (Monad m) => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r
254 liftM3 f m1 m2 m3       = do { x1 <- m1; x2 <- m2; x3 <- m3; return (f x1 x2 x3) }
255
256 -- | Promote a function to a monad, scanning the monadic arguments from
257 -- left to right (cf. 'liftM2').
258 liftM4  :: (Monad m) => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r
259 liftM4 f m1 m2 m3 m4    = do { x1 <- m1; x2 <- m2; x3 <- m3; x4 <- m4; return (f x1 x2 x3 x4) }
260
261 -- | Promote a function to a monad, scanning the monadic arguments from
262 -- left to right (cf. 'liftM2').
263 liftM5  :: (Monad m) => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r
264 liftM5 f m1 m2 m3 m4 m5 = do { x1 <- m1; x2 <- m2; x3 <- m3; x4 <- m4; x5 <- m5; return (f x1 x2 x3 x4 x5) }
265
266 {- | In many situations, the 'liftM' operations can be replaced by uses of
267 'ap', which promotes function application. 
268
269 >       return f `ap` x1 `ap` ... `ap` xn
270
271 is equivalent to 
272
273 >       liftMn f x1 x2 ... xn
274
275 -}
276
277 ap                :: (Monad m) => m (a -> b) -> m a -> m b
278 ap                =  liftM2 id
279
280 {- $naming
281
282 The functions in this library use the following naming conventions: 
283
284 * A postfix \'@M@\' always stands for a function in the Kleisli category:
285   The monad type constructor @m@ is added to function results
286   (modulo currying) and nowhere else.  So, for example, 
287
288 >  filter  ::              (a ->   Bool) -> [a] ->   [a]
289 >  filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
290
291 * A postfix \'@_@\' changes the result type from @(m a)@ to @(m ())@.
292   Thus, for example: 
293
294 >  sequence  :: Monad m => [m a] -> m [a] 
295 >  sequence_ :: Monad m => [m a] -> m () 
296
297 * A prefix \'@m@\' generalizes an existing function to a monadic form.
298   Thus, for example: 
299
300 >  sum  :: Num a       => [a]   -> a
301 >  msum :: MonadPlus m => [m a] -> m a
302
303 -}