[project @ 1998-01-08 18:03:08 by simonm]
[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, showString_RDR, showParen_RDR, readParen_RDR, lex_RDR,
25         showSpace_RDR, showList___RDR, readList___RDR, negate_RDR,
26
27         numClass_RDR, fractionalClass_RDR, eqClass_RDR, 
28         ccallableClass_RDR, creturnableClass_RDR,
29         monadZeroClass_RDR, enumClass_RDR, evalClass_RDR, ordClass_RDR,
30         ioDataCon_RDR, ioOkDataCon_RDR,
31
32         main_NAME, allClass_NAME, ioTyCon_NAME,
33
34         needsDataDeclCtxtClassKeys, cCallishClassKeys, cCallishTyKeys, isNoDictClass,
35         isNumericClass, isStandardClass, isCcallishClass
36     ) where
37
38 #include "HsVersions.h"
39
40 import IdUtils ( primOpName )
41
42 -- friends:
43 import PrelMods         -- Prelude module names
44 import PrelVals         -- VALUES
45 import PrimOp           ( PrimOp(..), allThePrimOps )
46 import PrimRep          ( PrimRep(..) )
47 import TysPrim          -- TYPES
48 import TysWiredIn
49
50 -- others:
51 import RdrHsSyn         ( RdrName(..), varQual, tcQual, qual )
52 import BasicTypes       ( IfaceFlavour )
53 import Id               ( GenId, Id )
54 import Name             ( Name, OccName(..), Provenance(..),
55                           getName, mkGlobalName, modAndOcc
56                         )
57 import Class            ( Class, classKey )
58 import TyCon            ( tyConDataCons, mkFunTyCon, TyCon )
59 import Type
60 import Bag
61 import Unique           -- *Key stuff
62 import UniqFM           ( UniqFM, listToUFM ) 
63 import Util             ( isIn )
64 \end{code}
65
66 %************************************************************************
67 %*                                                                      *
68 \subsection[builtinNameInfo]{Lookup built-in names}
69 %*                                                                      *
70 %************************************************************************
71
72 We have two ``builtin name funs,'' one to look up @TyCons@ and
73 @Classes@, the other to look up values.
74
75 \begin{code}
76 type BuiltinNames = Bag Name
77
78 builtinNames :: BuiltinNames
79 builtinNames
80   =     -- Wired in TyCons
81     unionManyBags (map getTyConNames wired_in_tycons)   `unionBags`
82
83         -- Wired in Ids
84     listToBag (map getName wired_in_ids)                `unionBags`
85
86         -- PrimOps
87     listToBag (map (getName.primOpName) allThePrimOps)  `unionBags`
88
89         -- Other names with magic keys
90     listToBag knownKeyNames
91 \end{code}
92
93
94 \begin{code}
95 getTyConNames :: TyCon -> Bag Name
96 getTyConNames tycon
97     =  getName tycon `consBag` listToBag (map getName (tyConDataCons tycon))
98         -- Synonyms return empty list of constructors
99 \end{code}
100
101
102 We let a lot of "non-standard" values be visible, so that we can make
103 sense of them in interface pragmas. It's cool, though they all have
104 "non-standard" names, so they won't get past the parser in user code.
105
106 %************************************************************************
107 %*                                                                      *
108 \subsection{Wired in TyCons}
109 %*                                                                      *
110 %************************************************************************
111
112
113 \begin{code}
114 wired_in_tycons = [mkFunTyCon] ++
115                   prim_tycons ++
116                   tuple_tycons ++
117                   data_tycons
118
119 prim_tycons
120   = [ addrPrimTyCon
121     , arrayPrimTyCon
122     , byteArrayPrimTyCon
123     , charPrimTyCon
124     , doublePrimTyCon
125     , floatPrimTyCon
126     , intPrimTyCon
127     , foreignObjPrimTyCon
128     , mutableArrayPrimTyCon
129     , mutableByteArrayPrimTyCon
130     , synchVarPrimTyCon
131     , realWorldTyCon
132     , stablePtrPrimTyCon
133     , statePrimTyCon
134     , wordPrimTyCon
135     ]
136
137 tuple_tycons = unitTyCon : [tupleTyCon i | i <- [2..37] ]
138
139
140 data_tycons
141   = [ listTyCon
142     , addrTyCon
143     , boolTyCon
144     , charTyCon
145     , doubleTyCon
146     , floatTyCon
147     , foreignObjTyCon
148     , intTyCon
149     , integerTyCon
150     , liftTyCon
151     , return2GMPsTyCon
152     , returnIntAndGMPTyCon
153     , stTyCon
154     , stRetTyCon
155     , stablePtrTyCon
156     , stateAndAddrPrimTyCon
157     , stateAndArrayPrimTyCon
158     , stateAndByteArrayPrimTyCon
159     , stateAndCharPrimTyCon
160     , stateAndDoublePrimTyCon
161     , stateAndFloatPrimTyCon
162     , stateAndForeignObjPrimTyCon
163     , stateAndIntPrimTyCon
164     , stateAndMutableArrayPrimTyCon
165     , stateAndMutableByteArrayPrimTyCon
166     , stateAndPtrPrimTyCon
167     , stateAndStablePtrPrimTyCon
168     , stateAndSynchVarPrimTyCon
169     , stateAndWordPrimTyCon
170     , voidTyCon
171     , wordTyCon
172     ]
173
174 min_nonprim_tycon_list  -- used w/ HideMostBuiltinNames
175   = [ boolTyCon
176     , charTyCon
177     , intTyCon
178     , floatTyCon
179     , doubleTyCon
180     , integerTyCon
181     , liftTyCon
182     , return2GMPsTyCon  -- ADR asked for these last two (WDP 94/11)
183     , returnIntAndGMPTyCon
184     ]
185 \end{code}
186
187 %************************************************************************
188 %*                                                                      *
189 \subsection{Wired in Ids}
190 %*                                                                      *
191 %************************************************************************
192
193 The WiredIn Ids ...
194 ToDo: Some of these should be moved to id_keys_infos!
195
196 \begin{code}
197 wired_in_ids
198   = [ aBSENT_ERROR_ID
199     , augmentId
200     , buildId
201     , eRROR_ID
202     , foldlId
203     , foldrId
204     , iRREFUT_PAT_ERROR_ID
205     , integerMinusOneId
206     , integerPlusOneId
207     , integerPlusTwoId
208     , integerZeroId
209     , nON_EXHAUSTIVE_GUARDS_ERROR_ID
210     , nO_DEFAULT_METHOD_ERROR_ID
211     , nO_EXPLICIT_METHOD_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 (iO_BASE,   SLIT("IO"))
342 ioDataCon_RDR           = varQual (iO_BASE,   SLIT("IO"))
343 ioOkDataCon_RDR         = varQual (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 (aRR_BASE,  SLIT("ByteArray"))
350 mutableByteArrayTyCon_RDR       = tcQual (aRR_BASE,  SLIT("MutableByteArray"))
351
352 allClass_RDR            = tcQual (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 (gHC__,   SLIT("CCallable"))
373 creturnableClass_RDR    = tcQual (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 (eRROR, SLIT("error"))
435
436 eqH_Char_RDR    = prelude_primop CharEqOp
437 ltH_Char_RDR    = prelude_primop CharLtOp
438 eqH_Word_RDR    = prelude_primop WordEqOp
439 ltH_Word_RDR    = prelude_primop WordLtOp
440 eqH_Addr_RDR    = prelude_primop AddrEqOp
441 ltH_Addr_RDR    = prelude_primop AddrLtOp
442 eqH_Float_RDR   = prelude_primop FloatEqOp
443 ltH_Float_RDR   = prelude_primop FloatLtOp
444 eqH_Double_RDR  = prelude_primop DoubleEqOp
445 ltH_Double_RDR  = prelude_primop DoubleLtOp
446 eqH_Int_RDR     = prelude_primop IntEqOp
447 ltH_Int_RDR     = prelude_primop IntLtOp
448 geH_RDR         = prelude_primop IntGeOp
449 leH_RDR         = prelude_primop IntLeOp
450 minusH_RDR      = prelude_primop IntSubOp
451
452 main_RDR        = varQual (mAIN,     SLIT("main"))
453
454 otherwiseId_RDR = varQual (pREL_BASE, SLIT("otherwise"))
455 \end{code}
456
457 %************************************************************************
458 %*                                                                      *
459 \subsection[Class-std-groups]{Standard groups of Prelude classes}
460 %*                                                                      *
461 %************************************************************************
462
463 @derivableClassKeys@ is also used in checking \tr{deriving} constructs
464 (@TcDeriv@).
465
466 @derivingOccurrences@ maps a class name to a list of the (qualified) occurrences
467 that will be mentioned by  the derived code for the class when it is later generated.
468 We don't need to put in things that are WiredIn (because they are already mapped to their
469 correct name by the @NameSupply@.  The class itself, and all its class ops, is
470 already flagged as an occurrence so we don't need to mention that either.
471
472 @derivingOccurrences@ has an item for every derivable class, even if that item is empty,
473 because we treat lookup failure as indicating that the class is illegal in a deriving clause.
474
475 \begin{code}
476 derivingOccurrences :: UniqFM [RdrName]
477 derivingOccurrences = listToUFM deriving_occ_info
478
479 derivableClassKeys  = map fst deriving_occ_info
480
481 deriving_occ_info
482   = [ (eqClassKey,      [intTyCon_RDR, and_RDR, not_RDR])
483     , (ordClassKey,     [intTyCon_RDR, compose_RDR, eqTag_RDR])
484                                 -- EQ (from Ordering) is needed to force in the constructors
485                                 -- as well as the type constructor.
486     , (enumClassKey,    [intTyCon_RDR, map_RDR])
487     , (evalClassKey,    [intTyCon_RDR])
488     , (boundedClassKey, [intTyCon_RDR])
489     , (showClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, compose_RDR, showString_RDR, 
490                          showParen_RDR, showSpace_RDR, showList___RDR])
491     , (readClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, append_RDR, 
492                          lex_RDR, readParen_RDR, readList___RDR])
493     , (ixClassKey,      [intTyCon_RDR, numClass_RDR, and_RDR, map_RDR, enumFromTo_RDR, 
494                          returnM_RDR, zeroM_RDR])
495                              -- the last two are needed to force returnM, thenM and zeroM
496                              -- in before typechecking the list(monad) comprehension
497                              -- generated for derived Ix instances (range method)
498                              -- of single constructor types.  -- SOF 8/97
499     ]
500         -- intTyCon: Practically any deriving needs Int, either for index calculations, 
501         --              or for taggery.
502         -- ordClass: really it's the methods that are actually used.
503         -- numClass: for Int literals
504 \end{code}
505
506
507 NOTE: @Eq@ and @Text@ do need to appear in @standardClasses@
508 even though every numeric class has these two as a superclass,
509 because the list of ambiguous dictionaries hasn't been simplified.
510
511 \begin{code}
512 isCcallishClass, isNoDictClass, isNumericClass, isStandardClass :: Class -> Bool
513
514 isNumericClass   clas = classKey clas `is_elem` numericClassKeys
515 isStandardClass  clas = classKey clas `is_elem` standardClassKeys
516 isCcallishClass  clas = classKey clas `is_elem` cCallishClassKeys
517 isNoDictClass    clas = classKey clas `is_elem` noDictClassKeys
518 is_elem = isIn "is_X_Class"
519
520 numericClassKeys
521   = [ numClassKey
522     , realClassKey
523     , integralClassKey
524     , fractionalClassKey
525     , floatingClassKey
526     , realFracClassKey
527     , realFloatClassKey
528     ]
529
530 needsDataDeclCtxtClassKeys -- see comments in TcDeriv
531   = [ readClassKey
532     ]
533
534 cCallishClassKeys = [ cCallableClassKey, cReturnableClassKey ]
535
536         -- Renamer always imports these data decls replete with constructors
537         -- so that desugarer can always see the constructor.  Ugh!
538 cCallishTyKeys = [ addrTyConKey, wordTyConKey, byteArrayTyConKey, 
539                    mutableByteArrayTyConKey, foreignObjTyConKey ]
540
541 standardClassKeys
542   = derivableClassKeys ++ numericClassKeys ++ cCallishClassKeys
543     --
544     -- We have to have "CCallable" and "CReturnable" in the standard
545     -- classes, so that if you go...
546     --
547     --      _ccall_ foo ... 93{-numeric literal-} ...
548     --
549     -- ... it can do The Right Thing on the 93.
550
551 noDictClassKeys         -- These classes are used only for type annotations;
552                         -- they are not implemented by dictionaries, ever.
553   = cCallishClassKeys
554         -- I used to think that class Eval belonged in here, but
555         -- we really want functions with type (Eval a => ...) and that
556         -- means that we really want to pass a placeholder for an Eval
557         -- dictionary.  The unit tuple is what we'll get if we leave things
558         -- alone, and that'll do for now.  Could arrange to drop that parameter
559         -- in the end.
560 \end{code}