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