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