[project @ 1999-04-13 15:50:29 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                         -- wired-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     , integerTyCon
192     , listTyCon
193     , wordTyCon
194     ]
195 \end{code}
196
197
198 %************************************************************************
199 %*                                                                      *
200 \subsection{Wired in Ids}
201 %*                                                                      *
202 %************************************************************************
203
204 \begin{code}
205 wired_in_ids
206   = [   -- These error-y things are wired in because we don't yet have
207         -- a way to express in an interface file that the result type variable
208         -- is 'open'; that is can be unified with an unboxed type
209         -- 
210         -- [The interface file format now carry such information, but there's
211         --  no way yet of expressing at the definition site for these error-reporting
212         --  functions that they have an 'open' result type. -- sof 1/99]
213         -- 
214       aBSENT_ERROR_ID
215     , eRROR_ID
216     , iRREFUT_PAT_ERROR_ID
217     , nON_EXHAUSTIVE_GUARDS_ERROR_ID
218     , nO_METHOD_BINDING_ERROR_ID
219     , pAR_ERROR_ID
220     , pAT_ERROR_ID
221     , rEC_CON_ERROR_ID
222     , rEC_UPD_ERROR_ID
223
224         -- These two can't be defined in Haskell
225     , realWorldPrimId
226     , unsafeCoerceId
227     ]
228
229 \end{code}
230
231 %************************************************************************
232 %*                                                                      *
233 \subsection{Thin air entities}
234 %*                                                                      *
235 %************************************************************************
236
237 These are Ids that we need to reference in various parts of the
238 system, and we'd like to pull them out of thin air rather than pass
239 them around.  We'd also like to have all the IdInfo available for each
240 one: i.e. everything that gets pulled out of the interface file.
241
242 The solution is to generate this map of global Ids after the
243 typechecker, and assign it to a global variable.  Any subsequent
244 pass may refer to the map to pull Ids out.  Any invalid
245 (i.e. pre-typechecker) access to the map will result in a panic.
246
247 \begin{code}
248 thinAirIdNames 
249   = map mkKnownKeyGlobal
250     [
251         -- Needed for converting literals to Integers (used in tidyCoreExpr)
252       (varQual pREL_BASE SLIT("addr2Integer"), addr2IntegerIdKey)
253
254         -- String literals
255     , (varQual pREL_PACK SLIT("packCString#"),   packCStringIdKey)
256     , (varQual pREL_PACK SLIT("unpackCString#"), unpackCStringIdKey)
257     , (varQual pREL_PACK SLIT("unpackNBytes#"),  unpackCString2IdKey)
258     , (varQual pREL_PACK SLIT("unpackAppendCString#"), unpackCStringAppendIdKey)
259     , (varQual pREL_PACK SLIT("unpackFoldrCString#"),  unpackCStringFoldrIdKey)
260
261         -- Folds; introduced by desugaring list comprehensions
262     , (varQual pREL_BASE SLIT("foldr"), foldrIdKey)
263     ]
264
265 thinAirModules = [pREL_PACK]    -- See notes with RnIfaces.findAndReadIface
266
267 noRepIntegerIds = [addr2IntegerId]
268
269 noRepStrIds = [unpackCString2Id, unpackCStringId]
270
271 addr2IntegerId = lookupThinAirId addr2IntegerIdKey
272
273 packStringForCId = lookupThinAirId packCStringIdKey
274 unpackCStringId  = lookupThinAirId unpackCStringIdKey
275 unpackCString2Id = lookupThinAirId unpackCString2IdKey 
276 unpackCStringAppendId = lookupThinAirId unpackCStringAppendIdKey 
277 unpackCStringFoldrId  = lookupThinAirId unpackCStringFoldrIdKey 
278
279 foldrId = lookupThinAirId foldrIdKey
280 \end{code}
281
282
283 \begin{code}
284 \end{code}
285
286 \begin{code}
287 thinAirIdMapRef :: IORef (UniqFM Id)
288 thinAirIdMapRef = unsafePerformIO (newIORef (panic "thinAirIdMap: still empty"))
289
290 setThinAirIds :: [Id] -> IO ()
291 setThinAirIds thin_air_ids
292   = writeIORef thinAirIdMapRef the_map
293   where
294     the_map = listToUFM [(varUnique id, id) | id <- thin_air_ids]
295
296 thinAirIdMap :: UniqFM Id
297 thinAirIdMap = unsafePerformIO (readIORef thinAirIdMapRef)
298   -- Read it just once, the first time someone tugs on thinAirIdMap
299
300 lookupThinAirId :: Unique -> Id
301 lookupThinAirId uniq = lookupWithDefaultUFM thinAirIdMap
302                         (panic "lookupThinAirId: no mapping") uniq 
303 \end{code}
304
305
306 %************************************************************************
307 %*                                                                      *
308 \subsection{Built-in keys}
309 %*                                                                      *
310 %************************************************************************
311
312 Ids, Synonyms, Classes and ClassOps with builtin keys. 
313
314 \begin{code}
315 mkKnownKeyGlobal :: (RdrName, Unique) -> Name
316 mkKnownKeyGlobal (rdr_name, uniq)
317   = mkGlobalName uniq (rdrNameModule rdr_name) (rdrNameOcc rdr_name)
318                  systemProvenance
319
320 ioTyCon_NAME      = mkKnownKeyGlobal (ioTyCon_RDR,       ioTyConKey)
321 main_NAME         = mkKnownKeyGlobal (main_RDR,          mainKey)
322
323  -- Operations needed when compiling FFI decls
324 bindIO_NAME         = mkKnownKeyGlobal (bindIO_RDR,         bindIOIdKey)
325 deRefStablePtr_NAME = mkKnownKeyGlobal (deRefStablePtr_RDR, deRefStablePtrIdKey)
326 makeStablePtr_NAME  = mkKnownKeyGlobal (makeStablePtr_RDR,  makeStablePtrIdKey)
327
328 knownKeyNames :: [Name]
329 knownKeyNames
330   = [main_NAME, ioTyCon_NAME]
331     ++
332     map mkKnownKeyGlobal
333     [
334         -- Type constructors (synonyms especially)
335       (orderingTyCon_RDR,       orderingTyConKey)
336     , (rationalTyCon_RDR,       rationalTyConKey)
337     , (ratioDataCon_RDR,        ratioDataConKey)
338     , (ratioTyCon_RDR,          ratioTyConKey)
339     , (byteArrayTyCon_RDR,      byteArrayTyConKey)
340     , (mutableByteArrayTyCon_RDR, mutableByteArrayTyConKey)
341     , (foreignObjTyCon_RDR,     foreignObjTyConKey)
342     , (stablePtrTyCon_RDR,      stablePtrTyConKey)
343     , (stablePtrDataCon_RDR,    stablePtrDataConKey)
344
345         --  Classes.  *Must* include:
346         --      classes that are grabbed by key (e.g., eqClassKey)
347         --      classes in "Class.standardClassKeys" (quite a few)
348     , (eqClass_RDR,             eqClassKey)             -- mentioned, derivable
349     , (ordClass_RDR,            ordClassKey)            -- derivable
350     , (boundedClass_RDR,        boundedClassKey)        -- derivable
351     , (numClass_RDR,            numClassKey)            -- mentioned, numeric
352     , (enumClass_RDR,           enumClassKey)           -- derivable
353     , (monadClass_RDR,          monadClassKey)
354     , (monadPlusClass_RDR,      monadPlusClassKey)
355     , (functorClass_RDR,        functorClassKey)
356     , (showClass_RDR,           showClassKey)           -- derivable
357     , (realClass_RDR,           realClassKey)           -- numeric
358     , (integralClass_RDR,       integralClassKey)       -- numeric
359     , (fractionalClass_RDR,     fractionalClassKey)     -- numeric
360     , (floatingClass_RDR,       floatingClassKey)       -- numeric
361     , (realFracClass_RDR,       realFracClassKey)       -- numeric
362     , (realFloatClass_RDR,      realFloatClassKey)      -- numeric
363     , (readClass_RDR,           readClassKey)           -- derivable
364     , (ixClass_RDR,             ixClassKey)             -- derivable (but it isn't Prelude.Ix; hmmm)
365     , (ccallableClass_RDR,      cCallableClassKey)      -- mentioned, ccallish
366     , (creturnableClass_RDR,    cReturnableClassKey)    -- mentioned, ccallish
367
368         -- ClassOps 
369     , (fromInt_RDR,             fromIntClassOpKey)
370     , (fromInteger_RDR,         fromIntegerClassOpKey)
371     , (ge_RDR,                  geClassOpKey) 
372     , (minus_RDR,               minusClassOpKey)
373     , (enumFrom_RDR,            enumFromClassOpKey)
374     , (enumFromThen_RDR,        enumFromThenClassOpKey)
375     , (enumFromTo_RDR,          enumFromToClassOpKey)
376     , (enumFromThenTo_RDR,      enumFromThenToClassOpKey)
377     , (fromEnum_RDR,            fromEnumClassOpKey)
378     , (toEnum_RDR,              toEnumClassOpKey)
379     , (eq_RDR,                  eqClassOpKey)
380     , (thenM_RDR,               thenMClassOpKey)
381     , (returnM_RDR,             returnMClassOpKey)
382     , (failM_RDR,               failMClassOpKey)
383     , (fromRational_RDR,        fromRationalClassOpKey)
384     
385     , (deRefStablePtr_RDR,      deRefStablePtrIdKey)
386     , (makeStablePtr_RDR,       makeStablePtrIdKey)
387     , (bindIO_RDR,              bindIOIdKey)
388
389     , (map_RDR,                 mapIdKey)
390     , (append_RDR,              appendIdKey)
391
392         -- List operations
393     , (concat_RDR,              concatIdKey)
394     , (filter_RDR,              filterIdKey)
395     , (zip_RDR,                 zipIdKey)
396
397         -- FFI primitive types that are not wired-in.
398     , (int8TyCon_RDR,           int8TyConKey)
399     , (int16TyCon_RDR,          int16TyConKey)
400     , (int32TyCon_RDR,          int32TyConKey)
401     , (int64TyCon_RDR,          int64TyConKey)
402     , (word8TyCon_RDR,          word8TyConKey)
403     , (word16TyCon_RDR,         word16TyConKey)
404     , (word32TyCon_RDR,         word32TyConKey)
405     , (word64TyCon_RDR,         word64TyConKey)
406
407         -- Others
408     , (otherwiseId_RDR,         otherwiseIdKey)
409     , (assert_RDR,              assertIdKey)
410     ]
411 \end{code}
412
413 ToDo: make it do the ``like'' part properly (as in 0.26 and before).
414
415 \begin{code}
416 maybeCharLikeCon, maybeIntLikeCon :: DataCon -> Bool
417 maybeCharLikeCon con = getUnique con == charDataConKey
418 maybeIntLikeCon  con = getUnique con == intDataConKey
419 \end{code}
420
421 %************************************************************************
422 %*                                                                      *
423 \subsection{Commonly-used RdrNames}
424 %*                                                                      *
425 %************************************************************************
426
427 These RdrNames are not really "built in", but some parts of the compiler
428 (notably the deriving mechanism) need to mention their names, and it's convenient
429 to write them all down in one place.
430
431 \begin{code}
432 prelude_primop op = nameRdrName (getName (mkPrimitiveId op))
433
434 main_RDR                = varQual mAIN      SLIT("main")
435 otherwiseId_RDR         = varQual pREL_BASE SLIT("otherwise")
436
437 intTyCon_RDR            = nameRdrName (getName intTyCon)
438 ioTyCon_RDR             = tcQual   pREL_IO_BASE SLIT("IO")
439 ioDataCon_RDR           = dataQual pREL_IO_BASE SLIT("IO")
440 bindIO_RDR              = varQual  pREL_IO_BASE SLIT("bindIO")
441
442 orderingTyCon_RDR       = tcQual   pREL_BASE SLIT("Ordering")
443 rationalTyCon_RDR       = tcQual   pREL_NUM  SLIT("Rational")
444 ratioTyCon_RDR          = tcQual   pREL_NUM  SLIT("Ratio")
445 ratioDataCon_RDR        = dataQual pREL_NUM  SLIT(":%")
446
447 byteArrayTyCon_RDR              = tcQual pREL_ARR  SLIT("ByteArray")
448 mutableByteArrayTyCon_RDR       = tcQual pREL_ARR  SLIT("MutableByteArray")
449
450 foreignObjTyCon_RDR     = tcQual   pREL_IO_BASE SLIT("ForeignObj")
451 stablePtrTyCon_RDR      = tcQual   pREL_STABLE SLIT("StablePtr")
452 stablePtrDataCon_RDR    = dataQual pREL_STABLE SLIT("StablePtr")
453 deRefStablePtr_RDR      = varQual  pREL_STABLE SLIT("deRefStablePtr")
454 makeStablePtr_RDR       = varQual  pREL_STABLE SLIT("makeStablePtr")
455
456 eqClass_RDR             = clsQual pREL_BASE SLIT("Eq")
457 ordClass_RDR            = clsQual pREL_BASE SLIT("Ord")
458 boundedClass_RDR        = clsQual pREL_BASE SLIT("Bounded")
459 numClass_RDR            = clsQual pREL_BASE SLIT("Num")
460 enumClass_RDR           = clsQual pREL_BASE SLIT("Enum")
461 monadClass_RDR          = clsQual pREL_BASE SLIT("Monad")
462 monadPlusClass_RDR      = clsQual pREL_BASE SLIT("MonadPlus")
463 functorClass_RDR        = clsQual pREL_BASE SLIT("Functor")
464 showClass_RDR           = clsQual pREL_BASE SLIT("Show")
465 realClass_RDR           = clsQual pREL_NUM  SLIT("Real")
466 integralClass_RDR       = clsQual pREL_NUM  SLIT("Integral")
467 fractionalClass_RDR     = clsQual pREL_NUM  SLIT("Fractional")
468 floatingClass_RDR       = clsQual pREL_NUM  SLIT("Floating")
469 realFracClass_RDR       = clsQual pREL_NUM  SLIT("RealFrac")
470 realFloatClass_RDR      = clsQual pREL_NUM  SLIT("RealFloat")
471 readClass_RDR           = clsQual pREL_READ SLIT("Read")
472 ixClass_RDR             = clsQual iX        SLIT("Ix")
473 ccallableClass_RDR      = clsQual pREL_GHC  SLIT("CCallable")
474 creturnableClass_RDR    = clsQual pREL_GHC  SLIT("CReturnable")
475
476 fromInt_RDR        = varQual pREL_BASE SLIT("fromInt")
477 fromInteger_RDR    = varQual pREL_BASE SLIT("fromInteger")
478 minus_RDR          = varQual pREL_BASE SLIT("-")
479 succ_RDR           = varQual pREL_BASE SLIT("succ")
480 pred_RDR           = varQual pREL_BASE SLIT("pred")
481 toEnum_RDR         = varQual pREL_BASE SLIT("toEnum")
482 fromEnum_RDR       = varQual pREL_BASE SLIT("fromEnum")
483 enumFrom_RDR       = varQual pREL_BASE SLIT("enumFrom")
484 enumFromTo_RDR     = varQual pREL_BASE SLIT("enumFromTo")
485 enumFromThen_RDR   = varQual pREL_BASE SLIT("enumFromThen")
486 enumFromThenTo_RDR = varQual pREL_BASE SLIT("enumFromThenTo")
487
488 thenM_RDR          = varQual pREL_BASE SLIT(">>=")
489 returnM_RDR        = varQual pREL_BASE SLIT("return")
490 failM_RDR          = varQual pREL_BASE SLIT("fail")
491
492 fromRational_RDR   = varQual pREL_NUM  SLIT("fromRational")
493 negate_RDR         = varQual pREL_BASE SLIT("negate")
494 eq_RDR             = varQual pREL_BASE SLIT("==")
495 ne_RDR             = varQual pREL_BASE SLIT("/=")
496 le_RDR             = varQual pREL_BASE SLIT("<=")
497 lt_RDR             = varQual pREL_BASE SLIT("<")
498 ge_RDR             = varQual pREL_BASE SLIT(">=")
499 gt_RDR             = varQual pREL_BASE SLIT(">")
500 ltTag_RDR          = dataQual pREL_BASE SLIT("LT")
501 eqTag_RDR          = dataQual pREL_BASE SLIT("EQ")
502 gtTag_RDR          = dataQual pREL_BASE SLIT("GT")
503 max_RDR            = varQual pREL_BASE SLIT("max")
504 min_RDR            = varQual pREL_BASE SLIT("min")
505 compare_RDR        = varQual pREL_BASE SLIT("compare")
506 minBound_RDR       = varQual pREL_BASE SLIT("minBound")
507 maxBound_RDR       = varQual pREL_BASE SLIT("maxBound")
508 false_RDR          = dataQual pREL_BASE SLIT("False")
509 true_RDR           = dataQual pREL_BASE SLIT("True")
510 and_RDR            = varQual pREL_BASE SLIT("&&")
511 not_RDR            = varQual pREL_BASE SLIT("not")
512 compose_RDR        = varQual pREL_BASE SLIT(".")
513 append_RDR         = varQual pREL_BASE SLIT("++")
514 map_RDR            = varQual pREL_BASE SLIT("map")
515 concat_RDR         = varQual mONAD     SLIT("concat")
516 filter_RDR         = varQual mONAD     SLIT("filter")
517 zip_RDR            = varQual pREL_LIST SLIT("zip")
518
519 showList___RDR     = varQual pREL_BASE  SLIT("showList__")
520 showsPrec_RDR      = varQual pREL_BASE SLIT("showsPrec")
521 showList_RDR       = varQual pREL_BASE SLIT("showList")
522 showSpace_RDR      = varQual pREL_BASE SLIT("showSpace")
523 showString_RDR     = varQual pREL_BASE SLIT("showString")
524 showParen_RDR      = varQual pREL_BASE SLIT("showParen")
525
526 range_RDR          = varQual iX   SLIT("range")
527 index_RDR          = varQual iX   SLIT("index")
528 inRange_RDR        = varQual iX   SLIT("inRange")
529
530 readsPrec_RDR      = varQual pREL_READ SLIT("readsPrec")
531 readList_RDR       = varQual pREL_READ SLIT("readList")
532 readParen_RDR      = varQual pREL_READ SLIT("readParen")
533 lex_RDR            = varQual pREL_READ SLIT("lex")
534 readList___RDR     = varQual pREL_READ SLIT("readList__")
535
536 plus_RDR           = varQual pREL_BASE SLIT("+")
537 times_RDR          = varQual pREL_BASE SLIT("*")
538 mkInt_RDR          = dataQual pREL_BASE SLIT("I#")
539
540 int8TyCon_RDR    = tcQual iNT       SLIT("Int8")
541 int16TyCon_RDR   = tcQual iNT       SLIT("Int16")
542 int32TyCon_RDR   = tcQual iNT       SLIT("Int32")
543 int64TyCon_RDR   = tcQual pREL_ADDR SLIT("Int64")
544
545 word8TyCon_RDR    = tcQual wORD      SLIT("Word8")
546 word16TyCon_RDR   = tcQual wORD      SLIT("Word16")
547 word32TyCon_RDR   = tcQual wORD      SLIT("Word32")
548 word64TyCon_RDR   = tcQual pREL_ADDR SLIT("Word64")
549
550 error_RDR          = varQual pREL_ERR SLIT("error")
551 assert_RDR         = varQual pREL_GHC SLIT("assert")
552 assertErr_RDR      = varQual pREL_ERR SLIT("assertError")
553
554 eqH_Char_RDR    = prelude_primop CharEqOp
555 ltH_Char_RDR    = prelude_primop CharLtOp
556 eqH_Word_RDR    = prelude_primop WordEqOp
557 ltH_Word_RDR    = prelude_primop WordLtOp
558 eqH_Addr_RDR    = prelude_primop AddrEqOp
559 ltH_Addr_RDR    = prelude_primop AddrLtOp
560 eqH_Float_RDR   = prelude_primop FloatEqOp
561 ltH_Float_RDR   = prelude_primop FloatLtOp
562 eqH_Double_RDR  = prelude_primop DoubleEqOp
563 ltH_Double_RDR  = prelude_primop DoubleLtOp
564 eqH_Int_RDR     = prelude_primop IntEqOp
565 ltH_Int_RDR     = prelude_primop IntLtOp
566 geH_RDR         = prelude_primop IntGeOp
567 leH_RDR         = prelude_primop IntLeOp
568 minusH_RDR      = prelude_primop IntSubOp
569 \end{code}
570
571 \begin{code}
572 mkTupConRdrName :: Int -> RdrName 
573 mkTupConRdrName arity = case mkTupNameStr arity of
574                           (mod, occ) -> dataQual mod occ
575
576 mkUbxTupConRdrName :: Int -> RdrName
577 mkUbxTupConRdrName arity = case mkUbxTupNameStr arity of
578                                 (mod, occ) -> dataQual mod occ
579 \end{code}
580
581
582 %************************************************************************
583 %*                                                                      *
584 \subsection[Class-std-groups]{Standard groups of Prelude classes}
585 %*                                                                      *
586 %************************************************************************
587
588 @derivableClassKeys@ is also used in checking \tr{deriving} constructs
589 (@TcDeriv@).
590
591 @derivingOccurrences@ maps a class name to a list of the (qualified) occurrences
592 that will be mentioned by  the derived code for the class when it is later generated.
593 We don't need to put in things that are WiredIn (because they are already mapped to their
594 correct name by the @NameSupply@.  The class itself, and all its class ops, is
595 already flagged as an occurrence so we don't need to mention that either.
596
597 @derivingOccurrences@ has an item for every derivable class, even if that item is empty,
598 because we treat lookup failure as indicating that the class is illegal in a deriving clause.
599
600 \begin{code}
601 derivingOccurrences :: UniqFM [RdrName]
602 derivingOccurrences = listToUFM deriving_occ_info
603
604 derivableClassKeys  = map fst deriving_occ_info
605
606 deriving_occ_info
607   = [ (eqClassKey,      [intTyCon_RDR, and_RDR, not_RDR])
608     , (ordClassKey,     [intTyCon_RDR, compose_RDR, eqTag_RDR])
609                                 -- EQ (from Ordering) is needed to force in the constructors
610                                 -- as well as the type constructor.
611     , (enumClassKey,    [intTyCon_RDR, eq_RDR, ge_RDR, and_RDR, map_RDR, plus_RDR, showsPrec_RDR, append_RDR]) 
612                                 -- The last two Enum deps are only used to produce better
613                                 -- error msgs for derived toEnum methods.
614     , (boundedClassKey, [intTyCon_RDR])
615     , (showClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, compose_RDR, showString_RDR, 
616                          showParen_RDR, showSpace_RDR, showList___RDR])
617     , (readClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, append_RDR, 
618                          lex_RDR, readParen_RDR, readList___RDR, thenM_RDR])
619                              -- returnM (and the rest of the Monad class decl) 
620                              -- will be forced in as result of depending
621                              -- on thenM.   -- SOF 1/99
622     , (ixClassKey,      [intTyCon_RDR, numClass_RDR, and_RDR, map_RDR, enumFromTo_RDR, 
623                          returnM_RDR, failM_RDR])
624                              -- the last two are needed to force returnM, thenM and failM
625                              -- in before typechecking the list(monad) comprehension
626                              -- generated for derived Ix instances (range method)
627                              -- of single constructor types.  -- SOF 8/97
628     ]
629         -- intTyCon: Practically any deriving needs Int, either for index calculations, 
630         --              or for taggery.
631         -- ordClass: really it's the methods that are actually used.
632         -- numClass: for Int literals
633 \end{code}
634
635
636 NOTE: @Eq@ and @Text@ do need to appear in @standardClasses@
637 even though every numeric class has these two as a superclass,
638 because the list of ambiguous dictionaries hasn't been simplified.
639
640 \begin{code}
641 isCcallishClass, isCreturnableClass, isNoDictClass, 
642   isNumericClass, isStandardClass :: Class -> Bool
643
644 isNumericClass     clas = classKey clas `is_elem` numericClassKeys
645 isStandardClass    clas = classKey clas `is_elem` standardClassKeys
646 isCcallishClass    clas = classKey clas `is_elem` cCallishClassKeys
647 isCreturnableClass clas = classKey clas == cReturnableClassKey
648 isNoDictClass      clas = classKey clas `is_elem` noDictClassKeys
649 is_elem = isIn "is_X_Class"
650
651 numericClassKeys =
652         [ numClassKey
653         , realClassKey
654         , integralClassKey
655         , fractionalClassKey
656         , floatingClassKey
657         , realFracClassKey
658         , realFloatClassKey
659         ]
660
661         -- the strictness analyser needs to know about numeric types
662         -- (see SaAbsInt.lhs)
663 numericTyKeys = 
664         [ addrTyConKey
665         , wordTyConKey
666         , intTyConKey
667         , integerTyConKey
668         , doubleTyConKey
669         , floatTyConKey
670         ]
671
672 needsDataDeclCtxtClassKeys = -- see comments in TcDeriv
673         [ readClassKey
674         ]
675
676 cCallishClassKeys = 
677         [ cCallableClassKey
678         , cReturnableClassKey
679         ]
680
681         -- Renamer always imports these data decls replete with constructors
682         -- so that desugarer can always see their constructors.  Ugh!
683 cCallishTyKeys = 
684         [ addrTyConKey
685         , wordTyConKey
686         , byteArrayTyConKey
687         , mutableByteArrayTyConKey
688         , foreignObjTyConKey
689         , stablePtrTyConKey
690         , int8TyConKey
691         , int16TyConKey
692         , int32TyConKey
693         , int64TyConKey
694         , word8TyConKey
695         , word16TyConKey
696         , word32TyConKey
697         , word64TyConKey
698         ]
699
700 standardClassKeys
701   = derivableClassKeys ++ numericClassKeys ++ cCallishClassKeys
702     --
703     -- We have to have "CCallable" and "CReturnable" in the standard
704     -- classes, so that if you go...
705     --
706     --      _ccall_ foo ... 93{-numeric literal-} ...
707     --
708     -- ... it can do The Right Thing on the 93.
709
710 noDictClassKeys         -- These classes are used only for type annotations;
711                         -- they are not implemented by dictionaries, ever.
712   = cCallishClassKeys
713 \end{code}
714
715
716 %************************************************************************
717 %*                                                                      *
718 \subsection{Local helpers}
719 %*                                                                      *
720 %************************************************************************
721
722 \begin{code}
723 varQual  = mkPreludeQual varName
724 dataQual = mkPreludeQual dataName
725 tcQual   = mkPreludeQual tcName
726 clsQual  = mkPreludeQual clsName
727 \end{code}
728