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