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