[project @ 2003-07-28 15:03:05 by panne]
[haskell-directory.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, mkMp, mkB,
20         extT, extQ, extM, extMp, 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         recoverMp,
35         recoverQ,
36         choiceMp,
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        )
82     => (b -> m b) -> a -> m a
83 mkM f = case castarr f of
84               Just g  -> g
85               Nothing -> return
86
87
88 {-
89
90 For the remaining definitions, we stick to a more concise style, i.e.,
91 we fold maybies with "maybe" instead of case ... of ..., and we also
92 use a point-free style whenever possible.
93
94 -}
95
96
97 -- | Make a generic monadic transformation for MonadPlus;
98 --   use \"const mzero\" (i.e., failure) instead of return as default.
99 --
100 mkMp :: ( MonadPlus m,
101           Typeable a,
102           Typeable b
103         )
104      => (b -> m b) -> a -> m a
105 mkMp = maybe (const mzero) id . castarr
106
107
108 -- | Make a generic builder;
109 --   start from a type-specific ase;
110 --   resort to no build (i.e., mzero) otherwise
111 --
112 mkB :: ( MonadPlus m,
113          Typeable a,
114          Typeable b
115        )
116     => m b -> m a
117 mkB = maybe mzero id . castss
118
119
120 -- | Extend a generic transformation by a type-specific case
121 extT :: (Typeable a, Typeable b) => (a -> a) -> (b -> b) -> a -> a
122 extT f = maybe f id . cast
123
124
125 -- | Extend a generic query by a type-specific case
126 extQ :: (Typeable a, Typeable b) => (a -> q) -> (b -> q) -> a -> q
127 extQ f g a = maybe (f a) g (cast a)
128
129
130 -- | Extend a generic monadic transformation by a type-specific case
131 extM :: ( Monad m,
132           Typeable a,
133           Typeable b
134         )
135      => (a -> m a) -> (b -> m b) -> a -> m a
136 extM f = maybe f id . castarr
137
138
139 -- | Extend a generic MonadPlus transformation by a type-specific case
140 extMp :: ( MonadPlus m,
141            Typeable a,
142            Typeable b
143          )
144       => (a -> m a) -> (b -> m b) -> a -> m a
145 extMp = extM
146
147
148
149 -- | Extend a generic builder by a type-specific case
150 extB :: (Monad m,
151          Typeable a,
152          Typeable b
153         )
154      => m a -> m b -> m a
155 extB f = maybe f id . castss
156
157
158 ------------------------------------------------------------------------------
159 --
160 --      Type synonyms for generic function types
161 --
162 ------------------------------------------------------------------------------
163
164
165 -- | Generic transformations,
166 --   i.e., take an \"a\" and return an \"a\"
167 --
168 type GenericT = forall a. Data a => a -> a
169
170
171 -- | Generic queries of type \"r\",
172 --   i.e., take any \"a\" and return an \"r\"
173 --
174 type GenericQ r = forall a. Data a => a -> r
175
176
177 -- | Generic monadic transformations,
178 --   i.e., take an \"a\" and compute an \"a\"
179 --
180 type GenericM m = forall a. Data a => a -> m a
181
182
183 -- | Generic monadic builders with input i,
184 --   i.e., produce an \"a\" with the help of a monad \"m\".
185 --
186 type GenericB m = forall a. Data a => m a
187
188
189 -- | The general scheme underlying generic functions
190 --   assumed by gfoldl; there are isomorphisms such as
191 --   GenericT = Generic ID.
192 --
193 type Generic c = forall a. Data a => a -> c a
194
195
196 -- | Wrapped generic functions;
197 --   recall: [Generic c] would be legal but [Generic' c] not.
198 --
199 data Generic' c = Generic' { unGeneric' :: Generic c }
200
201
202
203 -- | Left-biased choice on maybies
204 orElse :: Maybe a -> Maybe a -> Maybe a
205 x `orElse` y = case x of
206                  Just _  -> x
207                  Nothing -> y
208
209
210 {-
211
212 The following variations take "orElse" to the function
213 level. Furthermore, we generalise from "Maybe" to any
214 "MonadPlus". This makes sense for monadic transformations and
215 queries. We say that the resulting combinators modell choice. We also
216 provide a prime example of choice, that is, recovery from failure. In
217 the case of transformations, we recover via return whereas for
218 queries a given constant is returned.
219
220 -}
221
222 -- | Choice for monadic transformations
223 choiceMp :: MonadPlus m => GenericM m -> GenericM m -> GenericM m
224 choiceMp f g x = f x `mplus` g x
225
226
227 -- | Choice for monadic queries
228 choiceQ :: MonadPlus m => GenericQ (m r) -> GenericQ (m r) -> GenericQ (m r)
229 choiceQ f g x = f x `mplus` g x
230
231
232 -- | Recover from the failure of monadic transformation by identity
233 recoverMp :: MonadPlus m => GenericM m -> GenericM m
234 recoverMp f = f `choiceMp` return
235
236
237 -- | Recover from the failure of monadic query by a constant
238 recoverQ :: MonadPlus m => r -> GenericQ (m r) -> GenericQ (m r)
239 recoverQ r f = f `choiceQ` const (return r)