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