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