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