[project @ 1997-03-17 20:34:25 by simonpj]
[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, toEnum_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     , (toEnum_RDR,              toEnumClassOpKey)
303     , (eq_RDR,                  eqClassOpKey)
304     , (thenM_RDR,               thenMClassOpKey)
305     , (returnM_RDR,             returnMClassOpKey)
306     , (zeroM_RDR,               zeroClassOpKey)
307     , (fromRational_RDR,        fromRationalClassOpKey)
308
309         -- Others
310     , (otherwiseId_RDR,         otherwiseIdKey)
311     ]
312 \end{code}
313
314 ToDo: make it do the ``like'' part properly (as in 0.26 and before).
315
316 \begin{code}
317 maybeCharLikeTyCon tc = if (uniqueOf tc == charDataConKey) then Just charDataCon else Nothing
318 maybeIntLikeTyCon  tc = if (uniqueOf tc == intDataConKey)  then Just intDataCon  else Nothing
319 \end{code}
320
321 %************************************************************************
322 %*                                                                      *
323 \subsection{Commonly-used RdrNames}
324 %*                                                                      *
325 %************************************************************************
326
327 These RdrNames are not really "built in", but some parts of the compiler
328 (notably the deriving mechanism) need to mention their names, and it's convenient
329 to write them all down in one place.
330
331 \begin{code}
332 prelude_primop op = qual (modAndOcc (primOpName op))
333
334 intTyCon_RDR            = qual (modAndOcc intTyCon)
335 ioTyCon_RDR             = tcQual (iO_BASE,   SLIT("IO"))
336 orderingTyCon_RDR       = tcQual (pREL_BASE, SLIT("Ordering"))
337 rationalTyCon_RDR       = tcQual (pREL_NUM,  SLIT("Rational"))
338 ratioTyCon_RDR          = tcQual (pREL_NUM,  SLIT("Ratio"))
339
340 eqClass_RDR             = tcQual (pREL_BASE, SLIT("Eq"))
341 ordClass_RDR            = tcQual (pREL_BASE, SLIT("Ord"))
342 evalClass_RDR           = tcQual (pREL_BASE, SLIT("Eval"))
343 boundedClass_RDR        = tcQual (pREL_BASE, SLIT("Bounded"))
344 numClass_RDR            = tcQual (pREL_BASE, SLIT("Num"))
345 enumClass_RDR           = tcQual (pREL_BASE, SLIT("Enum"))
346 monadClass_RDR          = tcQual (pREL_BASE, SLIT("Monad"))
347 monadZeroClass_RDR      = tcQual (pREL_BASE, SLIT("MonadZero"))
348 monadPlusClass_RDR      = tcQual (pREL_BASE, SLIT("MonadPlus"))
349 functorClass_RDR        = tcQual (pREL_BASE, SLIT("Functor"))
350 showClass_RDR           = tcQual (pREL_BASE, SLIT("Show"))
351 realClass_RDR           = tcQual (pREL_NUM,  SLIT("Real"))
352 integralClass_RDR       = tcQual (pREL_NUM,  SLIT("Integral"))
353 fractionalClass_RDR     = tcQual (pREL_NUM,  SLIT("Fractional"))
354 floatingClass_RDR       = tcQual (pREL_NUM,  SLIT("Floating"))
355 realFracClass_RDR       = tcQual (pREL_NUM,  SLIT("RealFrac"))
356 realFloatClass_RDR      = tcQual (pREL_NUM,  SLIT("RealFloat"))
357 readClass_RDR           = tcQual (pREL_READ, SLIT("Read"))
358 ixClass_RDR             = tcQual (iX,        SLIT("Ix"))
359 ccallableClass_RDR      = tcQual (fOREIGN,   SLIT("CCallable"))
360 creturnableClass_RDR    = tcQual (fOREIGN,   SLIT("CReturnable"))
361
362 fromInt_RDR        = varQual (pREL_BASE, SLIT("fromInt"))
363 fromInteger_RDR    = varQual (pREL_BASE, SLIT("fromInteger"))
364 minus_RDR          = varQual (pREL_BASE, SLIT("-"))
365 toEnum_RDR         = varQual (pREL_BASE, SLIT("toEnum"))
366 fromEnum_RDR       = varQual (pREL_BASE, SLIT("fromEnum"))
367 enumFrom_RDR       = varQual (pREL_BASE, SLIT("enumFrom"))
368 enumFromTo_RDR     = varQual (pREL_BASE, SLIT("enumFromTo"))
369 enumFromThen_RDR   = varQual (pREL_BASE, SLIT("enumFromThen"))
370 enumFromThenTo_RDR = varQual (pREL_BASE, SLIT("enumFromThenTo"))
371
372 thenM_RDR          = varQual (pREL_BASE, SLIT(">>="))
373 returnM_RDR        = varQual (pREL_BASE, SLIT("return"))
374 zeroM_RDR          = varQual (pREL_BASE, SLIT("zero"))
375 fromRational_RDR   = varQual (pREL_NUM, SLIT("fromRational"))
376
377 negate_RDR         = varQual (pREL_BASE, SLIT("negate"))
378 eq_RDR             = varQual (pREL_BASE, SLIT("=="))
379 ne_RDR             = varQual (pREL_BASE, SLIT("/="))
380 le_RDR             = varQual (pREL_BASE, SLIT("<="))
381 lt_RDR             = varQual (pREL_BASE, SLIT("<"))
382 ge_RDR             = varQual (pREL_BASE, SLIT(">="))
383 gt_RDR             = varQual (pREL_BASE, SLIT(">"))
384 ltTag_RDR          = varQual (pREL_BASE,  SLIT("LT"))
385 eqTag_RDR          = varQual (pREL_BASE,  SLIT("EQ"))
386 gtTag_RDR          = varQual (pREL_BASE,  SLIT("GT"))
387 max_RDR            = varQual (pREL_BASE, SLIT("max"))
388 min_RDR            = varQual (pREL_BASE, SLIT("min"))
389 compare_RDR        = varQual (pREL_BASE, SLIT("compare"))
390 minBound_RDR       = varQual (pREL_BASE, SLIT("minBound"))
391 maxBound_RDR       = varQual (pREL_BASE, SLIT("maxBound"))
392 false_RDR          = varQual (pREL_BASE,  SLIT("False"))
393 true_RDR           = varQual (pREL_BASE,  SLIT("True"))
394 and_RDR            = varQual (pREL_BASE,  SLIT("&&"))
395 not_RDR            = varQual (pREL_BASE,  SLIT("not"))
396 compose_RDR        = varQual (pREL_BASE, SLIT("."))
397 append_RDR         = varQual (pREL_BASE, SLIT("++"))
398 map_RDR            = varQual (pREL_BASE, SLIT("map"))
399
400 showList___RDR     = varQual (pREL_BASE,  SLIT("showList__"))
401 showsPrec_RDR      = varQual (pREL_BASE, SLIT("showsPrec"))
402 showList_RDR       = varQual (pREL_BASE, SLIT("showList"))
403 showSpace_RDR      = varQual (pREL_BASE,  SLIT("showSpace"))
404 showString_RDR     = varQual (pREL_BASE, SLIT("showString"))
405 showParen_RDR      = varQual (pREL_BASE, SLIT("showParen"))
406
407 range_RDR          = varQual (iX,   SLIT("range"))
408 index_RDR          = varQual (iX,   SLIT("index"))
409 inRange_RDR        = varQual (iX,   SLIT("inRange"))
410
411 readsPrec_RDR      = varQual (pREL_READ, SLIT("readsPrec"))
412 readList_RDR       = varQual (pREL_READ, SLIT("readList"))
413 readParen_RDR      = varQual (pREL_READ, SLIT("readParen"))
414 lex_RDR            = varQual (pREL_READ,  SLIT("lex"))
415 readList___RDR     = varQual (pREL_READ,  SLIT("readList__"))
416
417 plus_RDR           = varQual (pREL_BASE, SLIT("+"))
418 times_RDR          = varQual (pREL_BASE, SLIT("*"))
419 mkInt_RDR          = varQual (pREL_BASE, SLIT("I#"))
420
421 error_RDR          = varQual (iO_BASE, SLIT("error"))
422
423 eqH_Char_RDR    = prelude_primop CharEqOp
424 ltH_Char_RDR    = prelude_primop CharLtOp
425 eqH_Word_RDR    = prelude_primop WordEqOp
426 ltH_Word_RDR    = prelude_primop WordLtOp
427 eqH_Addr_RDR    = prelude_primop AddrEqOp
428 ltH_Addr_RDR    = prelude_primop AddrLtOp
429 eqH_Float_RDR   = prelude_primop FloatEqOp
430 ltH_Float_RDR   = prelude_primop FloatLtOp
431 eqH_Double_RDR  = prelude_primop DoubleEqOp
432 ltH_Double_RDR  = prelude_primop DoubleLtOp
433 eqH_Int_RDR     = prelude_primop IntEqOp
434 ltH_Int_RDR     = prelude_primop IntLtOp
435 geH_RDR         = prelude_primop IntGeOp
436 leH_RDR         = prelude_primop IntLeOp
437 minusH_RDR      = prelude_primop IntSubOp
438
439 main_RDR        = varQual (mAIN,     SLIT("main"))
440 mainPrimIO_RDR  = varQual (gHC_MAIN, SLIT("mainPrimIO"))
441
442 otherwiseId_RDR = varQual (pREL_BASE, SLIT("otherwise"))
443 \end{code}
444
445 %************************************************************************
446 %*                                                                      *
447 \subsection[Class-std-groups]{Standard groups of Prelude classes}
448 %*                                                                      *
449 %************************************************************************
450
451 @derivableClassKeys@ is also used in checking \tr{deriving} constructs
452 (@TcDeriv@).
453
454 @derivingOccurrences@ maps a class name to a list of the (qualified) occurrences
455 that will be mentioned by  the derived code for the class when it is later generated.
456 We don't need to put in things that are WiredIn (because they are already mapped to their
457 correct name by the @NameSupply@.  The class itself, and all its class ops, is
458 already flagged as an occurrence so we don't need to mention that either.
459
460 @derivingOccurrences@ has an item for every derivable class, even if that item is empty,
461 because we treat lookup failure as indicating that the class is illegal in a deriving clause.
462
463 \begin{code}
464 derivingOccurrences :: UniqFM [RdrName]
465 derivingOccurrences = listToUFM deriving_occ_info
466
467 derivableClassKeys  = map fst deriving_occ_info
468
469 deriving_occ_info
470   = [ (eqClassKey,      [intTyCon_RDR, and_RDR, not_RDR])
471     , (ordClassKey,     [intTyCon_RDR, compose_RDR])
472     , (enumClassKey,    [intTyCon_RDR, map_RDR])
473     , (evalClassKey,    [intTyCon_RDR])
474     , (boundedClassKey, [intTyCon_RDR])
475     , (showClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, compose_RDR, showString_RDR, 
476                          showParen_RDR, showSpace_RDR, showList___RDR])
477     , (readClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, append_RDR, 
478                          lex_RDR, readParen_RDR, readList___RDR])
479     , (ixClassKey,      [intTyCon_RDR, numClass_RDR, and_RDR, map_RDR, enumFromTo_RDR])
480     ]
481         -- intTyCon: Practically any deriving needs Int, either for index calculations, 
482         --              or for taggery.
483         -- ordClass: really it's the methods that are actually used.
484         -- numClass: for Int literals
485 \end{code}
486
487
488 NOTE: @Eq@ and @Text@ do need to appear in @standardClasses@
489 even though every numeric class has these two as a superclass,
490 because the list of ambiguous dictionaries hasn't been simplified.
491
492 \begin{code}
493 isCcallishClass, isNoDictClass, isNumericClass, isStandardClass :: Class -> Bool
494
495 isNumericClass   clas = classKey clas `is_elem` numericClassKeys
496 isStandardClass  clas = classKey clas `is_elem` standardClassKeys
497 isCcallishClass  clas = classKey clas `is_elem` cCallishClassKeys
498 isNoDictClass    clas = classKey clas `is_elem` noDictClassKeys
499 is_elem = isIn "is_X_Class"
500
501 numericClassKeys
502   = [ numClassKey
503     , realClassKey
504     , integralClassKey
505     , fractionalClassKey
506     , floatingClassKey
507     , realFracClassKey
508     , realFloatClassKey
509     ]
510
511 needsDataDeclCtxtClassKeys -- see comments in TcDeriv
512   = [ readClassKey
513     ]
514
515 cCallishClassKeys = [ cCallableClassKey, cReturnableClassKey ]
516
517 standardClassKeys
518   = derivableClassKeys ++ numericClassKeys ++ cCallishClassKeys
519     --
520     -- We have to have "CCallable" and "CReturnable" in the standard
521     -- classes, so that if you go...
522     --
523     --      _ccall_ foo ... 93{-numeric literal-} ...
524     --
525     -- ... it can do The Right Thing on the 93.
526
527 noDictClassKeys         -- These classes are used only for type annotations;
528                         -- they are not implemented by dictionaries, ever.
529   = cCallishClassKeys
530         -- I used to think that class Eval belonged in here, but
531         -- we really want functions with type (Eval a => ...) and that
532         -- means that we really want to pass a placeholder for an Eval
533         -- dictionary.  The unit tuple is what we'll get if we leave things
534         -- alone, and that'll do for now.  Could arrange to drop that parameter
535         -- in the end.
536 \end{code}