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