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