805996fb76055daf02bfc77dac1177df4dc154c1
[ghc-base.git] / Control / Monad.hs
1 {-# OPTIONS -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     -- $lifting
60
61     , liftM         -- :: (Monad m) => (a -> b) -> (m a -> m b)
62     , liftM2        -- :: (Monad m) => (a -> b -> c) -> (m a -> m b -> m c)
63     , liftM3        -- :: ...
64     , liftM4        -- :: ...
65     , liftM5        -- :: ...
66
67     , ap            -- :: (Monad m) => m (a -> b) -> m a -> m b
68
69     ) where
70
71 import Data.Maybe
72
73 #ifdef __GLASGOW_HASKELL__
74 import GHC.List
75 import GHC.Base
76 #endif
77
78 #ifdef __GLASGOW_HASKELL__
79 infixr 1 =<<
80
81 -- -----------------------------------------------------------------------------
82 -- Prelude monad functions
83
84 {-# SPECIALISE (=<<) :: (a -> [b]) -> [a] -> [b] #-}
85 (=<<)           :: Monad m => (a -> m b) -> m a -> m b
86 f =<< x         = x >>= f
87
88 sequence       :: Monad m => [m a] -> m [a] 
89 {-# INLINE sequence #-}
90 sequence ms = foldr k (return []) ms
91             where
92               k m m' = do { x <- m; xs <- m'; return (x:xs) }
93
94 sequence_        :: Monad m => [m a] -> m () 
95 {-# INLINE sequence_ #-}
96 sequence_ ms     =  foldr (>>) (return ()) ms
97
98 mapM            :: Monad m => (a -> m b) -> [a] -> m [b]
99 {-# INLINE mapM #-}
100 mapM f as       =  sequence (map f as)
101
102 mapM_           :: Monad m => (a -> m b) -> [a] -> m ()
103 {-# INLINE mapM_ #-}
104 mapM_ f as      =  sequence_ (map f as)
105 #endif  /* __GLASGOW_HASKELL__ */
106
107 -- -----------------------------------------------------------------------------
108 -- |The MonadPlus class definition
109
110 class Monad m => MonadPlus m where
111    mzero :: m a
112    mplus :: m a -> m a -> m a
113
114 instance MonadPlus [] where
115    mzero = []
116    mplus = (++)
117
118 instance MonadPlus Maybe where
119    mzero = Nothing
120
121    Nothing `mplus` ys  = ys
122    xs      `mplus` _ys = xs
123
124 -- -----------------------------------------------------------------------------
125 -- Functions mandated by the Prelude
126
127 guard           :: (MonadPlus m) => Bool -> m ()
128 guard True      =  return ()
129 guard False     =  mzero
130
131 -- This subsumes the list-based filter function.
132
133 filterM          :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
134 filterM _ []     =  return []
135 filterM p (x:xs) =  do
136    flg <- p x
137    ys  <- filterM p xs
138    return (if flg then x:ys else ys)
139
140 -- This subsumes the list-based concat function.
141
142 msum        :: MonadPlus m => [m a] -> m a
143 {-# INLINE msum #-}
144 msum        =  foldr mplus mzero
145
146 -- -----------------------------------------------------------------------------
147 -- Other monad functions
148
149 -- | The 'join' function is the conventional monad join operator. It is used to
150 -- remove one level of monadic structure, projecting its bound argument into the
151 -- outer level.
152 join              :: (Monad m) => m (m a) -> m a
153 join x            =  x >>= id
154
155 -- | The 'mapAndUnzipM' function maps its first argument over a list, returning
156 -- the result as a pair of lists. This function is mainly used with complicated
157 -- data structures or a state-transforming monad.
158 mapAndUnzipM      :: (Monad m) => (a -> m (b,c)) -> [a] -> m ([b], [c])
159 mapAndUnzipM f xs =  sequence (map f xs) >>= return . unzip
160
161 -- | The 'zipWithM' function generalises 'zipWith' to arbitrary monads.
162 zipWithM          :: (Monad m) => (a -> b -> m c) -> [a] -> [b] -> m [c]
163 zipWithM f xs ys  =  sequence (zipWith f xs ys)
164
165 -- | 'zipWithM_' is the extension of 'zipWithM' which ignores the final result.
166 zipWithM_         :: (Monad m) => (a -> b -> m c) -> [a] -> [b] -> m ()
167 zipWithM_ f xs ys =  sequence_ (zipWith f xs ys)
168
169 {- | The 'foldM' function is analogous to 'foldl', except that its result is
170 encapsulated in a monad. Note that 'foldM' works from left-to-right over
171 the list arguments. This could be an issue where '(>>)' and the `folded
172 function' are not commutative.
173
174
175 >       foldM f a1 [x1, x2, ..., xm ]
176
177 ==  
178
179 >       do
180 >         a2 <- f a1 x1
181 >         a3 <- f a2 x2
182 >         ...
183 >         f am xm
184
185 If right-to-left evaluation is required, the input list should be reversed.
186 -}
187
188 foldM             :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m a
189 foldM _ a []      =  return a
190 foldM f a (x:xs)  =  f a x >>= \fax -> foldM f fax xs
191
192 foldM_            :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m ()
193 foldM_ f a xs     = foldM f a xs >> return ()
194
195 replicateM        :: (Monad m) => Int -> m a -> m [a]
196 replicateM n x    = sequence (replicate n x)
197
198 replicateM_       :: (Monad m) => Int -> m a -> m ()
199 replicateM_ n x   = sequence_ (replicate n x)
200
201 {- | Conditional execution of monadic expressions. For example, 
202
203 >       when debug (putStr "Debugging\n")
204
205 will output the string @Debugging\\n@ if the Boolean value @debug@ is 'True',
206 and otherwise do nothing.
207 -}
208
209 when              :: (Monad m) => Bool -> m () -> m ()
210 when p s          =  if p then s else return ()
211
212 -- | The reverse of 'when'.
213
214 unless            :: (Monad m) => Bool -> m () -> m ()
215 unless p s        =  if p then return () else s
216
217 {- $lifting
218
219 The monadic lifting operators promote a function to a monad.
220 The function arguments are scanned left to right. For example, 
221
222 >       liftM2 (+) [0,1] [0,2] = [0,2,1,3]
223 >       liftM2 (+) (Just 1) Nothing = Nothing
224
225 -}
226
227 liftM   :: (Monad m) => (a1 -> r) -> m a1 -> m r
228 liftM2  :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
229 liftM3  :: (Monad m) => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r
230 liftM4  :: (Monad m) => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r
231 liftM5  :: (Monad m) => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r
232
233 liftM f m1              = do { x1 <- m1; return (f x1) }
234 liftM2 f m1 m2          = do { x1 <- m1; x2 <- m2; return (f x1 x2) }
235 liftM3 f m1 m2 m3       = do { x1 <- m1; x2 <- m2; x3 <- m3; return (f x1 x2 x3) }
236 liftM4 f m1 m2 m3 m4    = do { x1 <- m1; x2 <- m2; x3 <- m3; x4 <- m4; return (f x1 x2 x3 x4) }
237 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) }
238
239 {- | In many situations, the 'liftM' operations can be replaced by uses of
240 'ap', which promotes function application. 
241
242 >       return f `ap` x1 `ap` ... `ap` xn
243
244 is equivalent to 
245
246 >       liftMn f x1 x2 ... xn
247
248 -}
249
250 ap                :: (Monad m) => m (a -> b) -> m a -> m b
251 ap                =  liftM2 id
252
253 {- $naming
254
255 The functions in this library use the following naming conventions: 
256
257 * A postfix \`M\' always stands for a function in the Kleisli category:
258   @m@ is added to function results (modulo currying) and nowhere else.
259   So, for example, 
260
261 >  filter  ::              (a ->   Bool) -> [a] ->   [a]
262 >  filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
263
264 * A postfix \`_\' changes the result type from @(m a)@ to @(m ())@.
265   Thus (in the "Prelude"): 
266
267 >  sequence  :: Monad m => [m a] -> m [a] 
268 >  sequence_ :: Monad m => [m a] -> m () 
269
270 * A prefix \`m\' generalises an existing function to a monadic form.
271   Thus, for example: 
272
273 >  sum  :: Num a       => [a]   -> a
274 >  msum :: MonadPlus m => [m a] -> m a
275
276 -}