e0d6dad361e141659a82d470789cee49144a2594
[haskell-directory.git] / Data / Generics / Basics.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  Data.Generics.Basics
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.Basics ( 
17
18         -- Module Data.Typeable re-exported for convenience
19         module Data.Typeable,
20
21         -- * The Data class for processing constructor applications
22         Data( 
23                 gfoldl,         -- :: ... -> a -> c a
24                 toConstr,       -- :: a -> Constr
25                 fromConstr,     -- :: Constr -> a
26                 dataTypeOf      -- :: a -> DataType
27                 
28             ),
29
30         -- * Constructor representations
31         Constr,         -- abstract, instance of: Eq, Show
32         ConIndex,       -- alias for Int, start at 1
33         Fixity(..),     -- instance of: Eq, Show
34         DataType,       -- abstract, instance of: Show
35
36         -- * Constructing constructor representations
37         mkConstr,       -- :: ConIndex -> String -> Fixity -> Constr
38         mkDataType,     -- :: [Constr] -> DataType
39
40         -- * Observing constructor representations
41         conString,      -- :: Constr -> String
42         conFixity,      -- :: Constr -> Fixity
43         conIndex,       -- :: Constr -> ConIndex
44         stringCon,      -- :: DataType -> String -> Maybe Constr
45         indexCon,       -- :: DataType -> ConIndex -> Constr
46         maxConIndex,    -- :: DataType -> ConIndex
47         dataTypeCons,   -- :: DataType -> [Constr]
48
49         -- * Generic maps defined in terms of gfoldl 
50         gmapT,
51         gmapQ, 
52         gmapL,
53         gmapM,
54         gmapF,
55
56         -- * Generic unfolding defined in terms of gfoldl and fromConstr
57         gunfoldM        -- :: Monad m => ... -> m a
58
59   ) where
60
61
62 ------------------------------------------------------------------------------
63
64
65 import Data.Typeable
66 import Data.Maybe
67 import Control.Monad
68
69
70 ------------------------------------------------------------------------------
71 --
72 --      The Data class
73 --
74 ------------------------------------------------------------------------------
75
76 {- 
77
78 The Data class comprehends a fundamental primitive "gfoldl" for
79 folding over constructor applications, say terms. This primitive can
80 be instantiated in several ways to map over the immediate subterms of
81 a term; see the "gmap" combinators later in this module. Indeed, a
82 generic programmer does not necessarily need to use the ingenious
83 gfoldl primitive but rather the intuitive "gmap" combinators. The
84 "gfoldl" primitive is completed by means to query top-level
85 constructors, to turn constructor representations into proper terms,
86 and to list all possible datatype constructors. This completion
87 allows us to serve generic programming scenarios like read, show,
88 equality, term generation.
89
90 -}
91
92 class Typeable a => Data a where
93
94 {-
95
96 Folding constructor applications ("gfoldl")
97
98 The combinator takes two arguments "f" and "z" to fold over a term
99 "x".  The result type is defined in terms of "x" but variability is
100 achieved by means of type constructor "c" for the construction of the
101 actual result type. The purpose of the argument "z" is to define how
102 the empty constructor application is folded. So "z" is like the
103 neutral / start element for list folding. The purpose of the argument
104 "f" is to define how the nonempty constructor application is
105 folded. That is, "f" takes the folded "tail" of the constructor
106 application and its head, i.e., an immediate subterm, and combines
107 them in some way. See the Data instances in this file for an
108 illustration of "gfoldl". Conclusion: the type of gfoldl is a
109 headache, but operationally it is simple generalisation of a list
110 fold.
111
112 -}
113
114   -- | Left-associative fold operation for constructor applications
115   gfoldl  :: (forall a b. Data a => c (a -> b) -> a -> c b)
116           -> (forall g. g -> c g)
117           -> a -> c a
118
119   -- Default definition for gfoldl
120   -- which copes immediately with basic datatypes
121   --
122   gfoldl _ z = z
123
124
125   -- | Obtaining the constructor from a given datum.
126   -- For proper terms, this is meant to be the top-level constructor.
127   -- Primitive datatypes are here viewed as potentially infinite sets of
128   -- values (i.e., constructors).
129   --
130   toConstr   :: a -> Constr
131
132
133   -- | Building a term from a constructor
134   fromConstr   :: Constr -> a
135
136
137   -- | Provide access to list of all constructors
138   dataTypeOf  :: a -> DataType
139
140
141 ------------------------------------------------------------------------------
142 --
143 --      Typical generic maps defined in terms of gfoldl
144 --
145 ------------------------------------------------------------------------------
146
147 {-
148
149 The combinators gmapT, gmapQ, gmapL, gmapM, gmapF can all be defined
150 in terms of gfoldl. We provide corresponding default definitions
151 leaving open the opportunity to provide datatype-specific definitions.
152
153 (The inclusion of the gmap combinators as members of class Data allows
154 the programmer or the compiler to derive specialised, and maybe more
155 efficient code per datatype. Note: gfoldl is more higher-order than
156 the gmap combinators. This is subject to ongoing benchmarking
157 experiments. It might turn out that the gmap combinators will be moved
158 out of the class Data.)
159
160 Conceptually, the definition of the gmap combinators in terms of the
161 primitive gfoldl requires the identification of the gfoldl function
162 arguments. Technically, we also need to identify the type constructor
163 "c" for the construction of the result type from the folded term type.
164
165 -}
166
167
168   -- | A generic transformation that maps over the immediate subterms
169   gmapT :: (forall b. Data b => b -> b) -> a -> a
170
171   -- Use an identity datatype constructor ID (see below)
172   -- to instantiate the type constructor c in the type of gfoldl,
173   -- and perform injections ID and projections unID accordingly.
174   --
175   gmapT f x = unID (gfoldl k ID x)
176     where
177       k (ID c) x = ID (c (f x))
178
179
180   -- | A generic query with monoid-like operators
181   gmapQ :: (r -> r -> r) -> r -> (forall a. Data a => a -> r) -> a -> r
182   gmapQ o r f = unCONST . gfoldl k z
183     where
184       k c x = CONST $ (unCONST c) `o` f x 
185       z _   = CONST r
186
187
188   -- | A generic query that processes the immediate subterms and returns a list
189   gmapL   :: (forall a. Data a => a -> u) -> a -> [u]
190
191   -- Use a phantom + function datatype constructor QL (see below),
192   -- to instantiate the type constructor c in the type of gfoldl,
193   -- and perform injections QL and projections unQL accordingly.
194   --
195   gmapL f x = unQL (gfoldl k (const (QL id)) x) []
196     where
197       k (QL c) x = QL (\rs -> c (f x : rs))
198
199
200   -- | A generic monadic transformation that maps over the immediate subterms
201   gmapM   :: Monad m => (forall a. Data a => a -> m a) -> a -> m a
202
203   -- Use immediately the monad datatype constructor 
204   -- to instantiate the type constructor c in the type of gfoldl,
205   -- so injection and projection is done by return and >>=.
206   --  
207   gmapM f = gfoldl k return
208     where
209       k c x = do c' <- c
210                  x' <- f x
211                  return (c' x')
212
213
214   -- | Transformation of at least one immediate subterm does not fail
215   gmapF :: MonadPlus m => (forall a. Data a => a -> m a) -> a -> m a
216
217   -- Use a datatype constructor F (see below)
218   -- to instantiate the type constructor c in the type of gfoldl.
219   --  
220   gmapF f x = unFAIL (gfoldl k z x) >>= \(x',b) ->
221               if b then return x' else mzero
222     where
223       z g = FAIL (return (g,False))
224       k (FAIL c) x
225         = FAIL ( c >>= \(h,b) -> 
226                  (f x >>= \x' -> return (h x',True))
227                  `mplus` return (h x, b)
228                )
229
230
231 -- | The identity type constructor needed for the definition of gmapT
232 newtype ID x = ID { unID :: x }
233
234
235 -- | The constant type constructor needed for the definition of gmapQ
236 newtype CONST c a = CONST { unCONST :: c }
237
238
239 -- | A phantom datatype constructor used in definition of gmapL;
240 --   the function-typed component is needed to mediate between
241 --   left-associative constructor application vs. right-associative lists.
242 -- 
243 newtype QL r a = QL { unQL  :: [r] -> [r] }
244
245
246 -- | A pairing type constructor needed for the definition of gmapF;
247 -- we keep track of the fact if a subterm was ever transformed successfully.
248 newtype FAIL m x = FAIL { unFAIL :: m (x, Bool) }
249
250
251
252 ------------------------------------------------------------------------------
253 --
254 --      Constructor representations
255 --
256 ------------------------------------------------------------------------------
257
258
259 -- | Representation of constructors
260 data Constr =
261         -- The prime case for proper datatype constructors
262                DataConstr ConIndex String Fixity
263
264         -- Provision for built-in types
265             | IntConstr     Int
266             | IntegerConstr Integer
267             | FloatConstr   Float
268             | CharConstr    Char
269
270         -- Provision for any type that can be read/shown as string
271             | StringConstr  String
272
273         -- Provision for function types
274             | FunConstr
275
276               deriving (Show, Typeable)
277
278 -- 
279 -- Equality of datatype constructors via index.
280 -- Use designated equalities for primitive types.
281 -- 
282 instance Eq Constr where
283   (DataConstr i1 _ _) == (DataConstr i2 _ _) = i1 == i2
284   (IntConstr i1)      == (IntConstr i2)      = i1 == i2
285   (IntegerConstr i1)  == (IntegerConstr i2)  = i1 == i2
286   (FloatConstr i1)    == (FloatConstr i2)    = i1 == i2
287   (CharConstr i1)     == (CharConstr i2)     = i1 == i2
288   (StringConstr i1)   == (StringConstr i2)   = i1 == i2
289   _ == _ = False
290
291
292 -- | Unique index for datatype constructors.
293 --   Textual order is respected. Starts at 1.
294 --
295 type ConIndex = Int
296
297
298 -- | Fixity of constructors
299 data Fixity = Prefix
300             | Infix     -- Later: add associativity and precedence
301             deriving (Eq,Show)
302
303 -- | A package of constructor representations;
304 --   could be a list, an array, a balanced tree, or others.
305 --
306 data DataType =
307         -- The prime case for algebraic datatypes
308                DataType [Constr]
309
310         -- Provision for built-in types
311             | IntType
312             | IntegerType
313             | FloatType
314             | CharType
315
316         -- Provision for any type that can be read/shown as string
317             | StringType
318
319         -- Provision for function types
320             | FunType
321
322               deriving Show
323
324
325 ------------------------------------------------------------------------------
326 --
327 --      Constructing constructor representations
328 --
329 ------------------------------------------------------------------------------
330
331
332 -- | Make a representation for a datatype constructor
333 mkConstr   :: ConIndex -> String -> Fixity -> Constr
334 --      ToDo: consider adding arity?
335 mkConstr = DataConstr
336
337 -- | Make a package of constructor representations
338 mkDataType :: [Constr] -> DataType
339 mkDataType = DataType
340
341
342 ------------------------------------------------------------------------------
343 --
344 --      Observing constructor representations
345 --
346 ------------------------------------------------------------------------------
347
348
349 -- | Turn a constructor into a string
350 conString :: Constr -> String
351 conString (DataConstr _ str _) = str
352 conString (IntConstr int)      = show int
353 conString (IntegerConstr int)  = show int
354 conString (FloatConstr real)   = show real
355 conString (CharConstr char)    = show char
356 conString (StringConstr str)   = show str
357 conString FunConstr            = "->"
358
359
360 -- | Determine fixity of a constructor;
361 --   undefined for primitive types.
362 conFixity :: Constr -> Fixity
363 conFixity (DataConstr _ _ fix) = fix
364 conFixity _                    = undefined
365
366
367 -- | Determine index of a constructor.
368 --   Undefined for primitive types.
369 conIndex   :: Constr -> ConIndex
370 conIndex (DataConstr idx _ _) = idx
371 conIndex _                    = undefined
372
373
374 -- | Lookup a constructor via a string
375 stringCon :: DataType -> String -> Maybe Constr
376 stringCon (DataType cs) str = worker cs
377   where
378     worker (c:cs) =
379       case c of
380         (DataConstr _ str' _) -> if str == str'
381                                    then Just c
382                                    else worker cs
383         _ -> undefined -- other forms of Constr not valid here
384
385 stringCon IntType str       = Just . IntConstr     $ read str
386 stringCon IntegerType str   = Just . IntegerConstr $ read str
387 stringCon FloatType str     = Just . FloatConstr   $ read str
388 stringCon CharType str      = Just . CharConstr    $ read str
389 stringCon StringType str    = Just . StringConstr  $ read str
390 stringCon FunType str       = Just FunConstr
391
392
393 -- | Lookup a constructor by its index;
394 ---  not defined for primitive types.
395 indexCon :: DataType -> ConIndex -> Constr
396 indexCon (DataType cs) idx = cs !! (idx-1)
397 indexCon _ _ = undefined -- otherwise
398
399
400 -- | Return maximum index;
401 --   0 for primitive types
402 maxConIndex :: DataType -> ConIndex
403 maxConIndex (DataType cs) = length cs
404 maxConIndex _ = 0 -- otherwise
405
406
407 -- | Return all constructors in increasing order of indicies;
408 -- empty list for primitive types
409 dataTypeCons :: DataType -> [Constr] 
410 dataTypeCons (DataType cs) = cs
411 dataTypeCons _ = [] -- otherwise
412
413
414 ------------------------------------------------------------------------------
415 --
416 --      Instances of the Data class for Prelude types
417 --
418 ------------------------------------------------------------------------------
419
420 -- Basic datatype Int; folding and unfolding is trivial
421 instance Data Int where
422   toConstr x = IntConstr x
423   fromConstr (IntConstr x) = x
424   dataTypeOf _ = IntType
425
426 -- Another basic datatype instance
427 instance Data Integer where
428   toConstr x = IntegerConstr x
429   fromConstr (IntegerConstr x) = x
430   dataTypeOf _ = IntegerType
431
432 -- Another basic datatype instance
433 instance Data Float where
434   toConstr x = FloatConstr x
435   fromConstr (FloatConstr x) = x
436   dataTypeOf _ = FloatType
437
438 -- Another basic datatype instance
439 instance Data Char where
440   toConstr x = CharConstr x
441   fromConstr (CharConstr x) = x
442   dataTypeOf _ = CharType
443
444 -- A basic datatype without a specific branch in Constr
445 instance Data Rational where
446   toConstr x = StringConstr (show x)
447   fromConstr (StringConstr x) = read x
448   dataTypeOf _ = StringType
449
450 --
451 -- Bool as the most trivial algebraic datatype;
452 -- define top-level definitions for representations.
453 --
454
455 falseConstr  = mkConstr 1 "False" Prefix
456 trueConstr   = mkConstr 2 "True"  Prefix
457 boolDataType = mkDataType [falseConstr,trueConstr]
458
459 instance Data Bool where
460   toConstr False = falseConstr
461   toConstr True  = trueConstr
462   fromConstr c = case conIndex c of
463                    1 -> False
464                    2 -> True
465   dataTypeOf _ = boolDataType
466
467
468 --
469 -- Lists as an example of a polymorphic algebraic datatype.
470 -- Cons-lists are terms with two immediate subterms.
471 --
472
473 nilConstr    = mkConstr 1 "[]"  Prefix
474 consConstr   = mkConstr 2 "(:)" Infix
475 listDataType = mkDataType [nilConstr,consConstr]
476
477 instance Data a => Data [a] where
478   gfoldl f z []     = z []
479   gfoldl f z (x:xs) = z (:) `f` x `f` xs
480   toConstr []    = nilConstr
481   toConstr (_:_) = consConstr
482   fromConstr c = case conIndex c of
483                    1 -> []
484                    2 -> undefined:undefined
485   dataTypeOf _ = listDataType
486
487 --
488 -- The gmaps are given as an illustration.
489 -- This shows that the gmaps for lists are different from list maps.
490 --
491   gmapT  f   []     = []
492   gmapT  f   (x:xs) = (f x:f xs)
493   gmapL  f   []     = []
494   gmapL  f   (x:xs) = [f x,f xs]
495   gmapM  f   []     = return []
496   gmapM  f   (x:xs) = f x >>= \x' -> f xs >>= \xs' -> return (x':xs')
497
498
499 --
500 -- Yet another polymorphic datatype constructor
501 -- No surprises.
502 --
503
504 nothingConstr = mkConstr 1 "Nothing" Prefix
505 justConstr    = mkConstr 2 "Just"    Prefix
506 maybeDataType = mkDataType [nothingConstr,justConstr]
507
508 instance Data a => Data (Maybe a) where
509   gfoldl f z Nothing  = z Nothing
510   gfoldl f z (Just x) = z Just `f` x
511   toConstr Nothing  = nothingConstr
512   toConstr (Just _) = justConstr
513   fromConstr c = case conIndex c of
514                    1 -> Nothing
515                    2 -> Just undefined
516   dataTypeOf _ = maybeDataType
517
518 --
519 -- Yet another polymorphic datatype constructor.
520 -- No surprises.
521 --
522
523 pairConstr = mkConstr 1 "(,)" Infix
524 productDataType = mkDataType [pairConstr]
525
526 instance (Data a, Data b) => Data (a,b) where
527   gfoldl f z (a,b) = z (,) `f` a `f` b
528   toConstr _ = pairConstr
529   fromConstr c = case conIndex c of
530                    1 -> (undefined,undefined)
531   dataTypeOf _ = productDataType
532
533
534 {-
535
536 We should better not FOLD over characters in a string for efficiency.
537 However, the following instance would clearly overlap with the
538 instance for polymorphic lists. Given the current scheme of allowing
539 overlapping instances, this would imply that ANY module that imports
540 Data.Generics would need to explicitly and generally allow overlapping
541 instances. This is prohibitive and calls for a more constrained model
542 of allowing overlapping instances. The present instance would be
543 sensible even more for UNFOLDING. In the definition of "gread"
544 (generic read --- based on unfolding), we succeed handling strings in a
545 special way by using a type-specific case for String.
546
547 instance Data String where
548   toConstr x = StringConstr x
549   fromConstr (StringConstr x) = x
550   dataTypeOf _ = StringType
551
552 -}
553
554 -- A last resort for functions
555 instance (Typeable a, Typeable b) => Data (a -> b) where
556   toConstr _   = FunConstr
557   fromConstr _ = undefined
558   dataTypeOf _ = FunType
559
560
561 ------------------------------------------------------------------------------
562 --
563 --      Generic unfolding
564 --
565 ------------------------------------------------------------------------------
566
567 -- | Construct an initial with undefined immediate subterms
568 --   and then map over the skeleton to fill in proper terms.
569 --
570 gunfoldM :: (Monad m, Data a)
571          => Constr
572          -> (forall a. Data a => m a)
573          -> m a
574 gunfoldM c f = gmapM (const f) $ fromConstr c