[project @ 2004-02-14 18:18:46 by ralf]
[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         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   ) where
50
51 #ifdef __HADDOCK__
52 import Prelude
53 #endif
54 import Control.Monad
55 import Data.Generics.Basics
56
57 ------------------------------------------------------------------------------
58 --
59 --      Combinators to "make" generic functions
60 --      We use type-safe cast in a number of ways to make generic functions.
61 --
62 ------------------------------------------------------------------------------
63
64 -- | Make a generic transformation;
65 --   start from a type-specific case;
66 --   preserve the term otherwise
67 --
68 mkT :: ( Typeable a
69        , Typeable b
70        )
71     => (b -> b)
72     -> a 
73     -> a
74 mkT f = case cast f of
75                Just g -> g
76                Nothing -> 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 f = case castarr f of
107               Just g  -> g
108               Nothing -> return
109
110
111 {-
112
113 For the remaining definitions, we stick to a more concise style, i.e.,
114 we fold maybies with "maybe" instead of case ... of ..., and we also
115 use a point-free style whenever possible.
116
117 -}
118
119
120 -- | Make a generic monadic transformation for MonadPlus;
121 --   use \"const mzero\" (i.e., failure) instead of return as default.
122 --
123 mkMp :: ( MonadPlus m
124         , Typeable a
125         , Typeable b
126         )
127      => (b -> m b)
128      -> a
129      -> m a
130 mkMp = maybe (const mzero) id . castarr
131
132
133 -- | Make a generic builder;
134 --   start from a type-specific ase;
135 --   resort to no build (i.e., mzero) otherwise
136 --
137 mkR :: ( MonadPlus m
138        , Typeable a
139        , Typeable b
140        )
141     => m b -> m a
142 mkR = maybe mzero id . castss
143
144
145 -- | Extend a generic transformation by a type-specific case
146 extT :: ( Typeable a
147         , Typeable b 
148         )
149      => (a -> a)
150      -> (b -> b)
151      -> a
152      -> a
153 extT f = maybe f id . cast
154
155
156 -- | Extend a generic query by a type-specific case
157 extQ :: ( Typeable a
158         , Typeable b
159         )
160      => (a -> q)
161      -> (b -> q)
162      -> a
163      -> q
164 extQ f g a = maybe (f a) g (cast a)
165
166
167 -- | Extend a generic monadic transformation by a type-specific case
168 extM :: ( Monad m
169         , Typeable a
170         , Typeable b
171         )
172      => (a -> m a) -> (b -> m b) -> a -> m a
173 extM f = maybe f id . castarr
174
175
176 -- | Extend a generic MonadPlus transformation by a type-specific case
177 extMp :: ( MonadPlus m
178          , Typeable a
179          , Typeable b
180          )
181       => (a -> m a) -> (b -> m b) -> a -> m a
182 extMp = extM
183
184
185 -- | Extend a generic builder
186 extB :: ( Typeable a
187         , Typeable b
188         )
189      => a -> b -> a
190 extB a = maybe a id . cast
191
192
193 -- | Extend a generic reader
194 extR :: ( Monad m
195         , Typeable a
196         , Typeable b
197         )
198      => m a -> m b -> m a
199 extR f = maybe f id . castss
200
201
202 ------------------------------------------------------------------------------
203 --
204 --      Type synonyms for generic function types
205 --
206 ------------------------------------------------------------------------------
207
208
209 -- | Generic transformations,
210 --   i.e., take an \"a\" and return an \"a\"
211 --
212 type GenericT = forall a. Data a => a -> a
213
214
215 -- | Generic queries of type \"r\",
216 --   i.e., take any \"a\" and return an \"r\"
217 --
218 type GenericQ r = forall a. Data a => a -> r
219
220
221 -- | Generic monadic transformations,
222 --   i.e., take an \"a\" and compute an \"a\"
223 --
224 type GenericM m = forall a. Data a => a -> m a
225
226
227 -- | Generic builders
228 --   i.e., produce an \"a\".
229 --
230 type GenericB = forall a. Data a => a
231
232
233 -- | Generic readers, say monadic builders,
234 --   i.e., produce an \"a\" with the help of a monad \"m\".
235 --
236 type GenericR m = forall a. Data a => m a
237
238
239 -- | The general scheme underlying generic functions
240 --   assumed by gfoldl; there are isomorphisms such as
241 --   GenericT = Generic ID.
242 --
243 type Generic c = forall a. Data a => a -> c a
244
245
246 -- | Wrapped generic functions;
247 --   recall: [Generic c] would be legal but [Generic' c] not.
248 --
249 data Generic' c = Generic' { unGeneric' :: Generic c }
250
251
252 -- | Other first-class polymorphic wrappers
253 newtype GenericT'   = GenericT' { unGenericT' :: Data a => a -> a }
254 newtype GenericQ' r = GenericQ' { unGenericQ' :: GenericQ r }
255 newtype GenericM' m = GenericM' { unGenericM' :: Data a => a -> m a }
256
257
258 -- | Left-biased choice on maybies
259 orElse :: Maybe a -> Maybe a -> Maybe a
260 x `orElse` y = case x of
261                  Just _  -> x
262                  Nothing -> y
263
264
265 {-
266
267 The following variations take "orElse" to the function
268 level. Furthermore, we generalise from "Maybe" to any
269 "MonadPlus". This makes sense for monadic transformations and
270 queries. We say that the resulting combinators modell choice. We also
271 provide a prime example of choice, that is, recovery from failure. In
272 the case of transformations, we recover via return whereas for
273 queries a given constant is returned.
274
275 -}
276
277 -- | Choice for monadic transformations
278 choiceMp :: MonadPlus m => GenericM m -> GenericM m -> GenericM m
279 choiceMp f g x = f x `mplus` g x
280
281
282 -- | Choice for monadic queries
283 choiceQ :: MonadPlus m => GenericQ (m r) -> GenericQ (m r) -> GenericQ (m r)
284 choiceQ f g x = f x `mplus` g x
285
286
287 -- | Recover from the failure of monadic transformation by identity
288 recoverMp :: MonadPlus m => GenericM m -> GenericM m
289 recoverMp f = f `choiceMp` return
290
291
292 -- | Recover from the failure of monadic query by a constant
293 recoverQ :: MonadPlus m => r -> GenericQ (m r) -> GenericQ (m r)
294 recoverQ r f = f `choiceQ` const (return r)
295
296
297
298 ------------------------------------------------------------------------------
299 --
300 --      Generic unfolding
301 --
302 ------------------------------------------------------------------------------
303
304 -- | Construct an initial term with undefined immediate subterms
305 --   and then map over the skeleton to fill in proper terms.
306 gunfoldB :: Data a
307          => Constr
308          -> (forall a. Data a => a)
309          -> a
310 gunfoldB c f = gmapT (const f) (fromConstr c)
311
312
313 -- | Monadic variation on \"gunfoldB\"
314 gunfoldR :: (Monad m, Data a)
315          => Constr
316          -> (forall a. Data a => m a)
317          -> m a
318 gunfoldR c f = gmapM (const f) $ fromConstr c