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