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