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