1 {-# OPTIONS_GHC -XNoImplicitPrelude -XOverlappingInstances -funbox-strict-fields #-}
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)
9 -----------------------------------------------------------------------------
11 -- Module : Data.Typeable
12 -- Copyright : (c) The University of Glasgow, CWI 2001--2004
13 -- License : BSD-style (see the file libraries/base/LICENSE)
15 -- Maintainer : libraries@haskell.org
16 -- Stability : experimental
17 -- Portability : portable
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.
28 -----------------------------------------------------------------------------
33 -- * The Typeable class
34 Typeable
( typeOf
), -- :: a -> TypeRep
37 cast
, -- :: (Typeable a, Typeable b) => a -> Maybe b
38 gcast
, -- a generalisation of cast
40 -- * Type representations
41 TypeRep
, -- abstract, instance of: Eq, Show, Typeable
42 TyCon
, -- abstract, instance of: Eq, Show, Typeable
45 -- * Construction of type representations
46 mkTyCon
, -- :: String -> TyCon
47 mkTyConApp
, -- :: TyCon -> [TypeRep] -> TypeRep
48 mkAppTy
, -- :: TypeRep -> TypeRep -> TypeRep
49 mkFunTy
, -- :: TypeRep -> TypeRep -> TypeRep
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
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))
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
84 import qualified Data
.HashTable
as HT
89 import Data
.List
( foldl, intersperse )
92 #ifdef __GLASGOW_HASKELL__
98 import GHC
.Real
( rem, Ratio )
99 import GHC
.IOBase
(IORef
,newIORef
,unsafePerformIO
)
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
.IOBase
( IO, MVar
, Handle, block
)
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
,
112 import GHC
.Arr
( Array, STArray
)
117 import Hugs
.Prelude
( Key
(..), TypeRep
(..), TyCon
(..), Ratio,
118 Exception
, ArithException
, IOException
,
119 ArrayException
, AsyncException
, Handle,
120 Ptr
, FunPtr
, ForeignPtr
, StablePtr
)
121 import Hugs
.IORef
( IORef
, newIORef
, readIORef
, writeIORef
)
122 import Hugs
.IOExts
( unsafePerformIO
)
123 -- For the Typeable instance
124 import Hugs
.Array ( Array )
125 import Hugs
.ConcBase
( MVar
)
129 import NHC
.IOExtras
(IORef
,newIORef
,readIORef
,writeIORef
,unsafePerformIO
)
132 -- For the Typeable instance
133 import NHC
.FFI
( Ptr
,FunPtr
,StablePtr
,ForeignPtr
)
134 import Array ( Array )
137 #include
"Typeable.h"
141 -------------------------------------------------------------
143 -- Type representations
145 -------------------------------------------------------------
147 -- | A concrete representation of a (monomorphic) type. 'TypeRep'
148 -- supports reasonably efficient equality.
149 data TypeRep
= TypeRep
!Key TyCon
[TypeRep
]
151 -- Compare keys for equality
152 instance Eq TypeRep
where
153 (TypeRep k1 _ _
) == (TypeRep k2 _ _
) = k1
== k2
155 -- | An abstract representation of a type constructor. 'TyCon' objects can
156 -- be built using 'mkTyCon'.
157 data TyCon
= TyCon
!Key
String
159 instance Eq TyCon
where
160 (TyCon t1 _
) == (TyCon t2 _
) = t1
== t2
163 -- | Returns a unique integer associated with a 'TypeRep'. This can
164 -- be used for making a mapping with TypeReps
165 -- as the keys, for example. It is guaranteed that @t1 == t2@ if and only if
166 -- @typeRepKey t1 == typeRepKey t2@.
168 -- It is in the 'IO' monad because the actual value of the key may
169 -- vary from run to run of the program. You should only rely on
170 -- the equality property, not any actual key value. The relative ordering
171 -- of keys has no meaning either.
173 typeRepKey
:: TypeRep
-> IO Int
174 typeRepKey
(TypeRep
(Key i
) _ _
) = return i
177 -- let fTy = mkTyCon "Foo" in show (mkTyConApp (mkTyCon ",,")
180 -- returns "(Foo,Foo,Foo)"
182 -- The TypeRep Show instance promises to print tuple types
183 -- correctly. Tuple type constructors are specified by a
184 -- sequence of commas, e.g., (mkTyCon ",,,,") returns
185 -- the 5-tuple tycon.
187 ----------------- Construction --------------------
189 -- | Applies a type constructor to a sequence of types
190 mkTyConApp
:: TyCon
-> [TypeRep
] -> TypeRep
191 mkTyConApp tc
@(TyCon tc_k _
) args
192 = TypeRep
(appKeys tc_k arg_ks
) tc args
194 arg_ks
= [k | TypeRep k _ _
<- args
]
196 -- | A special case of 'mkTyConApp', which applies the function
197 -- type constructor to a pair of types.
198 mkFunTy
:: TypeRep
-> TypeRep
-> TypeRep
199 mkFunTy f a
= mkTyConApp funTc
[f
,a
]
201 -- | Splits a type constructor application
202 splitTyConApp
:: TypeRep
-> (TyCon
,[TypeRep
])
203 splitTyConApp
(TypeRep _ tc trs
) = (tc
,trs
)
205 -- | Applies a type to a function type. Returns: @'Just' u@ if the
206 -- first argument represents a function of type @t -> u@ and the
207 -- second argument represents a function of type @t@. Otherwise,
208 -- returns 'Nothing'.
209 funResultTy
:: TypeRep
-> TypeRep
-> Maybe TypeRep
210 funResultTy trFun trArg
211 = case splitTyConApp trFun
of
212 (tc
, [t1
,t2
]) | tc
== funTc
&& t1
== trArg
-> Just t2
215 -- | Adds a TypeRep argument to a TypeRep.
216 mkAppTy
:: TypeRep
-> TypeRep
-> TypeRep
217 mkAppTy
(TypeRep tr_k tc trs
) arg_tr
218 = let (TypeRep arg_k _ _
) = arg_tr
219 in TypeRep
(appKey tr_k arg_k
) tc
(trs
++[arg_tr
])
221 -- If we enforce the restriction that there is only one
222 -- @TyCon@ for a type & it is shared among all its uses,
223 -- we can map them onto Ints very simply. The benefit is,
224 -- of course, that @TyCon@s can then be compared efficiently.
226 -- Provided the implementor of other @Typeable@ instances
227 -- takes care of making all the @TyCon@s CAFs (toplevel constants),
230 -- If this constraint does turn out to be a sore thumb, changing
231 -- the Eq instance for TyCons is trivial.
233 -- | Builds a 'TyCon' object representing a type constructor. An
234 -- implementation of "Data.Typeable" should ensure that the following holds:
236 -- > mkTyCon "a" == mkTyCon "a"
239 mkTyCon
:: String -- ^ the name of the type constructor (should be unique
240 -- in the program, so it might be wise to use the
241 -- fully qualified name).
242 -> TyCon
-- ^ A unique 'TyCon' object
243 mkTyCon str
= TyCon
(mkTyConKey str
) str
245 ----------------- Observation ---------------------
247 -- | Observe the type constructor of a type representation
248 typeRepTyCon
:: TypeRep
-> TyCon
249 typeRepTyCon
(TypeRep _ tc _
) = tc
251 -- | Observe the argument types of a type representation
252 typeRepArgs
:: TypeRep
-> [TypeRep
]
253 typeRepArgs
(TypeRep _ _ args
) = args
255 -- | Observe string encoding of a type representation
256 tyConString
:: TyCon
-> String
257 tyConString
(TyCon _ str
) = str
259 ----------------- Showing TypeReps --------------------
261 instance Show TypeRep
where
262 showsPrec p
(TypeRep _ tycon tys
) =
264 [] -> showsPrec p tycon
265 [x
] | tycon
== listTc
-> showChar '[' . shows x
. showChar ']'
266 [a
,r
] | tycon
== funTc
-> showParen (p
> 8) $
270 xs | isTupleTyCon tycon
-> showTuple xs
277 showsTypeRep
:: TypeRep
-> ShowS
280 instance Show TyCon
where
281 showsPrec _
(TyCon _ s
) = showString s
283 isTupleTyCon
:: TyCon
-> Bool
284 isTupleTyCon
(TyCon _
('(':',':_
)) = True
285 isTupleTyCon _
= False
287 -- Some (Show.TypeRep) helpers:
289 showArgs
:: Show a
=> [a
] -> ShowS
291 showArgs
[a
] = showsPrec 10 a
292 showArgs
(a
:as) = showsPrec 10 a
. showString " " . showArgs
as
294 showTuple
:: [TypeRep
] -> ShowS
295 showTuple args
= showChar '('
296 . (foldr (.) id $ intersperse (showChar ',')
297 $ map (showsPrec 10) args
)
300 -------------------------------------------------------------
302 -- The Typeable class and friends
304 -------------------------------------------------------------
306 -- | The class 'Typeable' allows a concrete representation of a type to
308 class Typeable a
where
309 typeOf
:: a
-> TypeRep
310 -- ^ Takes a value of type @a@ and returns a concrete representation
311 -- of that type. The /value/ of the argument should be ignored by
312 -- any instance of 'Typeable', so that it is safe to pass 'undefined' as
315 -- | Variant for unary type constructors
316 class Typeable1 t
where
317 typeOf1
:: t a
-> TypeRep
319 -- | For defining a 'Typeable' instance from any 'Typeable1' instance.
320 typeOfDefault
:: (Typeable1 t
, Typeable a
) => t a
-> TypeRep
321 typeOfDefault x
= typeOf1 x `mkAppTy` typeOf
(argType x
)
326 -- | Variant for binary type constructors
327 class Typeable2 t
where
328 typeOf2
:: t a b
-> TypeRep
330 -- | For defining a 'Typeable1' instance from any 'Typeable2' instance.
331 typeOf1Default
:: (Typeable2 t
, Typeable a
) => t a b
-> TypeRep
332 typeOf1Default x
= typeOf2 x `mkAppTy` typeOf
(argType x
)
334 argType
:: t a b
-> a
337 -- | Variant for 3-ary type constructors
338 class Typeable3 t
where
339 typeOf3
:: t a b c
-> TypeRep
341 -- | For defining a 'Typeable2' instance from any 'Typeable3' instance.
342 typeOf2Default
:: (Typeable3 t
, Typeable a
) => t a b c
-> TypeRep
343 typeOf2Default x
= typeOf3 x `mkAppTy` typeOf
(argType x
)
345 argType
:: t a b c
-> a
348 -- | Variant for 4-ary type constructors
349 class Typeable4 t
where
350 typeOf4
:: t a b c d
-> TypeRep
352 -- | For defining a 'Typeable3' instance from any 'Typeable4' instance.
353 typeOf3Default
:: (Typeable4 t
, Typeable a
) => t a b c d
-> TypeRep
354 typeOf3Default x
= typeOf4 x `mkAppTy` typeOf
(argType x
)
356 argType
:: t a b c d
-> a
359 -- | Variant for 5-ary type constructors
360 class Typeable5 t
where
361 typeOf5
:: t a b c d e
-> TypeRep
363 -- | For defining a 'Typeable4' instance from any 'Typeable5' instance.
364 typeOf4Default
:: (Typeable5 t
, Typeable a
) => t a b c d e
-> TypeRep
365 typeOf4Default x
= typeOf5 x `mkAppTy` typeOf
(argType x
)
367 argType
:: t a b c d e
-> a
370 -- | Variant for 6-ary type constructors
371 class Typeable6 t
where
372 typeOf6
:: t a b c d e f
-> TypeRep
374 -- | For defining a 'Typeable5' instance from any 'Typeable6' instance.
375 typeOf5Default
:: (Typeable6 t
, Typeable a
) => t a b c d e f
-> TypeRep
376 typeOf5Default x
= typeOf6 x `mkAppTy` typeOf
(argType x
)
378 argType
:: t a b c d e f
-> a
381 -- | Variant for 7-ary type constructors
382 class Typeable7 t
where
383 typeOf7
:: t a b c d e f g
-> TypeRep
385 -- | For defining a 'Typeable6' instance from any 'Typeable7' instance.
386 typeOf6Default
:: (Typeable7 t
, Typeable a
) => t a b c d e f g
-> TypeRep
387 typeOf6Default x
= typeOf7 x `mkAppTy` typeOf
(argType x
)
389 argType
:: t a b c d e f g
-> a
392 #ifdef __GLASGOW_HASKELL__
393 -- Given a @Typeable@/n/ instance for an /n/-ary type constructor,
394 -- define the instances for partial applications.
395 -- Programmers using non-GHC implementations must do this manually
396 -- for each type constructor.
397 -- (The INSTANCE_TYPEABLE/n/ macros in Typeable.h include this.)
399 -- | One Typeable instance for all Typeable1 instances
400 instance (Typeable1 s
, Typeable a
)
401 => Typeable
(s a
) where
402 typeOf
= typeOfDefault
404 -- | One Typeable1 instance for all Typeable2 instances
405 instance (Typeable2 s
, Typeable a
)
406 => Typeable1
(s a
) where
407 typeOf1
= typeOf1Default
409 -- | One Typeable2 instance for all Typeable3 instances
410 instance (Typeable3 s
, Typeable a
)
411 => Typeable2
(s a
) where
412 typeOf2
= typeOf2Default
414 -- | One Typeable3 instance for all Typeable4 instances
415 instance (Typeable4 s
, Typeable a
)
416 => Typeable3
(s a
) where
417 typeOf3
= typeOf3Default
419 -- | One Typeable4 instance for all Typeable5 instances
420 instance (Typeable5 s
, Typeable a
)
421 => Typeable4
(s a
) where
422 typeOf4
= typeOf4Default
424 -- | One Typeable5 instance for all Typeable6 instances
425 instance (Typeable6 s
, Typeable a
)
426 => Typeable5
(s a
) where
427 typeOf5
= typeOf5Default
429 -- | One Typeable6 instance for all Typeable7 instances
430 instance (Typeable7 s
, Typeable a
)
431 => Typeable6
(s a
) where
432 typeOf6
= typeOf6Default
434 #endif
/* __GLASGOW_HASKELL__
*/
436 -------------------------------------------------------------
440 -------------------------------------------------------------
442 -- | The type-safe cast operation
443 cast
:: (Typeable a
, Typeable b
) => a
-> Maybe b
446 r
= if typeOf x
== typeOf
(fromJust r
)
447 then Just
$ unsafeCoerce x
450 -- | A flexible variation parameterised in a type constructor
451 gcast
:: (Typeable a
, Typeable b
) => c a
-> Maybe (c b
)
454 r
= if typeOf
(getArg x
) == typeOf
(getArg
(fromJust r
))
455 then Just
$ unsafeCoerce x
461 gcast1
:: (Typeable1 t
, Typeable1 t
') => c
(t a
) -> Maybe (c
(t
' a
))
464 r
= if typeOf1
(getArg x
) == typeOf1
(getArg
(fromJust r
))
465 then Just
$ unsafeCoerce x
470 -- | Cast for * -> * -> *
471 gcast2
:: (Typeable2 t
, Typeable2 t
') => c
(t a b
) -> Maybe (c
(t
' a b
))
474 r
= if typeOf2
(getArg x
) == typeOf2
(getArg
(fromJust r
))
475 then Just
$ unsafeCoerce x
480 -------------------------------------------------------------
482 -- Instances of the Typeable classes for Prelude types
484 -------------------------------------------------------------
486 INSTANCE_TYPEABLE0
((),unitTc
,"()")
487 INSTANCE_TYPEABLE1
([],listTc
,"[]")
488 INSTANCE_TYPEABLE1
(Maybe,maybeTc
,"Maybe")
489 INSTANCE_TYPEABLE1
(Ratio,ratioTc
,"Ratio")
490 INSTANCE_TYPEABLE2
(Either,eitherTc
,"Either")
491 INSTANCE_TYPEABLE2
((->),funTc
,"->")
492 INSTANCE_TYPEABLE1
(IO,ioTc
,"IO")
494 #if defined
(__GLASGOW_HASKELL__
) || defined
(__HUGS__
)
495 -- Types defined in GHC.IOBase
496 INSTANCE_TYPEABLE1
(MVar
,mvarTc
,"MVar" )
499 -- Types defined in GHC.Arr
500 INSTANCE_TYPEABLE2
(Array,arrayTc
,"Array")
502 #ifdef __GLASGOW_HASKELL__
503 -- Hugs has these too, but their Typeable<n> instances are defined
504 -- elsewhere to keep this module within Haskell 98.
505 -- This is important because every invocation of runhugs or ffihugs
506 -- uses this module via Data.Dynamic.
507 INSTANCE_TYPEABLE2
(ST
,stTc
,"ST")
508 INSTANCE_TYPEABLE2
(STRef
,stRefTc
,"STRef")
509 INSTANCE_TYPEABLE3
(STArray
,sTArrayTc
,"STArray")
513 INSTANCE_TYPEABLE2
((,),pairTc
,"(,)")
514 INSTANCE_TYPEABLE3
((,,),tup3Tc
,"(,,)")
517 tup4Tc
= mkTyCon
"(,,,)"
519 instance Typeable4
(,,,) where
520 typeOf4 _
= mkTyConApp tup4Tc
[]
523 tup5Tc
= mkTyCon
"(,,,,)"
525 instance Typeable5
(,,,,) where
526 typeOf5 _
= mkTyConApp tup5Tc
[]
529 tup6Tc
= mkTyCon
"(,,,,,)"
531 instance Typeable6
(,,,,,) where
532 typeOf6 _
= mkTyConApp tup6Tc
[]
535 tup7Tc
= mkTyCon
"(,,,,,,)"
537 instance Typeable7
(,,,,,,) where
538 typeOf7 _
= mkTyConApp tup7Tc
[]
541 INSTANCE_TYPEABLE1
(Ptr
,ptrTc
,"Ptr")
542 INSTANCE_TYPEABLE1
(FunPtr
,funPtrTc
,"FunPtr")
543 INSTANCE_TYPEABLE1
(ForeignPtr
,foreignPtrTc
,"ForeignPtr")
544 INSTANCE_TYPEABLE1
(StablePtr
,stablePtrTc
,"StablePtr")
545 INSTANCE_TYPEABLE1
(IORef
,iORefTc
,"IORef")
547 -------------------------------------------------------
549 -- Generate Typeable instances for standard datatypes
551 -------------------------------------------------------
553 INSTANCE_TYPEABLE0
(Bool,boolTc
,"Bool")
554 INSTANCE_TYPEABLE0
(Char,charTc
,"Char")
555 INSTANCE_TYPEABLE0
(Float,floatTc
,"Float")
556 INSTANCE_TYPEABLE0
(Double,doubleTc
,"Double")
557 INSTANCE_TYPEABLE0
(Int,intTc
,"Int")
559 INSTANCE_TYPEABLE0
(Word
,wordTc
,"Word" )
561 INSTANCE_TYPEABLE0
(Integer,integerTc
,"Integer")
562 INSTANCE_TYPEABLE0
(Ordering,orderingTc
,"Ordering")
563 INSTANCE_TYPEABLE0
(Handle,handleTc
,"Handle")
565 INSTANCE_TYPEABLE0
(Int8
,int8Tc
,"Int8")
566 INSTANCE_TYPEABLE0
(Int16
,int16Tc
,"Int16")
567 INSTANCE_TYPEABLE0
(Int32
,int32Tc
,"Int32")
568 INSTANCE_TYPEABLE0
(Int64
,int64Tc
,"Int64")
570 INSTANCE_TYPEABLE0
(Word8
,word8Tc
,"Word8" )
571 INSTANCE_TYPEABLE0
(Word16
,word16Tc
,"Word16")
572 INSTANCE_TYPEABLE0
(Word32
,word32Tc
,"Word32")
573 INSTANCE_TYPEABLE0
(Word64
,word64Tc
,"Word64")
575 INSTANCE_TYPEABLE0
(TyCon
,tyconTc
,"TyCon")
576 INSTANCE_TYPEABLE0
(TypeRep
,typeRepTc
,"TypeRep")
578 #ifdef __GLASGOW_HASKELL__
579 INSTANCE_TYPEABLE0
(RealWorld
,realWorldTc
,"RealWorld")
582 ---------------------------------------------
586 ---------------------------------------------
589 newtype Key
= Key
Int deriving( Eq
)
592 data KeyPr
= KeyPr
!Key
!Key
deriving( Eq
)
594 hashKP
:: KeyPr
-> Int32
595 hashKP
(KeyPr
(Key k1
) (Key k2
)) = (HT
.hashInt k1
+ HT
.hashInt k2
) `
rem` HT
.prime
597 data Cache
= Cache
{ next_key
:: !(IORef Key
), -- Not used by GHC (calls genSym instead)
598 tc_tbl
:: !(HT
.HashTable
String Key
),
599 ap_tbl
:: !(HT
.HashTable KeyPr Key
) }
601 {-# NOINLINE cache #-}
602 #ifdef __GLASGOW_HASKELL__
603 foreign import ccall unsafe
"RtsTypeable.h getOrSetTypeableStore"
604 getOrSetTypeableStore
:: Ptr a
-> IO (Ptr a
)
608 cache
= unsafePerformIO
$ do
609 empty_tc_tbl
<- HT
.new
(==) HT
.hashString
610 empty_ap_tbl
<- HT
.new
(==) hashKP
611 key_loc
<- newIORef
(Key
1)
612 let ret
= Cache
{ next_key
= key_loc
,
613 tc_tbl
= empty_tc_tbl
,
614 ap_tbl
= empty_ap_tbl
}
615 #ifdef __GLASGOW_HASKELL__
617 stable_ref
<- newStablePtr ret
618 let ref
= castStablePtrToPtr stable_ref
619 ref2
<- getOrSetTypeableStore ref
621 then deRefStablePtr stable_ref
623 freeStablePtr stable_ref
625 (castPtrToStablePtr ref2
)
630 newKey
:: IORef Key
-> IO Key
631 #ifdef __GLASGOW_HASKELL__
632 newKey _
= do i
<- genSym
; return (Key i
)
634 newKey kloc
= do { k
@(Key i
) <- readIORef kloc
;
635 writeIORef kloc
(Key
(i
+1)) ;
639 #ifdef __GLASGOW_HASKELL__
640 foreign import ccall unsafe
"genSymZh"
644 mkTyConKey
:: String -> Key
646 = unsafePerformIO
$ do
647 let Cache
{next_key
= kloc
, tc_tbl
= tbl
} = cache
648 mb_k
<- HT
.lookup tbl str
651 Nothing
-> do { k
<- newKey kloc
;
652 HT
.insert tbl str k
;
655 appKey
:: Key
-> Key
-> Key
657 = unsafePerformIO
$ do
658 let Cache
{next_key
= kloc
, ap_tbl
= tbl
} = cache
659 mb_k
<- HT
.lookup tbl kpr
662 Nothing
-> do { k
<- newKey kloc
;
663 HT
.insert tbl kpr k
;
668 appKeys
:: Key
-> [Key
] -> Key
669 appKeys k ks
= foldl appKey k ks