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