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