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