f4f3cabf18569f5955b16c1625f7be820a9f4dd7
[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 module PrelInfo (
8         -- finite maps for built-in things (for the renamer and typechecker):
9         builtinNames, derivingOccurrences,
10         BuiltinNames,
11
12         maybeCharLikeTyCon, maybeIntLikeTyCon,
13
14         eq_RDR, ne_RDR, le_RDR, lt_RDR, ge_RDR, gt_RDR, max_RDR, min_RDR, 
15         compare_RDR, minBound_RDR, maxBound_RDR, enumFrom_RDR, enumFromTo_RDR,
16         enumFromThen_RDR, enumFromThenTo_RDR, fromEnum_RDR, toEnum_RDR, 
17         ratioDataCon_RDR, range_RDR, index_RDR, inRange_RDR, readsPrec_RDR,
18         readList_RDR, showsPrec_RDR, showList_RDR, plus_RDR, times_RDR,
19         ltTag_RDR, eqTag_RDR, gtTag_RDR, eqH_Char_RDR, ltH_Char_RDR, 
20         eqH_Word_RDR, ltH_Word_RDR, eqH_Addr_RDR, ltH_Addr_RDR, eqH_Float_RDR,
21         ltH_Float_RDR, eqH_Double_RDR, ltH_Double_RDR, eqH_Int_RDR, 
22         ltH_Int_RDR, geH_RDR, leH_RDR, minusH_RDR, false_RDR, true_RDR,
23         and_RDR, not_RDR, append_RDR, map_RDR, compose_RDR, mkInt_RDR,
24         error_RDR, assert_RDR,
25         showString_RDR, showParen_RDR, readParen_RDR, lex_RDR,
26         showSpace_RDR, showList___RDR, readList___RDR, negate_RDR,
27
28         numClass_RDR, fractionalClass_RDR, eqClass_RDR, 
29         ccallableClass_RDR, creturnableClass_RDR,
30         monadZeroClass_RDR, enumClass_RDR, evalClass_RDR, ordClass_RDR,
31         ioDataCon_RDR, ioOkDataCon_RDR,
32
33         main_NAME, allClass_NAME, ioTyCon_NAME,
34
35         needsDataDeclCtxtClassKeys, cCallishClassKeys, cCallishTyKeys, isNoDictClass,
36         isNumericClass, isStandardClass, isCcallishClass
37     ) where
38
39 #include "HsVersions.h"
40
41 import IdUtils ( primOpName )
42
43 -- friends:
44 import PrelMods         -- Prelude module names
45 import PrelVals         -- VALUES
46 import PrimOp           ( PrimOp(..), allThePrimOps )
47 import PrimRep          ( PrimRep(..) )
48 import TysPrim          -- TYPES
49 import TysWiredIn
50
51 -- others:
52 import RdrHsSyn         ( RdrName(..), varQual, tcQual, qual )
53 import BasicTypes       ( IfaceFlavour )
54 import Id               ( GenId, Id )
55 import Name             ( Name, OccName(..), Provenance(..),
56                           getName, mkGlobalName, modAndOcc
57                         )
58 import Class            ( Class, classKey )
59 import TyCon            ( tyConDataCons, mkFunTyCon, TyCon )
60 import Type
61 import Bag
62 import Unique           -- *Key stuff
63 import UniqFM           ( UniqFM, listToUFM ) 
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     , return2GMPsTyCon
153     , returnIntAndGMPTyCon
154     , stTyCon
155     , stRetTyCon
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     , voidTyCon
172     , wordTyCon
173     ]
174
175 min_nonprim_tycon_list  -- used w/ HideMostBuiltinNames
176   = [ boolTyCon
177     , charTyCon
178     , intTyCon
179     , floatTyCon
180     , doubleTyCon
181     , integerTyCon
182     , liftTyCon
183     , return2GMPsTyCon  -- ADR asked for these last two (WDP 94/11)
184     , returnIntAndGMPTyCon
185     ]
186 \end{code}
187
188 %************************************************************************
189 %*                                                                      *
190 \subsection{Wired in Ids}
191 %*                                                                      *
192 %************************************************************************
193
194 The WiredIn Ids ...
195 ToDo: Some of these should be moved to id_keys_infos!
196
197 \begin{code}
198 wired_in_ids
199   = [ aBSENT_ERROR_ID
200     , augmentId
201     , buildId
202     , eRROR_ID
203     , foldlId
204     , foldrId
205     , iRREFUT_PAT_ERROR_ID
206     , integerMinusOneId
207     , integerPlusOneId
208     , integerPlusTwoId
209     , integerZeroId
210     , nON_EXHAUSTIVE_GUARDS_ERROR_ID
211     , nO_METHOD_BINDING_ERROR_ID
212     , pAR_ERROR_ID
213     , pAT_ERROR_ID
214     , packStringForCId
215     , rEC_CON_ERROR_ID
216     , rEC_UPD_ERROR_ID
217     , realWorldPrimId
218     , tRACE_ID
219     , unpackCString2Id
220     , unpackCStringAppendId
221     , unpackCStringFoldrId
222     , unpackCStringId
223     , voidId
224
225 --  , copyableId
226 --  , forkId
227 --  , noFollowId
228 --    , parAtAbsId
229 --    , parAtForNowId
230 --    , parAtId
231 --    , parAtRelId
232 --    , parGlobalId
233 --    , parId
234 --    , parLocalId
235 --    , seqId
236     ]
237 \end{code}
238
239
240 %************************************************************************
241 %*                                                                      *
242 \subsection{Built-in keys}
243 %*                                                                      *
244 %************************************************************************
245
246 Ids, Synonyms, Classes and ClassOps with builtin keys. 
247
248 \begin{code}
249 mkKnownKeyGlobal :: (RdrName, Unique) -> Name
250 mkKnownKeyGlobal (Qual mod occ hif, uniq)
251   = mkGlobalName uniq mod occ NoProvenance
252
253 allClass_NAME    = mkKnownKeyGlobal (allClass_RDR,   allClassKey)
254 ioTyCon_NAME     = mkKnownKeyGlobal (ioTyCon_RDR,    ioTyConKey)
255 main_NAME        = mkKnownKeyGlobal (main_RDR,       mainKey)
256
257 knownKeyNames :: [Name]
258 knownKeyNames
259   = [main_NAME, allClass_NAME, ioTyCon_NAME]
260     ++
261     map mkKnownKeyGlobal
262     [
263         -- Type constructors (synonyms especially)
264       (ioOkDataCon_RDR,    ioOkDataConKey)
265     , (orderingTyCon_RDR,  orderingTyConKey)
266     , (rationalTyCon_RDR,  rationalTyConKey)
267     , (ratioDataCon_RDR,   ratioDataConKey)
268     , (ratioTyCon_RDR,     ratioTyConKey)
269     , (byteArrayTyCon_RDR, byteArrayTyConKey)
270     , (mutableByteArrayTyCon_RDR, mutableByteArrayTyConKey)
271
272
273         --  Classes.  *Must* include:
274         --      classes that are grabbed by key (e.g., eqClassKey)
275         --      classes in "Class.standardClassKeys" (quite a few)
276     , (eqClass_RDR,             eqClassKey)             -- mentioned, derivable
277     , (ordClass_RDR,            ordClassKey)            -- derivable
278     , (evalClass_RDR,           evalClassKey)           -- mentioned
279     , (boundedClass_RDR,        boundedClassKey)        -- derivable
280     , (numClass_RDR,            numClassKey)            -- mentioned, numeric
281     , (enumClass_RDR,           enumClassKey)           -- derivable
282     , (monadClass_RDR,          monadClassKey)
283     , (monadZeroClass_RDR,      monadZeroClassKey)
284     , (monadPlusClass_RDR,      monadPlusClassKey)
285     , (functorClass_RDR,        functorClassKey)
286     , (showClass_RDR,           showClassKey)           -- derivable
287     , (realClass_RDR,           realClassKey)           -- numeric
288     , (integralClass_RDR,       integralClassKey)       -- numeric
289     , (fractionalClass_RDR,     fractionalClassKey)     -- numeric
290     , (floatingClass_RDR,       floatingClassKey)       -- numeric
291     , (realFracClass_RDR,       realFracClassKey)       -- numeric
292     , (realFloatClass_RDR,      realFloatClassKey)      -- numeric
293     , (readClass_RDR,           readClassKey)           -- derivable
294     , (ixClass_RDR,             ixClassKey)             -- derivable (but it isn't Prelude.Ix; hmmm)
295     , (ccallableClass_RDR,      cCallableClassKey)      -- mentioned, ccallish
296     , (creturnableClass_RDR,    cReturnableClassKey)    -- mentioned, ccallish
297
298         -- ClassOps 
299     , (fromInt_RDR,             fromIntClassOpKey)
300     , (fromInteger_RDR,         fromIntegerClassOpKey)
301     , (ge_RDR,                  geClassOpKey) 
302     , (minus_RDR,               minusClassOpKey)
303     , (enumFrom_RDR,            enumFromClassOpKey)
304     , (enumFromThen_RDR,        enumFromThenClassOpKey)
305     , (enumFromTo_RDR,          enumFromToClassOpKey)
306     , (enumFromThenTo_RDR,      enumFromThenToClassOpKey)
307     , (fromEnum_RDR,            fromEnumClassOpKey)
308     , (toEnum_RDR,              toEnumClassOpKey)
309     , (eq_RDR,                  eqClassOpKey)
310     , (thenM_RDR,               thenMClassOpKey)
311     , (returnM_RDR,             returnMClassOpKey)
312     , (zeroM_RDR,               zeroClassOpKey)
313     , (fromRational_RDR,        fromRationalClassOpKey)
314
315         -- Others
316     , (otherwiseId_RDR,         otherwiseIdKey)
317     ]
318 \end{code}
319
320 ToDo: make it do the ``like'' part properly (as in 0.26 and before).
321
322 \begin{code}
323 maybeCharLikeTyCon tc = if (uniqueOf tc == charDataConKey) then Just charDataCon else Nothing
324 maybeIntLikeTyCon  tc = if (uniqueOf tc == intDataConKey)  then Just intDataCon  else Nothing
325 \end{code}
326
327 %************************************************************************
328 %*                                                                      *
329 \subsection{Commonly-used RdrNames}
330 %*                                                                      *
331 %************************************************************************
332
333 These RdrNames are not really "built in", but some parts of the compiler
334 (notably the deriving mechanism) need to mention their names, and it's convenient
335 to write them all down in one place.
336
337 \begin{code}
338 prelude_primop op = qual (modAndOcc (primOpName op))
339
340 intTyCon_RDR            = qual (modAndOcc intTyCon)
341 ioTyCon_RDR             = tcQual (pREL_IO_BASE,   SLIT("IO"))
342 ioDataCon_RDR           = varQual (pREL_IO_BASE,   SLIT("IO"))
343 ioOkDataCon_RDR         = varQual (pREL_IO_BASE,   SLIT("IOok"))
344 orderingTyCon_RDR       = tcQual (pREL_BASE, SLIT("Ordering"))
345 rationalTyCon_RDR       = tcQual (pREL_NUM,  SLIT("Rational"))
346 ratioTyCon_RDR          = tcQual (pREL_NUM,  SLIT("Ratio"))
347 ratioDataCon_RDR        = varQual (pREL_NUM, SLIT(":%"))
348
349 byteArrayTyCon_RDR              = tcQual (pREL_ARR,  SLIT("ByteArray"))
350 mutableByteArrayTyCon_RDR       = tcQual (pREL_ARR,  SLIT("MutableByteArray"))
351
352 allClass_RDR            = tcQual (pREL_GHC,  SLIT("All"))
353 eqClass_RDR             = tcQual (pREL_BASE, SLIT("Eq"))
354 ordClass_RDR            = tcQual (pREL_BASE, SLIT("Ord"))
355 evalClass_RDR           = tcQual (pREL_BASE, SLIT("Eval"))
356 boundedClass_RDR        = tcQual (pREL_BASE, SLIT("Bounded"))
357 numClass_RDR            = tcQual (pREL_BASE, SLIT("Num"))
358 enumClass_RDR           = tcQual (pREL_BASE, SLIT("Enum"))
359 monadClass_RDR          = tcQual (pREL_BASE, SLIT("Monad"))
360 monadZeroClass_RDR      = tcQual (pREL_BASE, SLIT("MonadZero"))
361 monadPlusClass_RDR      = tcQual (pREL_BASE, SLIT("MonadPlus"))
362 functorClass_RDR        = tcQual (pREL_BASE, SLIT("Functor"))
363 showClass_RDR           = tcQual (pREL_BASE, SLIT("Show"))
364 realClass_RDR           = tcQual (pREL_NUM,  SLIT("Real"))
365 integralClass_RDR       = tcQual (pREL_NUM,  SLIT("Integral"))
366 fractionalClass_RDR     = tcQual (pREL_NUM,  SLIT("Fractional"))
367 floatingClass_RDR       = tcQual (pREL_NUM,  SLIT("Floating"))
368 realFracClass_RDR       = tcQual (pREL_NUM,  SLIT("RealFrac"))
369 realFloatClass_RDR      = tcQual (pREL_NUM,  SLIT("RealFloat"))
370 readClass_RDR           = tcQual (pREL_READ, SLIT("Read"))
371 ixClass_RDR             = tcQual (iX,        SLIT("Ix"))
372 ccallableClass_RDR      = tcQual (pREL_GHC,  SLIT("CCallable"))
373 creturnableClass_RDR    = tcQual (pREL_GHC,  SLIT("CReturnable"))
374
375 fromInt_RDR        = varQual (pREL_BASE, SLIT("fromInt"))
376 fromInteger_RDR    = varQual (pREL_BASE, SLIT("fromInteger"))
377 minus_RDR          = varQual (pREL_BASE, SLIT("-"))
378 toEnum_RDR         = varQual (pREL_BASE, SLIT("toEnum"))
379 fromEnum_RDR       = varQual (pREL_BASE, SLIT("fromEnum"))
380 enumFrom_RDR       = varQual (pREL_BASE, SLIT("enumFrom"))
381 enumFromTo_RDR     = varQual (pREL_BASE, SLIT("enumFromTo"))
382 enumFromThen_RDR   = varQual (pREL_BASE, SLIT("enumFromThen"))
383 enumFromThenTo_RDR = varQual (pREL_BASE, SLIT("enumFromThenTo"))
384
385 thenM_RDR          = varQual (pREL_BASE, SLIT(">>="))
386 returnM_RDR        = varQual (pREL_BASE, SLIT("return"))
387 zeroM_RDR          = varQual (pREL_BASE, SLIT("zero"))
388 fromRational_RDR   = varQual (pREL_NUM,  SLIT("fromRational"))
389
390 negate_RDR         = varQual (pREL_BASE, SLIT("negate"))
391 eq_RDR             = varQual (pREL_BASE, SLIT("=="))
392 ne_RDR             = varQual (pREL_BASE, SLIT("/="))
393 le_RDR             = varQual (pREL_BASE, SLIT("<="))
394 lt_RDR             = varQual (pREL_BASE, SLIT("<"))
395 ge_RDR             = varQual (pREL_BASE, SLIT(">="))
396 gt_RDR             = varQual (pREL_BASE, SLIT(">"))
397 ltTag_RDR          = varQual (pREL_BASE,  SLIT("LT"))
398 eqTag_RDR          = varQual (pREL_BASE,  SLIT("EQ"))
399 gtTag_RDR          = varQual (pREL_BASE,  SLIT("GT"))
400 max_RDR            = varQual (pREL_BASE, SLIT("max"))
401 min_RDR            = varQual (pREL_BASE, SLIT("min"))
402 compare_RDR        = varQual (pREL_BASE, SLIT("compare"))
403 minBound_RDR       = varQual (pREL_BASE, SLIT("minBound"))
404 maxBound_RDR       = varQual (pREL_BASE, SLIT("maxBound"))
405 false_RDR          = varQual (pREL_BASE,  SLIT("False"))
406 true_RDR           = varQual (pREL_BASE,  SLIT("True"))
407 and_RDR            = varQual (pREL_BASE,  SLIT("&&"))
408 not_RDR            = varQual (pREL_BASE,  SLIT("not"))
409 compose_RDR        = varQual (pREL_BASE, SLIT("."))
410 append_RDR         = varQual (pREL_BASE, SLIT("++"))
411 map_RDR            = varQual (pREL_BASE, SLIT("map"))
412
413 showList___RDR     = varQual (pREL_BASE,  SLIT("showList__"))
414 showsPrec_RDR      = varQual (pREL_BASE, SLIT("showsPrec"))
415 showList_RDR       = varQual (pREL_BASE, SLIT("showList"))
416 showSpace_RDR      = varQual (pREL_BASE,  SLIT("showSpace"))
417 showString_RDR     = varQual (pREL_BASE, SLIT("showString"))
418 showParen_RDR      = varQual (pREL_BASE, SLIT("showParen"))
419
420 range_RDR          = varQual (iX,   SLIT("range"))
421 index_RDR          = varQual (iX,   SLIT("index"))
422 inRange_RDR        = varQual (iX,   SLIT("inRange"))
423
424 readsPrec_RDR      = varQual (pREL_READ, SLIT("readsPrec"))
425 readList_RDR       = varQual (pREL_READ, SLIT("readList"))
426 readParen_RDR      = varQual (pREL_READ, SLIT("readParen"))
427 lex_RDR            = varQual (pREL_READ,  SLIT("lex"))
428 readList___RDR     = varQual (pREL_READ,  SLIT("readList__"))
429
430 plus_RDR           = varQual (pREL_BASE, SLIT("+"))
431 times_RDR          = varQual (pREL_BASE, SLIT("*"))
432 mkInt_RDR          = varQual (pREL_BASE, SLIT("I#"))
433
434 error_RDR          = varQual (pREL_ERR, SLIT("error"))
435 assert_RDR         = varQual (pREL_ERR, SLIT("assert__"))
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
455 otherwiseId_RDR = varQual (pREL_BASE, SLIT("otherwise"))
456 \end{code}
457
458 %************************************************************************
459 %*                                                                      *
460 \subsection[Class-std-groups]{Standard groups of Prelude classes}
461 %*                                                                      *
462 %************************************************************************
463
464 @derivableClassKeys@ is also used in checking \tr{deriving} constructs
465 (@TcDeriv@).
466
467 @derivingOccurrences@ maps a class name to a list of the (qualified) occurrences
468 that will be mentioned by  the derived code for the class when it is later generated.
469 We don't need to put in things that are WiredIn (because they are already mapped to their
470 correct name by the @NameSupply@.  The class itself, and all its class ops, is
471 already flagged as an occurrence so we don't need to mention that either.
472
473 @derivingOccurrences@ has an item for every derivable class, even if that item is empty,
474 because we treat lookup failure as indicating that the class is illegal in a deriving clause.
475
476 \begin{code}
477 derivingOccurrences :: UniqFM [RdrName]
478 derivingOccurrences = listToUFM deriving_occ_info
479
480 derivableClassKeys  = map fst deriving_occ_info
481
482 deriving_occ_info
483   = [ (eqClassKey,      [intTyCon_RDR, and_RDR, not_RDR])
484     , (ordClassKey,     [intTyCon_RDR, compose_RDR, eqTag_RDR])
485                                 -- EQ (from Ordering) is needed to force in the constructors
486                                 -- as well as the type constructor.
487     , (enumClassKey,    [intTyCon_RDR, map_RDR])
488     , (evalClassKey,    [intTyCon_RDR])
489     , (boundedClassKey, [intTyCon_RDR])
490     , (showClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, compose_RDR, showString_RDR, 
491                          showParen_RDR, showSpace_RDR, showList___RDR])
492     , (readClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, append_RDR, 
493                          lex_RDR, readParen_RDR, readList___RDR])
494     , (ixClassKey,      [intTyCon_RDR, numClass_RDR, and_RDR, map_RDR, enumFromTo_RDR, 
495                          returnM_RDR, zeroM_RDR])
496                              -- the last two are needed to force returnM, thenM and zeroM
497                              -- in before typechecking the list(monad) comprehension
498                              -- generated for derived Ix instances (range method)
499                              -- of single constructor types.  -- SOF 8/97
500     ]
501         -- intTyCon: Practically any deriving needs Int, either for index calculations, 
502         --              or for taggery.
503         -- ordClass: really it's the methods that are actually used.
504         -- numClass: for Int literals
505 \end{code}
506
507
508 NOTE: @Eq@ and @Text@ do need to appear in @standardClasses@
509 even though every numeric class has these two as a superclass,
510 because the list of ambiguous dictionaries hasn't been simplified.
511
512 \begin{code}
513 isCcallishClass, isNoDictClass, isNumericClass, isStandardClass :: Class -> Bool
514
515 isNumericClass   clas = classKey clas `is_elem` numericClassKeys
516 isStandardClass  clas = classKey clas `is_elem` standardClassKeys
517 isCcallishClass  clas = classKey clas `is_elem` cCallishClassKeys
518 isNoDictClass    clas = classKey clas `is_elem` noDictClassKeys
519 is_elem = isIn "is_X_Class"
520
521 numericClassKeys
522   = [ numClassKey
523     , realClassKey
524     , integralClassKey
525     , fractionalClassKey
526     , floatingClassKey
527     , realFracClassKey
528     , realFloatClassKey
529     ]
530
531 needsDataDeclCtxtClassKeys -- see comments in TcDeriv
532   = [ readClassKey
533     ]
534
535 cCallishClassKeys = [ cCallableClassKey, cReturnableClassKey ]
536
537         -- Renamer always imports these data decls replete with constructors
538         -- so that desugarer can always see the constructor.  Ugh!
539 cCallishTyKeys = [ addrTyConKey, wordTyConKey, byteArrayTyConKey, 
540                    mutableByteArrayTyConKey, foreignObjTyConKey ]
541
542 standardClassKeys
543   = derivableClassKeys ++ numericClassKeys ++ cCallishClassKeys
544     --
545     -- We have to have "CCallable" and "CReturnable" in the standard
546     -- classes, so that if you go...
547     --
548     --      _ccall_ foo ... 93{-numeric literal-} ...
549     --
550     -- ... it can do The Right Thing on the 93.
551
552 noDictClassKeys         -- These classes are used only for type annotations;
553                         -- they are not implemented by dictionaries, ever.
554   = cCallishClassKeys
555         -- I used to think that class Eval belonged in here, but
556         -- we really want functions with type (Eval a => ...) and that
557         -- means that we really want to pass a placeholder for an Eval
558         -- dictionary.  The unit tuple is what we'll get if we leave things
559         -- alone, and that'll do for now.  Could arrange to drop that parameter
560         -- in the end.
561 \end{code}