[project @ 2003-06-03 22:26:44 by diatchki]
[ghc-base.git] / Control / Monad / X / Trans.hs
1 module Control.Monad.X.Trans 
2   ( -- * General transformer classes
3     MonadTrans(..),
4     HasBaseMonad(..),
5
6     -- * Plumbing transformers
7     -- $PlumbingDoc
8
9     -- ** Reader
10     MonadReader(..), 
11     -- $MonadReaderDoc
12     asks,
13     localSet,
14
15     -- ** Writer
16     MonadWriter(..),
17     -- $MonadWriterDoc
18     listens,
19     censor,
20     pass,
21
22     -- ** State
23     MonadState(..),   
24     -- $MonadStateDoc
25     gets,
26     modify,
27
28     -- * Control transformers
29     -- $ControlDoc
30
31     -- ** Exceptions
32     MonadError(..),
33     -- $MonadErrorDoc
34
35     -- ** Non-determinism
36     MonadNondet(..),
37     -- $MonadNondetDoc
38
39     -- ** Resumptions
40     MonadResume(..),
41     -- $MonadResumeDoc
42
43     -- ** Continuations
44     MonadCont(..),
45     -- $MonadContDoc
46   )
47   where
48
49 import Prelude (Monad(..),(.),const,IO,Maybe,id)
50 import Control.Monad(MonadPlus,liftM)
51
52 import Data.Monoid(Monoid)
53
54
55
56 --------------------------------------------------------------------------------
57 -- | Provides a way of going across one transformer layer.
58
59 class MonadTrans t where
60   lift  :: Monad m => m a -> t m a
61   -- ^ Provides a way of going across one transformer layer.
62
63
64 --------------------------------------------------------------------------------
65 -- | The predicate @HasBaseMonad m n@ indicates that 'm' is a monad
66 -- built by applying a number of transformers to 'n'.
67
68 class (Monad m, Monad n) => HasBaseMonad m n | m -> n where
69   inBase :: n a -> m a
70   -- ^ Provides a way of going across multiple transformer layers,
71   -- all the way to the innermost atomic monad.
72
73
74 -- Move me somewhere else.
75 instance HasBaseMonad IO IO where inBase = id
76 instance HasBaseMonad [] [] where inBase = id
77 instance HasBaseMonad Maybe Maybe where inBase = id
78
79
80
81
82 {- $PlumbingDoc
83   /Plumbing transformers/ take care of propagating information around in a computation.
84 They all commute with each other.  This means that it doesn't meter 
85 in what order they are added to a computation, the final effect is the same.
86 -}
87
88 -- | A reader monad has the ability to propagate around a read-only environment.
89 -- One can think of the environment as a special read only variable that can
90 -- be accessed via the methods of the class.
91
92 class (Monad m) => MonadReader r m | m -> r where
93   ask         :: m r
94   -- ^ Read the value of the variable.
95
96   local       :: (r -> r) -> m a -> m a
97   -- ^ The method @local f m@ uses @f@ to change the value of the variable 
98   -- for the duration of a computation @m@. After @m@ completes its execution
99   -- the original value of the variable is restored.
100
101 {- $MonadReaderDoc
102   Read-only variables are useful when some information needs to be carried
103 around, but is not used all the time. Such a situation may occur when a deeply nested
104 function call needs the information, but most of the functions involved in
105 a computation will not use it and simply pass it around.  Read-only variables
106 are very closely related to /implicit parameters/ <...>.
107 See also `MonadWriter'. 
108 -}
109
110
111 -- | Gets specific component of the environment, using the projection function
112 -- supplied.
113 asks          :: (MonadReader r m) => (r -> a) -> m a
114 asks f        = liftM f ask
115
116
117 -- | Temporarily sets the value of the read-only variable. One can think of
118 -- @localSet x m@ as a @let@ construct.  
119 localSet      :: MonadReader r m => r -> m a -> m a
120 localSet      = local . const
121
122
123 -- | A writer monad has the ability to collect a number of outputs generated
124 -- during a computation.  It is like carrying around a buffer that can be
125 -- manipulated with the methods of the class.  The 'Monoid' class specifies
126 -- how to make an empty buffer, and how to join two buffers together.
127 class (Monoid w, Monad m) => MonadWriter w m | m -> w where
128   tell        :: w -> m ()
129   -- ^ @tell w@ appends the new information @w@ to the buffer.
130
131   listen      :: m a -> m (a, w)
132   -- ^ @listen m@ moves the contents of the buffer of computation @m@ to its result.
133   -- The resulting computation has an empty buffer.
134
135 {- $MonadWriterDoc
136   Buffer variables are often useful when one needs to collect some
137 information, for example while traversing a data structure.  In a sense,
138 they are the dual of read-only variables, as they propagate outputs
139 of functions, rather then their inputs.
140 -}
141
142
143 -- | Gets specific component of the output, using the projection function supplied.
144 listens       :: (MonadWriter w m) => (w -> b) -> m a -> m (a, b)
145 listens f m   = liftM (\ ~(a,w) -> (a,f w)) (listen m)
146
147
148 -- | @censor f m@ behaves like @m@ except its output is modified by @f@. 
149 censor        :: MonadWriter w m => (w -> w) -> m a -> m a
150 censor f m    = do (a,w) <- listen m
151                    tell (f w)   -- the media :-)
152                    return a
153
154 -- | NOTE: SHOULD THIS BE IN THE LIBRARY?
155 -- Does what the type suggests.
156 pass          :: (MonadWriter w m) => m (a, w -> w) -> m a
157 pass m        = do ((a,f),w) <- listen m
158                    tell (f w)
159                    return a
160
161
162
163 -- | A state monad carries around a piece of state.  It is just like
164 -- having a read-write variable in an imperative language.
165
166 class (Monad m) => MonadState s m | m -> s where
167   get         :: m s
168   -- ^ reads the value of the variable 
169
170   put         :: s -> m ()
171   -- ^ @put s@ permanently changes the value of the variable to @s@.
172
173 -- $MonadStateDoc
174 -- 
175
176 -- | Gets specific component of the state, using the projection function supplied.
177 gets          :: (MonadState s m) => (s -> a) -> m a
178 gets f        = liftM f get
179
180 -- | Update the state with a function.
181 modify        :: (MonadState s m) => (s -> s) -> m ()
182 modify f      = get >>= put . f
183
184
185 -- $ControlDoc
186 -- /Control transformers/ are used to manipulate the control flow in a program.
187 -- In general they do not commute between themselves and with other transformers.
188 -- This means that it is important in what order they are added on top of a monad.
189 -- Different orders yield monads with different behavior.  See "FeatureInteract.hs".
190
191
192
193 -- | An error (or exception) monad is aware that computations may fail.
194 -- The type @e@ specifies what errors may occur in a computation.
195 class (Monad m) => MonadError e m | m -> e where
196   throwError  :: e -> m a
197   -- ^ The method @throwError e@ raises exception @e@.
198   -- It never returns a value.
199
200   catchError  :: m a -> (e -> m a) -> m a
201   -- ^ The method @catchError m h@ uses the handler @h@ to handle exceptions
202   -- raised in computation @m@.  If no exceptions are
203   -- raised, the final computation behaves as @m@.  It is possible
204   -- for the handler itself to throw an exception.
205
206 -- $ErrorDoc
207
208 -- | A nondeterminism (or backtracking) monad supports computations that 
209 -- may fail and backtrack or produce multiple results.  
210 --
211 -- Currently some of the methods in this class are inherited from 
212 -- the class 'MonadPlus' defined in module "Control.Monad".
213 -- 'mzero' is used to indicate no results. 
214 -- 'mplus' is used to indicate alternatives.
215 --
216 -- Since the use of 'MonadPlus' is somewhat overloaded in Haskell
217 -- (it is also used for exception handling)
218 -- in the future 'mzero' and 'mplus' may be added explicitly to this class
219 -- (with different names).
220 class (MonadPlus m) => MonadNondet m where
221   findAll     :: m a -> m [a]
222   -- ^ @findAll m@ is analogous to the construct found in logic languages
223   -- (e.g. Prolog, Curry). It produces all possible results of @m@.
224   commit      :: m a -> m a
225   -- ^ @commit m@ behaves like @m@ except it will produce at most one result.
226   -- Thus, it resembles the /cut/ operator of Prolog.
227   -- (VERIFY) @findAll (commit m)@ should never produce a list with more than one element.
228
229 class Monad m => MonadResume m where
230   delay       :: m a -> m a
231   force       :: m a -> m a
232
233 -- | TODO.
234 class (Monad m) => MonadCont m where
235   callCC      :: ((a -> m b) -> m a) -> m a
236
237
238
239
240
241