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