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