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