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