[project @ 2000-04-10 12:12:27 by simonpj]
[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         module ThinAir,
9         module MkId,
10
11         builtinNames,   -- Names of things whose *unique* must be known, but 
12                         -- that is all. If something is in here, you know that
13                         -- if it's used at all then it's Name will be just as
14                         -- it is here, unique and all.  Includes all the 
15
16         derivingOccurrences,    -- For a given class C, this tells what other 
17         derivableClassKeys,     -- things are needed as a result of a 
18                                 -- deriving(C) clause
19
20
21         -- Random other things
22         main_NAME, ioTyCon_NAME,
23         deRefStablePtr_NAME, makeStablePtr_NAME,
24         bindIO_NAME, returnIO_NAME,
25
26         maybeCharLikeCon, maybeIntLikeCon,
27         needsDataDeclCtxtClassKeys, cCallishClassKeys, cCallishTyKeys, 
28         isNoDictClass, isNumericClass, isStandardClass, isCcallishClass, 
29         isCreturnableClass, numericTyKeys, fractionalClassKeys,
30
31         -- RdrNames for lots of things, mainly used in derivings
32         eq_RDR, ne_RDR, le_RDR, lt_RDR, ge_RDR, gt_RDR, max_RDR, min_RDR, 
33         compare_RDR, minBound_RDR, maxBound_RDR, enumFrom_RDR, enumFromTo_RDR,
34         enumFromThen_RDR, enumFromThenTo_RDR, succ_RDR, pred_RDR, fromEnum_RDR, toEnum_RDR, 
35         ratioDataCon_RDR, range_RDR, index_RDR, inRange_RDR, readsPrec_RDR,
36         readList_RDR, showsPrec_RDR, showList_RDR, plus_RDR, times_RDR,
37         ltTag_RDR, eqTag_RDR, gtTag_RDR, eqH_Char_RDR, ltH_Char_RDR, 
38         eqH_Word_RDR, ltH_Word_RDR, eqH_Addr_RDR, ltH_Addr_RDR, eqH_Float_RDR,
39         ltH_Float_RDR, eqH_Double_RDR, ltH_Double_RDR, eqH_Int_RDR, 
40         ltH_Int_RDR, geH_RDR, leH_RDR, minusH_RDR, false_RDR, true_RDR,
41         and_RDR, not_RDR, append_RDR, map_RDR, compose_RDR, mkInt_RDR,
42         error_RDR, assertErr_RDR, getTag_RDR, tagToEnumH_RDR,
43         showString_RDR, showParen_RDR, readParen_RDR, lex_RDR,
44         showSpace_RDR, showList___RDR, readList___RDR, negate_RDR,
45
46         numClass_RDR, fractionalClass_RDR, eqClass_RDR, 
47         ccallableClass_RDR, creturnableClass_RDR,
48         monadClass_RDR, enumClass_RDR, ordClass_RDR,
49         ioDataCon_RDR,
50
51         main_RDR,
52
53         mkTupConRdrName, mkUbxTupConRdrName
54
55     ) where
56
57 #include "HsVersions.h"
58
59
60
61 -- friends:
62 import ThinAir          -- Re-export all these
63 import MkId             -- Ditto
64
65 import PrelMods         -- Prelude module names
66 import PrimOp           ( PrimOp(..), allThePrimOps, primOpRdrName )
67 import DataCon          ( DataCon, dataConId, dataConWrapId )
68 import PrimRep          ( PrimRep(..) )
69 import TysPrim          -- TYPES
70 import TysWiredIn
71
72 -- others:
73 import RdrName          ( RdrName, mkPreludeQual )
74 import Var              ( varUnique, Id )
75 import Name             ( Name, OccName, Provenance(..), 
76                           NameSpace, tcName, clsName, varName, dataName,
77                           mkKnownKeyGlobal,
78                           getName, mkGlobalName, nameRdrName
79                         )
80 import RdrName          ( rdrNameModule, rdrNameOcc, mkSrcQual )
81 import Class            ( Class, classKey )
82 import TyCon            ( tyConDataCons, TyCon )
83 import Type             ( funTyCon )
84 import Bag
85 import Unique           -- *Key stuff
86 import UniqFM           ( UniqFM, listToUFM )
87 import Util             ( isIn )
88 import Panic            ( panic )
89 \end{code}
90
91 %************************************************************************
92 %*                                                                      *
93 \subsection[builtinNameInfo]{Lookup built-in names}
94 %*                                                                      *
95 %************************************************************************
96
97 We have two ``builtin name funs,'' one to look up @TyCons@ and
98 @Classes@, the other to look up values.
99
100 \begin{code}
101 builtinNames :: Bag Name
102 builtinNames
103   = unionManyBags
104         [       -- Wired in TyCons
105           unionManyBags (map getTyConNames wired_in_tycons)
106
107                 -- Wired in Ids
108         , listToBag (map getName wiredInIds)
109
110                 -- PrimOps
111         , listToBag (map (getName . mkPrimOpId) allThePrimOps)
112
113                 -- Thin-air ids
114         , listToBag thinAirIdNames
115
116                 -- Other names with magic keys
117         , listToBag knownKeyNames
118         ]
119 \end{code}
120
121
122 \begin{code}
123 getTyConNames :: TyCon -> Bag Name
124 getTyConNames tycon
125     = getName tycon `consBag` 
126       unionManyBags (map get_data_con_names (tyConDataCons tycon))
127         -- Synonyms return empty list of constructors
128     where
129       get_data_con_names dc = listToBag [getName (dataConId dc),        -- Worker
130                                          getName (dataConWrapId dc)]    -- Wrapper
131 \end{code}
132
133 We let a lot of "non-standard" values be visible, so that we can make
134 sense of them in interface pragmas. It's cool, though they all have
135 "non-standard" names, so they won't get past the parser in user code.
136
137
138 %************************************************************************
139 %*                                                                      *
140 \subsection{Wired in TyCons}
141 %*                                                                      *
142 %************************************************************************
143
144 \begin{code}
145 wired_in_tycons = [funTyCon] ++
146                   prim_tycons ++
147                   tuple_tycons ++
148                   unboxed_tuple_tycons ++
149                   data_tycons
150
151 prim_tycons
152   = [ addrPrimTyCon
153     , arrayPrimTyCon
154     , byteArrayPrimTyCon
155     , charPrimTyCon
156     , doublePrimTyCon
157     , floatPrimTyCon
158     , intPrimTyCon
159     , int64PrimTyCon
160     , foreignObjPrimTyCon
161     , weakPrimTyCon
162     , mutableArrayPrimTyCon
163     , mutableByteArrayPrimTyCon
164     , mVarPrimTyCon
165     , mutVarPrimTyCon
166     , realWorldTyCon
167     , stablePtrPrimTyCon
168     , stableNamePrimTyCon
169     , statePrimTyCon
170     , threadIdPrimTyCon
171     , wordPrimTyCon
172     , word64PrimTyCon
173     ]
174
175 tuple_tycons = unitTyCon : [tupleTyCon i | i <- [2..37] ]
176 unboxed_tuple_tycons = [unboxedTupleTyCon i | i <- [1..37] ]
177
178 data_tycons
179   = [ addrTyCon
180     , boolTyCon
181     , charTyCon
182     , doubleTyCon
183     , floatTyCon
184     , intTyCon
185     , integerTyCon
186     , listTyCon
187     , wordTyCon
188     ]
189 \end{code}
190
191
192 %************************************************************************
193 %*                                                                      *
194 \subsection{Built-in keys}
195 %*                                                                      *
196 %************************************************************************
197
198 Ids, Synonyms, Classes and ClassOps with builtin keys. 
199
200 \begin{code}
201 ioTyCon_NAME      = mkKnownKeyGlobal (ioTyCon_RDR,       ioTyConKey)
202 main_NAME         = mkKnownKeyGlobal (main_RDR,          mainKey)
203
204  -- Operations needed when compiling FFI decls
205 bindIO_NAME         = mkKnownKeyGlobal (bindIO_RDR,         bindIOIdKey)
206 returnIO_NAME       = mkKnownKeyGlobal (returnIO_RDR,       returnIOIdKey)
207 deRefStablePtr_NAME = mkKnownKeyGlobal (deRefStablePtr_RDR, deRefStablePtrIdKey)
208 makeStablePtr_NAME  = mkKnownKeyGlobal (makeStablePtr_RDR,  makeStablePtrIdKey)
209
210 knownKeyNames :: [Name]
211 knownKeyNames
212   = [main_NAME, ioTyCon_NAME]
213     ++
214     map mkKnownKeyGlobal
215     [
216         -- Type constructors (synonyms especially)
217       (orderingTyCon_RDR,       orderingTyConKey)
218     , (rationalTyCon_RDR,       rationalTyConKey)
219     , (ratioDataCon_RDR,        ratioDataConKey)
220     , (ratioTyCon_RDR,          ratioTyConKey)
221     , (byteArrayTyCon_RDR,      byteArrayTyConKey)
222     , (mutableByteArrayTyCon_RDR, mutableByteArrayTyConKey)
223     , (foreignObjTyCon_RDR,     foreignObjTyConKey)
224     , (stablePtrTyCon_RDR,      stablePtrTyConKey)
225     , (stablePtrDataCon_RDR,    stablePtrDataConKey)
226
227         --  Classes.  *Must* include:
228         --      classes that are grabbed by key (e.g., eqClassKey)
229         --      classes in "Class.standardClassKeys" (quite a few)
230     , (eqClass_RDR,             eqClassKey)             -- mentioned, derivable
231     , (ordClass_RDR,            ordClassKey)            -- derivable
232     , (boundedClass_RDR,        boundedClassKey)        -- derivable
233     , (numClass_RDR,            numClassKey)            -- mentioned, numeric
234     , (enumClass_RDR,           enumClassKey)           -- derivable
235     , (monadClass_RDR,          monadClassKey)
236     , (monadPlusClass_RDR,      monadPlusClassKey)
237     , (functorClass_RDR,        functorClassKey)
238     , (showClass_RDR,           showClassKey)           -- derivable
239     , (realClass_RDR,           realClassKey)           -- numeric
240     , (integralClass_RDR,       integralClassKey)       -- numeric
241     , (fractionalClass_RDR,     fractionalClassKey)     -- numeric
242     , (floatingClass_RDR,       floatingClassKey)       -- numeric
243     , (realFracClass_RDR,       realFracClassKey)       -- numeric
244     , (realFloatClass_RDR,      realFloatClassKey)      -- numeric
245     , (readClass_RDR,           readClassKey)           -- derivable
246     , (ixClass_RDR,             ixClassKey)             -- derivable (but it isn't Prelude.Ix; hmmm)
247     , (ccallableClass_RDR,      cCallableClassKey)      -- mentioned, ccallish
248     , (creturnableClass_RDR,    cReturnableClassKey)    -- mentioned, ccallish
249
250         -- ClassOps 
251     , (fromInt_RDR,             fromIntClassOpKey)
252     , (fromInteger_RDR,         fromIntegerClassOpKey)
253     , (ge_RDR,                  geClassOpKey) 
254     , (minus_RDR,               minusClassOpKey)
255     , (enumFrom_RDR,            enumFromClassOpKey)
256     , (enumFromThen_RDR,        enumFromThenClassOpKey)
257     , (enumFromTo_RDR,          enumFromToClassOpKey)
258     , (enumFromThenTo_RDR,      enumFromThenToClassOpKey)
259     , (fromEnum_RDR,            fromEnumClassOpKey)
260     , (toEnum_RDR,              toEnumClassOpKey)
261     , (eq_RDR,                  eqClassOpKey)
262     , (thenM_RDR,               thenMClassOpKey)
263     , (returnM_RDR,             returnMClassOpKey)
264     , (failM_RDR,               failMClassOpKey)
265     , (fromRational_RDR,        fromRationalClassOpKey)
266     
267     , (deRefStablePtr_RDR,      deRefStablePtrIdKey)
268     , (makeStablePtr_RDR,       makeStablePtrIdKey)
269     , (bindIO_RDR,              bindIOIdKey)
270     , (returnIO_RDR,            returnIOIdKey)
271
272     , (map_RDR,                 mapIdKey)
273     , (append_RDR,              appendIdKey)
274
275         -- List operations
276     , (concat_RDR,              concatIdKey)
277     , (filter_RDR,              filterIdKey)
278     , (zip_RDR,                 zipIdKey)
279     , (build_RDR,               buildIdKey)
280     , (augment_RDR,             augmentIdKey)
281
282         -- FFI primitive types that are not wired-in.
283     , (int8TyCon_RDR,           int8TyConKey)
284     , (int16TyCon_RDR,          int16TyConKey)
285     , (int32TyCon_RDR,          int32TyConKey)
286     , (int64TyCon_RDR,          int64TyConKey)
287     , (word8TyCon_RDR,          word8TyConKey)
288     , (word16TyCon_RDR,         word16TyConKey)
289     , (word32TyCon_RDR,         word32TyConKey)
290     , (word64TyCon_RDR,         word64TyConKey)
291
292         -- Others
293     , (otherwiseId_RDR,         otherwiseIdKey)
294     , (assert_RDR,              assertIdKey)
295     , (runSTRep_RDR,            runSTRepIdKey)
296     ]
297 \end{code}
298
299 ToDo: make it do the ``like'' part properly (as in 0.26 and before).
300
301 \begin{code}
302 maybeCharLikeCon, maybeIntLikeCon :: DataCon -> Bool
303 maybeCharLikeCon con = getUnique con == charDataConKey
304 maybeIntLikeCon  con = getUnique con == intDataConKey
305 \end{code}
306
307 %************************************************************************
308 %*                                                                      *
309 \subsection{Commonly-used RdrNames}
310 %*                                                                      *
311 %************************************************************************
312
313 These RdrNames are not really "built in", but some parts of the compiler
314 (notably the deriving mechanism) need to mention their names, and it's convenient
315 to write them all down in one place.
316
317 \begin{code}
318 main_RDR                = varQual mAIN_Name      SLIT("main")
319 otherwiseId_RDR         = varQual pREL_BASE_Name SLIT("otherwise")
320
321 intTyCon_RDR            = nameRdrName (getName intTyCon)
322 ioTyCon_RDR             = tcQual   pREL_IO_BASE_Name SLIT("IO")
323 ioDataCon_RDR           = dataQual pREL_IO_BASE_Name SLIT("IO")
324 bindIO_RDR              = varQual  pREL_IO_BASE_Name SLIT("bindIO")
325 returnIO_RDR            = varQual  pREL_IO_BASE_Name SLIT("returnIO")
326
327 orderingTyCon_RDR       = tcQual   pREL_BASE_Name SLIT("Ordering")
328
329 rationalTyCon_RDR       = tcQual   pREL_REAL_Name  SLIT("Rational")
330 ratioTyCon_RDR          = tcQual   pREL_REAL_Name  SLIT("Ratio")
331 ratioDataCon_RDR        = dataQual pREL_REAL_Name  SLIT(":%")
332
333 byteArrayTyCon_RDR              = tcQual pREL_BYTEARR_Name  SLIT("ByteArray")
334 mutableByteArrayTyCon_RDR       = tcQual pREL_BYTEARR_Name  SLIT("MutableByteArray")
335
336 foreignObjTyCon_RDR     = tcQual   pREL_IO_BASE_Name SLIT("ForeignObj")
337 stablePtrTyCon_RDR      = tcQual   pREL_STABLE_Name SLIT("StablePtr")
338 stablePtrDataCon_RDR    = dataQual pREL_STABLE_Name SLIT("StablePtr")
339 deRefStablePtr_RDR      = varQual  pREL_STABLE_Name SLIT("deRefStablePtr")
340 makeStablePtr_RDR       = varQual  pREL_STABLE_Name SLIT("makeStablePtr")
341
342 -- Random PrelBase data constructors
343 mkInt_RDR          = dataQual pREL_BASE_Name SLIT("I#")
344 false_RDR          = dataQual pREL_BASE_Name SLIT("False")
345 true_RDR           = dataQual pREL_BASE_Name SLIT("True")
346
347 -- Random PrelBase functions
348 and_RDR            = varQual pREL_BASE_Name SLIT("&&")
349 not_RDR            = varQual pREL_BASE_Name SLIT("not")
350 compose_RDR        = varQual pREL_BASE_Name SLIT(".")
351 append_RDR         = varQual pREL_BASE_Name SLIT("++")
352 map_RDR            = varQual pREL_BASE_Name SLIT("map")
353 build_RDR          = varQual pREL_BASE_Name SLIT("build")
354 augment_RDR        = varQual pREL_BASE_Name SLIT("augment")
355
356 -- Classes Eq and Ord
357 eqClass_RDR             = clsQual pREL_BASE_Name SLIT("Eq")
358 ordClass_RDR            = clsQual pREL_BASE_Name SLIT("Ord")
359 eq_RDR             = varQual pREL_BASE_Name SLIT("==")
360 ne_RDR             = varQual pREL_BASE_Name SLIT("/=")
361 le_RDR             = varQual pREL_BASE_Name SLIT("<=")
362 lt_RDR             = varQual pREL_BASE_Name SLIT("<")
363 ge_RDR             = varQual pREL_BASE_Name SLIT(">=")
364 gt_RDR             = varQual pREL_BASE_Name SLIT(">")
365 ltTag_RDR          = dataQual pREL_BASE_Name SLIT("LT")
366 eqTag_RDR          = dataQual pREL_BASE_Name SLIT("EQ")
367 gtTag_RDR          = dataQual pREL_BASE_Name SLIT("GT")
368 max_RDR            = varQual pREL_BASE_Name SLIT("max")
369 min_RDR            = varQual pREL_BASE_Name SLIT("min")
370 compare_RDR        = varQual pREL_BASE_Name SLIT("compare")
371
372 -- Class Monad
373 monadClass_RDR     = clsQual pREL_BASE_Name SLIT("Monad")
374 monadPlusClass_RDR = clsQual pREL_BASE_Name SLIT("MonadPlus")
375 thenM_RDR          = varQual pREL_BASE_Name SLIT(">>=")
376 returnM_RDR        = varQual pREL_BASE_Name SLIT("return")
377 failM_RDR          = varQual pREL_BASE_Name SLIT("fail")
378
379 -- Class Functor
380 functorClass_RDR        = clsQual pREL_BASE_Name SLIT("Functor")
381
382 -- Class Show
383 showClass_RDR      = clsQual pREL_SHOW_Name SLIT("Show")
384 showList___RDR     = varQual pREL_SHOW_Name SLIT("showList__")
385 showsPrec_RDR      = varQual pREL_SHOW_Name SLIT("showsPrec")
386 showList_RDR       = varQual pREL_SHOW_Name SLIT("showList")
387 showSpace_RDR      = varQual pREL_SHOW_Name SLIT("showSpace")
388 showString_RDR     = varQual pREL_SHOW_Name SLIT("showString")
389 showParen_RDR      = varQual pREL_SHOW_Name SLIT("showParen")
390
391
392 -- Class Read
393 readClass_RDR      = clsQual pREL_READ_Name SLIT("Read")
394 readsPrec_RDR      = varQual pREL_READ_Name SLIT("readsPrec")
395 readList_RDR       = varQual pREL_READ_Name SLIT("readList")
396 readParen_RDR      = varQual pREL_READ_Name SLIT("readParen")
397 lex_RDR            = varQual pREL_READ_Name SLIT("lex")
398 readList___RDR     = varQual pREL_READ_Name SLIT("readList__")
399
400
401 -- Class Num
402 numClass_RDR       = clsQual pREL_NUM_Name SLIT("Num")
403 fromInt_RDR        = varQual pREL_NUM_Name SLIT("fromInt")
404 fromInteger_RDR    = varQual pREL_NUM_Name SLIT("fromInteger")
405 minus_RDR          = varQual pREL_NUM_Name SLIT("-")
406 negate_RDR         = varQual pREL_NUM_Name SLIT("negate")
407 plus_RDR           = varQual pREL_NUM_Name SLIT("+")
408 times_RDR          = varQual pREL_NUM_Name SLIT("*")
409
410 -- Other numberic classes
411 realClass_RDR           = clsQual pREL_REAL_Name  SLIT("Real")
412 integralClass_RDR       = clsQual pREL_REAL_Name  SLIT("Integral")
413 realFracClass_RDR       = clsQual pREL_REAL_Name  SLIT("RealFrac")
414 fractionalClass_RDR     = clsQual pREL_REAL_Name  SLIT("Fractional")
415 fromRational_RDR        = varQual pREL_REAL_Name  SLIT("fromRational")
416
417 floatingClass_RDR       = clsQual pREL_FLOAT_Name  SLIT("Floating")
418 realFloatClass_RDR      = clsQual pREL_FLOAT_Name  SLIT("RealFloat")
419
420 -- Class Ix
421 ixClass_RDR        = clsQual pREL_ARR_Name SLIT("Ix")
422 range_RDR          = varQual pREL_ARR_Name SLIT("range")
423 index_RDR          = varQual pREL_ARR_Name SLIT("index")
424 inRange_RDR        = varQual pREL_ARR_Name SLIT("inRange")
425
426 -- Class CCallable and CReturnable
427 ccallableClass_RDR      = clsQual pREL_GHC_Name  SLIT("CCallable")
428 creturnableClass_RDR    = clsQual pREL_GHC_Name  SLIT("CReturnable")
429
430 -- Class Enum
431 enumClass_RDR      = clsQual pREL_ENUM_Name SLIT("Enum")
432 succ_RDR           = varQual pREL_ENUM_Name SLIT("succ")
433 pred_RDR           = varQual pREL_ENUM_Name SLIT("pred")
434 toEnum_RDR         = varQual pREL_ENUM_Name SLIT("toEnum")
435 fromEnum_RDR       = varQual pREL_ENUM_Name SLIT("fromEnum")
436 enumFrom_RDR       = varQual pREL_ENUM_Name SLIT("enumFrom")
437 enumFromTo_RDR     = varQual pREL_ENUM_Name SLIT("enumFromTo")
438 enumFromThen_RDR   = varQual pREL_ENUM_Name SLIT("enumFromThen")
439 enumFromThenTo_RDR = varQual pREL_ENUM_Name SLIT("enumFromThenTo")
440
441 -- Class Bounded
442 boundedClass_RDR   = clsQual pREL_ENUM_Name SLIT("Bounded")
443 minBound_RDR       = varQual pREL_ENUM_Name SLIT("minBound")
444 maxBound_RDR       = varQual pREL_ENUM_Name SLIT("maxBound")
445
446
447 -- List functions
448 concat_RDR         = varQual pREL_LIST_Name SLIT("concat")
449 filter_RDR         = varQual pREL_LIST_Name SLIT("filter")
450 zip_RDR            = varQual pREL_LIST_Name SLIT("zip")
451
452 int8TyCon_RDR    = tcQual iNT_Name       SLIT("Int8")
453 int16TyCon_RDR   = tcQual iNT_Name       SLIT("Int16")
454 int32TyCon_RDR   = tcQual iNT_Name       SLIT("Int32")
455 int64TyCon_RDR   = tcQual pREL_ADDR_Name SLIT("Int64")
456
457 word8TyCon_RDR    = tcQual wORD_Name      SLIT("Word8")
458 word16TyCon_RDR   = tcQual wORD_Name      SLIT("Word16")
459 word32TyCon_RDR   = tcQual wORD_Name      SLIT("Word32")
460 word64TyCon_RDR   = tcQual pREL_ADDR_Name SLIT("Word64")
461
462 error_RDR          = varQual pREL_ERR_Name SLIT("error")
463 assert_RDR         = varQual pREL_GHC_Name SLIT("assert")
464 assertErr_RDR      = varQual pREL_ERR_Name SLIT("assertError")
465 runSTRep_RDR       = varQual pREL_ST_Name  SLIT("runSTRep")
466
467 eqH_Char_RDR    = primOpRdrName CharEqOp
468 ltH_Char_RDR    = primOpRdrName CharLtOp
469 eqH_Word_RDR    = primOpRdrName WordEqOp
470 ltH_Word_RDR    = primOpRdrName WordLtOp
471 eqH_Addr_RDR    = primOpRdrName AddrEqOp
472 ltH_Addr_RDR    = primOpRdrName AddrLtOp
473 eqH_Float_RDR   = primOpRdrName FloatEqOp
474 ltH_Float_RDR   = primOpRdrName FloatLtOp
475 eqH_Double_RDR  = primOpRdrName DoubleEqOp
476 ltH_Double_RDR  = primOpRdrName DoubleLtOp
477 eqH_Int_RDR     = primOpRdrName IntEqOp
478 ltH_Int_RDR     = primOpRdrName IntLtOp
479 geH_RDR         = primOpRdrName IntGeOp
480 leH_RDR         = primOpRdrName IntLeOp
481 minusH_RDR      = primOpRdrName IntSubOp
482
483 tagToEnumH_RDR  = primOpRdrName TagToEnumOp
484 getTag_RDR      = varQual pREL_GHC_Name SLIT("getTag#")
485 \end{code}
486
487 \begin{code}
488 mkTupConRdrName :: Int -> RdrName 
489 mkTupConRdrName arity = case mkTupNameStr arity of
490                           (mod, occ) -> dataQual mod occ
491
492 mkUbxTupConRdrName :: Int -> RdrName
493 mkUbxTupConRdrName arity = case mkUbxTupNameStr arity of
494                                 (mod, occ) -> dataQual mod occ
495 \end{code}
496
497
498 %************************************************************************
499 %*                                                                      *
500 \subsection[Class-std-groups]{Standard groups of Prelude classes}
501 %*                                                                      *
502 %************************************************************************
503
504 @derivableClassKeys@ is also used in checking \tr{deriving} constructs
505 (@TcDeriv@).
506
507 @derivingOccurrences@ maps a class name to a list of the (qualified) occurrences
508 that will be mentioned by  the derived code for the class when it is later generated.
509 We don't need to put in things that are WiredIn (because they are already mapped to their
510 correct name by the @NameSupply@.  The class itself, and all its class ops, is
511 already flagged as an occurrence so we don't need to mention that either.
512
513 @derivingOccurrences@ has an item for every derivable class, even if that item is empty,
514 because we treat lookup failure as indicating that the class is illegal in a deriving clause.
515
516 \begin{code}
517 derivingOccurrences :: UniqFM [RdrName]
518 derivingOccurrences = listToUFM deriving_occ_info
519
520 derivableClassKeys  = map fst deriving_occ_info
521
522 deriving_occ_info
523   = [ (eqClassKey,      [intTyCon_RDR, and_RDR, not_RDR])
524     , (ordClassKey,     [intTyCon_RDR, compose_RDR, eqTag_RDR])
525                                 -- EQ (from Ordering) is needed to force in the constructors
526                                 -- as well as the type constructor.
527     , (enumClassKey,    [intTyCon_RDR, eq_RDR, ge_RDR, and_RDR, map_RDR, plus_RDR, showsPrec_RDR, append_RDR]) 
528                                 -- The last two Enum deps are only used to produce better
529                                 -- error msgs for derived toEnum methods.
530     , (boundedClassKey, [intTyCon_RDR])
531     , (showClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, compose_RDR, showString_RDR, 
532                          showParen_RDR, showSpace_RDR, showList___RDR])
533     , (readClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, append_RDR, 
534                          lex_RDR, readParen_RDR, readList___RDR, thenM_RDR])
535                              -- returnM (and the rest of the Monad class decl) 
536                              -- will be forced in as result of depending
537                              -- on thenM.   -- SOF 1/99
538     , (ixClassKey,      [intTyCon_RDR, numClass_RDR, and_RDR, map_RDR, enumFromTo_RDR, 
539                          returnM_RDR, failM_RDR])
540                              -- the last two are needed to force returnM, thenM and failM
541                              -- in before typechecking the list(monad) comprehension
542                              -- generated for derived Ix instances (range method)
543                              -- of single constructor types.  -- SOF 8/97
544     ]
545         -- intTyCon: Practically any deriving needs Int, either for index calculations, 
546         --              or for taggery.
547         -- ordClass: really it's the methods that are actually used.
548         -- numClass: for Int literals
549 \end{code}
550
551
552 NOTE: @Eq@ and @Text@ do need to appear in @standardClasses@
553 even though every numeric class has these two as a superclass,
554 because the list of ambiguous dictionaries hasn't been simplified.
555
556 \begin{code}
557 isCcallishClass, isCreturnableClass, isNoDictClass, 
558   isNumericClass, isStandardClass :: Class -> Bool
559
560 isFractionalClass  clas = classKey clas `is_elem` fractionalClassKeys
561 isNumericClass     clas = classKey clas `is_elem` numericClassKeys
562 isStandardClass    clas = classKey clas `is_elem` standardClassKeys
563 isCcallishClass    clas = classKey clas `is_elem` cCallishClassKeys
564 isCreturnableClass clas = classKey clas == cReturnableClassKey
565 isNoDictClass      clas = classKey clas `is_elem` noDictClassKeys
566 is_elem = isIn "is_X_Class"
567
568 numericClassKeys =
569         [ numClassKey
570         , realClassKey
571         , integralClassKey
572         ]
573         ++ fractionalClassKeys
574
575 fractionalClassKeys = 
576         [ fractionalClassKey
577         , floatingClassKey
578         , realFracClassKey
579         , realFloatClassKey
580         ]
581
582         -- the strictness analyser needs to know about numeric types
583         -- (see SaAbsInt.lhs)
584 numericTyKeys = 
585         [ addrTyConKey
586         , wordTyConKey
587         , intTyConKey
588         , integerTyConKey
589         , doubleTyConKey
590         , floatTyConKey
591         ]
592
593 needsDataDeclCtxtClassKeys = -- see comments in TcDeriv
594         [ readClassKey
595         ]
596
597 cCallishClassKeys = 
598         [ cCallableClassKey
599         , cReturnableClassKey
600         ]
601
602         -- Renamer always imports these data decls replete with constructors
603         -- so that desugarer can always see their constructors.  Ugh!
604 cCallishTyKeys = 
605         [ addrTyConKey
606         , wordTyConKey
607         , byteArrayTyConKey
608         , mutableByteArrayTyConKey
609         , foreignObjTyConKey
610         , stablePtrTyConKey
611         , int8TyConKey
612         , int16TyConKey
613         , int32TyConKey
614         , int64TyConKey
615         , word8TyConKey
616         , word16TyConKey
617         , word32TyConKey
618         , word64TyConKey
619         ]
620
621 standardClassKeys
622   = derivableClassKeys ++ numericClassKeys ++ cCallishClassKeys
623     --
624     -- We have to have "CCallable" and "CReturnable" in the standard
625     -- classes, so that if you go...
626     --
627     --      _ccall_ foo ... 93{-numeric literal-} ...
628     --
629     -- ... it can do The Right Thing on the 93.
630
631 noDictClassKeys         -- These classes are used only for type annotations;
632                         -- they are not implemented by dictionaries, ever.
633   = cCallishClassKeys
634 \end{code}
635
636
637 %************************************************************************
638 %*                                                                      *
639 \subsection{Local helpers}
640 %*                                                                      *
641 %************************************************************************
642
643 \begin{code}
644 varQual  = mkPreludeQual varName
645 dataQual = mkPreludeQual dataName
646 tcQual   = mkPreludeQual tcName
647 clsQual  = mkPreludeQual clsName
648 \end{code}
649