ac5c0397d8b144520ce3f28204e0b027962a62f4
[haskell-directory.git] / Data / Generics / Aliases.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  Data.Generics.Aliases
4 -- Copyright   :  (c) The University of Glasgow, CWI 2001--2004
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         ext0, 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         GenericT'(..),
33         GenericQ'(..),
34         GenericM'(..),
35
36         -- * Inredients of generic functions
37         orElse,
38
39         -- * Function combinators on generic functions
40         recoverMp,
41         recoverQ,
42         choiceMp,
43         choiceQ,
44
45         -- * Operators for (over-appreciated) unfolding
46         gunfoldB,
47         gunfoldR,
48
49         -- * Type extension for unary type constructors
50         ext1T, 
51         ext1M,
52         ext1Q,
53         ext1R
54
55   ) where
56
57 #ifdef __HADDOCK__
58 import Prelude
59 #endif
60 import Control.Monad
61 import Data.Generics.Basics
62
63 ------------------------------------------------------------------------------
64 --
65 --      Combinators to "make" generic functions
66 --      We use type-safe cast in a number of ways to make generic functions.
67 --
68 ------------------------------------------------------------------------------
69
70 -- | Make a generic transformation;
71 --   start from a type-specific case;
72 --   preserve the term otherwise
73 --
74 mkT :: ( Typeable a
75        , Typeable b
76        )
77     => (b -> b)
78     -> a 
79     -> a
80 mkT = extT id
81
82
83 -- | Make a generic query;
84 --   start from a type-specific case;
85 --   return a constant otherwise
86 --
87 mkQ :: ( Typeable a
88        , Typeable b
89        )
90     => r
91     -> (b -> r)
92     -> a 
93     -> r
94 (r `mkQ` br) a = case cast a of
95                         Just b  -> br b
96                         Nothing -> r
97
98
99 -- | Make a generic monadic transformation;
100 --   start from a type-specific case;
101 --   resort to return otherwise
102 --
103 mkM :: ( Monad m
104        , Typeable a
105        , Typeable b
106        )
107     => (b -> m b)
108     -> a 
109     -> m a
110 mkM = extM return
111
112
113 {-
114
115 For the remaining definitions, we stick to a more concise style, i.e.,
116 we fold maybies with "maybe" instead of case ... of ..., and we also
117 use a point-free style whenever possible.
118
119 -}
120
121
122 -- | Make a generic monadic transformation for MonadPlus;
123 --   use \"const mzero\" (i.e., failure) instead of return as default.
124 --
125 mkMp :: ( MonadPlus m
126         , Typeable a
127         , Typeable b
128         )
129      => (b -> m b)
130      -> a
131      -> m a
132 mkMp = extM (const mzero)
133
134
135 -- | Make a generic builder;
136 --   start from a type-specific ase;
137 --   resort to no build (i.e., mzero) otherwise
138 --
139 mkR :: ( MonadPlus m
140        , Typeable a
141        , Typeable b
142        )
143     => m b -> m a
144 mkR f = mzero `extR` f
145
146
147 -- | Flexible type extension
148 ext0 :: (Typeable a, Typeable b) => c a -> c b -> c a
149 ext0 def ext = maybe def id (gcast ext)
150
151
152 -- | Extend a generic transformation by a type-specific case
153 extT :: ( Typeable a
154         , Typeable b
155         )
156      => (a -> a)
157      -> (b -> b)
158      -> a
159      -> a
160 extT def ext = unT ((T def) `ext0` (T ext))
161
162
163 -- | Extend a generic query by a type-specific case
164 extQ :: ( Typeable a
165         , Typeable b
166         )
167      => (a -> q)
168      -> (b -> q)
169      -> a
170      -> q
171 extQ f g a = maybe (f a) g (cast a)
172
173
174 -- | Extend a generic monadic transformation by a type-specific case
175 extM :: ( Monad m
176         , Typeable a
177         , Typeable b
178         )
179      => (a -> m a) -> (b -> m b) -> a -> m a
180 extM def ext = unM ((M def) `ext0` (M ext))
181
182
183 -- | Extend a generic MonadPlus transformation by a type-specific case
184 extMp :: ( MonadPlus m
185          , Typeable a
186          , Typeable b
187          )
188       => (a -> m a) -> (b -> m b) -> a -> m a
189 extMp = extM
190
191
192 -- | Extend a generic builder
193 extB :: ( Typeable a
194         , Typeable b
195         )
196      => a -> b -> a
197 extB a = maybe a id . cast
198
199
200 -- | Extend a generic reader
201 extR :: ( Monad m
202         , Typeable a
203         , Typeable b
204         )
205      => m a -> m b -> m a
206 extR def ext = unR ((R def) `ext0` (R ext))
207
208
209
210 ------------------------------------------------------------------------------
211 --
212 --      Type synonyms for generic function types
213 --
214 ------------------------------------------------------------------------------
215
216
217 -- | Generic transformations,
218 --   i.e., take an \"a\" and return an \"a\"
219 --
220 type GenericT = forall a. Data a => a -> a
221
222
223 -- | Generic queries of type \"r\",
224 --   i.e., take any \"a\" and return an \"r\"
225 --
226 type GenericQ r = forall a. Data a => a -> r
227
228
229 -- | Generic monadic transformations,
230 --   i.e., take an \"a\" and compute an \"a\"
231 --
232 type GenericM m = forall a. Data a => a -> m a
233
234
235 -- | Generic builders
236 --   i.e., produce an \"a\".
237 --
238 type GenericB = forall a. Data a => a
239
240
241 -- | Generic readers, say monadic builders,
242 --   i.e., produce an \"a\" with the help of a monad \"m\".
243 --
244 type GenericR m = forall a. Data a => m a
245
246
247 -- | The general scheme underlying generic functions
248 --   assumed by gfoldl; there are isomorphisms such as
249 --   GenericT = Generic T.
250 --
251 type Generic c = forall a. Data a => a -> c a
252
253
254 -- | Wrapped generic functions;
255 --   recall: [Generic c] would be legal but [Generic' c] not.
256 --
257 data Generic' c = Generic' { unGeneric' :: Generic c }
258
259
260 -- | Other first-class polymorphic wrappers
261 newtype GenericT'   = GT { unGT :: Data a => a -> a }
262 newtype GenericQ' r = GQ { unGQ :: GenericQ r }
263 newtype GenericM' m = GM { unGM :: Data a => a -> m a }
264
265
266 -- | Left-biased choice on maybies
267 orElse :: Maybe a -> Maybe a -> Maybe a
268 x `orElse` y = case x of
269                  Just _  -> x
270                  Nothing -> y
271
272
273 {-
274
275 The following variations take "orElse" to the function
276 level. Furthermore, we generalise from "Maybe" to any
277 "MonadPlus". This makes sense for monadic transformations and
278 queries. We say that the resulting combinators modell choice. We also
279 provide a prime example of choice, that is, recovery from failure. In
280 the case of transformations, we recover via return whereas for
281 queries a given constant is returned.
282
283 -}
284
285 -- | Choice for monadic transformations
286 choiceMp :: MonadPlus m => GenericM m -> GenericM m -> GenericM m
287 choiceMp f g x = f x `mplus` g x
288
289
290 -- | Choice for monadic queries
291 choiceQ :: MonadPlus m => GenericQ (m r) -> GenericQ (m r) -> GenericQ (m r)
292 choiceQ f g x = f x `mplus` g x
293
294
295 -- | Recover from the failure of monadic transformation by identity
296 recoverMp :: MonadPlus m => GenericM m -> GenericM m
297 recoverMp f = f `choiceMp` return
298
299
300 -- | Recover from the failure of monadic query by a constant
301 recoverQ :: MonadPlus m => r -> GenericQ (m r) -> GenericQ (m r)
302 recoverQ r f = f `choiceQ` const (return r)
303
304
305
306 ------------------------------------------------------------------------------
307 --
308 --      Generic unfolding
309 --
310 ------------------------------------------------------------------------------
311
312 -- | Construct an initial term with undefined immediate subterms
313 --   and then map over the skeleton to fill in proper terms.
314 gunfoldB :: Data a
315          => Constr
316          -> (forall a. Data a => a)
317          -> a
318 gunfoldB c f = gmapT (const f) (fromConstr c)
319
320
321 -- | Monadic variation on \"gunfoldB\"
322 gunfoldR :: (Monad m, Data a)
323          => Constr
324          -> (forall a. Data a => m a)
325          -> m a
326 gunfoldR c f = gmapM (const f) $ fromConstr c
327
328
329
330 ------------------------------------------------------------------------------
331 --
332 --      Type extension for unary type constructors
333 --
334 ------------------------------------------------------------------------------
335
336
337
338 -- | Flexible type extension
339 ext1 :: (Data a, Typeable1 t)
340      => c a
341      -> (forall a. Data a => c (t a))
342      -> c a
343 ext1 def ext = maybe def id (dataCast1 ext)
344
345
346 -- | Type extension of transformations for unary type constructors
347 ext1T :: (Data d, Typeable1 t)
348       => (forall d. Data d => d -> d)
349       -> (forall d. Data d => t d -> t d)
350       -> d -> d
351 ext1T def ext = unT ((T def) `ext1` (T ext))
352
353
354 -- | Type extension of monadic transformations for type constructors
355 ext1M :: (Monad m, Data d, Typeable1 t)
356       => (forall d. Data d => d -> m d)
357       -> (forall d. Data d => t d -> m (t d))
358       -> d -> m d
359 ext1M def ext = unM ((M def) `ext1` (M ext))
360
361
362 -- | Type extension of queries for type constructors
363 ext1Q :: (Data d, Typeable1 t)
364       => (d -> q)
365       -> (forall d. Data d => t d -> q)
366       -> d -> q
367 ext1Q def ext = unQ ((Q def) `ext1` (Q ext))
368
369
370 -- | Type extension of readers for type constructors
371 ext1R :: (Monad m, Data d, Typeable1 t)
372       => m d
373       -> (forall d. Data d => m (t d))
374       -> m d
375 ext1R def ext = unR ((R def) `ext1` (R ext))
376
377
378
379 ------------------------------------------------------------------------------
380 --
381 --      Type constructors for type-level lambdas
382 --
383 ------------------------------------------------------------------------------
384
385
386 -- | The type constructor for transformations
387 newtype T x = T { unT :: x -> x }
388
389 -- | The type constructor for transformations
390 newtype M m x = M { unM :: x -> m x }
391
392 -- | The type constructor for queries
393 newtype Q q x = Q { unQ :: x -> q }
394
395 -- | The type constructor for readers
396 newtype R m x = R { unR :: m x }