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