[project @ 2003-07-24 12:19:57 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/>.
13 --
14 -----------------------------------------------------------------------------
15
16 module Data.Generics.Aliases ( 
17
18         -- * Combinators to \"make\" generic functions via cast
19         mkT, mkQ, mkM, mkF, mkB,
20         extT, extQ, extM, extF, extB,
21
22         -- * Type synonyms for generic function types
23         GenericT, 
24         GenericQ,
25         GenericM,
26         GenericB,
27         Generic,
28         Generic'(..),
29
30         -- * Inredients of generic functions
31         orElse,
32
33         -- * Function combinators on generic functions
34         recoverF,
35         recoverQ,
36         choiceF,
37         choiceQ
38
39   ) where
40
41
42 import Control.Monad
43 import Data.Generics.Basics
44
45
46
47 ------------------------------------------------------------------------------
48 --
49 --      Combinators to "make" generic functions
50 --      We use type-safe cast in a number of ways to make generic functions.
51 --
52 ------------------------------------------------------------------------------
53
54 -- | Make a generic transformation;
55 --   start from a type-specific case;
56 --   preserve the term otherwise
57 --
58 mkT :: (Typeable a, Typeable b) => (b -> b) -> a -> a
59 mkT f = case cast f of
60                Just g -> g
61                Nothing -> id
62
63
64 -- | Make a generic query;
65 --   start from a type-specific case;
66 --   return a constant otherwise
67 --
68 mkQ :: (Typeable a, Typeable b) => r -> (b -> r) -> a -> r
69 (r `mkQ` br) a = case cast a of
70                         Just b  -> br b
71                         Nothing -> r
72
73
74 -- | Make a generic monadic transformation;
75 --   start from a type-specific case;
76 --   resort to return otherwise
77 --
78 mkM :: ( Monad m,
79          Typeable a, 
80          Typeable b,
81          Typeable (m a),
82          Typeable (m b)
83        )
84     => (b -> m b) -> a -> m a
85 mkM f = case cast f of
86               Just g  -> g
87               Nothing -> return
88
89
90 {-
91
92 For the remaining definitions, we stick to a more concise style, i.e.,
93 we fold maybies with "maybe" instead of case ... of ..., and we also
94 use a point-free style whenever possible.
95
96 -}
97
98
99 -- | Make a generic monadic transformation for MonadPlus;
100 --   use \"const mzero\" (i.e., failure) instead of return as default.
101 --
102 mkF :: ( MonadPlus m,
103          Typeable a,
104          Typeable b,
105          Typeable (m a),
106          Typeable (m b)
107        )
108     => (b -> m b) -> a -> m a
109 mkF = maybe (const mzero) id . cast
110
111
112 -- | Make a generic builder;
113 --   start from a type-specific ase;
114 --   resort to no build (i.e., mzero) otherwise
115 --
116 mkB :: ( MonadPlus m,
117          Typeable a,
118          Typeable b,
119          Typeable (m a),
120          Typeable (m b)
121        )
122     => m b -> m a
123 mkB = maybe mzero id . cast
124
125
126 -- | Extend a generic transformation by a type-specific case
127 extT :: (Typeable a, Typeable b) => (a -> a) -> (b -> b) -> a -> a
128 extT f = maybe f id . cast
129
130
131 -- | Extend a generic query by a type-specific case
132 extQ :: (Typeable a, Typeable b) => (a -> q) -> (b -> q) -> a -> q
133 extQ f g a = maybe (f a) g (cast a)
134
135
136 -- | Extend a generic monadic transformation by a type-specific case
137 extM :: (Typeable a, Typeable b,
138          Typeable (m a), Typeable (m b), 
139          Monad m)
140      => (a -> m a) -> (b -> m b) -> a -> m a
141 extM f = maybe f id . cast
142
143
144 -- | Extend a generic MonadPlus transformation by a type-specific case
145 extF :: ( MonadPlus m,
146           Typeable a,
147           Typeable b,
148           Typeable (m a),
149           Typeable (m b)
150         )
151      => (a -> m a) -> (b -> m b) -> a -> m a
152 extF = extM
153
154
155
156 -- | Extend a generic builder by a type-specific case
157 extB :: ( Monad m,
158           Typeable a,
159           Typeable b,
160           Typeable (m a),
161           Typeable (m b)
162         )
163      => m a -> m b -> m a
164 extB f = maybe f id . cast
165
166
167 ------------------------------------------------------------------------------
168 --
169 --      Type synonyms for generic function types
170 --
171 ------------------------------------------------------------------------------
172
173
174 -- | Generic transformations,
175 --   i.e., take an \"a\" and return an \"a\"
176 --
177 type GenericT = forall a. Data a => a -> a
178
179
180 -- | Generic queries of type \"r\",
181 --   i.e., take any \"a\" and return an \"r\"
182 --
183 type GenericQ r = forall a. Data a => a -> r
184
185
186 -- | Generic monadic transformations,
187 --   i.e., take an \"a\" and compute an \"a\"
188 --
189 type GenericM m = forall a. Data a => a -> m a
190
191
192 -- | Generic monadic builders with input i,
193 --   i.e., produce an \"a\" with the help of a monad \"m\".
194 --
195 type GenericB m = forall a. Data a => m a
196
197
198 -- | The general scheme underlying generic functions
199 --   assumed by gfoldl; there are isomorphisms such as
200 --   GenericT = Generic ID.
201 --
202 type Generic c = forall a. Data a => a -> c a
203
204
205 -- | Wrapped generic functions;
206 --   recall: [Generic c] would be legal but [Generic' c] not.
207 --
208 data Generic' c = Generic' { unGeneric' :: Generic c }
209
210
211
212 -- | Left-biased choice on maybies
213 orElse :: Maybe a -> Maybe a -> Maybe a
214 x `orElse` y = case x of
215                  Just _  -> x
216                  Nothing -> y
217
218
219 {-
220
221 The following variations take "orElse" to the function
222 level. Furthermore, we generalise from "Maybe" to any
223 "MonadPlus". This makes sense for monadic transformations and
224 queries. We say that the resulting combinators modell choice. We also
225 provide a prime example of choice, that is, recovery from failure. In
226 the case of transformations, we recover via return whereas for
227 queries a given constant is returned.
228
229 -}
230
231 -- | Choice for monadic transformations
232 choiceF :: MonadPlus m => GenericM m -> GenericM m -> GenericM m
233 choiceF f g x = f x `mplus` g x
234
235
236 -- | Choice for monadic queries
237 choiceQ :: MonadPlus m => GenericQ (m r) -> GenericQ (m r) -> GenericQ (m r)
238 choiceQ f g x = f x `mplus` g x
239
240
241 -- | Recover from the failure of monadic transformation by identity
242 recoverF :: MonadPlus m => GenericM m -> GenericM m
243 recoverF f = f `choiceF` return
244
245
246 -- | Recover from the failure of monadic query by a constant
247 recoverQ :: MonadPlus m => r -> GenericQ (m r) -> GenericQ (m r)
248 recoverQ r f = f `choiceQ` const (return r)