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