98364f2573f29685c05f8c7d71fe80766f90053d
[ghc-hetmet.git] / ghc / compiler / prelude / PrelInfo.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
3 %
4 \section[PrelInfo]{The @PrelInfo@ interface to the compiler's prelude knowledge}
5
6 \begin{code}
7 #include "HsVersions.h"
8
9 module PrelInfo (
10         -- finite maps for built-in things (for the renamer and typechecker):
11         builtinNames, derivingOccurrences,
12         SYN_IE(BuiltinNames),
13
14         maybeCharLikeTyCon, maybeIntLikeTyCon,
15
16         eq_RDR, ne_RDR, le_RDR, lt_RDR, ge_RDR, gt_RDR, max_RDR, min_RDR, compare_RDR, 
17         minBound_RDR, maxBound_RDR, enumFrom_RDR, enumFromTo_RDR, enumFromThen_RDR, 
18         enumFromThenTo_RDR, fromEnum_RDR,
19         range_RDR, index_RDR, inRange_RDR, readsPrec_RDR, readList_RDR, 
20         showsPrec_RDR, showList_RDR, plus_RDR, times_RDR, ltTag_RDR, eqTag_RDR, gtTag_RDR, 
21         eqH_Char_RDR, ltH_Char_RDR, eqH_Word_RDR, ltH_Word_RDR, eqH_Addr_RDR, ltH_Addr_RDR, 
22         eqH_Float_RDR, ltH_Float_RDR, eqH_Double_RDR, ltH_Double_RDR, eqH_Int_RDR, ltH_Int_RDR, 
23         geH_RDR, leH_RDR, minusH_RDR, false_RDR, true_RDR, and_RDR, not_RDR, append_RDR, 
24         map_RDR, compose_RDR, mkInt_RDR, error_RDR, showString_RDR, showParen_RDR, readParen_RDR, 
25         lex_RDR, showSpace_RDR, showList___RDR, readList___RDR, negate_RDR,
26
27         numClass_RDR, fractionalClass_RDR, eqClass_RDR, ccallableClass_RDR, creturnableClass_RDR,
28         monadZeroClass_RDR, enumClass_RDR, evalClass_RDR, ordClass_RDR,
29
30         main_NAME, mainPrimIO_NAME, ioTyCon_NAME, primIoTyCon_NAME,
31
32         needsDataDeclCtxtClassKeys, cCallishClassKeys, isNoDictClass,
33         isNumericClass, isStandardClass, isCcallishClass
34     ) where
35
36 IMP_Ubiq()
37 IMPORT_DELOOPER(PrelLoop) ( primOpName )
38 -- IMPORT_DELOOPER(IdLoop)        ( SpecEnv )
39
40 -- friends:
41 import PrelMods         -- Prelude module names
42 import PrelVals         -- VALUES
43 import PrimOp           ( PrimOp(..), allThePrimOps )
44 import PrimRep          ( PrimRep(..) )
45 import TysPrim          -- TYPES
46 import TysWiredIn
47
48 -- others:
49 import SpecEnv          ( SpecEnv )
50 import RdrHsSyn         ( RdrName(..), varQual, tcQual, qual )
51 import Id               ( GenId, SYN_IE(Id) )
52 import Name             ( Name, OccName(..), DefnInfo(..), Provenance(..),
53                           getName, mkGlobalName, modAndOcc )
54 import Class            ( Class(..), GenClass, classKey )
55 import TyCon            ( tyConDataCons, mkFunTyCon, TyCon )
56 import Type
57 import Bag
58 import Unique           -- *Key stuff
59 import UniqFM           ( UniqFM, listToUFM ) 
60 import Util             ( isIn )
61 \end{code}
62
63 %************************************************************************
64 %*                                                                      *
65 \subsection[builtinNameInfo]{Lookup built-in names}
66 %*                                                                      *
67 %************************************************************************
68
69 We have two ``builtin name funs,'' one to look up @TyCons@ and
70 @Classes@, the other to look up values.
71
72 \begin{code}
73 type BuiltinNames = Bag Name
74
75 builtinNames :: BuiltinNames
76 builtinNames
77   =     -- Wired in TyCons
78     unionManyBags (map getTyConNames wired_in_tycons)   `unionBags`
79
80         -- Wired in Ids
81     listToBag (map getName wired_in_ids)                `unionBags`
82
83         -- PrimOps
84     listToBag (map (getName.primOpName) allThePrimOps)  `unionBags`
85
86         -- Other names with magic keys
87     listToBag knownKeyNames
88 \end{code}
89
90
91 \begin{code}
92 getTyConNames :: TyCon -> Bag Name
93 getTyConNames tycon
94     =  getName tycon `consBag` listToBag (map getName (tyConDataCons tycon))
95         -- Synonyms return empty list of constructors
96 \end{code}
97
98
99 We let a lot of "non-standard" values be visible, so that we can make
100 sense of them in interface pragmas. It's cool, though they all have
101 "non-standard" names, so they won't get past the parser in user code.
102
103 %************************************************************************
104 %*                                                                      *
105 \subsection{Wired in TyCons}
106 %*                                                                      *
107 %************************************************************************
108
109
110 \begin{code}
111 wired_in_tycons = [mkFunTyCon] ++
112                   prim_tycons ++
113                   tuple_tycons ++
114                   data_tycons
115
116 prim_tycons
117   = [ addrPrimTyCon
118     , arrayPrimTyCon
119     , byteArrayPrimTyCon
120     , charPrimTyCon
121     , doublePrimTyCon
122     , floatPrimTyCon
123     , intPrimTyCon
124     , foreignObjPrimTyCon
125     , mutableArrayPrimTyCon
126     , mutableByteArrayPrimTyCon
127     , synchVarPrimTyCon
128     , realWorldTyCon
129     , stablePtrPrimTyCon
130     , statePrimTyCon
131     , wordPrimTyCon
132     ]
133
134 tuple_tycons = unitTyCon : [tupleTyCon i | i <- [2..37] ]
135
136
137 data_tycons
138   = [ listTyCon
139     , addrTyCon
140     , boolTyCon
141     , charTyCon
142     , doubleTyCon
143     , floatTyCon
144     , foreignObjTyCon
145     , intTyCon
146     , integerTyCon
147     , liftTyCon
148     , primIoTyCon
149     , return2GMPsTyCon
150     , returnIntAndGMPTyCon
151     , stTyCon
152     , stablePtrTyCon
153     , stateAndAddrPrimTyCon
154     , stateAndArrayPrimTyCon
155     , stateAndByteArrayPrimTyCon
156     , stateAndCharPrimTyCon
157     , stateAndDoublePrimTyCon
158     , stateAndFloatPrimTyCon
159     , stateAndForeignObjPrimTyCon
160     , stateAndIntPrimTyCon
161     , stateAndMutableArrayPrimTyCon
162     , stateAndMutableByteArrayPrimTyCon
163     , stateAndPtrPrimTyCon
164     , stateAndStablePtrPrimTyCon
165     , stateAndSynchVarPrimTyCon
166     , stateAndWordPrimTyCon
167     , stateTyCon
168     , voidTyCon
169     , wordTyCon
170     ]
171
172 min_nonprim_tycon_list  -- used w/ HideMostBuiltinNames
173   = [ boolTyCon
174     , charTyCon
175     , intTyCon
176     , floatTyCon
177     , doubleTyCon
178     , integerTyCon
179     , liftTyCon
180     , return2GMPsTyCon  -- ADR asked for these last two (WDP 94/11)
181     , returnIntAndGMPTyCon
182     ]
183 \end{code}
184
185 %************************************************************************
186 %*                                                                      *
187 \subsection{Wired in Ids}
188 %*                                                                      *
189 %************************************************************************
190
191 The WiredIn Ids ...
192 ToDo: Some of these should be moved to id_keys_infos!
193
194 \begin{code}
195 wired_in_ids
196   = [ aBSENT_ERROR_ID
197     , augmentId
198     , buildId
199     , eRROR_ID
200     , foldlId
201     , foldrId
202     , iRREFUT_PAT_ERROR_ID
203     , integerMinusOneId
204     , integerPlusOneId
205     , integerPlusTwoId
206     , integerZeroId
207     , nON_EXHAUSTIVE_GUARDS_ERROR_ID
208     , nO_DEFAULT_METHOD_ERROR_ID
209     , nO_EXPLICIT_METHOD_ERROR_ID
210     , pAR_ERROR_ID
211     , pAT_ERROR_ID
212     , packStringForCId
213     , rEC_CON_ERROR_ID
214     , rEC_UPD_ERROR_ID
215     , realWorldPrimId
216     , runSTId
217     , tRACE_ID
218     , unpackCString2Id
219     , unpackCStringAppendId
220     , unpackCStringFoldrId
221     , unpackCStringId
222     , voidId
223
224 --  , copyableId
225 --  , forkId
226 --  , noFollowId
227 --    , parAtAbsId
228 --    , parAtForNowId
229 --    , parAtId
230 --    , parAtRelId
231 --    , parGlobalId
232 --    , parId
233 --    , parLocalId
234 --    , seqId
235     ]
236 \end{code}
237
238
239 %************************************************************************
240 %*                                                                      *
241 \subsection{Built-in keys}
242 %*                                                                      *
243 %************************************************************************
244
245 Ids, Synonyms, Classes and ClassOps with builtin keys. 
246
247 \begin{code}
248 mkKnownKeyGlobal :: (RdrName, Unique) -> Name
249 mkKnownKeyGlobal (Qual mod occ, uniq) = mkGlobalName uniq mod occ VanillaDefn Implicit
250
251 main_NAME        = mkKnownKeyGlobal (main_RDR,       mainKey)
252 mainPrimIO_NAME  = mkKnownKeyGlobal (mainPrimIO_RDR, mainPrimIoKey)
253 ioTyCon_NAME     = mkKnownKeyGlobal (ioTyCon_RDR,    iOTyConKey)
254 primIoTyCon_NAME = getName primIoTyCon
255
256 knownKeyNames :: [Name]
257 knownKeyNames
258   = [main_NAME, mainPrimIO_NAME, ioTyCon_NAME]
259     ++
260     map mkKnownKeyGlobal
261     [
262         -- Type constructors (synonyms especially)
263       (orderingTyCon_RDR,  orderingTyConKey)
264     , (rationalTyCon_RDR,  rationalTyConKey)
265     , (ratioTyCon_RDR,     ratioTyConKey)
266
267         --  Classes.  *Must* include:
268         --      classes that are grabbed by key (e.g., eqClassKey)
269         --      classes in "Class.standardClassKeys" (quite a few)
270     , (eqClass_RDR,             eqClassKey)             -- mentioned, derivable
271     , (ordClass_RDR,            ordClassKey)            -- derivable
272     , (evalClass_RDR,           evalClassKey)           -- mentioned
273     , (boundedClass_RDR,        boundedClassKey)        -- derivable
274     , (numClass_RDR,            numClassKey)            -- mentioned, numeric
275     , (enumClass_RDR,           enumClassKey)           -- derivable
276     , (monadClass_RDR,          monadClassKey)
277     , (monadZeroClass_RDR,      monadZeroClassKey)
278     , (monadPlusClass_RDR,      monadPlusClassKey)
279     , (functorClass_RDR,        functorClassKey)
280     , (showClass_RDR,           showClassKey)           -- derivable
281     , (realClass_RDR,           realClassKey)           -- numeric
282     , (integralClass_RDR,       integralClassKey)       -- numeric
283     , (fractionalClass_RDR,     fractionalClassKey)     -- numeric
284     , (floatingClass_RDR,       floatingClassKey)       -- numeric
285     , (realFracClass_RDR,       realFracClassKey)       -- numeric
286     , (realFloatClass_RDR,      realFloatClassKey)      -- numeric
287     , (readClass_RDR,           readClassKey)           -- derivable
288     , (ixClass_RDR,             ixClassKey)             -- derivable (but it isn't Prelude.Ix; hmmm)
289     , (ccallableClass_RDR,      cCallableClassKey)      -- mentioned, ccallish
290     , (creturnableClass_RDR,    cReturnableClassKey)    -- mentioned, ccallish
291
292         -- ClassOps 
293     , (fromInt_RDR,             fromIntClassOpKey)
294     , (fromInteger_RDR,         fromIntegerClassOpKey)
295     , (ge_RDR,                  geClassOpKey) 
296     , (minus_RDR,               minusClassOpKey)
297     , (enumFrom_RDR,            enumFromClassOpKey)
298     , (enumFromThen_RDR,        enumFromThenClassOpKey)
299     , (enumFromTo_RDR,          enumFromToClassOpKey)
300     , (enumFromThenTo_RDR,      enumFromThenToClassOpKey)
301     , (fromEnum_RDR,            fromEnumClassOpKey)
302     , (eq_RDR,                  eqClassOpKey)
303     , (thenM_RDR,               thenMClassOpKey)
304     , (returnM_RDR,             returnMClassOpKey)
305     , (zeroM_RDR,               zeroClassOpKey)
306     , (fromRational_RDR,        fromRationalClassOpKey)
307
308         -- Others
309     , (otherwiseId_RDR,         otherwiseIdKey)
310     ]
311 \end{code}
312
313 ToDo: make it do the ``like'' part properly (as in 0.26 and before).
314
315 \begin{code}
316 maybeCharLikeTyCon tc = if (uniqueOf tc == charDataConKey) then Just charDataCon else Nothing
317 maybeIntLikeTyCon  tc = if (uniqueOf tc == intDataConKey)  then Just intDataCon  else Nothing
318 \end{code}
319
320 %************************************************************************
321 %*                                                                      *
322 \subsection{Commonly-used RdrNames}
323 %*                                                                      *
324 %************************************************************************
325
326 These RdrNames are not really "built in", but some parts of the compiler
327 (notably the deriving mechanism) need to mention their names, and it's convenient
328 to write them all down in one place.
329
330 \begin{code}
331 prelude_primop op = qual (modAndOcc (primOpName op))
332
333 intTyCon_RDR            = qual (modAndOcc intTyCon)
334 ioTyCon_RDR             = tcQual (iO_BASE,   SLIT("IO"))
335 orderingTyCon_RDR       = tcQual (pREL_BASE, SLIT("Ordering"))
336 rationalTyCon_RDR       = tcQual (pREL_NUM,  SLIT("Rational"))
337 ratioTyCon_RDR          = tcQual (pREL_NUM,  SLIT("Ratio"))
338
339 eqClass_RDR             = tcQual (pREL_BASE, SLIT("Eq"))
340 ordClass_RDR            = tcQual (pREL_BASE, SLIT("Ord"))
341 evalClass_RDR           = tcQual (pREL_BASE, SLIT("Eval"))
342 boundedClass_RDR        = tcQual (pREL_BASE, SLIT("Bounded"))
343 numClass_RDR            = tcQual (pREL_BASE, SLIT("Num"))
344 enumClass_RDR           = tcQual (pREL_BASE, SLIT("Enum"))
345 monadClass_RDR          = tcQual (pREL_BASE, SLIT("Monad"))
346 monadZeroClass_RDR      = tcQual (pREL_BASE, SLIT("MonadZero"))
347 monadPlusClass_RDR      = tcQual (pREL_BASE, SLIT("MonadPlus"))
348 functorClass_RDR        = tcQual (pREL_BASE, SLIT("Functor"))
349 showClass_RDR           = tcQual (pREL_BASE, SLIT("Show"))
350 realClass_RDR           = tcQual (pREL_NUM,  SLIT("Real"))
351 integralClass_RDR       = tcQual (pREL_NUM,  SLIT("Integral"))
352 fractionalClass_RDR     = tcQual (pREL_NUM,  SLIT("Fractional"))
353 floatingClass_RDR       = tcQual (pREL_NUM,  SLIT("Floating"))
354 realFracClass_RDR       = tcQual (pREL_NUM,  SLIT("RealFrac"))
355 realFloatClass_RDR      = tcQual (pREL_NUM,  SLIT("RealFloat"))
356 readClass_RDR           = tcQual (pREL_READ, SLIT("Read"))
357 ixClass_RDR             = tcQual (iX,        SLIT("Ix"))
358 ccallableClass_RDR      = tcQual (fOREIGN,   SLIT("CCallable"))
359 creturnableClass_RDR    = tcQual (fOREIGN,   SLIT("CReturnable"))
360
361 fromInt_RDR        = varQual (pREL_BASE, SLIT("fromInt"))
362 fromInteger_RDR    = varQual (pREL_BASE, SLIT("fromInteger"))
363 minus_RDR          = varQual (pREL_BASE, SLIT("-"))
364 fromEnum_RDR       = varQual (pREL_BASE, SLIT("fromEnum"))
365 enumFrom_RDR       = varQual (pREL_BASE, SLIT("enumFrom"))
366 enumFromTo_RDR     = varQual (pREL_BASE, SLIT("enumFromTo"))
367 enumFromThen_RDR   = varQual (pREL_BASE, SLIT("enumFromThen"))
368 enumFromThenTo_RDR = varQual (pREL_BASE, SLIT("enumFromThenTo"))
369
370 thenM_RDR          = varQual (pREL_BASE, SLIT(">>="))
371 returnM_RDR        = varQual (pREL_BASE, SLIT("return"))
372 zeroM_RDR          = varQual (pREL_BASE, SLIT("zero"))
373 fromRational_RDR   = varQual (pREL_NUM, SLIT("fromRational"))
374
375 negate_RDR         = varQual (pREL_BASE, SLIT("negate"))
376 eq_RDR             = varQual (pREL_BASE, SLIT("=="))
377 ne_RDR             = varQual (pREL_BASE, SLIT("/="))
378 le_RDR             = varQual (pREL_BASE, SLIT("<="))
379 lt_RDR             = varQual (pREL_BASE, SLIT("<"))
380 ge_RDR             = varQual (pREL_BASE, SLIT(">="))
381 gt_RDR             = varQual (pREL_BASE, SLIT(">"))
382 ltTag_RDR          = varQual (pREL_BASE,  SLIT("LT"))
383 eqTag_RDR          = varQual (pREL_BASE,  SLIT("EQ"))
384 gtTag_RDR          = varQual (pREL_BASE,  SLIT("GT"))
385 max_RDR            = varQual (pREL_BASE, SLIT("max"))
386 min_RDR            = varQual (pREL_BASE, SLIT("min"))
387 compare_RDR        = varQual (pREL_BASE, SLIT("compare"))
388 minBound_RDR       = varQual (pREL_BASE, SLIT("minBound"))
389 maxBound_RDR       = varQual (pREL_BASE, SLIT("maxBound"))
390 false_RDR          = varQual (pREL_BASE,  SLIT("False"))
391 true_RDR           = varQual (pREL_BASE,  SLIT("True"))
392 and_RDR            = varQual (pREL_BASE,  SLIT("&&"))
393 not_RDR            = varQual (pREL_BASE,  SLIT("not"))
394 compose_RDR        = varQual (pREL_BASE, SLIT("."))
395 append_RDR         = varQual (pREL_BASE, SLIT("++"))
396 map_RDR            = varQual (pREL_BASE, SLIT("map"))
397
398 showList___RDR     = varQual (pREL_BASE,  SLIT("showList__"))
399 showsPrec_RDR      = varQual (pREL_BASE, SLIT("showsPrec"))
400 showList_RDR       = varQual (pREL_BASE, SLIT("showList"))
401 showSpace_RDR      = varQual (pREL_BASE,  SLIT("showSpace"))
402 showString_RDR     = varQual (pREL_BASE, SLIT("showString"))
403 showParen_RDR      = varQual (pREL_BASE, SLIT("showParen"))
404
405 range_RDR          = varQual (iX,   SLIT("range"))
406 index_RDR          = varQual (iX,   SLIT("index"))
407 inRange_RDR        = varQual (iX,   SLIT("inRange"))
408
409 readsPrec_RDR      = varQual (pREL_READ, SLIT("readsPrec"))
410 readList_RDR       = varQual (pREL_READ, SLIT("readList"))
411 readParen_RDR      = varQual (pREL_READ, SLIT("readParen"))
412 lex_RDR            = varQual (pREL_READ,  SLIT("lex"))
413 readList___RDR     = varQual (pREL_READ,  SLIT("readList__"))
414
415 plus_RDR           = varQual (pREL_BASE, SLIT("+"))
416 times_RDR          = varQual (pREL_BASE, SLIT("*"))
417 mkInt_RDR          = varQual (pREL_BASE, SLIT("I#"))
418
419 error_RDR          = varQual (iO_BASE, SLIT("error"))
420
421 eqH_Char_RDR    = prelude_primop CharEqOp
422 ltH_Char_RDR    = prelude_primop CharLtOp
423 eqH_Word_RDR    = prelude_primop WordEqOp
424 ltH_Word_RDR    = prelude_primop WordLtOp
425 eqH_Addr_RDR    = prelude_primop AddrEqOp
426 ltH_Addr_RDR    = prelude_primop AddrLtOp
427 eqH_Float_RDR   = prelude_primop FloatEqOp
428 ltH_Float_RDR   = prelude_primop FloatLtOp
429 eqH_Double_RDR  = prelude_primop DoubleEqOp
430 ltH_Double_RDR  = prelude_primop DoubleLtOp
431 eqH_Int_RDR     = prelude_primop IntEqOp
432 ltH_Int_RDR     = prelude_primop IntLtOp
433 geH_RDR         = prelude_primop IntGeOp
434 leH_RDR         = prelude_primop IntLeOp
435 minusH_RDR      = prelude_primop IntSubOp
436
437 main_RDR        = varQual (mAIN,     SLIT("main"))
438 mainPrimIO_RDR  = varQual (gHC_MAIN, SLIT("mainPrimIO"))
439
440 otherwiseId_RDR = varQual (pREL_BASE, SLIT("otherwise"))
441 \end{code}
442
443 %************************************************************************
444 %*                                                                      *
445 \subsection[Class-std-groups]{Standard groups of Prelude classes}
446 %*                                                                      *
447 %************************************************************************
448
449 @derivableClassKeys@ is also used in checking \tr{deriving} constructs
450 (@TcDeriv@).
451
452 @derivingOccurrences@ maps a class name to a list of the (qualified) occurrences
453 that will be mentioned by  the derived code for the class when it is later generated.
454 We don't need to put in things that are WiredIn (because they are already mapped to their
455 correct name by the @NameSupply@.  The class itself, and all its class ops, is
456 already flagged as an occurrence so we don't need to mention that either.
457
458 @derivingOccurrences@ has an item for every derivable class, even if that item is empty,
459 because we treat lookup failure as indicating that the class is illegal in a deriving clause.
460
461 \begin{code}
462 derivingOccurrences :: UniqFM [RdrName]
463 derivingOccurrences = listToUFM deriving_occ_info
464
465 derivableClassKeys  = map fst deriving_occ_info
466
467 deriving_occ_info
468   = [ (eqClassKey,      [intTyCon_RDR, and_RDR, not_RDR])
469     , (ordClassKey,     [intTyCon_RDR, compose_RDR])
470     , (enumClassKey,    [intTyCon_RDR, map_RDR])
471     , (evalClassKey,    [intTyCon_RDR])
472     , (boundedClassKey, [intTyCon_RDR])
473     , (showClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, compose_RDR, showString_RDR, 
474                          showParen_RDR, showSpace_RDR, showList___RDR])
475     , (readClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, append_RDR, 
476                          lex_RDR, readParen_RDR, readList___RDR])
477     , (ixClassKey,      [intTyCon_RDR, numClass_RDR, and_RDR, map_RDR, enumFromTo_RDR])
478     ]
479         -- intTyCon: Practically any deriving needs Int, either for index calculations, 
480         --              or for taggery.
481         -- ordClass: really it's the methods that are actually used.
482         -- numClass: for Int literals
483 \end{code}
484
485
486 NOTE: @Eq@ and @Text@ do need to appear in @standardClasses@
487 even though every numeric class has these two as a superclass,
488 because the list of ambiguous dictionaries hasn't been simplified.
489
490 \begin{code}
491 isCcallishClass, isNoDictClass, isNumericClass, isStandardClass :: Class -> Bool
492
493 isNumericClass   clas = classKey clas `is_elem` numericClassKeys
494 isStandardClass  clas = classKey clas `is_elem` standardClassKeys
495 isCcallishClass  clas = classKey clas `is_elem` cCallishClassKeys
496 isNoDictClass    clas = classKey clas `is_elem` noDictClassKeys
497 is_elem = isIn "is_X_Class"
498
499 numericClassKeys
500   = [ numClassKey
501     , realClassKey
502     , integralClassKey
503     , fractionalClassKey
504     , floatingClassKey
505     , realFracClassKey
506     , realFloatClassKey
507     ]
508
509 needsDataDeclCtxtClassKeys -- see comments in TcDeriv
510   = [ readClassKey
511     ]
512
513 cCallishClassKeys = [ cCallableClassKey, cReturnableClassKey ]
514
515 standardClassKeys
516   = derivableClassKeys ++ numericClassKeys ++ cCallishClassKeys
517     --
518     -- We have to have "CCallable" and "CReturnable" in the standard
519     -- classes, so that if you go...
520     --
521     --      _ccall_ foo ... 93{-numeric literal-} ...
522     --
523     -- ... it can do The Right Thing on the 93.
524
525 noDictClassKeys         -- These classes are used only for type annotations;
526                         -- they are not implemented by dictionaries, ever.
527   = cCallishClassKeys
528         -- I used to think that class Eval belonged in here, but
529         -- we really want functions with type (Eval a => ...) and that
530         -- means that we really want to pass a placeholder for an Eval
531         -- dictionary.  The unit tuple is what we'll get if we leave things
532         -- alone, and that'll do for now.  Could arrange to drop that parameter
533         -- in the end.
534 \end{code}