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