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