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