7e7cf7c5e79323ce9a05e3227574cfba21ebd959
[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/>. The present module provides
13 -- the Data class with its primitives for generic programming.
14 --
15 -----------------------------------------------------------------------------
16
17 module Data.Generics.Basics ( 
18
19         -- Module Data.Typeable re-exported for convenience
20         module Data.Typeable,
21
22         -- * The Data class for processing constructor applications
23         Data( 
24                 gfoldl,         -- :: ... -> a -> c a
25                 toConstr,       -- :: a -> Constr
26                 fromConstr,     -- :: Constr -> a
27                 dataTypeOf      -- :: a -> DataType
28                 
29             ),
30
31         -- * Constructor representations
32         Constr,         -- abstract, instance of: Eq, Show
33         ConIndex,       -- alias for Int, start at 1
34         Fixity(..),     -- instance of: Eq, Show
35         DataType,       -- abstract, instance of: Show
36
37         -- * Constructing constructor representations
38         mkConstr,       -- :: ConIndex -> String -> Fixity -> Constr
39         mkDataType,     -- :: [Constr] -> DataType
40
41         -- * Observing constructor representations
42         conString,      -- :: Constr -> String
43         conFixity,      -- :: Constr -> Fixity
44         conIndex,       -- :: Constr -> ConIndex
45         stringCon,      -- :: DataType -> String -> Maybe Constr
46         indexCon,       -- :: DataType -> ConIndex -> Constr
47         maxConIndex,    -- :: DataType -> ConIndex
48         dataTypeCons,   -- :: DataType -> [Constr]
49
50         -- * Generic maps defined in terms of gfoldl 
51         gmapT,
52         gmapQ, 
53         gmapQl,
54         gmapQr,
55         gmapM,
56         gmapMp,
57         gmapMo,
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, gmapM, ... can all be defined in terms
150 of gfoldl. We provide corresponding default definitions leaving open
151 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 a left-associative binary operator
181   gmapQl :: (r -> r' -> r) -> r -> (forall a. Data a => a -> r') -> a -> r
182   gmapQl 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
189 In the definition of gmapQ? combinators, we use phantom type
190 constructors for the "c" in the type of "gfoldl" because the result
191 type of a query does not involve the (polymorphic) type of the term
192 argument. In the definition of gmapQl we simply use the plain constant
193 type constructor because gfoldl is left-associative anyway and so it
194 is readily suited to fold a left-associative binary operation over the
195 immediate subterms. In the definition of gmapQr, extra effort is
196 needed. We use a higher-order accumulation trick to mediate between
197 left-associative constructor application vs. right-associative binary
198 operation (e.g., (:)). When the query is meant to compute a value of
199 type r, then the result type withing generic folding is r -> r. So the
200 result of folding is a function to which we finally pass the right
201 unit.
202
203 -}
204
205   -- | A generic query with a right-associative binary operator
206   gmapQr :: (r' -> r -> r) -> r -> (forall a. Data a => a -> r') -> a -> r
207   gmapQr o r f x = unQr (gfoldl k (const (Qr id)) x) r
208     where
209       k (Qr c) x = Qr (\r -> c (f x `o` r))
210
211   -- | A generic query that processes the immediate subterms and returns a list
212   gmapQ :: (forall a. Data a => a -> u) -> a -> [u]
213   gmapQ f = gmapQr (:) [] f
214
215
216   -- | A generic monadic transformation that maps over the immediate subterms
217   gmapM   :: Monad m => (forall a. Data a => a -> m a) -> a -> m a
218
219   -- Use immediately the monad datatype constructor 
220   -- to instantiate the type constructor c in the type of gfoldl,
221   -- so injection and projection is done by return and >>=.
222   --  
223   gmapM f = gfoldl k return
224     where
225       k c x = do c' <- c
226                  x' <- f x
227                  return (c' x')
228
229
230   -- | Transformation of at least one immediate subterm does not fail
231   gmapMp :: MonadPlus m => (forall a. Data a => a -> m a) -> a -> m a
232
233 {-
234
235 The type constructor that we use here simply keeps track of the fact
236 if we already succeeded for an immediate subterm; see Mp below. To
237 this end, we couple the monadic computation with a Boolean.
238
239 -}
240
241   gmapMp f x = unMp (gfoldl k z x) >>= \(x',b) ->
242                 if b then return x' else mzero
243     where
244       z g = Mp (return (g,False))
245       k (Mp c) x
246         = Mp ( c >>= \(h,b) -> 
247                  (f x >>= \x' -> return (h x',True))
248                  `mplus` return (h x,b)
249              )
250
251   -- | Transformation of one immediate subterm with success
252   gmapMo :: MonadPlus m => (forall a. Data a => a -> m a) -> a -> m a
253
254 {-
255
256 We use the same pairing trick as for gmapMp, 
257 i.e., we use an extra Bool component to keep track of the 
258 fact whether an immediate subterm was processed successfully.
259 However, we cut of mapping over subterms once a first subterm
260 was transformed successfully.
261
262 -}
263
264   gmapMo f x = unMp (gfoldl k z x) >>= \(x',b) ->
265                 if b then return x' else mzero
266     where
267       z g = Mp (return (g,False))
268       k (Mp c) x
269         = Mp ( c >>= \(h,b) -> if b 
270                         then return (h x,b)
271                         else (f x >>= \x' -> return (h x',True))
272                              `mplus` return (h x,b)
273              )
274
275
276 -- | The identity type constructor needed for the definition of gmapT
277 newtype ID x = ID { unID :: x }
278
279
280 -- | The constant type constructor needed for the definition of gmapQl
281 newtype CONST c a = CONST { unCONST :: c }
282
283
284 -- | The type constructor used in definition of gmapQr
285 newtype Qr r a = Qr { unQr  :: r -> r }
286
287
288 -- | The type constructor used in definition of gmapMp
289 newtype Mp m x = Mp { unMp :: m (x, Bool) }
290
291
292
293 ------------------------------------------------------------------------------
294 --
295 --      Constructor representations
296 --
297 ------------------------------------------------------------------------------
298
299
300 -- | Representation of constructors
301 data Constr =
302         -- The prime case for proper datatype constructors
303                DataConstr ConIndex String Fixity
304
305         -- Provision for built-in types
306             | IntConstr     Int
307             | IntegerConstr Integer
308             | FloatConstr   Float
309             | CharConstr    Char
310
311         -- Provision for any type that can be read/shown as string
312             | StringConstr  String
313
314         -- Provision for function types
315             | FunConstr
316
317               deriving (Show, Typeable)
318
319 -- 
320 -- Equality of datatype constructors via index.
321 -- Use designated equalities for primitive types.
322 -- 
323 instance Eq Constr where
324   (DataConstr i1 _ _) == (DataConstr i2 _ _) = i1 == i2
325   (IntConstr i1)      == (IntConstr i2)      = i1 == i2
326   (IntegerConstr i1)  == (IntegerConstr i2)  = i1 == i2
327   (FloatConstr i1)    == (FloatConstr i2)    = i1 == i2
328   (CharConstr i1)     == (CharConstr i2)     = i1 == i2
329   (StringConstr i1)   == (StringConstr i2)   = i1 == i2
330   _ == _ = False
331
332
333 -- | Unique index for datatype constructors.
334 --   Textual order is respected. Starts at 1.
335 --
336 type ConIndex = Int
337
338
339 -- | Fixity of constructors
340 data Fixity = Prefix
341             | Infix     -- Later: add associativity and precedence
342             deriving (Eq,Show)
343
344 -- | A package of constructor representations;
345 --   could be a list, an array, a balanced tree, or others.
346 --
347 data DataType =
348         -- The prime case for algebraic datatypes
349                DataType [Constr]
350
351         -- Provision for built-in types
352             | IntType
353             | IntegerType
354             | FloatType
355             | CharType
356
357         -- Provision for any type that can be read/shown as string
358             | StringType
359
360         -- Provision for function types
361             | FunType
362
363               deriving Show
364
365
366 ------------------------------------------------------------------------------
367 --
368 --      Constructing constructor representations
369 --
370 ------------------------------------------------------------------------------
371
372
373 -- | Make a representation for a datatype constructor
374 mkConstr   :: ConIndex -> String -> Fixity -> Constr
375 --      ToDo: consider adding arity?
376 mkConstr = DataConstr
377
378 -- | Make a package of constructor representations
379 mkDataType :: [Constr] -> DataType
380 mkDataType = DataType
381
382
383 ------------------------------------------------------------------------------
384 --
385 --      Observing constructor representations
386 --
387 ------------------------------------------------------------------------------
388
389
390 -- | Turn a constructor into a string
391 conString :: Constr -> String
392 conString (DataConstr _ str _) = str
393 conString (IntConstr int)      = show int
394 conString (IntegerConstr int)  = show int
395 conString (FloatConstr real)   = show real
396 conString (CharConstr char)    = show char
397 conString (StringConstr str)   = show str
398 conString FunConstr            = "->"
399
400
401 -- | Determine fixity of a constructor;
402 --   undefined for primitive types.
403 conFixity :: Constr -> Fixity
404 conFixity (DataConstr _ _ fix) = fix
405 conFixity _                    = undefined
406
407
408 -- | Determine index of a constructor.
409 --   Undefined for primitive types.
410 conIndex   :: Constr -> ConIndex
411 conIndex (DataConstr idx _ _) = idx
412 conIndex _                    = undefined
413
414
415 -- | Lookup a constructor via a string
416 stringCon :: DataType -> String -> Maybe Constr
417 stringCon (DataType cs) str = worker cs
418   where
419     worker []     = Nothing
420     worker (c:cs) =
421       case c of
422         (DataConstr _ str' _) -> if str == str'
423                                    then Just c
424                                    else worker cs
425         _ -> undefined -- other forms of Constr not valid here
426
427 stringCon IntType str       = Just . IntConstr     $ read str
428 stringCon IntegerType str   = Just . IntegerConstr $ read str
429 stringCon FloatType str     = Just . FloatConstr   $ read str
430 stringCon CharType str      = Just . CharConstr    $ read str
431 stringCon StringType str    = Just . StringConstr  $ read str
432 stringCon FunType str       = Just FunConstr
433
434
435 -- | Lookup a constructor by its index;
436 ---  not defined for primitive types.
437 indexCon :: DataType -> ConIndex -> Constr
438 indexCon (DataType cs) idx = cs !! (idx-1)
439 indexCon _ _ = undefined -- otherwise
440
441
442 -- | Return maximum index;
443 --   0 for primitive types
444 maxConIndex :: DataType -> ConIndex
445 maxConIndex (DataType cs) = length cs
446 maxConIndex _ = 0 -- otherwise
447
448
449 -- | Return all constructors in increasing order of indicies;
450 -- empty list for primitive types
451 dataTypeCons :: DataType -> [Constr] 
452 dataTypeCons (DataType cs) = cs
453 dataTypeCons _ = [] -- otherwise
454
455
456 ------------------------------------------------------------------------------
457 --
458 --      Instances of the Data class for Prelude types
459 --
460 ------------------------------------------------------------------------------
461
462 -- Basic datatype Int; folding and unfolding is trivial
463 instance Data Int where
464   toConstr x = IntConstr x
465   fromConstr (IntConstr x) = x
466   dataTypeOf _ = IntType
467
468 -- Another basic datatype instance
469 instance Data Integer where
470   toConstr x = IntegerConstr x
471   fromConstr (IntegerConstr x) = x
472   dataTypeOf _ = IntegerType
473
474 -- Another basic datatype instance
475 instance Data Float where
476   toConstr x = FloatConstr x
477   fromConstr (FloatConstr x) = x
478   dataTypeOf _ = FloatType
479
480 -- Another basic datatype instance
481 instance Data Char where
482   toConstr x = CharConstr x
483   fromConstr (CharConstr x) = x
484   dataTypeOf _ = CharType
485
486 -- A basic datatype without a specific branch in Constr
487 instance Data Rational where
488   toConstr x = StringConstr (show x)
489   fromConstr (StringConstr x) = read x
490   dataTypeOf _ = StringType
491
492 --
493 -- Bool as the most trivial algebraic datatype;
494 -- define top-level definitions for representations.
495 --
496
497 falseConstr  = mkConstr 1 "False" Prefix
498 trueConstr   = mkConstr 2 "True"  Prefix
499 boolDataType = mkDataType [falseConstr,trueConstr]
500
501 instance Data Bool where
502   toConstr False = falseConstr
503   toConstr True  = trueConstr
504   fromConstr c = case conIndex c of
505                    1 -> False
506                    2 -> True
507   dataTypeOf _ = boolDataType
508
509
510 --
511 -- Lists as an example of a polymorphic algebraic datatype.
512 -- Cons-lists are terms with two immediate subterms.
513 --
514
515 nilConstr    = mkConstr 1 "[]"  Prefix
516 consConstr   = mkConstr 2 "(:)" Infix
517 listDataType = mkDataType [nilConstr,consConstr]
518
519 instance Data a => Data [a] where
520   gfoldl f z []     = z []
521   gfoldl f z (x:xs) = z (:) `f` x `f` xs
522   toConstr []    = nilConstr
523   toConstr (_:_) = consConstr
524   fromConstr c = case conIndex c of
525                    1 -> []
526                    2 -> undefined:undefined
527   dataTypeOf _ = listDataType
528
529 --
530 -- The gmaps are given as an illustration.
531 -- This shows that the gmaps for lists are different from list maps.
532 --
533   gmapT  f   []     = []
534   gmapT  f   (x:xs) = (f x:f xs)
535   gmapQ  f   []     = []
536   gmapQ  f   (x:xs) = [f x,f xs]
537   gmapM  f   []     = return []
538   gmapM  f   (x:xs) = f x >>= \x' -> f xs >>= \xs' -> return (x':xs')
539
540
541 --
542 -- Yet another polymorphic datatype constructor
543 -- No surprises.
544 --
545
546 nothingConstr = mkConstr 1 "Nothing" Prefix
547 justConstr    = mkConstr 2 "Just"    Prefix
548 maybeDataType = mkDataType [nothingConstr,justConstr]
549
550 instance Data a => Data (Maybe a) where
551   gfoldl f z Nothing  = z Nothing
552   gfoldl f z (Just x) = z Just `f` x
553   toConstr Nothing  = nothingConstr
554   toConstr (Just _) = justConstr
555   fromConstr c = case conIndex c of
556                    1 -> Nothing
557                    2 -> Just undefined
558   dataTypeOf _ = maybeDataType
559
560
561 --
562 -- Yet another polymorphic datatype constructor.
563 -- No surprises.
564 --
565
566 pairConstr = mkConstr 1 "(,)" Infix
567 productDataType = mkDataType [pairConstr]
568
569 instance (Data a, Data b) => Data (a,b) where
570   gfoldl f z (a,b) = z (,) `f` a `f` b
571   toConstr _ = pairConstr
572   fromConstr c = case conIndex c of
573                    1 -> (undefined,undefined)
574   dataTypeOf _ = productDataType
575
576
577 --
578 -- Yet another polymorphic datatype constructor.
579 -- No surprises.
580 --
581  
582 tripleConstr = mkConstr 1 "(,,)" Infix
583 tripleDataType = mkDataType [tripleConstr]
584
585 instance (Data a, Data b, Data c) => Data (a,b,c) where
586   gfoldl f z (a,b,c) = z (,,) `f` a `f` b `f` c
587   toConstr _ = tripleConstr
588   fromConstr c = case conIndex c of
589                    1 -> (undefined,undefined,undefined)
590   dataTypeOf _ = tripleDataType
591  
592 quadrupleConstr = mkConstr 1 "(,,,)" Infix
593 quadrupleDataType = mkDataType [quadrupleConstr]
594  
595 instance (Data a, Data b, Data c, Data d) => Data (a,b,c,d) where
596   gfoldl f z (a,b,c,d) = z (,,,) `f` a `f` b `f` c `f` d
597   toConstr _ = quadrupleConstr
598   fromConstr c = case conIndex c of
599                    1 -> (undefined,undefined,undefined,undefined)
600   dataTypeOf _ = quadrupleDataType
601
602
603 --
604 -- Yet another polymorphic datatype constructor.
605 -- No surprises.
606 --
607
608 leftConstr     = mkConstr 1 "Left"  Prefix
609 rightConstr    = mkConstr 2 "Right" Prefix
610 eitherDataType = mkDataType [leftConstr,rightConstr]
611
612 instance (Data a, Data b) => Data (Either a b) where
613   gfoldl f z (Left a)   = z Left  `f` a
614   gfoldl f z (Right a)  = z Right `f` a
615   toConstr (Left _)  = leftConstr
616   toConstr (Right _) = rightConstr
617   fromConstr c = case conIndex c of
618                    1 -> Left undefined
619                    2 -> Right undefined
620   dataTypeOf _ = eitherDataType
621
622
623 {-
624
625 We should better not FOLD over characters in a string for efficiency.
626 However, the following instance would clearly overlap with the
627 instance for polymorphic lists. Given the current scheme of allowing
628 overlapping instances, this would imply that ANY module that imports
629 Data.Generics would need to explicitly and generally allow overlapping
630 instances. This is prohibitive and calls for a more constrained model
631 of allowing overlapping instances. The present instance would be
632 sensible even more for UNFOLDING. In the definition of "gread"
633 (generic read --- based on unfolding), we succeed handling strings in a
634 special way by using a type-specific case for String.
635
636 instance Data String where
637   toConstr x = StringConstr x
638   fromConstr (StringConstr x) = x
639   dataTypeOf _ = StringType
640
641 -}
642
643 -- A last resort for functions
644 instance (Typeable a, Typeable b) => Data (a -> b) where
645   toConstr _   = FunConstr
646   fromConstr _ = undefined
647   dataTypeOf _ = FunType