cb0a3064ff2fde5d55179025c81b028861340e9b
[ghc-hetmet.git] / ghc / compiler / prelude / PrelInfo.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[PrelInfo]{The @PrelInfo@ interface to the compiler's prelude knowledge}
5
6 \begin{code}
7 module PrelInfo (
8         builtinNames,   -- Names of things whose *unique* must be known, but 
9                         -- that is all. If something is in here, you know that
10                         -- if it's used at all then it's Name will be just as
11                         -- it is here, unique and all.  Includes all the 
12                         -- wiredd-in names.
13
14         thinAirIdNames, -- Names of non-wired-in Ids that may be used out of
15         setThinAirIds,  -- thin air in any compilation. If they are not wired in
16         thinAirModules, -- we must be sure to import them from some Prelude 
17                         -- interface file even if they are not overtly 
18                         -- mentioned.  Subset of builtinNames.
19         noRepIntegerIds,
20         noRepStrIds,
21
22         derivingOccurrences,    -- For a given class C, this tells what other 
23                                 -- things are needed as a result of a 
24                                 -- deriving(C) clause
25
26
27         -- Here are the thin-air Ids themselves
28         addr2IntegerId,
29         packStringForCId, unpackCStringId, unpackCString2Id,
30         unpackCStringAppendId, unpackCStringFoldrId,
31         foldrId,
32
33         -- Random other things
34         main_NAME, ioTyCon_NAME,
35         deRefStablePtr_NAME, makeStablePtr_NAME,
36         bindIO_NAME,
37
38         maybeCharLikeCon, maybeIntLikeCon,
39         needsDataDeclCtxtClassKeys, cCallishClassKeys, cCallishTyKeys, 
40         isNoDictClass, isNumericClass, isStandardClass, isCcallishClass, 
41         isCreturnableClass, numericTyKeys,
42
43         -- RdrNames for lots of things, mainly used in derivings
44         eq_RDR, ne_RDR, le_RDR, lt_RDR, ge_RDR, gt_RDR, max_RDR, min_RDR, 
45         compare_RDR, minBound_RDR, maxBound_RDR, enumFrom_RDR, enumFromTo_RDR,
46         enumFromThen_RDR, enumFromThenTo_RDR, succ_RDR, pred_RDR, fromEnum_RDR, toEnum_RDR, 
47         ratioDataCon_RDR, range_RDR, index_RDR, inRange_RDR, readsPrec_RDR,
48         readList_RDR, showsPrec_RDR, showList_RDR, plus_RDR, times_RDR,
49         ltTag_RDR, eqTag_RDR, gtTag_RDR, eqH_Char_RDR, ltH_Char_RDR, 
50         eqH_Word_RDR, ltH_Word_RDR, eqH_Addr_RDR, ltH_Addr_RDR, eqH_Float_RDR,
51         ltH_Float_RDR, eqH_Double_RDR, ltH_Double_RDR, eqH_Int_RDR, 
52         ltH_Int_RDR, geH_RDR, leH_RDR, minusH_RDR, false_RDR, true_RDR,
53         and_RDR, not_RDR, append_RDR, map_RDR, compose_RDR, mkInt_RDR,
54         error_RDR, assertErr_RDR,
55         showString_RDR, showParen_RDR, readParen_RDR, lex_RDR,
56         showSpace_RDR, showList___RDR, readList___RDR, negate_RDR,
57
58         numClass_RDR, fractionalClass_RDR, eqClass_RDR, 
59         ccallableClass_RDR, creturnableClass_RDR,
60         monadClass_RDR, enumClass_RDR, ordClass_RDR,
61         ioDataCon_RDR,
62
63         mkTupConRdrName, mkUbxTupConRdrName
64
65     ) where
66
67 #include "HsVersions.h"
68
69
70 -- friends:
71 import PrelMods         -- Prelude module names
72 import PrelVals         -- VALUES
73 import MkId             ( mkPrimitiveId )
74 import PrimOp           ( PrimOp(..), allThePrimOps )
75 import DataCon          ( DataCon )
76 import PrimRep          ( PrimRep(..) )
77 import TysPrim          -- TYPES
78 import TysWiredIn
79
80 -- others:
81 import RdrName          ( RdrName, mkPreludeQual )
82 import Var              ( varUnique, Id )
83 import Name             ( Name, OccName, Provenance(..), 
84                           NameSpace, tcName, clsName, varName, dataName,
85                           getName, mkGlobalName, nameRdrName, systemProvenance
86                         )
87 import RdrName          ( rdrNameModule, rdrNameOcc, mkSrcQual )
88 import Class            ( Class, classKey )
89 import TyCon            ( tyConDataCons, TyCon )
90 import Type             ( funTyCon )
91 import Bag
92 import Unique           -- *Key stuff
93 import UniqFM           ( UniqFM, listToUFM, lookupWithDefaultUFM ) 
94 import Util             ( isIn )
95 import Panic            ( panic )
96
97 import IOExts
98 \end{code}
99
100 %************************************************************************
101 %*                                                                      *
102 \subsection[builtinNameInfo]{Lookup built-in names}
103 %*                                                                      *
104 %************************************************************************
105
106 We have two ``builtin name funs,'' one to look up @TyCons@ and
107 @Classes@, the other to look up values.
108
109 \begin{code}
110 builtinNames :: Bag Name
111 builtinNames
112   = unionManyBags
113         [       -- Wired in TyCons
114           unionManyBags (map getTyConNames wired_in_tycons)
115
116                 -- Wired in Ids
117         , listToBag (map getName wired_in_ids)
118
119                 -- PrimOps
120         , listToBag (map (getName . mkPrimitiveId) allThePrimOps)
121
122                 -- Thin-air ids
123         , listToBag thinAirIdNames
124
125                 -- Other names with magic keys
126         , listToBag knownKeyNames
127         ]
128 \end{code}
129
130
131 \begin{code}
132 getTyConNames :: TyCon -> Bag Name
133 getTyConNames tycon
134     = getName tycon `consBag` 
135       listToBag (map getName (tyConDataCons tycon))
136         -- Synonyms return empty list of constructors
137 \end{code}
138
139 We let a lot of "non-standard" values be visible, so that we can make
140 sense of them in interface pragmas. It's cool, though they all have
141 "non-standard" names, so they won't get past the parser in user code.
142
143
144 %************************************************************************
145 %*                                                                      *
146 \subsection{Wired in TyCons}
147 %*                                                                      *
148 %************************************************************************
149
150 \begin{code}
151 wired_in_tycons = [funTyCon] ++
152                   prim_tycons ++
153                   tuple_tycons ++
154                   unboxed_tuple_tycons ++
155                   data_tycons
156
157 prim_tycons
158   = [ addrPrimTyCon
159     , arrayPrimTyCon
160     , byteArrayPrimTyCon
161     , charPrimTyCon
162     , doublePrimTyCon
163     , floatPrimTyCon
164     , intPrimTyCon
165     , int64PrimTyCon
166     , foreignObjPrimTyCon
167     , weakPrimTyCon
168     , mutableArrayPrimTyCon
169     , mutableByteArrayPrimTyCon
170     , mVarPrimTyCon
171     , mutVarPrimTyCon
172     , realWorldTyCon
173     , stablePtrPrimTyCon
174     , stableNamePrimTyCon
175     , statePrimTyCon
176     , threadIdPrimTyCon
177     , wordPrimTyCon
178     , word64PrimTyCon
179     ]
180
181 tuple_tycons = unitTyCon : [tupleTyCon i | i <- [2..37] ]
182 unboxed_tuple_tycons = [unboxedTupleTyCon i | i <- [1..37] ]
183
184 data_tycons
185   = [ addrTyCon
186     , boolTyCon
187     , charTyCon
188     , doubleTyCon
189     , floatTyCon
190     , intTyCon
191     , int8TyCon
192     , int16TyCon
193     , int32TyCon
194     , int64TyCon
195     , integerTyCon
196     , listTyCon
197     , wordTyCon
198     , word8TyCon
199     , word16TyCon
200     , word32TyCon
201     , word64TyCon
202     ]
203 \end{code}
204
205
206 %************************************************************************
207 %*                                                                      *
208 \subsection{Wired in Ids}
209 %*                                                                      *
210 %************************************************************************
211
212 \begin{code}
213 wired_in_ids
214   = [   -- These error-y things are wired in because we don't yet have
215         -- a way to express in an interface file that the result type variable
216         -- is 'open'; that is can be unified with an unboxed type
217         -- 
218         -- [The interface file format now carry such information, but there's
219         --  no way yet of expressing at the definition site for these error-reporting
220         --  functions that they have an 'open' result type. -- sof 1/99]
221         -- 
222       aBSENT_ERROR_ID
223     , eRROR_ID
224     , iRREFUT_PAT_ERROR_ID
225     , nON_EXHAUSTIVE_GUARDS_ERROR_ID
226     , nO_METHOD_BINDING_ERROR_ID
227     , pAR_ERROR_ID
228     , pAT_ERROR_ID
229     , rEC_CON_ERROR_ID
230     , rEC_UPD_ERROR_ID
231
232         -- These two can't be defined in Haskell
233     , realWorldPrimId
234     , unsafeCoerceId
235     ]
236
237 \end{code}
238
239 %************************************************************************
240 %*                                                                      *
241 \subsection{Thin air entities}
242 %*                                                                      *
243 %************************************************************************
244
245 These are Ids that we need to reference in various parts of the
246 system, and we'd like to pull them out of thin air rather than pass
247 them around.  We'd also like to have all the IdInfo available for each
248 one: i.e. everything that gets pulled out of the interface file.
249
250 The solution is to generate this map of global Ids after the
251 typechecker, and assign it to a global variable.  Any subsequent
252 pass may refer to the map to pull Ids out.  Any invalid
253 (i.e. pre-typechecker) access to the map will result in a panic.
254
255 \begin{code}
256 thinAirIdNames 
257   = map mkKnownKeyGlobal
258     [
259         -- Needed for converting literals to Integers (used in tidyCoreExpr)
260       (varQual pREL_BASE SLIT("addr2Integer"), addr2IntegerIdKey)
261
262         -- String literals
263     , (varQual pREL_PACK SLIT("packCString#"),   packCStringIdKey)
264     , (varQual pREL_PACK SLIT("unpackCString#"), unpackCStringIdKey)
265     , (varQual pREL_PACK SLIT("unpackNBytes#"),  unpackCString2IdKey)
266     , (varQual pREL_PACK SLIT("unpackAppendCString#"), unpackCStringAppendIdKey)
267     , (varQual pREL_PACK SLIT("unpackFoldrCString#"),  unpackCStringFoldrIdKey)
268
269         -- Folds; introduced by desugaring list comprehensions
270     , (varQual pREL_BASE SLIT("foldr"), foldrIdKey)
271     ]
272
273 thinAirModules = [pREL_PACK]    -- See notes with RnIfaces.findAndReadIface
274
275 noRepIntegerIds = [addr2IntegerId]
276
277 noRepStrIds = [unpackCString2Id, unpackCStringId]
278
279 addr2IntegerId = lookupThinAirId addr2IntegerIdKey
280
281 packStringForCId = lookupThinAirId packCStringIdKey
282 unpackCStringId  = lookupThinAirId unpackCStringIdKey
283 unpackCString2Id = lookupThinAirId unpackCString2IdKey 
284 unpackCStringAppendId = lookupThinAirId unpackCStringAppendIdKey 
285 unpackCStringFoldrId  = lookupThinAirId unpackCStringFoldrIdKey 
286
287 foldrId = lookupThinAirId foldrIdKey
288 \end{code}
289
290
291 \begin{code}
292 \end{code}
293
294 \begin{code}
295 thinAirIdMapRef :: IORef (UniqFM Id)
296 thinAirIdMapRef = unsafePerformIO (newIORef (panic "thinAirIdMap: still empty"))
297
298 setThinAirIds :: [Id] -> IO ()
299 setThinAirIds thin_air_ids
300   = writeIORef thinAirIdMapRef the_map
301   where
302     the_map = listToUFM [(varUnique id, id) | id <- thin_air_ids]
303
304 thinAirIdMap :: UniqFM Id
305 thinAirIdMap = unsafePerformIO (readIORef thinAirIdMapRef)
306   -- Read it just once, the first time someone tugs on thinAirIdMap
307
308 lookupThinAirId :: Unique -> Id
309 lookupThinAirId uniq = lookupWithDefaultUFM thinAirIdMap
310                         (panic "lookupThinAirId: no mapping") uniq 
311 \end{code}
312
313
314 %************************************************************************
315 %*                                                                      *
316 \subsection{Built-in keys}
317 %*                                                                      *
318 %************************************************************************
319
320 Ids, Synonyms, Classes and ClassOps with builtin keys. 
321
322 \begin{code}
323 mkKnownKeyGlobal :: (RdrName, Unique) -> Name
324 mkKnownKeyGlobal (rdr_name, uniq)
325   = mkGlobalName uniq (rdrNameModule rdr_name) (rdrNameOcc rdr_name)
326                  systemProvenance
327
328 ioTyCon_NAME      = mkKnownKeyGlobal (ioTyCon_RDR,       ioTyConKey)
329 main_NAME         = mkKnownKeyGlobal (main_RDR,          mainKey)
330
331  -- Operations needed when compiling FFI decls
332 bindIO_NAME         = mkKnownKeyGlobal (bindIO_RDR,         bindIOIdKey)
333 deRefStablePtr_NAME = mkKnownKeyGlobal (deRefStablePtr_RDR, deRefStablePtrIdKey)
334 makeStablePtr_NAME  = mkKnownKeyGlobal (makeStablePtr_RDR,  makeStablePtrIdKey)
335
336 knownKeyNames :: [Name]
337 knownKeyNames
338   = [main_NAME, ioTyCon_NAME]
339     ++
340     map mkKnownKeyGlobal
341     [
342         -- Type constructors (synonyms especially)
343       (orderingTyCon_RDR,       orderingTyConKey)
344     , (rationalTyCon_RDR,       rationalTyConKey)
345     , (ratioDataCon_RDR,        ratioDataConKey)
346     , (ratioTyCon_RDR,          ratioTyConKey)
347     , (byteArrayTyCon_RDR,      byteArrayTyConKey)
348     , (mutableByteArrayTyCon_RDR, mutableByteArrayTyConKey)
349     , (foreignObjTyCon_RDR,     foreignObjTyConKey)
350     , (stablePtrTyCon_RDR,      stablePtrTyConKey)
351     , (stablePtrDataCon_RDR,    stablePtrDataConKey)
352
353         --  Classes.  *Must* include:
354         --      classes that are grabbed by key (e.g., eqClassKey)
355         --      classes in "Class.standardClassKeys" (quite a few)
356     , (eqClass_RDR,             eqClassKey)             -- mentioned, derivable
357     , (ordClass_RDR,            ordClassKey)            -- derivable
358     , (boundedClass_RDR,        boundedClassKey)        -- derivable
359     , (numClass_RDR,            numClassKey)            -- mentioned, numeric
360     , (enumClass_RDR,           enumClassKey)           -- derivable
361     , (monadClass_RDR,          monadClassKey)
362     , (monadPlusClass_RDR,      monadPlusClassKey)
363     , (functorClass_RDR,        functorClassKey)
364     , (showClass_RDR,           showClassKey)           -- derivable
365     , (realClass_RDR,           realClassKey)           -- numeric
366     , (integralClass_RDR,       integralClassKey)       -- numeric
367     , (fractionalClass_RDR,     fractionalClassKey)     -- numeric
368     , (floatingClass_RDR,       floatingClassKey)       -- numeric
369     , (realFracClass_RDR,       realFracClassKey)       -- numeric
370     , (realFloatClass_RDR,      realFloatClassKey)      -- numeric
371     , (readClass_RDR,           readClassKey)           -- derivable
372     , (ixClass_RDR,             ixClassKey)             -- derivable (but it isn't Prelude.Ix; hmmm)
373     , (ccallableClass_RDR,      cCallableClassKey)      -- mentioned, ccallish
374     , (creturnableClass_RDR,    cReturnableClassKey)    -- mentioned, ccallish
375
376         -- ClassOps 
377     , (fromInt_RDR,             fromIntClassOpKey)
378     , (fromInteger_RDR,         fromIntegerClassOpKey)
379     , (ge_RDR,                  geClassOpKey) 
380     , (minus_RDR,               minusClassOpKey)
381     , (enumFrom_RDR,            enumFromClassOpKey)
382     , (enumFromThen_RDR,        enumFromThenClassOpKey)
383     , (enumFromTo_RDR,          enumFromToClassOpKey)
384     , (enumFromThenTo_RDR,      enumFromThenToClassOpKey)
385     , (fromEnum_RDR,            fromEnumClassOpKey)
386     , (toEnum_RDR,              toEnumClassOpKey)
387     , (eq_RDR,                  eqClassOpKey)
388     , (thenM_RDR,               thenMClassOpKey)
389     , (returnM_RDR,             returnMClassOpKey)
390     , (failM_RDR,               failMClassOpKey)
391     , (fromRational_RDR,        fromRationalClassOpKey)
392     
393     , (deRefStablePtr_RDR,      deRefStablePtrIdKey)
394     , (makeStablePtr_RDR,       makeStablePtrIdKey)
395     , (bindIO_RDR,              bindIOIdKey)
396
397     , (map_RDR,                 mapIdKey)
398     , (append_RDR,              appendIdKey)
399
400         -- List operations
401     , (concat_RDR,              concatIdKey)
402     , (filter_RDR,              filterIdKey)
403     , (zip_RDR,                 zipIdKey)
404
405         -- Others
406     , (otherwiseId_RDR,         otherwiseIdKey)
407     , (assert_RDR,              assertIdKey)
408     ]
409 \end{code}
410
411 ToDo: make it do the ``like'' part properly (as in 0.26 and before).
412
413 \begin{code}
414 maybeCharLikeCon, maybeIntLikeCon :: DataCon -> Bool
415 maybeCharLikeCon con = getUnique con == charDataConKey
416 maybeIntLikeCon  con = getUnique con == intDataConKey
417 \end{code}
418
419 %************************************************************************
420 %*                                                                      *
421 \subsection{Commonly-used RdrNames}
422 %*                                                                      *
423 %************************************************************************
424
425 These RdrNames are not really "built in", but some parts of the compiler
426 (notably the deriving mechanism) need to mention their names, and it's convenient
427 to write them all down in one place.
428
429 \begin{code}
430 prelude_primop op = nameRdrName (getName (mkPrimitiveId op))
431
432 main_RDR                = varQual mAIN      SLIT("main")
433 otherwiseId_RDR         = varQual pREL_BASE SLIT("otherwise")
434
435 intTyCon_RDR            = nameRdrName (getName intTyCon)
436 ioTyCon_RDR             = tcQual   pREL_IO_BASE SLIT("IO")
437 ioDataCon_RDR           = dataQual pREL_IO_BASE SLIT("IO")
438 bindIO_RDR              = varQual  pREL_IO_BASE SLIT("bindIO")
439
440 orderingTyCon_RDR       = tcQual   pREL_BASE SLIT("Ordering")
441 rationalTyCon_RDR       = tcQual   pREL_NUM  SLIT("Rational")
442 ratioTyCon_RDR          = tcQual   pREL_NUM  SLIT("Ratio")
443 ratioDataCon_RDR        = dataQual pREL_NUM  SLIT(":%")
444
445 byteArrayTyCon_RDR              = tcQual pREL_ARR  SLIT("ByteArray")
446 mutableByteArrayTyCon_RDR       = tcQual pREL_ARR  SLIT("MutableByteArray")
447
448 foreignObjTyCon_RDR     = tcQual   pREL_IO_BASE SLIT("ForeignObj")
449 stablePtrTyCon_RDR      = tcQual   pREL_STABLE SLIT("StablePtr")
450 stablePtrDataCon_RDR    = dataQual pREL_STABLE SLIT("StablePtr")
451 deRefStablePtr_RDR      = varQual  pREL_STABLE SLIT("deRefStablePtr")
452 makeStablePtr_RDR       = varQual  pREL_STABLE SLIT("makeStablePtr")
453
454 eqClass_RDR             = clsQual pREL_BASE SLIT("Eq")
455 ordClass_RDR            = clsQual pREL_BASE SLIT("Ord")
456 boundedClass_RDR        = clsQual pREL_BASE SLIT("Bounded")
457 numClass_RDR            = clsQual pREL_BASE SLIT("Num")
458 enumClass_RDR           = clsQual pREL_BASE SLIT("Enum")
459 monadClass_RDR          = clsQual pREL_BASE SLIT("Monad")
460 monadPlusClass_RDR      = clsQual pREL_BASE SLIT("MonadPlus")
461 functorClass_RDR        = clsQual pREL_BASE SLIT("Functor")
462 showClass_RDR           = clsQual pREL_BASE SLIT("Show")
463 realClass_RDR           = clsQual pREL_NUM  SLIT("Real")
464 integralClass_RDR       = clsQual pREL_NUM  SLIT("Integral")
465 fractionalClass_RDR     = clsQual pREL_NUM  SLIT("Fractional")
466 floatingClass_RDR       = clsQual pREL_NUM  SLIT("Floating")
467 realFracClass_RDR       = clsQual pREL_NUM  SLIT("RealFrac")
468 realFloatClass_RDR      = clsQual pREL_NUM  SLIT("RealFloat")
469 readClass_RDR           = clsQual pREL_READ SLIT("Read")
470 ixClass_RDR             = clsQual iX        SLIT("Ix")
471 ccallableClass_RDR      = clsQual pREL_GHC  SLIT("CCallable")
472 creturnableClass_RDR    = clsQual pREL_GHC  SLIT("CReturnable")
473
474 fromInt_RDR        = varQual pREL_BASE SLIT("fromInt")
475 fromInteger_RDR    = varQual pREL_BASE SLIT("fromInteger")
476 minus_RDR          = varQual pREL_BASE SLIT("-")
477 succ_RDR           = varQual pREL_BASE SLIT("succ")
478 pred_RDR           = varQual pREL_BASE SLIT("pred")
479 toEnum_RDR         = varQual pREL_BASE SLIT("toEnum")
480 fromEnum_RDR       = varQual pREL_BASE SLIT("fromEnum")
481 enumFrom_RDR       = varQual pREL_BASE SLIT("enumFrom")
482 enumFromTo_RDR     = varQual pREL_BASE SLIT("enumFromTo")
483 enumFromThen_RDR   = varQual pREL_BASE SLIT("enumFromThen")
484 enumFromThenTo_RDR = varQual pREL_BASE SLIT("enumFromThenTo")
485
486 thenM_RDR          = varQual pREL_BASE SLIT(">>=")
487 returnM_RDR        = varQual pREL_BASE SLIT("return")
488 failM_RDR          = varQual pREL_BASE SLIT("fail")
489
490 fromRational_RDR   = varQual pREL_NUM  SLIT("fromRational")
491 negate_RDR         = varQual pREL_BASE SLIT("negate")
492 eq_RDR             = varQual pREL_BASE SLIT("==")
493 ne_RDR             = varQual pREL_BASE SLIT("/=")
494 le_RDR             = varQual pREL_BASE SLIT("<=")
495 lt_RDR             = varQual pREL_BASE SLIT("<")
496 ge_RDR             = varQual pREL_BASE SLIT(">=")
497 gt_RDR             = varQual pREL_BASE SLIT(">")
498 ltTag_RDR          = dataQual pREL_BASE SLIT("LT")
499 eqTag_RDR          = dataQual pREL_BASE SLIT("EQ")
500 gtTag_RDR          = dataQual pREL_BASE SLIT("GT")
501 max_RDR            = varQual pREL_BASE SLIT("max")
502 min_RDR            = varQual pREL_BASE SLIT("min")
503 compare_RDR        = varQual pREL_BASE SLIT("compare")
504 minBound_RDR       = varQual pREL_BASE SLIT("minBound")
505 maxBound_RDR       = varQual pREL_BASE SLIT("maxBound")
506 false_RDR          = dataQual pREL_BASE SLIT("False")
507 true_RDR           = dataQual pREL_BASE SLIT("True")
508 and_RDR            = varQual pREL_BASE SLIT("&&")
509 not_RDR            = varQual pREL_BASE SLIT("not")
510 compose_RDR        = varQual pREL_BASE SLIT(".")
511 append_RDR         = varQual pREL_BASE SLIT("++")
512 map_RDR            = varQual pREL_BASE SLIT("map")
513 concat_RDR         = varQual mONAD     SLIT("concat")
514 filter_RDR         = varQual mONAD     SLIT("filter")
515 zip_RDR            = varQual pREL_LIST SLIT("zip")
516
517 showList___RDR     = varQual pREL_BASE  SLIT("showList__")
518 showsPrec_RDR      = varQual pREL_BASE SLIT("showsPrec")
519 showList_RDR       = varQual pREL_BASE SLIT("showList")
520 showSpace_RDR      = varQual pREL_BASE SLIT("showSpace")
521 showString_RDR     = varQual pREL_BASE SLIT("showString")
522 showParen_RDR      = varQual pREL_BASE SLIT("showParen")
523
524 range_RDR          = varQual iX   SLIT("range")
525 index_RDR          = varQual iX   SLIT("index")
526 inRange_RDR        = varQual iX   SLIT("inRange")
527
528 readsPrec_RDR      = varQual pREL_READ SLIT("readsPrec")
529 readList_RDR       = varQual pREL_READ SLIT("readList")
530 readParen_RDR      = varQual pREL_READ SLIT("readParen")
531 lex_RDR            = varQual pREL_READ SLIT("lex")
532 readList___RDR     = varQual pREL_READ SLIT("readList__")
533
534 plus_RDR           = varQual pREL_BASE SLIT("+")
535 times_RDR          = varQual pREL_BASE SLIT("*")
536 mkInt_RDR          = dataQual pREL_BASE SLIT("I#")
537
538 error_RDR          = varQual pREL_ERR SLIT("error")
539 assert_RDR         = varQual pREL_GHC SLIT("assert")
540 assertErr_RDR      = varQual pREL_ERR SLIT("assertError")
541
542 eqH_Char_RDR    = prelude_primop CharEqOp
543 ltH_Char_RDR    = prelude_primop CharLtOp
544 eqH_Word_RDR    = prelude_primop WordEqOp
545 ltH_Word_RDR    = prelude_primop WordLtOp
546 eqH_Addr_RDR    = prelude_primop AddrEqOp
547 ltH_Addr_RDR    = prelude_primop AddrLtOp
548 eqH_Float_RDR   = prelude_primop FloatEqOp
549 ltH_Float_RDR   = prelude_primop FloatLtOp
550 eqH_Double_RDR  = prelude_primop DoubleEqOp
551 ltH_Double_RDR  = prelude_primop DoubleLtOp
552 eqH_Int_RDR     = prelude_primop IntEqOp
553 ltH_Int_RDR     = prelude_primop IntLtOp
554 geH_RDR         = prelude_primop IntGeOp
555 leH_RDR         = prelude_primop IntLeOp
556 minusH_RDR      = prelude_primop IntSubOp
557 \end{code}
558
559 \begin{code}
560 mkTupConRdrName :: Int -> RdrName 
561 mkTupConRdrName arity = case mkTupNameStr arity of
562                           (mod, occ) -> dataQual mod occ
563
564 mkUbxTupConRdrName :: Int -> RdrName
565 mkUbxTupConRdrName arity = case mkUbxTupNameStr arity of
566                                 (mod, occ) -> dataQual mod occ
567 \end{code}
568
569
570 %************************************************************************
571 %*                                                                      *
572 \subsection[Class-std-groups]{Standard groups of Prelude classes}
573 %*                                                                      *
574 %************************************************************************
575
576 @derivableClassKeys@ is also used in checking \tr{deriving} constructs
577 (@TcDeriv@).
578
579 @derivingOccurrences@ maps a class name to a list of the (qualified) occurrences
580 that will be mentioned by  the derived code for the class when it is later generated.
581 We don't need to put in things that are WiredIn (because they are already mapped to their
582 correct name by the @NameSupply@.  The class itself, and all its class ops, is
583 already flagged as an occurrence so we don't need to mention that either.
584
585 @derivingOccurrences@ has an item for every derivable class, even if that item is empty,
586 because we treat lookup failure as indicating that the class is illegal in a deriving clause.
587
588 \begin{code}
589 derivingOccurrences :: UniqFM [RdrName]
590 derivingOccurrences = listToUFM deriving_occ_info
591
592 derivableClassKeys  = map fst deriving_occ_info
593
594 deriving_occ_info
595   = [ (eqClassKey,      [intTyCon_RDR, and_RDR, not_RDR])
596     , (ordClassKey,     [intTyCon_RDR, compose_RDR, eqTag_RDR])
597                                 -- EQ (from Ordering) is needed to force in the constructors
598                                 -- as well as the type constructor.
599     , (enumClassKey,    [intTyCon_RDR, eq_RDR, ge_RDR, and_RDR, map_RDR, plus_RDR, showsPrec_RDR, append_RDR]) 
600                                 -- The last two Enum deps are only used to produce better
601                                 -- error msgs for derived toEnum methods.
602     , (boundedClassKey, [intTyCon_RDR])
603     , (showClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, compose_RDR, showString_RDR, 
604                          showParen_RDR, showSpace_RDR, showList___RDR])
605     , (readClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, append_RDR, 
606                          lex_RDR, readParen_RDR, readList___RDR, thenM_RDR])
607                              -- returnM (and the rest of the Monad class decl) 
608                              -- will be forced in as result of depending
609                              -- on thenM.   -- SOF 1/99
610     , (ixClassKey,      [intTyCon_RDR, numClass_RDR, and_RDR, map_RDR, enumFromTo_RDR, 
611                          returnM_RDR, failM_RDR])
612                              -- the last two are needed to force returnM, thenM and failM
613                              -- in before typechecking the list(monad) comprehension
614                              -- generated for derived Ix instances (range method)
615                              -- of single constructor types.  -- SOF 8/97
616     ]
617         -- intTyCon: Practically any deriving needs Int, either for index calculations, 
618         --              or for taggery.
619         -- ordClass: really it's the methods that are actually used.
620         -- numClass: for Int literals
621 \end{code}
622
623
624 NOTE: @Eq@ and @Text@ do need to appear in @standardClasses@
625 even though every numeric class has these two as a superclass,
626 because the list of ambiguous dictionaries hasn't been simplified.
627
628 \begin{code}
629 isCcallishClass, isCreturnableClass, isNoDictClass, 
630   isNumericClass, isStandardClass :: Class -> Bool
631
632 isNumericClass     clas = classKey clas `is_elem` numericClassKeys
633 isStandardClass    clas = classKey clas `is_elem` standardClassKeys
634 isCcallishClass    clas = classKey clas `is_elem` cCallishClassKeys
635 isCreturnableClass clas = classKey clas == cReturnableClassKey
636 isNoDictClass      clas = classKey clas `is_elem` noDictClassKeys
637 is_elem = isIn "is_X_Class"
638
639 numericClassKeys =
640         [ numClassKey
641         , realClassKey
642         , integralClassKey
643         , fractionalClassKey
644         , floatingClassKey
645         , realFracClassKey
646         , realFloatClassKey
647         ]
648
649         -- the strictness analyser needs to know about numeric types
650         -- (see SaAbsInt.lhs)
651 numericTyKeys = 
652         [ addrTyConKey
653         , wordTyConKey
654         , intTyConKey
655         , integerTyConKey
656         , doubleTyConKey
657         , floatTyConKey
658         ]
659
660 needsDataDeclCtxtClassKeys = -- see comments in TcDeriv
661         [ readClassKey
662         ]
663
664 cCallishClassKeys = 
665         [ cCallableClassKey
666         , cReturnableClassKey
667         ]
668
669         -- Renamer always imports these data decls replete with constructors
670         -- so that desugarer can always see the constructor.  Ugh!
671 cCallishTyKeys = 
672         [ addrTyConKey
673         , wordTyConKey
674         , byteArrayTyConKey
675         , mutableByteArrayTyConKey
676         , foreignObjTyConKey
677         , stablePtrTyConKey
678         ]
679
680 standardClassKeys
681   = derivableClassKeys ++ numericClassKeys ++ cCallishClassKeys
682     --
683     -- We have to have "CCallable" and "CReturnable" in the standard
684     -- classes, so that if you go...
685     --
686     --      _ccall_ foo ... 93{-numeric literal-} ...
687     --
688     -- ... it can do The Right Thing on the 93.
689
690 noDictClassKeys         -- These classes are used only for type annotations;
691                         -- they are not implemented by dictionaries, ever.
692   = cCallishClassKeys
693 \end{code}
694
695
696 %************************************************************************
697 %*                                                                      *
698 \subsection{Local helpers}
699 %*                                                                      *
700 %************************************************************************
701
702 \begin{code}
703 varQual  = mkPreludeQual varName
704 dataQual = mkPreludeQual dataName
705 tcQual   = mkPreludeQual tcName
706 clsQual  = mkPreludeQual clsName
707 \end{code}
708