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