[project @ 2004-03-19 20:31:50 by panne]
[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         mkAppTy,        -- :: TyCon   -> [TypeRep] -> TypeRep
40         mkFunTy,        -- :: TypeRep -> TypeRep   -> TypeRep
41         applyTy,        -- :: TypeRep -> TypeRep   -> Maybe TypeRep
42         popStarTy,      -- :: TypeRep -> TypeRep   -> TypeRep
43
44         -- * Observation of type representations
45         typerepTyCon,   -- :: TypeRep -> TyCon
46         typerepArgs,    -- :: TypeRep -> [TypeRep]
47         tyconString,    -- :: TyCon   -> String
48
49         -- * The other Typeable classes
50         Typeable1( typeOf1 ),   -- :: t a -> TypeRep
51         Typeable2( typeOf2 ),   -- :: t a b -> TypeRep
52         Typeable3( typeOf3 ),   -- :: t a b c -> TypeRep
53         Typeable4( typeOf4 ),   -- :: t a b c d -> TypeRep
54         Typeable5( typeOf5 ),   -- :: t a b c d e -> TypeRep
55         Typeable6( typeOf6 ),   -- :: t a b c d e f -> TypeRep
56         Typeable7( typeOf7 ),   -- :: t a b c d e f g -> TypeRep
57         gcast1,                 -- :: ... => c (t a) -> Maybe (c (t' a))
58         gcast2                  -- :: ... => c (t a b) -> Maybe (c (t' a b))
59
60   ) where
61
62
63 import qualified Data.HashTable as HT
64 import Data.Maybe
65 import Data.Either
66 import Data.Int
67 import Data.Word
68 import Data.List( foldl )
69
70 #ifdef __GLASGOW_HASKELL__
71 import GHC.Base
72 import GHC.Show
73 import GHC.Err
74 import GHC.Num
75 import GHC.Float
76 import GHC.Real( rem, Ratio )
77 import GHC.IOBase
78 import GHC.Ptr          -- So we can give Typeable instance for Ptr
79 import GHC.Stable       -- So we can give Typeable instance for StablePtr
80 #endif
81
82 #ifdef __HUGS__
83 import Hugs.Prelude
84 import Hugs.IO
85 import Hugs.IORef
86 import Hugs.IOExts
87 #endif
88
89 #ifdef __GLASGOW_HASKELL__
90 unsafeCoerce :: a -> b
91 unsafeCoerce = unsafeCoerce#
92 #endif
93
94 #ifdef __NHC__
95 import NonStdUnsafeCoerce (unsafeCoerce)
96 import NHC.IOExtras (IORef,newIORef,readIORef,writeIORef,unsafePerformIO)
97 #else
98 #include "Typeable.h"
99 #endif
100
101
102 #ifndef __HUGS__
103
104 -------------------------------------------------------------
105 --
106 --              Type representations
107 --
108 -------------------------------------------------------------
109
110
111 -- | A concrete representation of a (monomorphic) type.  'TypeRep'
112 -- supports reasonably efficient equality.
113 data TypeRep = TypeRep !Key TyCon [TypeRep] 
114
115 -- Compare keys for equality
116 instance Eq TypeRep where
117   (TypeRep k1 _ _) == (TypeRep k2 _ _) = k1 == k2
118
119 -- | An abstract representation of a type constructor.  'TyCon' objects can
120 -- be built using 'mkTyCon'.
121 data TyCon = TyCon !Key String
122
123 instance Eq TyCon where
124   (TyCon t1 _) == (TyCon t2 _) = t1 == t2
125
126 #endif
127
128         -- 
129         -- let fTy = mkTyCon "Foo" in show (mkAppTy (mkTyCon ",,")
130         --                                 [fTy,fTy,fTy])
131         -- 
132         -- returns "(Foo,Foo,Foo)"
133         --
134         -- The TypeRep Show instance promises to print tuple types
135         -- correctly. Tuple type constructors are specified by a 
136         -- sequence of commas, e.g., (mkTyCon ",,,,") returns
137         -- the 5-tuple tycon.
138
139
140 ----------------- Construction --------------------
141
142 -- | Applies a type constructor to a sequence of types
143 mkAppTy  :: TyCon -> [TypeRep] -> TypeRep
144 mkAppTy tc@(TyCon tc_k _) args 
145   = TypeRep (appKeys tc_k arg_ks) tc args
146   where
147     arg_ks = [k | TypeRep k _ _ <- args]
148
149
150 -- The function type constructor
151 funTc :: TyCon
152 funTc = mkTyCon "->"
153
154
155 -- | A special case of 'mkAppTy', which applies the function 
156 -- type constructor to a pair of types.
157 mkFunTy  :: TypeRep -> TypeRep -> TypeRep
158 mkFunTy f a = mkAppTy funTc [f,a]
159
160
161 -- | Applies a type to a function type.  Returns: @'Just' u@ if the
162 -- first argument represents a function of type @t -> u@ and the
163 -- second argument represents a function of type @t@.  Otherwise,
164 -- returns 'Nothing'.
165 applyTy :: TypeRep -> TypeRep -> Maybe TypeRep
166 applyTy (TypeRep _ tc [t1,t2]) t3
167   | tc == funTc && t1 == t3     = Just t2
168 applyTy _ _                     = Nothing
169
170
171 -- | Adds a TypeRep argument to a TypeRep.
172 popStarTy :: TypeRep -> TypeRep -> TypeRep
173 popStarTy (TypeRep tr_k tc trs) arg_tr
174   = let (TypeRep arg_k _ _) = arg_tr
175      in  TypeRep (appKey tr_k arg_k) tc (trs++[arg_tr])
176
177
178 -- If we enforce the restriction that there is only one
179 -- @TyCon@ for a type & it is shared among all its uses,
180 -- we can map them onto Ints very simply. The benefit is,
181 -- of course, that @TyCon@s can then be compared efficiently.
182
183 -- Provided the implementor of other @Typeable@ instances
184 -- takes care of making all the @TyCon@s CAFs (toplevel constants),
185 -- this will work. 
186
187 -- If this constraint does turn out to be a sore thumb, changing
188 -- the Eq instance for TyCons is trivial.
189
190 -- | Builds a 'TyCon' object representing a type constructor.  An
191 -- implementation of "Data.Typeable" should ensure that the following holds:
192 --
193 -- >  mkTyCon "a" == mkTyCon "a"
194 --
195
196 mkTyCon :: String       -- ^ the name of the type constructor (should be unique
197                         -- in the program, so it might be wise to use the
198                         -- fully qualified name).
199         -> TyCon        -- ^ A unique 'TyCon' object
200 mkTyCon str = TyCon (mkTyConKey str) str
201
202
203
204 ----------------- Observation ---------------------
205
206
207 -- | Observe the type constructor of a type representation
208 typerepTyCon :: TypeRep -> TyCon
209 typerepTyCon (TypeRep _ tc _) = tc
210
211
212 -- | Observe the argument types of a type representation
213 typerepArgs :: TypeRep -> [TypeRep]
214 typerepArgs (TypeRep _ _ args) = args
215
216
217 -- | Observe string encoding of a type representation
218 tyconString :: TyCon   -> String
219 tyconString  (TyCon _ str) = str
220
221
222 ----------------- Showing TypeReps --------------------
223
224 instance Show TypeRep where
225   showsPrec p (TypeRep _ tycon tys) =
226     case tys of
227       [] -> showsPrec p tycon
228       [x]   | tycon == listTc -> showChar '[' . shows x . showChar ']'
229       [a,r] | tycon == funTc  -> showParen (p > 8) $
230                                  showsPrec 9 a .
231                                  showString " -> " .
232                                  showsPrec 8 r
233       xs | isTupleTyCon tycon -> showTuple tycon xs
234          | otherwise         ->
235             showParen (p > 9) $
236             showsPrec p tycon . 
237             showChar ' '      . 
238             showArgs tys
239
240 instance Show TyCon where
241   showsPrec _ (TyCon _ s) = showString s
242
243 isTupleTyCon :: TyCon -> Bool
244 isTupleTyCon (TyCon _ (',':_)) = True
245 isTupleTyCon _                 = False
246
247
248 -- Some (Show.TypeRep) helpers:
249
250 showArgs :: Show a => [a] -> ShowS
251 showArgs [] = id
252 showArgs [a] = showsPrec 10 a
253 showArgs (a:as) = showsPrec 10 a . showString " " . showArgs as 
254
255 showTuple :: TyCon -> [TypeRep] -> ShowS
256 showTuple (TyCon _ str) args = showChar '(' . go str args
257  where
258   go [] [a] = showsPrec 10 a . showChar ')'
259   go _  []  = showChar ')' -- a failure condition, really.
260   go (',':xs) (a:as) = showsPrec 10 a . showChar ',' . go xs as
261   go _ _   = showChar ')'
262
263
264 -------------------------------------------------------------
265 --
266 --      The Typeable class and friends
267 --
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 -- HACK HACK HACK
281 #ifdef __HUGS__
282 #define INSTANCE_TYPEABLE1x(tycon,tcname,str) \
283 instance Typeable a => Typeable (tycon a) where { \
284   typeOf x = mkAppTy tcname [typeOf ((undefined :: tycon a -> a) x) ] }
285 #define INSTANCE_TYPEABLE2x(tycon,tcname,str) \
286 instance (Typeable a, Typeable b) => Typeable (tycon a b) where { \
287   typeOf x = mkAppTy tcname [typeOf ((undefined :: tycon a b -> a) x), \
288                              typeOf ((undefined :: tycon a b -> b) x)] }
289
290 INSTANCE_TYPEABLE1x(Ratio,ratioTc,"Ratio")
291 INSTANCE_TYPEABLE2x(Either,eitherTc,"Either")
292 INSTANCE_TYPEABLE1(IO,ioTc,"IO")
293 INSTANCE_TYPEABLE1x(Maybe,maybeTc,"Maybe")
294 INSTANCE_TYPEABLE1(Ptr,ptrTc,"Ptr")
295 INSTANCE_TYPEABLE1(StablePtr,stablePtrTc,"StablePtr")
296 INSTANCE_TYPEABLE1(IORef,ioRefTc,"IORef")
297 #endif
298
299 -- | Variant for unary type constructors
300 class Typeable1 t where
301   typeOf1 :: t a -> TypeRep
302
303
304 #ifndef __HUGS__
305 -- | One Typeable instance for all Typeable1 instances
306 instance (Typeable1 s, Typeable a)
307        => Typeable (s a) where
308   typeOf x = typeOf1 x `popStarTy` typeOf (argType x)
309    where
310      argType :: t x -> x
311      argType =  undefined
312 #endif
313
314
315 -- | Variant for binary type constructors
316 class Typeable2 t where
317   typeOf2 :: t a b -> TypeRep
318
319
320 #ifndef __HUGS__
321 -- | One Typeable1 instance for all Typeable2 instances
322 instance (Typeable2 s, Typeable a)
323        => Typeable1 (s a) where
324   typeOf1 x = typeOf2 x `popStarTy` typeOf (argType x)
325    where
326      argType :: t x y -> x
327      argType =  undefined
328 #endif
329
330
331 -- | Variant for 3-ary type constructors
332 class Typeable3 t where
333   typeOf3 :: t a b c -> TypeRep
334
335
336 #ifndef __HUGS__
337 -- | One Typeable2 instance for all Typeable3 instances
338 instance (Typeable3 s, Typeable a)
339        => Typeable2 (s a) where
340   typeOf2 x = typeOf3 x `popStarTy` typeOf (argType x)
341    where
342      argType :: t x y z -> x
343      argType =  undefined
344 #endif
345
346
347 -- | Variant for 4-ary type constructors
348 class Typeable4 t where
349   typeOf4 :: t a b c d -> TypeRep
350
351
352 #ifndef __HUGS__
353 -- | One Typeable3 instance for all Typeable4 instances
354 instance (Typeable4 s, Typeable a)
355        => Typeable3 (s a) where
356   typeOf3 x = typeOf4 x `popStarTy` typeOf (argType x)
357    where
358      argType :: t x y z z' -> x
359      argType =  undefined
360 #endif
361
362
363 -- | Variant for 5-ary type constructors
364 class Typeable5 t where
365   typeOf5 :: t a b c d e -> TypeRep
366
367
368 #ifndef __HUGS__
369 -- | One Typeable4 instance for all Typeable5 instances
370 instance (Typeable5 s, Typeable a)
371        => Typeable4 (s a) where
372   typeOf4 x = typeOf5 x `popStarTy` typeOf (argType x)
373    where
374      argType :: t x y z z' z'' -> x
375      argType =  undefined
376 #endif
377
378
379 -- | Variant for 6-ary type constructors
380 class Typeable6 t where
381   typeOf6 :: t a b c d e f -> TypeRep
382
383
384 #ifndef __HUGS__
385 -- | One Typeable5 instance for all Typeable6 instances
386 instance (Typeable6 s, Typeable a)
387        => Typeable5 (s a) where
388   typeOf5 x = typeOf6 x `popStarTy` typeOf (argType x)
389    where
390      argType :: t x y z z' z'' z''' -> x
391      argType =  undefined
392 #endif
393
394
395 -- | Variant for 7-ary type constructors
396 class Typeable7 t where
397   typeOf7 :: t a b c d e f g -> TypeRep
398
399
400 #ifndef __HUGS__
401 -- | One Typeable6 instance for all Typeable7 instances
402 instance (Typeable7 s, Typeable a)
403        => Typeable6 (s a) where
404   typeOf6 x = typeOf7 x `popStarTy` typeOf (argType x)
405    where
406      argType :: t x y z z' z'' z''' z'''' -> x
407      argType =  undefined
408 #endif
409
410
411
412 -------------------------------------------------------------
413 --
414 --              Type-safe cast
415 --
416 -------------------------------------------------------------
417
418 -- | The type-safe cast operation
419 cast :: (Typeable a, Typeable b) => a -> Maybe b
420 cast x = r
421        where
422          r = if typeOf x == typeOf (fromJust r)
423                then Just $ unsafeCoerce x
424                else Nothing
425
426
427 -- | A flexible variation parameterised in a type constructor
428 gcast :: (Typeable a, Typeable b) => c a -> Maybe (c b)
429 gcast x = r
430  where
431   r = if typeOf (getArg x) == typeOf (getArg (fromJust r))
432         then Just $ unsafeCoerce x
433         else Nothing
434   getArg :: c x -> x 
435   getArg = undefined
436
437
438
439 -- | Cast for * -> *
440 gcast1 :: (Typeable1 t, Typeable1 t') => c (t a) -> Maybe (c (t' a)) 
441 gcast1 x = r
442  where
443   r = if typeOf1 (getArg x) == typeOf1 (getArg (fromJust r))
444        then Just $ unsafeCoerce x
445        else Nothing
446   getArg :: c x -> x 
447   getArg = undefined
448
449
450 -- | Cast for * -> * -> *
451 gcast2 :: (Typeable2 t, Typeable2 t') => c (t a b) -> Maybe (c (t' a b)) 
452 gcast2 x = r
453  where
454   r = if typeOf2 (getArg x) == typeOf2 (getArg (fromJust r))
455        then Just $ unsafeCoerce x
456        else Nothing
457   getArg :: c x -> x 
458   getArg = undefined
459
460
461
462 -------------------------------------------------------------
463 --
464 --      Instances of the Typeable classes for Prelude types
465 --
466 -------------------------------------------------------------
467
468 unitTc :: TyCon
469 unitTc = mkTyCon "()"
470
471 instance Typeable () where
472   typeOf _ = mkAppTy unitTc []
473
474
475 tup3Tc :: TyCon
476 tup3Tc = mkTyCon ",,"
477
478 instance Typeable3 (,,) where
479   typeOf3 tu = mkAppTy tup3Tc []
480
481
482 tup4Tc :: TyCon
483 tup4Tc = mkTyCon ",,,"
484
485 instance Typeable4 (,,,) where
486   typeOf4 tu = mkAppTy tup4Tc []
487
488
489 tup5Tc :: TyCon
490 tup5Tc = mkTyCon ",,,,"
491
492 instance Typeable5 (,,,,) where
493   typeOf5 tu = mkAppTy tup5Tc []
494
495
496 tup6Tc :: TyCon
497 tup6Tc = mkTyCon ",,,,,"
498
499 instance Typeable6 (,,,,,) where
500   typeOf6 tu = mkAppTy tup6Tc []
501
502
503 tup7Tc :: TyCon
504 tup7Tc = mkTyCon ",,,,,"
505
506 instance Typeable7 (,,,,,,) where
507   typeOf7 tu = mkAppTy tup7Tc []
508
509
510 listTc :: TyCon
511 listTc = mkTyCon "[]"
512
513 -- | Instance for lists
514 instance Typeable1 [] where
515   typeOf1 _ = mkAppTy listTc []
516
517
518 maybeTc :: TyCon
519 maybeTc = mkTyCon "Maybe"
520
521 -- | Instance for maybes
522 instance Typeable1 Maybe where
523   typeOf1 _ = mkAppTy maybeTc []
524
525
526 ratioTc :: TyCon
527 ratioTc = mkTyCon "Ratio"
528
529 -- | Instance for ratios
530 instance Typeable1 Ratio where
531   typeOf1 _ = mkAppTy ratioTc []
532
533
534 pairTc :: TyCon
535 pairTc = mkTyCon "(,)"
536
537 -- | Instance for products
538 instance Typeable2 (,) where
539   typeOf2 _ = mkAppTy pairTc []
540
541
542 eitherTc :: TyCon
543 eitherTc = mkTyCon "Either"
544
545 -- | Instance for sums
546 instance Typeable2 Either where
547   typeOf2 _ = mkAppTy eitherTc []
548
549
550 -- | Instance for functions
551 instance Typeable2 (->) where
552   typeOf2 _ = mkAppTy funTc []
553
554
555 #ifdef __GLASGOW_HASKELL__
556
557 ioTc :: TyCon
558 ioTc = mkTyCon "GHC.IOBase.IO"
559
560 instance Typeable1 IO where
561   typeOf1 _ = mkAppTy ioTc []
562
563
564 ptrTc :: TyCon
565 ptrTc = mkTyCon "GHC.Ptr.Ptr"
566
567 instance Typeable1 Ptr where
568   typeOf1 _ = mkAppTy ptrTc []
569
570
571 stableptrTc :: TyCon
572 stableptrTc = mkTyCon "GHC.Stable.StablePtr"
573
574 instance Typeable1 StablePtr where
575   typeOf1 _ = mkAppTy stableptrTc []
576
577
578 iorefTc :: TyCon
579 iorefTc = mkTyCon "GHC.IOBase.IORef"
580
581 instance Typeable1 IORef where
582   typeOf1 _ = mkAppTy iorefTc []
583
584 #endif
585
586
587
588 -------------------------------------------------------
589 --
590 -- Generate Typeable instances for standard datatypes
591 --
592 -------------------------------------------------------
593
594 #ifndef __NHC__
595 INSTANCE_TYPEABLE0(Bool,boolTc,"Bool")
596 INSTANCE_TYPEABLE0(Char,charTc,"Char")
597 INSTANCE_TYPEABLE0(Float,floatTc,"Float")
598 INSTANCE_TYPEABLE0(Double,doubleTc,"Double")
599 INSTANCE_TYPEABLE0(Int,intTc,"Int")
600 INSTANCE_TYPEABLE0(Integer,integerTc,"Integer")
601 INSTANCE_TYPEABLE0(Ordering,orderingTc,"Ordering")
602 INSTANCE_TYPEABLE0(Handle,handleTc,"Handle")
603
604 INSTANCE_TYPEABLE0(Int8,int8Tc,"Int8")
605 INSTANCE_TYPEABLE0(Int16,int16Tc,"Int16")
606 INSTANCE_TYPEABLE0(Int32,int32Tc,"Int32")
607 INSTANCE_TYPEABLE0(Int64,int64Tc,"Int64")
608
609 INSTANCE_TYPEABLE0(Word8,word8Tc,"Word8" )
610 INSTANCE_TYPEABLE0(Word16,word16Tc,"Word16")
611 INSTANCE_TYPEABLE0(Word32,word32Tc,"Word32")
612 INSTANCE_TYPEABLE0(Word64,word64Tc,"Word64")
613
614 INSTANCE_TYPEABLE0(TyCon,tyconTc,"TyCon")
615 INSTANCE_TYPEABLE0(TypeRep,typeRepTc,"TypeRep")
616 #endif
617
618 #ifdef __GLASGOW_HASKELL__
619 INSTANCE_TYPEABLE0(Word,wordTc,"Word" )
620 #endif
621
622
623
624 ---------------------------------------------
625 --
626 --              Internals 
627 --
628 ---------------------------------------------
629
630 #ifndef __HUGS__
631 newtype Key = Key Int deriving( Eq )
632 #endif
633
634 data KeyPr = KeyPr !Key !Key deriving( Eq )
635
636 hashKP :: KeyPr -> Int32
637 hashKP (KeyPr (Key k1) (Key k2)) = (HT.hashInt k1 + HT.hashInt k2) `rem` HT.prime
638
639 data Cache = Cache { next_key :: !(IORef Key),
640                      tc_tbl   :: !(HT.HashTable String Key),
641                      ap_tbl   :: !(HT.HashTable KeyPr Key) }
642
643 {-# NOINLINE cache #-}
644 cache :: Cache
645 cache = unsafePerformIO $ do
646                 empty_tc_tbl <- HT.new (==) HT.hashString
647                 empty_ap_tbl <- HT.new (==) hashKP
648                 key_loc      <- newIORef (Key 1) 
649                 return (Cache { next_key = key_loc,
650                                 tc_tbl = empty_tc_tbl, 
651                                 ap_tbl = empty_ap_tbl })
652
653 newKey :: IORef Key -> IO Key
654 #ifdef __GLASGOW_HASKELL__
655 newKey kloc = do i <- genSym; return (Key i)
656 #else
657 newKey kloc = do { k@(Key i) <- readIORef kloc ;
658                    writeIORef kloc (Key (i+1)) ;
659                    return k }
660 #endif
661
662 #ifdef __GLASGOW_HASKELL__
663 -- In GHC we use the RTS's genSym function to get a new unique,
664 -- because in GHCi we might have two copies of the Data.Typeable
665 -- library running (one in the compiler and one in the running
666 -- program), and we need to make sure they don't share any keys.  
667 --
668 -- This is really a hack.  A better solution would be to centralise the
669 -- whole mutable state used by this module, i.e. both hashtables.  But
670 -- the current solution solves the immediate problem, which is that
671 -- dynamics generated in one world with one type were erroneously
672 -- being recognised by the other world as having a different type.
673 foreign import ccall unsafe "genSymZh"
674   genSym :: IO Int
675 #endif
676
677 mkTyConKey :: String -> Key
678 mkTyConKey str 
679   = unsafePerformIO $ do
680         let Cache {next_key = kloc, tc_tbl = tbl} = cache
681         mb_k <- HT.lookup tbl str
682         case mb_k of
683           Just k  -> return k
684           Nothing -> do { k <- newKey kloc ;
685                           HT.insert tbl str k ;
686                           return k }
687
688 appKey :: Key -> Key -> Key
689 appKey k1 k2
690   = unsafePerformIO $ do
691         let Cache {next_key = kloc, ap_tbl = tbl} = cache
692         mb_k <- HT.lookup tbl kpr
693         case mb_k of
694           Just k  -> return k
695           Nothing -> do { k <- newKey kloc ;
696                           HT.insert tbl kpr k ;
697                           return k }
698   where
699     kpr = KeyPr k1 k2
700
701 appKeys :: Key -> [Key] -> Key
702 appKeys k ks = foldl appKey k ks