[project @ 2004-03-22 14:48:56 by malcolm]
[ghc-base.git] / Data / Typeable.hs
1 {-# OPTIONS -fno-implicit-prelude #-}
2 -----------------------------------------------------------------------------
3 -- |
4 -- Module      :  Data.Typeable
5 -- Copyright   :  (c) The University of Glasgow, CWI 2001--2004
6 -- License     :  BSD-style (see the file libraries/base/LICENSE)
7 -- 
8 -- Maintainer  :  libraries@haskell.org
9 -- Stability   :  experimental
10 -- Portability :  portable
11 --
12 -- The Typeable class reifies types to some extent by associating type
13 -- representations to types. These type representations can be compared,
14 -- and one can in turn define a type-safe cast operation. To this end,
15 -- an unsafe cast is guarded by a test for type (representation)
16 -- equivalence. The module Data.Dynamic uses Typeable for an
17 -- implementation of dynamics. The module Data.Generics uses Typeable
18 -- and type-safe cast (but not dynamics) to support the \"Scrap your
19 -- boilerplate\" style of generic programming.
20 --
21 -----------------------------------------------------------------------------
22
23 module Data.Typeable
24   (
25
26         -- * The Typeable class
27         Typeable( typeOf ),     -- :: a -> TypeRep
28
29         -- * Type-safe cast
30         cast,                   -- :: (Typeable a, Typeable b) => a -> Maybe b
31         gcast,                  -- a generalisation of cast
32
33         -- * Type representations
34         TypeRep,        -- abstract, instance of: Eq, Show, Typeable
35         TyCon,          -- abstract, instance of: Eq, Show, Typeable
36
37         -- * Construction of type representations
38         mkTyCon,        -- :: String  -> TyCon
39         mkTyConApp,     -- :: TyCon   -> [TypeRep] -> TypeRep
40         mkAppTy,        -- :: TypeRep -> TypeRep   -> TypeRep
41         mkFunTy,        -- :: TypeRep -> TypeRep   -> TypeRep
42         splitTyConApp,  -- :: TypeRep -> (TyCon, [TypeRep])
43         funResultTy,    -- :: TypeRep -> TypeRep   -> Maybe TypeRep
44
45         -- * Observation of type representations
46         typerepTyCon,   -- :: TypeRep -> TyCon
47         typerepArgs,    -- :: TypeRep -> [TypeRep]
48         tyconString,    -- :: TyCon   -> String
49
50         -- * The other Typeable classes
51         -- | /Note:/ The general instances are provided for GHC only.
52         Typeable1( typeOf1 ),   -- :: t a -> TypeRep
53         Typeable2( typeOf2 ),   -- :: t a b -> TypeRep
54         Typeable3( typeOf3 ),   -- :: t a b c -> TypeRep
55         Typeable4( typeOf4 ),   -- :: t a b c d -> TypeRep
56         Typeable5( typeOf5 ),   -- :: t a b c d e -> TypeRep
57         Typeable6( typeOf6 ),   -- :: t a b c d e f -> TypeRep
58         Typeable7( typeOf7 ),   -- :: t a b c d e f g -> TypeRep
59         gcast1,                 -- :: ... => c (t a) -> Maybe (c (t' a))
60         gcast2,                 -- :: ... => c (t a b) -> Maybe (c (t' a b))
61
62         -- * Default instances
63         -- | /Note:/ These are not needed by GHC, for which these instances
64         -- are generated by general instance declarations.
65         typeOfDefault,  -- :: (Typeable1 t, Typeable a) => t a -> TypeRep
66         typeOf1Default, -- :: (Typeable2 t, Typeable a) => t a b -> TypeRep
67         typeOf2Default, -- :: (Typeable3 t, Typeable a) => t a b c -> TypeRep
68         typeOf3Default, -- :: (Typeable4 t, Typeable a) => t a b c d -> TypeRep
69         typeOf4Default, -- :: (Typeable5 t, Typeable a) => t a b c d e -> TypeRep
70         typeOf5Default, -- :: (Typeable6 t, Typeable a) => t a b c d e f -> TypeRep
71         typeOf6Default  -- :: (Typeable7 t, Typeable a) => t a b c d e f g -> TypeRep
72
73   ) where
74
75 import qualified Data.HashTable as HT
76 import Data.Maybe
77 import Data.Either
78 import Data.Int
79 import Data.Word
80 import Data.List( foldl )
81
82 #ifdef __GLASGOW_HASKELL__
83 import GHC.Base
84 import GHC.Show
85 import GHC.Err
86 import GHC.Num
87 import GHC.Float
88 import GHC.Real( rem, Ratio )
89 import GHC.IOBase
90 import GHC.Ptr          -- So we can give Typeable instance for Ptr
91 import GHC.Stable       -- So we can give Typeable instance for StablePtr
92 #endif
93
94 #ifdef __HUGS__
95 import Hugs.Prelude
96 import Hugs.IO
97 import Hugs.IORef
98 import Hugs.IOExts
99 #endif
100
101 #ifdef __GLASGOW_HASKELL__
102 unsafeCoerce :: a -> b
103 unsafeCoerce = unsafeCoerce#
104 #endif
105
106 #ifdef __NHC__
107 import NonStdUnsafeCoerce (unsafeCoerce)
108 import NHC.IOExtras (IORef,newIORef,readIORef,writeIORef,unsafePerformIO)
109 import IO (Handle)
110 import Ratio (Ratio)
111 import NHC.FFI (Ptr,StablePtr)
112 #else
113 #endif
114
115 #include "Typeable.h"
116
117 #ifndef __HUGS__
118
119 -------------------------------------------------------------
120 --
121 --              Type representations
122 --
123 -------------------------------------------------------------
124
125 -- | A concrete representation of a (monomorphic) type.  'TypeRep'
126 -- supports reasonably efficient equality.
127 data TypeRep = TypeRep !Key TyCon [TypeRep] 
128
129 -- Compare keys for equality
130 instance Eq TypeRep where
131   (TypeRep k1 _ _) == (TypeRep k2 _ _) = k1 == k2
132
133 -- | An abstract representation of a type constructor.  'TyCon' objects can
134 -- be built using 'mkTyCon'.
135 data TyCon = TyCon !Key String
136
137 instance Eq TyCon where
138   (TyCon t1 _) == (TyCon t2 _) = t1 == t2
139
140 #endif
141
142         -- 
143         -- let fTy = mkTyCon "Foo" in show (mkTyConApp (mkTyCon ",,")
144         --                                 [fTy,fTy,fTy])
145         -- 
146         -- returns "(Foo,Foo,Foo)"
147         --
148         -- The TypeRep Show instance promises to print tuple types
149         -- correctly. Tuple type constructors are specified by a 
150         -- sequence of commas, e.g., (mkTyCon ",,,,") returns
151         -- the 5-tuple tycon.
152
153 ----------------- Construction --------------------
154
155 -- | Applies a type constructor to a sequence of types
156 mkTyConApp  :: TyCon -> [TypeRep] -> TypeRep
157 mkTyConApp tc@(TyCon tc_k _) args 
158   = TypeRep (appKeys tc_k arg_ks) tc args
159   where
160     arg_ks = [k | TypeRep k _ _ <- args]
161
162 -- | A special case of 'mkTyConApp', which applies the function 
163 -- type constructor to a pair of types.
164 mkFunTy  :: TypeRep -> TypeRep -> TypeRep
165 mkFunTy f a = mkTyConApp funTc [f,a]
166
167 -- | Splits a type constructor application
168 splitTyConApp :: TypeRep -> (TyCon,[TypeRep])
169 splitTyConApp (TypeRep _ tc trs) = (tc,trs)
170
171 -- | Applies a type to a function type.  Returns: @'Just' u@ if the
172 -- first argument represents a function of type @t -> u@ and the
173 -- second argument represents a function of type @t@.  Otherwise,
174 -- returns 'Nothing'.
175 funResultTy :: TypeRep -> TypeRep -> Maybe TypeRep
176 funResultTy trFun trArg
177   = case splitTyConApp trFun of
178       (tc, [t1,t2]) | tc == funTc && t1 == trArg -> Just t2
179       _ -> Nothing
180
181 -- | Adds a TypeRep argument to a TypeRep.
182 mkAppTy :: TypeRep -> TypeRep -> TypeRep
183 mkAppTy (TypeRep tr_k tc trs) arg_tr
184   = let (TypeRep arg_k _ _) = arg_tr
185      in  TypeRep (appKey tr_k arg_k) tc (trs++[arg_tr])
186
187 -- If we enforce the restriction that there is only one
188 -- @TyCon@ for a type & it is shared among all its uses,
189 -- we can map them onto Ints very simply. The benefit is,
190 -- of course, that @TyCon@s can then be compared efficiently.
191
192 -- Provided the implementor of other @Typeable@ instances
193 -- takes care of making all the @TyCon@s CAFs (toplevel constants),
194 -- this will work. 
195
196 -- If this constraint does turn out to be a sore thumb, changing
197 -- the Eq instance for TyCons is trivial.
198
199 -- | Builds a 'TyCon' object representing a type constructor.  An
200 -- implementation of "Data.Typeable" should ensure that the following holds:
201 --
202 -- >  mkTyCon "a" == mkTyCon "a"
203 --
204
205 mkTyCon :: String       -- ^ the name of the type constructor (should be unique
206                         -- in the program, so it might be wise to use the
207                         -- fully qualified name).
208         -> TyCon        -- ^ A unique 'TyCon' object
209 mkTyCon str = TyCon (mkTyConKey str) str
210
211 ----------------- Observation ---------------------
212
213 -- | Observe the type constructor of a type representation
214 typerepTyCon :: TypeRep -> TyCon
215 typerepTyCon (TypeRep _ tc _) = tc
216
217 -- | Observe the argument types of a type representation
218 typerepArgs :: TypeRep -> [TypeRep]
219 typerepArgs (TypeRep _ _ args) = args
220
221 -- | Observe string encoding of a type representation
222 tyconString :: TyCon   -> String
223 tyconString  (TyCon _ str) = str
224
225 ----------------- Showing TypeReps --------------------
226
227 instance Show TypeRep where
228   showsPrec p (TypeRep _ tycon tys) =
229     case tys of
230       [] -> showsPrec p tycon
231       [x]   | tycon == listTc -> showChar '[' . shows x . showChar ']'
232       [a,r] | tycon == funTc  -> showParen (p > 8) $
233                                  showsPrec 9 a .
234                                  showString " -> " .
235                                  showsPrec 8 r
236       xs | isTupleTyCon tycon -> showTuple tycon xs
237          | otherwise         ->
238             showParen (p > 9) $
239             showsPrec p tycon . 
240             showChar ' '      . 
241             showArgs tys
242
243 instance Show TyCon where
244   showsPrec _ (TyCon _ s) = showString s
245
246 isTupleTyCon :: TyCon -> Bool
247 isTupleTyCon (TyCon _ (',':_)) = True
248 isTupleTyCon _                 = False
249
250 -- Some (Show.TypeRep) helpers:
251
252 showArgs :: Show a => [a] -> ShowS
253 showArgs [] = id
254 showArgs [a] = showsPrec 10 a
255 showArgs (a:as) = showsPrec 10 a . showString " " . showArgs as 
256
257 showTuple :: TyCon -> [TypeRep] -> ShowS
258 showTuple (TyCon _ str) args = showChar '(' . go str args
259  where
260   go [] [a] = showsPrec 10 a . showChar ')'
261   go _  []  = showChar ')' -- a failure condition, really.
262   go (',':xs) (a:as) = showsPrec 10 a . showChar ',' . go xs as
263   go _ _   = showChar ')'
264
265 -------------------------------------------------------------
266 --
267 --      The Typeable class and friends
268 --
269 -------------------------------------------------------------
270
271 -- | The class 'Typeable' allows a concrete representation of a type to
272 -- be calculated.
273 class Typeable a where
274   typeOf :: a -> TypeRep
275   -- ^ Takes a value of type @a@ and returns a concrete representation
276   -- of that type.  The /value/ of the argument should be ignored by
277   -- any instance of 'Typeable', so that it is safe to pass 'undefined' as
278   -- the argument.
279
280 -- | Variant for unary type constructors
281 class Typeable1 t where
282   typeOf1 :: t a -> TypeRep
283
284 -- | For defining a 'Typeable' instance from any 'Typeable1' instance.
285 typeOfDefault :: (Typeable1 t, Typeable a) => t a -> TypeRep
286 typeOfDefault x = typeOf1 x `mkAppTy` typeOf (argType x)
287  where
288    argType :: t a -> a
289    argType =  undefined
290
291 -- | Variant for binary type constructors
292 class Typeable2 t where
293   typeOf2 :: t a b -> TypeRep
294
295 -- | For defining a 'Typeable1' instance from any 'Typeable2' instance.
296 typeOf1Default :: (Typeable2 t, Typeable a) => t a b -> TypeRep
297 typeOf1Default x = typeOf2 x `mkAppTy` typeOf (argType x)
298  where
299    argType :: t a b -> a
300    argType =  undefined
301
302 -- | Variant for 3-ary type constructors
303 class Typeable3 t where
304   typeOf3 :: t a b c -> TypeRep
305
306 -- | For defining a 'Typeable2' instance from any 'Typeable3' instance.
307 typeOf2Default :: (Typeable3 t, Typeable a) => t a b c -> TypeRep
308 typeOf2Default x = typeOf3 x `mkAppTy` typeOf (argType x)
309  where
310    argType :: t a b c -> a
311    argType =  undefined
312
313 -- | Variant for 4-ary type constructors
314 class Typeable4 t where
315   typeOf4 :: t a b c d -> TypeRep
316
317 -- | For defining a 'Typeable3' instance from any 'Typeable4' instance.
318 typeOf3Default :: (Typeable4 t, Typeable a) => t a b c d -> TypeRep
319 typeOf3Default x = typeOf4 x `mkAppTy` typeOf (argType x)
320  where
321    argType :: t a b c d -> a
322    argType =  undefined
323
324 -- | Variant for 5-ary type constructors
325 class Typeable5 t where
326   typeOf5 :: t a b c d e -> TypeRep
327
328 -- | For defining a 'Typeable4' instance from any 'Typeable5' instance.
329 typeOf4Default :: (Typeable5 t, Typeable a) => t a b c d e -> TypeRep
330 typeOf4Default x = typeOf5 x `mkAppTy` typeOf (argType x)
331  where
332    argType :: t a b c d e -> a
333    argType =  undefined
334
335 -- | Variant for 6-ary type constructors
336 class Typeable6 t where
337   typeOf6 :: t a b c d e f -> TypeRep
338
339 -- | For defining a 'Typeable5' instance from any 'Typeable6' instance.
340 typeOf5Default :: (Typeable6 t, Typeable a) => t a b c d e f -> TypeRep
341 typeOf5Default x = typeOf6 x `mkAppTy` typeOf (argType x)
342  where
343    argType :: t a b c d e f -> a
344    argType =  undefined
345
346 -- | Variant for 7-ary type constructors
347 class Typeable7 t where
348   typeOf7 :: t a b c d e f g -> TypeRep
349
350 -- | For defining a 'Typeable6' instance from any 'Typeable7' instance.
351 typeOf6Default :: (Typeable7 t, Typeable a) => t a b c d e f g -> TypeRep
352 typeOf6Default x = typeOf7 x `mkAppTy` typeOf (argType x)
353  where
354    argType :: t a b c d e f g -> a
355    argType =  undefined
356
357 #ifdef __GLASGOW_HASKELL__
358 -- Given a @Typeable@/n/ instance for an /n/-ary type constructor,
359 -- define the instances for partial applications.
360 -- Programmers using non-GHC implementations must do this manually
361 -- for each type constructor.
362 -- (The INSTANCE_TYPEABLE/n/ macros in Typeable.h include this.)
363
364 -- | One Typeable instance for all Typeable1 instances
365 instance (Typeable1 s, Typeable a)
366        => Typeable (s a) where
367   typeOf = typeOfDefault
368
369 -- | One Typeable1 instance for all Typeable2 instances
370 instance (Typeable2 s, Typeable a)
371        => Typeable1 (s a) where
372   typeOf1 = typeOf1Default
373
374 -- | One Typeable2 instance for all Typeable3 instances
375 instance (Typeable3 s, Typeable a)
376        => Typeable2 (s a) where
377   typeOf2 = typeOf2Default
378
379 -- | One Typeable3 instance for all Typeable4 instances
380 instance (Typeable4 s, Typeable a)
381        => Typeable3 (s a) where
382   typeOf3 = typeOf3Default
383
384 -- | One Typeable4 instance for all Typeable5 instances
385 instance (Typeable5 s, Typeable a)
386        => Typeable4 (s a) where
387   typeOf4 = typeOf4Default
388
389 -- | One Typeable5 instance for all Typeable6 instances
390 instance (Typeable6 s, Typeable a)
391        => Typeable5 (s a) where
392   typeOf5 = typeOf5Default
393
394 -- | One Typeable6 instance for all Typeable7 instances
395 instance (Typeable7 s, Typeable a)
396        => Typeable6 (s a) where
397   typeOf6 = typeOf6Default
398
399 #endif /* __GLASGOW_HASKELL__ */
400
401 -------------------------------------------------------------
402 --
403 --              Type-safe cast
404 --
405 -------------------------------------------------------------
406
407 -- | The type-safe cast operation
408 cast :: (Typeable a, Typeable b) => a -> Maybe b
409 cast x = r
410        where
411          r = if typeOf x == typeOf (fromJust r)
412                then Just $ unsafeCoerce x
413                else Nothing
414
415 -- | A flexible variation parameterised in a type constructor
416 gcast :: (Typeable a, Typeable b) => c a -> Maybe (c b)
417 gcast x = r
418  where
419   r = if typeOf (getArg x) == typeOf (getArg (fromJust r))
420         then Just $ unsafeCoerce x
421         else Nothing
422   getArg :: c x -> x 
423   getArg = undefined
424
425 -- | Cast for * -> *
426 gcast1 :: (Typeable1 t, Typeable1 t') => c (t a) -> Maybe (c (t' a)) 
427 gcast1 x = r
428  where
429   r = if typeOf1 (getArg x) == typeOf1 (getArg (fromJust r))
430        then Just $ unsafeCoerce x
431        else Nothing
432   getArg :: c x -> x 
433   getArg = undefined
434
435 -- | Cast for * -> * -> *
436 gcast2 :: (Typeable2 t, Typeable2 t') => c (t a b) -> Maybe (c (t' a b)) 
437 gcast2 x = r
438  where
439   r = if typeOf2 (getArg x) == typeOf2 (getArg (fromJust r))
440        then Just $ unsafeCoerce x
441        else Nothing
442   getArg :: c x -> x 
443   getArg = undefined
444
445 -------------------------------------------------------------
446 --
447 --      Instances of the Typeable classes for Prelude types
448 --
449 -------------------------------------------------------------
450
451 INSTANCE_TYPEABLE1([],listTc,"[]")
452 INSTANCE_TYPEABLE1(Maybe,maybeTc,"Maybe")
453 INSTANCE_TYPEABLE1(Ratio,ratioTc,"Ratio")
454 INSTANCE_TYPEABLE2(Either,eitherTc,"Either")
455 INSTANCE_TYPEABLE2((->),funTc,"->")
456 INSTANCE_TYPEABLE1(IO,ioTc,"IO")
457 INSTANCE_TYPEABLE0((),unitTc,"()")
458 #ifndef __NHC__
459 INSTANCE_TYPEABLE2((,),pairTc,",")
460 INSTANCE_TYPEABLE3((,,),tup3Tc,",,")
461
462 tup4Tc :: TyCon
463 tup4Tc = mkTyCon ",,,"
464
465 instance Typeable4 (,,,) where
466   typeOf4 tu = mkTyConApp tup4Tc []
467
468 tup5Tc :: TyCon
469 tup5Tc = mkTyCon ",,,,"
470
471 instance Typeable5 (,,,,) where
472   typeOf5 tu = mkTyConApp tup5Tc []
473
474 tup6Tc :: TyCon
475 tup6Tc = mkTyCon ",,,,,"
476
477 instance Typeable6 (,,,,,) where
478   typeOf6 tu = mkTyConApp tup6Tc []
479
480 tup7Tc :: TyCon
481 tup7Tc = mkTyCon ",,,,,"
482
483 instance Typeable7 (,,,,,,) where
484   typeOf7 tu = mkTyConApp tup7Tc []
485
486 #endif /* __NHC__ */
487 INSTANCE_TYPEABLE1(Ptr,ptrTc,"Foreign.Ptr.Ptr")
488 INSTANCE_TYPEABLE1(StablePtr,stableptrTc,"Foreign.StablePtr.StablePtr")
489 INSTANCE_TYPEABLE1(IORef,iorefTc,"Data.IORef.IORef")
490
491 -------------------------------------------------------
492 --
493 -- Generate Typeable instances for standard datatypes
494 --
495 -------------------------------------------------------
496
497 INSTANCE_TYPEABLE0(Bool,boolTc,"Bool")
498 INSTANCE_TYPEABLE0(Char,charTc,"Char")
499 INSTANCE_TYPEABLE0(Float,floatTc,"Float")
500 INSTANCE_TYPEABLE0(Double,doubleTc,"Double")
501 INSTANCE_TYPEABLE0(Int,intTc,"Int")
502 INSTANCE_TYPEABLE0(Integer,integerTc,"Integer")
503 INSTANCE_TYPEABLE0(Ordering,orderingTc,"Ordering")
504 INSTANCE_TYPEABLE0(Handle,handleTc,"Handle")
505
506 INSTANCE_TYPEABLE0(Int8,int8Tc,"Int8")
507 INSTANCE_TYPEABLE0(Int16,int16Tc,"Int16")
508 INSTANCE_TYPEABLE0(Int32,int32Tc,"Int32")
509 INSTANCE_TYPEABLE0(Int64,int64Tc,"Int64")
510
511 INSTANCE_TYPEABLE0(Word8,word8Tc,"Word8" )
512 INSTANCE_TYPEABLE0(Word16,word16Tc,"Word16")
513 INSTANCE_TYPEABLE0(Word32,word32Tc,"Word32")
514 INSTANCE_TYPEABLE0(Word64,word64Tc,"Word64")
515
516 INSTANCE_TYPEABLE0(TyCon,tyconTc,"TyCon")
517 INSTANCE_TYPEABLE0(TypeRep,typeRepTc,"TypeRep")
518
519 #ifdef __GLASGOW_HASKELL__
520 INSTANCE_TYPEABLE0(Word,wordTc,"Word" )
521 #endif
522
523 ---------------------------------------------
524 --
525 --              Internals 
526 --
527 ---------------------------------------------
528
529 #ifndef __HUGS__
530 newtype Key = Key Int deriving( Eq )
531 #endif
532
533 data KeyPr = KeyPr !Key !Key deriving( Eq )
534
535 hashKP :: KeyPr -> Int32
536 hashKP (KeyPr (Key k1) (Key k2)) = (HT.hashInt k1 + HT.hashInt k2) `rem` HT.prime
537
538 data Cache = Cache { next_key :: !(IORef Key),
539                      tc_tbl   :: !(HT.HashTable String Key),
540                      ap_tbl   :: !(HT.HashTable KeyPr Key) }
541
542 {-# NOINLINE cache #-}
543 cache :: Cache
544 cache = unsafePerformIO $ do
545                 empty_tc_tbl <- HT.new (==) HT.hashString
546                 empty_ap_tbl <- HT.new (==) hashKP
547                 key_loc      <- newIORef (Key 1) 
548                 return (Cache { next_key = key_loc,
549                                 tc_tbl = empty_tc_tbl, 
550                                 ap_tbl = empty_ap_tbl })
551
552 newKey :: IORef Key -> IO Key
553 #ifdef __GLASGOW_HASKELL__
554 newKey kloc = do i <- genSym; return (Key i)
555 #else
556 newKey kloc = do { k@(Key i) <- readIORef kloc ;
557                    writeIORef kloc (Key (i+1)) ;
558                    return k }
559 #endif
560
561 #ifdef __GLASGOW_HASKELL__
562 -- In GHC we use the RTS's genSym function to get a new unique,
563 -- because in GHCi we might have two copies of the Data.Typeable
564 -- library running (one in the compiler and one in the running
565 -- program), and we need to make sure they don't share any keys.  
566 --
567 -- This is really a hack.  A better solution would be to centralise the
568 -- whole mutable state used by this module, i.e. both hashtables.  But
569 -- the current solution solves the immediate problem, which is that
570 -- dynamics generated in one world with one type were erroneously
571 -- being recognised by the other world as having a different type.
572 foreign import ccall unsafe "genSymZh"
573   genSym :: IO Int
574 #endif
575
576 mkTyConKey :: String -> Key
577 mkTyConKey str 
578   = unsafePerformIO $ do
579         let Cache {next_key = kloc, tc_tbl = tbl} = cache
580         mb_k <- HT.lookup tbl str
581         case mb_k of
582           Just k  -> return k
583           Nothing -> do { k <- newKey kloc ;
584                           HT.insert tbl str k ;
585                           return k }
586
587 appKey :: Key -> Key -> Key
588 appKey k1 k2
589   = unsafePerformIO $ do
590         let Cache {next_key = kloc, ap_tbl = tbl} = cache
591         mb_k <- HT.lookup tbl kpr
592         case mb_k of
593           Just k  -> return k
594           Nothing -> do { k <- newKey kloc ;
595                           HT.insert tbl kpr k ;
596                           return k }
597   where
598     kpr = KeyPr k1 k2
599
600 appKeys :: Key -> [Key] -> Key
601 appKeys k ks = foldl appKey k ks