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