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