add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[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 {-# INLINABLE forever #-}  -- See Note [Make forever INLINABLE]
193 forever a   = a >> forever a
194
195 {- Note [Make forever INLINABLE]
196
197 If you say   x = forever a
198 you'll get   x = a >> a >> a >> a >> ... etc ...
199 and that can make a massive space leak (see Trac #5205)
200
201 In some monads, where (>>) is expensive, this might be the right
202 thing, but not in the IO monad.  We want to specialise 'forever' for
203 the IO monad, so that eta expansion happens and there's no space leak.
204 To achieve this we must make forever INLINABLE, so that it'll get
205 specialised at call sites.
206
207 Still delicate, though, because it depends on optimisation.  But there
208 really is a space/time tradeoff here, and only optimisation reveals
209 the "right" answer.
210 -}
211
212 -- | @'void' value@ discards or ignores the result of evaluation, such as the return value of an 'IO' action.
213 void :: Functor f => f a -> f ()
214 void = fmap (const ())
215
216 -- -----------------------------------------------------------------------------
217 -- Other monad functions
218
219 -- | The 'join' function is the conventional monad join operator. It is used to
220 -- remove one level of monadic structure, projecting its bound argument into the
221 -- outer level.
222 join              :: (Monad m) => m (m a) -> m a
223 join x            =  x >>= id
224
225 -- | The 'mapAndUnzipM' function maps its first argument over a list, returning
226 -- the result as a pair of lists. This function is mainly used with complicated
227 -- data structures or a state-transforming monad.
228 mapAndUnzipM      :: (Monad m) => (a -> m (b,c)) -> [a] -> m ([b], [c])
229 mapAndUnzipM f xs =  sequence (map f xs) >>= return . unzip
230
231 -- | The 'zipWithM' function generalizes 'zipWith' to arbitrary monads.
232 zipWithM          :: (Monad m) => (a -> b -> m c) -> [a] -> [b] -> m [c]
233 zipWithM f xs ys  =  sequence (zipWith f xs ys)
234
235 -- | 'zipWithM_' is the extension of 'zipWithM' which ignores the final result.
236 zipWithM_         :: (Monad m) => (a -> b -> m c) -> [a] -> [b] -> m ()
237 zipWithM_ f xs ys =  sequence_ (zipWith f xs ys)
238
239 {- | The 'foldM' function is analogous to 'foldl', except that its result is
240 encapsulated in a monad. Note that 'foldM' works from left-to-right over
241 the list arguments. This could be an issue where @('>>')@ and the `folded
242 function' are not commutative.
243
244
245 >       foldM f a1 [x1, x2, ..., xm]
246
247 ==  
248
249 >       do
250 >         a2 <- f a1 x1
251 >         a3 <- f a2 x2
252 >         ...
253 >         f am xm
254
255 If right-to-left evaluation is required, the input list should be reversed.
256 -}
257
258 foldM             :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m a
259 foldM _ a []      =  return a
260 foldM f a (x:xs)  =  f a x >>= \fax -> foldM f fax xs
261
262 -- | Like 'foldM', but discards the result.
263 foldM_            :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m ()
264 foldM_ f a xs     = foldM f a xs >> return ()
265
266 -- | @'replicateM' n act@ performs the action @n@ times,
267 -- gathering the results.
268 replicateM        :: (Monad m) => Int -> m a -> m [a]
269 replicateM n x    = sequence (replicate n x)
270
271 -- | Like 'replicateM', but discards the result.
272 replicateM_       :: (Monad m) => Int -> m a -> m ()
273 replicateM_ n x   = sequence_ (replicate n x)
274
275 {- | Conditional execution of monadic expressions. For example, 
276
277 >       when debug (putStr "Debugging\n")
278
279 will output the string @Debugging\\n@ if the Boolean value @debug@ is 'True',
280 and otherwise do nothing.
281 -}
282
283 when              :: (Monad m) => Bool -> m () -> m ()
284 when p s          =  if p then s else return ()
285
286 -- | The reverse of 'when'.
287
288 unless            :: (Monad m) => Bool -> m () -> m ()
289 unless p s        =  if p then return () else s
290
291 -- | Promote a function to a monad.
292 liftM   :: (Monad m) => (a1 -> r) -> m a1 -> m r
293 liftM f m1              = do { x1 <- m1; return (f x1) }
294
295 -- | Promote a function to a monad, scanning the monadic arguments from
296 -- left to right.  For example,
297 --
298 -- >    liftM2 (+) [0,1] [0,2] = [0,2,1,3]
299 -- >    liftM2 (+) (Just 1) Nothing = Nothing
300 --
301 liftM2  :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
302 liftM2 f m1 m2          = do { x1 <- m1; x2 <- m2; return (f x1 x2) }
303
304 -- | Promote a function to a monad, scanning the monadic arguments from
305 -- left to right (cf. 'liftM2').
306 liftM3  :: (Monad m) => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r
307 liftM3 f m1 m2 m3       = do { x1 <- m1; x2 <- m2; x3 <- m3; return (f x1 x2 x3) }
308
309 -- | Promote a function to a monad, scanning the monadic arguments from
310 -- left to right (cf. 'liftM2').
311 liftM4  :: (Monad m) => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r
312 liftM4 f m1 m2 m3 m4    = do { x1 <- m1; x2 <- m2; x3 <- m3; x4 <- m4; return (f x1 x2 x3 x4) }
313
314 -- | Promote a function to a monad, scanning the monadic arguments from
315 -- left to right (cf. 'liftM2').
316 liftM5  :: (Monad m) => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r
317 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) }
318
319 {- | In many situations, the 'liftM' operations can be replaced by uses of
320 'ap', which promotes function application. 
321
322 >       return f `ap` x1 `ap` ... `ap` xn
323
324 is equivalent to 
325
326 >       liftMn f x1 x2 ... xn
327
328 -}
329
330 ap                :: (Monad m) => m (a -> b) -> m a -> m b
331 ap                =  liftM2 id
332
333
334 -- -----------------------------------------------------------------------------
335 -- Other MonadPlus functions
336
337 -- | Direct 'MonadPlus' equivalent of 'filter'
338 -- @'filter'@ = @(mfilter:: (a -> Bool) -> [a] -> [a]@
339 -- applicable to any 'MonadPlus', for example
340 -- @mfilter odd (Just 1) == Just 1@
341 -- @mfilter odd (Just 2) == Nothing@
342
343 mfilter :: (MonadPlus m) => (a -> Bool) -> m a -> m a
344 mfilter p ma = do
345   a <- ma
346   if p a then return a else mzero
347
348 {- $naming
349
350 The functions in this library use the following naming conventions: 
351
352 * A postfix \'@M@\' always stands for a function in the Kleisli category:
353   The monad type constructor @m@ is added to function results
354   (modulo currying) and nowhere else.  So, for example, 
355
356 >  filter  ::              (a ->   Bool) -> [a] ->   [a]
357 >  filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
358
359 * A postfix \'@_@\' changes the result type from @(m a)@ to @(m ())@.
360   Thus, for example: 
361
362 >  sequence  :: Monad m => [m a] -> m [a] 
363 >  sequence_ :: Monad m => [m a] -> m () 
364
365 * A prefix \'@m@\' generalizes an existing function to a monadic form.
366   Thus, for example: 
367
368 >  sum  :: Num a       => [a]   -> a
369 >  msum :: MonadPlus m => [m a] -> m a
370
371 -}