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