[project @ 2004-01-10 12:53:42 by panne]
[ghc-base.git] / Data / Generics / Aliases.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  Data.Generics.Aliases
4 -- Copyright   :  (c) The University of Glasgow, CWI 2001--2003
5 -- License     :  BSD-style (see the file libraries/base/LICENSE)
6 -- 
7 -- Maintainer  :  libraries@haskell.org
8 -- Stability   :  experimental
9 -- Portability :  non-portable
10 --
11 -- \"Scrap your boilerplate\" --- Generic programming in Haskell 
12 -- See <http://www.cs.vu.nl/boilerplate/>. The present module provides
13 -- a number of declarations for typical generic function types,
14 -- corresponding type case, and others.
15 --
16 -----------------------------------------------------------------------------
17
18 module Data.Generics.Aliases ( 
19
20         -- * Combinators to \"make\" generic functions via cast
21         mkT, mkQ, mkM, mkMp, mkR,
22         extT, extQ, extM, extMp, extB, extR,
23
24         -- * Type synonyms for generic function types
25         GenericT, 
26         GenericQ,
27         GenericM,
28         GenericB,
29         GenericR,
30         Generic,
31         Generic'(..),
32
33         -- * Inredients of generic functions
34         orElse,
35
36         -- * Function combinators on generic functions
37         recoverMp,
38         recoverQ,
39         choiceMp,
40         choiceQ,
41
42         -- * Operators for (over-appreciated) unfolding
43         gunfoldB,
44         gunfoldR
45
46   ) where
47
48 #ifdef __HADDOCK__
49 import Prelude
50 #endif
51 import Control.Monad
52 import Data.Generics.Basics
53
54 ------------------------------------------------------------------------------
55 --
56 --      Combinators to "make" generic functions
57 --      We use type-safe cast in a number of ways to make generic functions.
58 --
59 ------------------------------------------------------------------------------
60
61 -- | Make a generic transformation;
62 --   start from a type-specific case;
63 --   preserve the term otherwise
64 --
65 mkT :: ( Typeable a
66        , Typeable b
67        )
68     => (b -> b)
69     -> a 
70     -> a
71 mkT f = case cast f of
72                Just g -> g
73                Nothing -> id
74
75
76 -- | Make a generic query;
77 --   start from a type-specific case;
78 --   return a constant otherwise
79 --
80 mkQ :: ( Typeable a
81        , Typeable b
82        )
83     => r
84     -> (b -> r)
85     -> a 
86     -> r
87 (r `mkQ` br) a = case cast a of
88                         Just b  -> br b
89                         Nothing -> r
90
91
92 -- | Make a generic monadic transformation;
93 --   start from a type-specific case;
94 --   resort to return otherwise
95 --
96 mkM :: ( Monad m
97        , Typeable a
98        , Typeable b
99        )
100     => (b -> m b)
101     -> a 
102     -> m a
103 mkM f = case castarr f of
104               Just g  -> g
105               Nothing -> return
106
107
108 {-
109
110 For the remaining definitions, we stick to a more concise style, i.e.,
111 we fold maybies with "maybe" instead of case ... of ..., and we also
112 use a point-free style whenever possible.
113
114 -}
115
116
117 -- | Make a generic monadic transformation for MonadPlus;
118 --   use \"const mzero\" (i.e., failure) instead of return as default.
119 --
120 mkMp :: ( MonadPlus m
121         , Typeable a
122         , Typeable b
123         )
124      => (b -> m b)
125      -> a
126      -> m a
127 mkMp = maybe (const mzero) id . castarr
128
129
130 -- | Make a generic builder;
131 --   start from a type-specific ase;
132 --   resort to no build (i.e., mzero) otherwise
133 --
134 mkR :: ( MonadPlus m
135        , Typeable a
136        , Typeable b
137        )
138     => m b -> m a
139 mkR = maybe mzero id . castss
140
141
142 -- | Extend a generic transformation by a type-specific case
143 extT :: ( Typeable a
144         , Typeable b 
145         )
146      => (a -> a)
147      -> (b -> b)
148      -> a
149      -> a
150 extT f = maybe f id . cast
151
152
153 -- | Extend a generic query by a type-specific case
154 extQ :: ( Typeable a
155         , Typeable b
156         )
157      => (a -> q)
158      -> (b -> q)
159      -> a
160      -> q
161 extQ f g a = maybe (f a) g (cast a)
162
163
164 -- | Extend a generic monadic transformation by a type-specific case
165 extM :: ( Monad m
166         , Typeable a
167         , Typeable b
168         )
169      => (a -> m a) -> (b -> m b) -> a -> m a
170 extM f = maybe f id . castarr
171
172
173 -- | Extend a generic MonadPlus transformation by a type-specific case
174 extMp :: ( MonadPlus m
175          , Typeable a
176          , Typeable b
177          )
178       => (a -> m a) -> (b -> m b) -> a -> m a
179 extMp = extM
180
181
182 -- | Extend a generic builder
183 extB :: ( Typeable a
184         , Typeable b
185         )
186      => a -> b -> a
187 extB a = maybe a id . cast
188
189
190 -- | Extend a generic reader
191 extR :: ( Monad m
192         , Typeable a
193         , Typeable b
194         )
195      => m a -> m b -> m a
196 extR f = maybe f id . castss
197
198
199 ------------------------------------------------------------------------------
200 --
201 --      Type synonyms for generic function types
202 --
203 ------------------------------------------------------------------------------
204
205
206 -- | Generic transformations,
207 --   i.e., take an \"a\" and return an \"a\"
208 --
209 type GenericT = forall a. Data a => a -> a
210
211
212 -- | Generic queries of type \"r\",
213 --   i.e., take any \"a\" and return an \"r\"
214 --
215 type GenericQ r = forall a. Data a => a -> r
216
217
218 -- | Generic monadic transformations,
219 --   i.e., take an \"a\" and compute an \"a\"
220 --
221 type GenericM m = forall a. Data a => a -> m a
222
223
224 -- | Generic builders
225 --   i.e., produce an \"a\".
226 --
227 type GenericB = forall a. Data a => a
228
229
230 -- | Generic readers, say monadic builders,
231 --   i.e., produce an \"a\" with the help of a monad \"m\".
232 --
233 type GenericR m = forall a. Data a => m a
234
235
236 -- | The general scheme underlying generic functions
237 --   assumed by gfoldl; there are isomorphisms such as
238 --   GenericT = Generic ID.
239 --
240 type Generic c = forall a. Data a => a -> c a
241
242
243 -- | Wrapped generic functions;
244 --   recall: [Generic c] would be legal but [Generic' c] not.
245 --
246 data Generic' c = Generic' { unGeneric' :: Generic c }
247
248
249
250 -- | Left-biased choice on maybies
251 orElse :: Maybe a -> Maybe a -> Maybe a
252 x `orElse` y = case x of
253                  Just _  -> x
254                  Nothing -> y
255
256
257 {-
258
259 The following variations take "orElse" to the function
260 level. Furthermore, we generalise from "Maybe" to any
261 "MonadPlus". This makes sense for monadic transformations and
262 queries. We say that the resulting combinators modell choice. We also
263 provide a prime example of choice, that is, recovery from failure. In
264 the case of transformations, we recover via return whereas for
265 queries a given constant is returned.
266
267 -}
268
269 -- | Choice for monadic transformations
270 choiceMp :: MonadPlus m => GenericM m -> GenericM m -> GenericM m
271 choiceMp f g x = f x `mplus` g x
272
273
274 -- | Choice for monadic queries
275 choiceQ :: MonadPlus m => GenericQ (m r) -> GenericQ (m r) -> GenericQ (m r)
276 choiceQ f g x = f x `mplus` g x
277
278
279 -- | Recover from the failure of monadic transformation by identity
280 recoverMp :: MonadPlus m => GenericM m -> GenericM m
281 recoverMp f = f `choiceMp` return
282
283
284 -- | Recover from the failure of monadic query by a constant
285 recoverQ :: MonadPlus m => r -> GenericQ (m r) -> GenericQ (m r)
286 recoverQ r f = f `choiceQ` const (return r)
287
288
289
290 ------------------------------------------------------------------------------
291 --
292 --      Generic unfolding
293 --
294 ------------------------------------------------------------------------------
295
296 -- | Construct an initial term with undefined immediate subterms
297 --   and then map over the skeleton to fill in proper terms.
298 gunfoldB :: Data a
299          => Constr
300          -> (forall a. Data a => a)
301          -> a
302 gunfoldB c f = gmapT (const f) (fromConstr c)
303
304
305 -- | Monadic variation on \"gunfoldB\"
306 gunfoldR :: (Monad m, Data a)
307          => Constr
308          -> (forall a. Data a => m a)
309          -> m a
310 gunfoldR c f = gmapM (const f) $ fromConstr c