Fix Trac #3245: memoising typeOf
[ghc-base.git] / Data / Typeable.hs
1 {-# OPTIONS_GHC -XNoImplicitPrelude -XOverlappingInstances -funbox-strict-fields #-}
2
3 -- The -XOverlappingInstances 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.Data" uses Typeable
25 -- and type-safe cast (but not dynamics) to support the \"Scrap your
26 -- boilerplate\" style of generic programming.
27 --
28 -----------------------------------------------------------------------------
29
30 module Data.Typeable
31   (
32
33         -- * The Typeable class
34         Typeable( typeOf ),     -- :: a -> TypeRep
35
36         -- * Type-safe cast
37         cast,                   -- :: (Typeable a, Typeable b) => a -> Maybe b
38         gcast,                  -- a generalisation of cast
39
40         -- * Type representations
41         TypeRep,        -- abstract, instance of: Eq, Show, Typeable
42         TyCon,          -- abstract, instance of: Eq, Show, Typeable
43         showsTypeRep,
44
45         -- * Construction of type representations
46         mkTyCon,        -- :: String  -> TyCon
47         mkTyConApp,     -- :: TyCon   -> [TypeRep] -> TypeRep
48         mkAppTy,        -- :: TypeRep -> TypeRep   -> TypeRep
49         mkFunTy,        -- :: TypeRep -> TypeRep   -> TypeRep
50
51         -- * Observation of type representations
52         splitTyConApp,  -- :: TypeRep -> (TyCon, [TypeRep])
53         funResultTy,    -- :: TypeRep -> TypeRep   -> Maybe TypeRep
54         typeRepTyCon,   -- :: TypeRep -> TyCon
55         typeRepArgs,    -- :: TypeRep -> [TypeRep]
56         tyConString,    -- :: TyCon   -> String
57         typeRepKey,     -- :: TypeRep -> IO Int
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.Int
87 import Data.Word
88 import Data.List( foldl, intersperse )
89 import Unsafe.Coerce
90
91 #ifdef __GLASGOW_HASKELL__
92 import GHC.Base
93 import GHC.Show         (Show(..), ShowS,
94                          shows, showString, showChar, showParen)
95 import GHC.Err          (undefined)
96 import GHC.Num          (Integer, fromInteger, (+))
97 import GHC.Real         ( rem, Ratio )
98 import GHC.IORef        (IORef,newIORef)
99 import GHC.IO           (unsafePerformIO,block)
100
101 -- These imports are so we can define Typeable instances
102 -- It'd be better to give Typeable instances in the modules themselves
103 -- but they all have to be compiled before Typeable
104 import GHC.IOArray
105 import GHC.MVar
106 import GHC.ST           ( ST )
107 import GHC.STRef        ( STRef )
108 import GHC.Ptr          ( Ptr, FunPtr )
109 import GHC.Stable       ( StablePtr, newStablePtr, freeStablePtr,
110                           deRefStablePtr, castStablePtrToPtr,
111                           castPtrToStablePtr )
112 import GHC.Arr          ( Array, STArray )
113
114 #endif
115
116 #ifdef __HUGS__
117 import Hugs.Prelude     ( Key(..), TypeRep(..), TyCon(..), Ratio,
118                           Handle, Ptr, FunPtr, ForeignPtr, StablePtr )
119 import Hugs.IORef       ( IORef, newIORef, readIORef, writeIORef )
120 import Hugs.IOExts      ( unsafePerformIO )
121         -- For the Typeable instance
122 import Hugs.Array       ( Array )
123 import Hugs.IOArray
124 import Hugs.ConcBase    ( MVar )
125 #endif
126
127 #ifdef __NHC__
128 import NHC.IOExtras (IOArray,IORef,newIORef,readIORef,writeIORef,unsafePerformIO)
129 import IO (Handle)
130 import Ratio (Ratio)
131         -- For the Typeable instance
132 import NHC.FFI  ( Ptr,FunPtr,StablePtr,ForeignPtr )
133 import Array    ( Array )
134 #endif
135
136 #include "Typeable.h"
137
138 #ifndef __HUGS__
139
140 -------------------------------------------------------------
141 --
142 --              Type representations
143 --
144 -------------------------------------------------------------
145
146 -- | A concrete representation of a (monomorphic) type.  'TypeRep'
147 -- supports reasonably efficient equality.
148 data TypeRep = TypeRep !Key TyCon [TypeRep] 
149
150 -- Compare keys for equality
151 instance Eq TypeRep where
152   (TypeRep k1 _ _) == (TypeRep k2 _ _) = k1 == k2
153
154 -- | An abstract representation of a type constructor.  'TyCon' objects can
155 -- be built using 'mkTyCon'.
156 data TyCon = TyCon !Key String
157
158 instance Eq TyCon where
159   (TyCon t1 _) == (TyCon t2 _) = t1 == t2
160 #endif
161
162 -- | Returns a unique integer associated with a 'TypeRep'.  This can
163 -- be used for making a mapping with TypeReps
164 -- as the keys, for example.  It is guaranteed that @t1 == t2@ if and only if
165 -- @typeRepKey t1 == typeRepKey t2@.
166 --
167 -- It is in the 'IO' monad because the actual value of the key may
168 -- vary from run to run of the program.  You should only rely on
169 -- the equality property, not any actual key value.  The relative ordering
170 -- of keys has no meaning either.
171 --
172 typeRepKey :: TypeRep -> IO Int
173 typeRepKey (TypeRep (Key i) _ _) = return i
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 xs
270          | otherwise         ->
271             showParen (p > 9) $
272             showsPrec p tycon . 
273             showChar ' '      . 
274             showArgs tys
275
276 showsTypeRep :: TypeRep -> ShowS
277 showsTypeRep = shows
278
279 instance Show TyCon where
280   showsPrec _ (TyCon _ s) = showString s
281
282 isTupleTyCon :: TyCon -> Bool
283 isTupleTyCon (TyCon _ ('(':',':_)) = True
284 isTupleTyCon _                     = False
285
286 -- Some (Show.TypeRep) helpers:
287
288 showArgs :: Show a => [a] -> ShowS
289 showArgs [] = id
290 showArgs [a] = showsPrec 10 a
291 showArgs (a:as) = showsPrec 10 a . showString " " . showArgs as 
292
293 showTuple :: [TypeRep] -> ShowS
294 showTuple args = showChar '('
295                . (foldr (.) id $ intersperse (showChar ',') 
296                                $ map (showsPrec 10) args)
297                . showChar ')'
298
299 -------------------------------------------------------------
300 --
301 --      The Typeable class and friends
302 --
303 -------------------------------------------------------------
304
305 {- Note [Memoising typeOf]
306 ~~~~~~~~~~~~~~~~~~~~~~~~~~
307 IMPORTANT: we don't want to recalculate the type-rep once per
308 call to the dummy argument.  This is what went wrong in Trac #3245
309 So we help GHC by manually keeping the 'rep' *outside* the value 
310 lambda, thus
311     
312     typeOfDefault :: forall t a. (Typeable1 t, Typeable a) => t a -> TypeRep
313     typeOfDefault = \_ -> rep
314       where
315         rep = typeOf1 (undefined :: t a) `mkAppTy` 
316               typeOf  (undefined :: a)
317
318 Notice the crucial use of scoped type variables here!
319 -}
320
321 -- | The class 'Typeable' allows a concrete representation of a type to
322 -- be calculated.
323 class Typeable a where
324   typeOf :: a -> TypeRep
325   -- ^ Takes a value of type @a@ and returns a concrete representation
326   -- of that type.  The /value/ of the argument should be ignored by
327   -- any instance of 'Typeable', so that it is safe to pass 'undefined' as
328   -- the argument.
329
330 -- | Variant for unary type constructors
331 class Typeable1 t where
332   typeOf1 :: t a -> TypeRep
333
334 -- | For defining a 'Typeable' instance from any 'Typeable1' instance.
335 typeOfDefault :: forall t a. (Typeable1 t, Typeable a) => t a -> TypeRep
336 typeOfDefault = \_ -> rep
337  where
338    rep = typeOf1 (undefined :: t a) `mkAppTy` 
339          typeOf  (undefined :: a)
340    -- Note [Memoising typeOf]
341
342 -- | Variant for binary type constructors
343 class Typeable2 t where
344   typeOf2 :: t a b -> TypeRep
345
346 -- | For defining a 'Typeable1' instance from any 'Typeable2' instance.
347 typeOf1Default :: forall t a b. (Typeable2 t, Typeable a) => t a b -> TypeRep
348 typeOf1Default = \_ -> rep 
349  where
350    rep = typeOf2 (undefined :: t a b) `mkAppTy` 
351          typeOf  (undefined :: a)
352    -- Note [Memoising typeOf]
353
354 -- | Variant for 3-ary type constructors
355 class Typeable3 t where
356   typeOf3 :: t a b c -> TypeRep
357
358 -- | For defining a 'Typeable2' instance from any 'Typeable3' instance.
359 typeOf2Default :: forall t a b c. (Typeable3 t, Typeable a) => t a b c -> TypeRep
360 typeOf2Default = \_ -> rep 
361  where
362    rep = typeOf3 (undefined :: t a b c) `mkAppTy` 
363          typeOf  (undefined :: a)
364    -- Note [Memoising typeOf]
365
366 -- | Variant for 4-ary type constructors
367 class Typeable4 t where
368   typeOf4 :: t a b c d -> TypeRep
369
370 -- | For defining a 'Typeable3' instance from any 'Typeable4' instance.
371 typeOf3Default :: forall t a b c d. (Typeable4 t, Typeable a) => t a b c d -> TypeRep
372 typeOf3Default = \_ -> rep
373  where
374    rep = typeOf4 (undefined :: t a b c d) `mkAppTy` 
375          typeOf  (undefined :: a)
376    -- Note [Memoising typeOf]
377    
378 -- | Variant for 5-ary type constructors
379 class Typeable5 t where
380   typeOf5 :: t a b c d e -> TypeRep
381
382 -- | For defining a 'Typeable4' instance from any 'Typeable5' instance.
383 typeOf4Default :: forall t a b c d e. (Typeable5 t, Typeable a) => t a b c d e -> TypeRep
384 typeOf4Default = \_ -> rep 
385  where
386    rep = typeOf5 (undefined :: t a b c d e) `mkAppTy` 
387          typeOf  (undefined :: a)
388    -- Note [Memoising typeOf]
389
390 -- | Variant for 6-ary type constructors
391 class Typeable6 t where
392   typeOf6 :: t a b c d e f -> TypeRep
393
394 -- | For defining a 'Typeable5' instance from any 'Typeable6' instance.
395 typeOf5Default :: forall t a b c d e f. (Typeable6 t, Typeable a) => t a b c d e f -> TypeRep
396 typeOf5Default = \_ -> rep
397  where
398    rep = typeOf6 (undefined :: t a b c d e f) `mkAppTy` 
399          typeOf  (undefined :: a)
400    -- Note [Memoising typeOf]
401
402 -- | Variant for 7-ary type constructors
403 class Typeable7 t where
404   typeOf7 :: t a b c d e f g -> TypeRep
405
406 -- | For defining a 'Typeable6' instance from any 'Typeable7' instance.
407 typeOf6Default :: forall t a b c d e f g. (Typeable7 t, Typeable a) => t a b c d e f g -> TypeRep
408 typeOf6Default = \_ -> rep
409  where
410    rep = typeOf7 (undefined :: t a b c d e f g) `mkAppTy` 
411          typeOf  (undefined :: a)
412    -- Note [Memoising typeOf]
413
414 #ifdef __GLASGOW_HASKELL__
415 -- Given a @Typeable@/n/ instance for an /n/-ary type constructor,
416 -- define the instances for partial applications.
417 -- Programmers using non-GHC implementations must do this manually
418 -- for each type constructor.
419 -- (The INSTANCE_TYPEABLE/n/ macros in Typeable.h include this.)
420
421 -- | One Typeable instance for all Typeable1 instances
422 instance (Typeable1 s, Typeable a)
423        => Typeable (s a) where
424   typeOf = typeOfDefault
425
426 -- | One Typeable1 instance for all Typeable2 instances
427 instance (Typeable2 s, Typeable a)
428        => Typeable1 (s a) where
429   typeOf1 = typeOf1Default
430
431 -- | One Typeable2 instance for all Typeable3 instances
432 instance (Typeable3 s, Typeable a)
433        => Typeable2 (s a) where
434   typeOf2 = typeOf2Default
435
436 -- | One Typeable3 instance for all Typeable4 instances
437 instance (Typeable4 s, Typeable a)
438        => Typeable3 (s a) where
439   typeOf3 = typeOf3Default
440
441 -- | One Typeable4 instance for all Typeable5 instances
442 instance (Typeable5 s, Typeable a)
443        => Typeable4 (s a) where
444   typeOf4 = typeOf4Default
445
446 -- | One Typeable5 instance for all Typeable6 instances
447 instance (Typeable6 s, Typeable a)
448        => Typeable5 (s a) where
449   typeOf5 = typeOf5Default
450
451 -- | One Typeable6 instance for all Typeable7 instances
452 instance (Typeable7 s, Typeable a)
453        => Typeable6 (s a) where
454   typeOf6 = typeOf6Default
455
456 #endif /* __GLASGOW_HASKELL__ */
457
458 -------------------------------------------------------------
459 --
460 --              Type-safe cast
461 --
462 -------------------------------------------------------------
463
464 -- | The type-safe cast operation
465 cast :: (Typeable a, Typeable b) => a -> Maybe b
466 cast x = r
467        where
468          r = if typeOf x == typeOf (fromJust r)
469                then Just $ unsafeCoerce x
470                else Nothing
471
472 -- | A flexible variation parameterised in a type constructor
473 gcast :: (Typeable a, Typeable b) => c a -> Maybe (c b)
474 gcast x = r
475  where
476   r = if typeOf (getArg x) == typeOf (getArg (fromJust r))
477         then Just $ unsafeCoerce x
478         else Nothing
479   getArg :: c x -> x 
480   getArg = undefined
481
482 -- | Cast for * -> *
483 gcast1 :: (Typeable1 t, Typeable1 t') => c (t a) -> Maybe (c (t' a)) 
484 gcast1 x = r
485  where
486   r = if typeOf1 (getArg x) == typeOf1 (getArg (fromJust r))
487        then Just $ unsafeCoerce x
488        else Nothing
489   getArg :: c x -> x 
490   getArg = undefined
491
492 -- | Cast for * -> * -> *
493 gcast2 :: (Typeable2 t, Typeable2 t') => c (t a b) -> Maybe (c (t' a b)) 
494 gcast2 x = r
495  where
496   r = if typeOf2 (getArg x) == typeOf2 (getArg (fromJust r))
497        then Just $ unsafeCoerce x
498        else Nothing
499   getArg :: c x -> x 
500   getArg = undefined
501
502 -------------------------------------------------------------
503 --
504 --      Instances of the Typeable classes for Prelude types
505 --
506 -------------------------------------------------------------
507
508 INSTANCE_TYPEABLE0((),unitTc,"()")
509 INSTANCE_TYPEABLE1([],listTc,"[]")
510 INSTANCE_TYPEABLE1(Maybe,maybeTc,"Maybe")
511 INSTANCE_TYPEABLE1(Ratio,ratioTc,"Ratio")
512 INSTANCE_TYPEABLE2((->),funTc,"->")
513 INSTANCE_TYPEABLE1(IO,ioTc,"IO")
514
515 #if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
516 -- Types defined in GHC.MVar
517 INSTANCE_TYPEABLE1(MVar,mvarTc,"MVar" )
518 #endif
519
520 INSTANCE_TYPEABLE2(Array,arrayTc,"Array")
521 INSTANCE_TYPEABLE2(IOArray,iOArrayTc,"IOArray")
522
523 #ifdef __GLASGOW_HASKELL__
524 -- Hugs has these too, but their Typeable<n> instances are defined
525 -- elsewhere to keep this module within Haskell 98.
526 -- This is important because every invocation of runhugs or ffihugs
527 -- uses this module via Data.Dynamic.
528 INSTANCE_TYPEABLE2(ST,stTc,"ST")
529 INSTANCE_TYPEABLE2(STRef,stRefTc,"STRef")
530 INSTANCE_TYPEABLE3(STArray,sTArrayTc,"STArray")
531 #endif
532
533 #ifndef __NHC__
534 INSTANCE_TYPEABLE2((,),pairTc,"(,)")
535 INSTANCE_TYPEABLE3((,,),tup3Tc,"(,,)")
536 INSTANCE_TYPEABLE4((,,,),tup4Tc,"(,,,)")
537 INSTANCE_TYPEABLE5((,,,,),tup5Tc,"(,,,,)")
538 INSTANCE_TYPEABLE6((,,,,,),tup6Tc,"(,,,,,)")
539 INSTANCE_TYPEABLE7((,,,,,,),tup7Tc,"(,,,,,,)")
540 #endif /* __NHC__ */
541
542 INSTANCE_TYPEABLE1(Ptr,ptrTc,"Ptr")
543 INSTANCE_TYPEABLE1(FunPtr,funPtrTc,"FunPtr")
544 #ifndef __GLASGOW_HASKELL__
545 INSTANCE_TYPEABLE1(ForeignPtr,foreignPtrTc,"ForeignPtr")
546 #endif
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 #ifndef __GLASGOW_HASKELL__
567 INSTANCE_TYPEABLE0(Handle,handleTc,"Handle")
568 #endif
569
570 INSTANCE_TYPEABLE0(Int8,int8Tc,"Int8")
571 INSTANCE_TYPEABLE0(Int16,int16Tc,"Int16")
572 INSTANCE_TYPEABLE0(Int32,int32Tc,"Int32")
573 INSTANCE_TYPEABLE0(Int64,int64Tc,"Int64")
574
575 INSTANCE_TYPEABLE0(Word8,word8Tc,"Word8" )
576 INSTANCE_TYPEABLE0(Word16,word16Tc,"Word16")
577 INSTANCE_TYPEABLE0(Word32,word32Tc,"Word32")
578 INSTANCE_TYPEABLE0(Word64,word64Tc,"Word64")
579
580 INSTANCE_TYPEABLE0(TyCon,tyconTc,"TyCon")
581 INSTANCE_TYPEABLE0(TypeRep,typeRepTc,"TypeRep")
582
583 #ifdef __GLASGOW_HASKELL__
584 INSTANCE_TYPEABLE0(RealWorld,realWorldTc,"RealWorld")
585 #endif
586
587 ---------------------------------------------
588 --
589 --              Internals 
590 --
591 ---------------------------------------------
592
593 #ifndef __HUGS__
594 newtype Key = Key Int deriving( Eq )
595 #endif
596
597 data KeyPr = KeyPr !Key !Key deriving( Eq )
598
599 hashKP :: KeyPr -> Int32
600 hashKP (KeyPr (Key k1) (Key k2)) = (HT.hashInt k1 + HT.hashInt k2) `rem` HT.prime
601
602 data Cache = Cache { next_key :: !(IORef Key),  -- Not used by GHC (calls genSym instead)
603                      tc_tbl   :: !(HT.HashTable String Key),
604                      ap_tbl   :: !(HT.HashTable KeyPr Key) }
605
606 {-# NOINLINE cache #-}
607 #ifdef __GLASGOW_HASKELL__
608 foreign import ccall unsafe "RtsTypeable.h getOrSetTypeableStore"
609     getOrSetTypeableStore :: Ptr a -> IO (Ptr a)
610 #endif
611
612 cache :: Cache
613 cache = unsafePerformIO $ do
614                 empty_tc_tbl <- HT.new (==) HT.hashString
615                 empty_ap_tbl <- HT.new (==) hashKP
616                 key_loc      <- newIORef (Key 1) 
617                 let ret = Cache {       next_key = key_loc,
618                                         tc_tbl = empty_tc_tbl, 
619                                         ap_tbl = empty_ap_tbl }
620 #ifdef __GLASGOW_HASKELL__
621                 block $ do
622                         stable_ref <- newStablePtr ret
623                         let ref = castStablePtrToPtr stable_ref
624                         ref2 <- getOrSetTypeableStore ref
625                         if ref==ref2
626                                 then deRefStablePtr stable_ref
627                                 else do
628                                         freeStablePtr stable_ref
629                                         deRefStablePtr
630                                                 (castPtrToStablePtr ref2)
631 #else
632                 return ret
633 #endif
634
635 newKey :: IORef Key -> IO Key
636 #ifdef __GLASGOW_HASKELL__
637 newKey _ = do i <- genSym; return (Key i)
638 #else
639 newKey kloc = do { k@(Key i) <- readIORef kloc ;
640                    writeIORef kloc (Key (i+1)) ;
641                    return k }
642 #endif
643
644 #ifdef __GLASGOW_HASKELL__
645 foreign import ccall unsafe "genSymZh"
646   genSym :: IO Int
647 #endif
648
649 mkTyConKey :: String -> Key
650 mkTyConKey str 
651   = unsafePerformIO $ do
652         let Cache {next_key = kloc, tc_tbl = tbl} = cache
653         mb_k <- HT.lookup tbl str
654         case mb_k of
655           Just k  -> return k
656           Nothing -> do { k <- newKey kloc ;
657                           HT.insert tbl str k ;
658                           return k }
659
660 appKey :: Key -> Key -> Key
661 appKey k1 k2
662   = unsafePerformIO $ do
663         let Cache {next_key = kloc, ap_tbl = tbl} = cache
664         mb_k <- HT.lookup tbl kpr
665         case mb_k of
666           Just k  -> return k
667           Nothing -> do { k <- newKey kloc ;
668                           HT.insert tbl kpr k ;
669                           return k }
670   where
671     kpr = KeyPr k1 k2
672
673 appKeys :: Key -> [Key] -> Key
674 appKeys k ks = foldl appKey k ks