[project @ 2004-03-17 23:22:51 by ralf]
[ghc-base.git] / Data / Typeable.hs
1 {-# OPTIONS -fno-implicit-prelude #-}
2 -----------------------------------------------------------------------------
3 -- |
4 -- Module      :  Data.Typeable
5 -- Copyright   :  (c) The University of Glasgow, CWI 2001--2004
6 -- License     :  BSD-style (see the file libraries/base/LICENSE)
7 -- 
8 -- Maintainer  :  libraries@haskell.org
9 -- Stability   :  experimental
10 -- Portability :  portable
11 --
12 -- The Typeable class reifies types to some extent by associating type
13 -- representations to types. These type representations can be compared,
14 -- and one can in turn define a type-safe cast operation. To this end,
15 -- an unsafe cast is guarded by a test for type (representation)
16 -- equivalence. The module Data.Dynamic uses Typeable for an
17 -- implementation of dynamics. The module Data.Generics uses Typeable
18 -- and type-safe cast (but not dynamics) to support the \"Scrap your
19 -- boilerplate\" style of generic programming.
20 --
21 -----------------------------------------------------------------------------
22
23 module Data.Typeable
24   (
25
26         -- * The Typeable class
27         Typeable( typeOf ),     -- :: a -> TypeRep
28
29         -- * Type-safe cast
30         cast,                   -- :: (Typeable a, Typeable b) => a -> Maybe b
31         gcast,                  -- a generalisation of cast
32
33         -- * Type representations
34         TypeRep,        -- abstract, instance of: Eq, Show, Typeable
35         TyCon,          -- abstract, instance of: Eq, Show, Typeable
36
37         -- * Construction of type representations
38         mkTyCon,        -- :: String  -> TyCon
39         mkAppTy,        -- :: TyCon   -> [TypeRep] -> TypeRep
40         mkFunTy,        -- :: TypeRep -> TypeRep   -> TypeRep
41         applyTy,        -- :: TypeRep -> TypeRep   -> Maybe TypeRep
42         popStarTy,      -- :: TypeRep -> TypeRep   -> TypeRep
43
44         -- * Observation of type representations
45         typerepTyCon,   -- :: TypeRep -> TyCon
46         typerepArgs,    -- :: TypeRep -> [TypeRep]
47         tyconString,    -- :: TyCon   -> String
48
49         -- * The other Typeable classes
50         Typeable1( typeOf1 ),   -- :: t a -> TypeRep
51         Typeable2( typeOf2 ),   -- :: t a b -> TypeRep
52         Typeable3( typeOf3 ),   -- :: t a b c -> TypeRep
53         Typeable4( typeOf4 ),   -- :: t a b c d -> TypeRep
54         Typeable5( typeOf5 ),   -- :: t a b c d e -> TypeRep
55         Typeable6( typeOf6 ),   -- :: t a b c d e f -> TypeRep
56         Typeable7( typeOf7 ),   -- :: t a b c d e f g -> TypeRep
57         gcast1,                 -- :: ... => c (t a) -> Maybe (c (t' a))
58         gcast2                  -- :: ... => c (t a b) -> Maybe (c (t' a b))
59
60   ) where
61
62
63 import qualified Data.HashTable as HT
64 import Data.Maybe
65 import Data.Either
66 import Data.Int
67 import Data.Word
68 import Data.List( foldl )
69
70 #ifdef __GLASGOW_HASKELL__
71 import GHC.Base
72 import GHC.Show
73 import GHC.Err
74 import GHC.Num
75 import GHC.Float
76 import GHC.Real( rem, Ratio )
77 import GHC.IOBase
78 import GHC.Ptr          -- So we can give Typeable instance for Ptr
79 import GHC.Stable       -- So we can give Typeable instance for StablePtr
80 #endif
81
82 #ifdef __HUGS__
83 import Hugs.Prelude
84 import Hugs.IO
85 import Hugs.IORef
86 import Hugs.IOExts
87 #endif
88
89 #ifdef __GLASGOW_HASKELL__
90 unsafeCoerce :: a -> b
91 unsafeCoerce = unsafeCoerce#
92 #endif
93
94 #ifdef __NHC__
95 import NonStdUnsafeCoerce (unsafeCoerce)
96 import NHC.IOExtras (IORef,newIORef,readIORef,writeIORef,unsafePerformIO)
97 #else
98 #include "Typeable.h"
99 #endif
100
101
102 #ifndef __HUGS__
103
104 -------------------------------------------------------------
105 --
106 --              Type representations
107 --
108 -------------------------------------------------------------
109
110
111 -- | A concrete representation of a (monomorphic) type.  'TypeRep'
112 -- supports reasonably efficient equality.
113 data TypeRep = TypeRep !Key TyCon [TypeRep] 
114
115 -- Compare keys for equality
116 instance Eq TypeRep where
117   (TypeRep k1 _ _) == (TypeRep k2 _ _) = k1 == k2
118
119 -- | An abstract representation of a type constructor.  'TyCon' objects can
120 -- be built using 'mkTyCon'.
121 data TyCon = TyCon !Key String
122
123 instance Eq TyCon where
124   (TyCon t1 _) == (TyCon t2 _) = t1 == t2
125
126 #endif
127
128         -- 
129         -- let fTy = mkTyCon "Foo" in show (mkAppTy (mkTyCon ",,")
130         --                                 [fTy,fTy,fTy])
131         -- 
132         -- returns "(Foo,Foo,Foo)"
133         --
134         -- The TypeRep Show instance promises to print tuple types
135         -- correctly. Tuple type constructors are specified by a 
136         -- sequence of commas, e.g., (mkTyCon ",,,,") returns
137         -- the 5-tuple tycon.
138
139
140 ----------------- Construction --------------------
141
142 -- | Applies a type constructor to a sequence of types
143 mkAppTy  :: TyCon -> [TypeRep] -> TypeRep
144 mkAppTy tc@(TyCon tc_k _) args 
145   = TypeRep (appKeys tc_k arg_ks) tc args
146   where
147     arg_ks = [k | TypeRep k _ _ <- args]
148
149
150 -- The function type constructor
151 funTc :: TyCon
152 funTc = mkTyCon "->"
153
154
155 -- | A special case of 'mkAppTy', which applies the function 
156 -- type constructor to a pair of types.
157 mkFunTy  :: TypeRep -> TypeRep -> TypeRep
158 mkFunTy f a = mkAppTy funTc [f,a]
159
160
161 -- | Applies a type to a function type.  Returns: @'Just' u@ if the
162 -- first argument represents a function of type @t -> u@ and the
163 -- second argument represents a function of type @t@.  Otherwise,
164 -- returns 'Nothing'.
165 applyTy :: TypeRep -> TypeRep -> Maybe TypeRep
166 applyTy (TypeRep _ tc [t1,t2]) t3
167   | tc == funTc && t1 == t3     = Just t2
168 applyTy _ _                     = Nothing
169
170
171 -- | Adds a TypeRep argument to a TypeRep.
172 popStarTy :: TypeRep -> TypeRep -> TypeRep
173 popStarTy (TypeRep tr_k tc trs) arg_tr
174   = let (TypeRep arg_k _ _) = arg_tr
175      in  TypeRep (appKey tr_k arg_k) tc (trs++[arg_tr])
176
177
178 -- If we enforce the restriction that there is only one
179 -- @TyCon@ for a type & it is shared among all its uses,
180 -- we can map them onto Ints very simply. The benefit is,
181 -- of course, that @TyCon@s can then be compared efficiently.
182
183 -- Provided the implementor of other @Typeable@ instances
184 -- takes care of making all the @TyCon@s CAFs (toplevel constants),
185 -- this will work. 
186
187 -- If this constraint does turn out to be a sore thumb, changing
188 -- the Eq instance for TyCons is trivial.
189
190 -- | Builds a 'TyCon' object representing a type constructor.  An
191 -- implementation of "Data.Typeable" should ensure that the following holds:
192 --
193 -- >  mkTyCon "a" == mkTyCon "a"
194 --
195
196 mkTyCon :: String       -- ^ the name of the type constructor (should be unique
197                         -- in the program, so it might be wise to use the
198                         -- fully qualified name).
199         -> TyCon        -- ^ A unique 'TyCon' object
200 mkTyCon str = TyCon (mkTyConKey str) str
201
202
203
204 ----------------- Observation ---------------------
205
206
207 -- | Observe the type constructor of a type representation
208 typerepTyCon :: TypeRep -> TyCon
209 typerepTyCon (TypeRep _ tc _) = tc
210
211
212 -- | Observe the argument types of a type representation
213 typerepArgs :: TypeRep -> [TypeRep]
214 typerepArgs (TypeRep _ _ args) = args
215
216
217 -- | Observe string encoding of a type representation
218 tyconString :: TyCon   -> String
219 tyconString  (TyCon _ str) = str
220
221
222 ----------------- Showing TypeReps --------------------
223
224 instance Show TypeRep where
225   showsPrec p (TypeRep _ tycon tys) =
226     case tys of
227       [] -> showsPrec p tycon
228       [x]   | tycon == listTc -> showChar '[' . shows x . showChar ']'
229       [a,r] | tycon == funTc  -> showParen (p > 8) $
230                                  showsPrec 9 a .
231                                  showString " -> " .
232                                  showsPrec 8 r
233       xs | isTupleTyCon tycon -> showTuple tycon xs
234          | otherwise         ->
235             showParen (p > 9) $
236             showsPrec p tycon . 
237             showChar ' '      . 
238             showArgs tys
239
240 instance Show TyCon where
241   showsPrec _ (TyCon _ s) = showString s
242
243 isTupleTyCon :: TyCon -> Bool
244 isTupleTyCon (TyCon _ (',':_)) = True
245 isTupleTyCon _                 = False
246
247
248 -- Some (Show.TypeRep) helpers:
249
250 showArgs :: Show a => [a] -> ShowS
251 showArgs [] = id
252 showArgs [a] = showsPrec 10 a
253 showArgs (a:as) = showsPrec 10 a . showString " " . showArgs as 
254
255 showTuple :: TyCon -> [TypeRep] -> ShowS
256 showTuple (TyCon _ str) args = showChar '(' . go str args
257  where
258   go [] [a] = showsPrec 10 a . showChar ')'
259   go _  []  = showChar ')' -- a failure condition, really.
260   go (',':xs) (a:as) = showsPrec 10 a . showChar ',' . go xs as
261   go _ _   = showChar ')'
262
263
264 -------------------------------------------------------------
265 --
266 --      The Typeable class and friends
267 --
268 -------------------------------------------------------------
269
270
271 -- | The class 'Typeable' allows a concrete representation of a type to
272 -- be calculated.
273 class Typeable a where
274   typeOf :: a -> TypeRep
275   -- ^ Takes a value of type @a@ and returns a concrete representation
276   -- of that type.  The /value/ of the argument should be ignored by
277   -- any instance of 'Typeable', so that it is safe to pass 'undefined' as
278   -- the argument.
279
280
281 -- | Variant for unary type constructors
282 class Typeable1 t where
283   typeOf1 :: t a -> TypeRep
284
285
286 -- | One Typeable instance for all Typeable1 instances
287 instance (Typeable1 s, Typeable a)
288        => Typeable (s a) where
289   typeOf x = typeOf1 x `popStarTy` typeOf (argType x)
290    where
291      argType :: t x -> x
292      argType =  undefined
293
294
295 -- | Variant for binary type constructors
296 class Typeable2 t where
297   typeOf2 :: t a b -> TypeRep
298
299
300 -- | One Typeable1 instance for all Typeable2 instances
301 instance (Typeable2 s, Typeable a)
302        => Typeable1 (s a) where
303   typeOf1 x = typeOf2 x `popStarTy` typeOf (argType x)
304    where
305      argType :: t x y -> x
306      argType =  undefined
307
308
309 -- | Variant for 3-ary type constructors
310 class Typeable3 t where
311   typeOf3 :: t a b c -> TypeRep
312
313
314 -- | One Typeable2 instance for all Typeable3 instances
315 instance (Typeable3 s, Typeable a)
316        => Typeable2 (s a) where
317   typeOf2 x = typeOf3 x `popStarTy` typeOf (argType x)
318    where
319      argType :: t x y z -> x
320      argType =  undefined
321
322
323 -- | Variant for 4-ary type constructors
324 class Typeable4 t where
325   typeOf4 :: t a b c d -> TypeRep
326
327
328 -- | One Typeable3 instance for all Typeable4 instances
329 instance (Typeable4 s, Typeable a)
330        => Typeable3 (s a) where
331   typeOf3 x = typeOf4 x `popStarTy` typeOf (argType x)
332    where
333      argType :: t x y z z' -> x
334      argType =  undefined
335
336
337 -- | Variant for 5-ary type constructors
338 class Typeable5 t where
339   typeOf5 :: t a b c d e -> TypeRep
340
341
342 -- | One Typeable4 instance for all Typeable5 instances
343 instance (Typeable5 s, Typeable a)
344        => Typeable4 (s a) where
345   typeOf4 x = typeOf5 x `popStarTy` typeOf (argType x)
346    where
347      argType :: t x y z z' z'' -> x
348      argType =  undefined
349
350
351 -- | Variant for 6-ary type constructors
352 class Typeable6 t where
353   typeOf6 :: t a b c d e f -> TypeRep
354
355
356 -- | One Typeable5 instance for all Typeable6 instances
357 instance (Typeable6 s, Typeable a)
358        => Typeable5 (s a) where
359   typeOf5 x = typeOf6 x `popStarTy` typeOf (argType x)
360    where
361      argType :: t x y z z' z'' z''' -> x
362      argType =  undefined
363
364
365 -- | Variant for 7-ary type constructors
366 class Typeable7 t where
367   typeOf7 :: t a b c d e f g -> TypeRep
368
369
370 -- | One Typeable6 instance for all Typeable7 instances
371 instance (Typeable7 s, Typeable a)
372        => Typeable6 (s a) where
373   typeOf6 x = typeOf7 x `popStarTy` typeOf (argType x)
374    where
375      argType :: t x y z z' z'' z''' z'''' -> x
376      argType =  undefined
377
378
379
380 -------------------------------------------------------------
381 --
382 --              Type-safe cast
383 --
384 -------------------------------------------------------------
385
386 -- | The type-safe cast operation
387 cast :: (Typeable a, Typeable b) => a -> Maybe b
388 cast x = r
389        where
390          r = if typeOf x == typeOf (fromJust r)
391                then Just $ unsafeCoerce x
392                else Nothing
393
394
395 -- | A flexible variation parameterised in a type constructor
396 gcast :: (Typeable a, Typeable b) => c a -> Maybe (c b)
397 gcast x = r
398  where
399   r = if typeOf (getArg x) == typeOf (getArg (fromJust r))
400         then Just $ unsafeCoerce x
401         else Nothing
402   getArg :: c x -> x 
403   getArg = undefined
404
405
406
407 -- | Cast for * -> *
408 gcast1 :: (Typeable1 t, Typeable1 t') => c (t a) -> Maybe (c (t' a)) 
409 gcast1 x = r
410  where
411   r = if typeOf1 (getArg x) == typeOf1 (getArg (fromJust r))
412        then Just $ unsafeCoerce x
413        else Nothing
414   getArg :: c x -> x 
415   getArg = undefined
416
417
418 -- | Cast for * -> * -> *
419 gcast2 :: (Typeable2 t, Typeable2 t') => c (t a b) -> Maybe (c (t' a b)) 
420 gcast2 x = r
421  where
422   r = if typeOf2 (getArg x) == typeOf2 (getArg (fromJust r))
423        then Just $ unsafeCoerce x
424        else Nothing
425   getArg :: c x -> x 
426   getArg = undefined
427
428
429
430 -------------------------------------------------------------
431 --
432 --      Instances of the Typeable classes for Prelude types
433 --
434 -------------------------------------------------------------
435
436 unitTc :: TyCon
437 unitTc = mkTyCon "()"
438
439 instance Typeable () where
440   typeOf _ = mkAppTy unitTc []
441
442
443 tup3Tc :: TyCon
444 tup3Tc = mkTyCon ",,"
445
446 instance Typeable3 (,,) where
447   typeOf3 tu = mkAppTy tup3Tc []
448
449
450 tup4Tc :: TyCon
451 tup4Tc = mkTyCon ",,,"
452
453 instance Typeable4 (,,,) where
454   typeOf4 tu = mkAppTy tup4Tc []
455
456
457 tup5Tc :: TyCon
458 tup5Tc = mkTyCon ",,,,"
459
460 instance Typeable5 (,,,,) where
461   typeOf5 tu = mkAppTy tup5Tc []
462
463
464 tup6Tc :: TyCon
465 tup6Tc = mkTyCon ",,,,,"
466
467 instance Typeable6 (,,,,,) where
468   typeOf6 tu = mkAppTy tup6Tc []
469
470
471 tup7Tc :: TyCon
472 tup7Tc = mkTyCon ",,,,,"
473
474 instance Typeable7 (,,,,,,) where
475   typeOf7 tu = mkAppTy tup7Tc []
476
477
478 listTc :: TyCon
479 listTc = mkTyCon "[]"
480
481 -- | Instance for lists
482 instance Typeable1 [] where
483   typeOf1 _ = mkAppTy listTc []
484
485
486 maybeTc :: TyCon
487 maybeTc = mkTyCon "Maybe"
488
489 -- | Instance for maybes
490 instance Typeable1 Maybe where
491   typeOf1 _ = mkAppTy maybeTc []
492
493
494 ratioTc :: TyCon
495 ratioTc = mkTyCon "Ratio"
496
497 -- | Instance for ratios
498 instance Typeable1 Ratio where
499   typeOf1 _ = mkAppTy ratioTc []
500
501
502 pairTc :: TyCon
503 pairTc = mkTyCon "(,)"
504
505 -- | Instance for products
506 instance Typeable2 (,) where
507   typeOf2 _ = mkAppTy pairTc []
508
509
510 eitherTc :: TyCon
511 eitherTc = mkTyCon "Either"
512
513 -- | Instance for sums
514 instance Typeable2 Either where
515   typeOf2 _ = mkAppTy eitherTc []
516
517
518 -- | Instance for functions
519 instance Typeable2 (->) where
520   typeOf2 _ = mkAppTy funTc []
521
522
523 #ifdef __GLASGOW_HASKELL__
524
525 ioTc :: TyCon
526 ioTc = mkTyCon "GHC.IOBase.IO"
527
528 instance Typeable1 IO where
529   typeOf1 _ = mkAppTy ioTc []
530
531
532 ptrTc :: TyCon
533 ptrTc = mkTyCon "GHC.Ptr.Ptr"
534
535 instance Typeable1 Ptr where
536   typeOf1 _ = mkAppTy ptrTc []
537
538
539 stableptrTc :: TyCon
540 stableptrTc = mkTyCon "GHC.Stable.StablePtr"
541
542 instance Typeable1 StablePtr where
543   typeOf1 _ = mkAppTy stableptrTc []
544
545
546 iorefTc :: TyCon
547 iorefTc = mkTyCon "GHC.IOBase.IORef"
548
549 instance Typeable1 IORef where
550   typeOf1 _ = mkAppTy iorefTc []
551
552 #endif
553
554
555
556 -------------------------------------------------------
557 --
558 -- Generate Typeable instances for standard datatypes
559 --
560 -------------------------------------------------------
561
562 #ifndef __NHC__
563 INSTANCE_TYPEABLE0(Bool,boolTc,"Bool")
564 INSTANCE_TYPEABLE0(Char,charTc,"Char")
565 INSTANCE_TYPEABLE0(Float,floatTc,"Float")
566 INSTANCE_TYPEABLE0(Double,doubleTc,"Double")
567 INSTANCE_TYPEABLE0(Int,intTc,"Int")
568 INSTANCE_TYPEABLE0(Integer,integerTc,"Integer")
569 INSTANCE_TYPEABLE0(Ordering,orderingTc,"Ordering")
570 INSTANCE_TYPEABLE0(Handle,handleTc,"Handle")
571
572 INSTANCE_TYPEABLE0(Int8,int8Tc,"Int8")
573 INSTANCE_TYPEABLE0(Int16,int16Tc,"Int16")
574 INSTANCE_TYPEABLE0(Int32,int32Tc,"Int32")
575 INSTANCE_TYPEABLE0(Int64,int64Tc,"Int64")
576
577 INSTANCE_TYPEABLE0(Word8,word8Tc,"Word8" )
578 INSTANCE_TYPEABLE0(Word16,word16Tc,"Word16")
579 INSTANCE_TYPEABLE0(Word32,word32Tc,"Word32")
580 INSTANCE_TYPEABLE0(Word64,word64Tc,"Word64")
581
582 INSTANCE_TYPEABLE0(TyCon,tyconTc,"TyCon")
583 INSTANCE_TYPEABLE0(TypeRep,typeRepTc,"TypeRep")
584 #endif
585
586 #ifdef __GLASGOW_HASKELL__
587 INSTANCE_TYPEABLE0(Word,wordTc,"Word" )
588 #endif
589
590
591
592 ---------------------------------------------
593 --
594 --              Internals 
595 --
596 ---------------------------------------------
597
598 #ifndef __HUGS__
599 newtype Key = Key Int deriving( Eq )
600 #endif
601
602 data KeyPr = KeyPr !Key !Key deriving( Eq )
603
604 hashKP :: KeyPr -> Int32
605 hashKP (KeyPr (Key k1) (Key k2)) = (HT.hashInt k1 + HT.hashInt k2) `rem` HT.prime
606
607 data Cache = Cache { next_key :: !(IORef Key),
608                      tc_tbl   :: !(HT.HashTable String Key),
609                      ap_tbl   :: !(HT.HashTable KeyPr Key) }
610
611 {-# NOINLINE cache #-}
612 cache :: Cache
613 cache = unsafePerformIO $ do
614                 empty_tc_tbl <- HT.new (==) HT.hashString
615                 empty_ap_tbl <- HT.new (==) hashKP
616                 key_loc      <- newIORef (Key 1) 
617                 return (Cache { next_key = key_loc,
618                                 tc_tbl = empty_tc_tbl, 
619                                 ap_tbl = empty_ap_tbl })
620
621 newKey :: IORef Key -> IO Key
622 #ifdef __GLASGOW_HASKELL__
623 newKey kloc = do i <- genSym; return (Key i)
624 #else
625 newKey kloc = do { k@(Key i) <- readIORef kloc ;
626                    writeIORef kloc (Key (i+1)) ;
627                    return k }
628 #endif
629
630 #ifdef __GLASGOW_HASKELL__
631 -- In GHC we use the RTS's genSym function to get a new unique,
632 -- because in GHCi we might have two copies of the Data.Typeable
633 -- library running (one in the compiler and one in the running
634 -- program), and we need to make sure they don't share any keys.  
635 --
636 -- This is really a hack.  A better solution would be to centralise the
637 -- whole mutable state used by this module, i.e. both hashtables.  But
638 -- the current solution solves the immediate problem, which is that
639 -- dynamics generated in one world with one type were erroneously
640 -- being recognised by the other world as having a different type.
641 foreign import ccall unsafe "genSymZh"
642   genSym :: IO Int
643 #endif
644
645 mkTyConKey :: String -> Key
646 mkTyConKey str 
647   = unsafePerformIO $ do
648         let Cache {next_key = kloc, tc_tbl = tbl} = cache
649         mb_k <- HT.lookup tbl str
650         case mb_k of
651           Just k  -> return k
652           Nothing -> do { k <- newKey kloc ;
653                           HT.insert tbl str k ;
654                           return k }
655
656 appKey :: Key -> Key -> Key
657 appKey k1 k2
658   = unsafePerformIO $ do
659         let Cache {next_key = kloc, ap_tbl = tbl} = cache
660         mb_k <- HT.lookup tbl kpr
661         case mb_k of
662           Just k  -> return k
663           Nothing -> do { k <- newKey kloc ;
664                           HT.insert tbl kpr k ;
665                           return k }
666   where
667     kpr = KeyPr k1 k2
668
669 appKeys :: Key -> [Key] -> Key
670 appKeys k ks = foldl appKey k ks