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