[project @ 2000-03-23 17:45:17 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,
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 deRefStablePtr_NAME = mkKnownKeyGlobal (deRefStablePtr_RDR, deRefStablePtrIdKey)
207 makeStablePtr_NAME  = mkKnownKeyGlobal (makeStablePtr_RDR,  makeStablePtrIdKey)
208
209 knownKeyNames :: [Name]
210 knownKeyNames
211   = [main_NAME, ioTyCon_NAME]
212     ++
213     map mkKnownKeyGlobal
214     [
215         -- Type constructors (synonyms especially)
216       (orderingTyCon_RDR,       orderingTyConKey)
217     , (rationalTyCon_RDR,       rationalTyConKey)
218     , (ratioDataCon_RDR,        ratioDataConKey)
219     , (ratioTyCon_RDR,          ratioTyConKey)
220     , (byteArrayTyCon_RDR,      byteArrayTyConKey)
221     , (mutableByteArrayTyCon_RDR, mutableByteArrayTyConKey)
222     , (foreignObjTyCon_RDR,     foreignObjTyConKey)
223     , (stablePtrTyCon_RDR,      stablePtrTyConKey)
224     , (stablePtrDataCon_RDR,    stablePtrDataConKey)
225
226         --  Classes.  *Must* include:
227         --      classes that are grabbed by key (e.g., eqClassKey)
228         --      classes in "Class.standardClassKeys" (quite a few)
229     , (eqClass_RDR,             eqClassKey)             -- mentioned, derivable
230     , (ordClass_RDR,            ordClassKey)            -- derivable
231     , (boundedClass_RDR,        boundedClassKey)        -- derivable
232     , (numClass_RDR,            numClassKey)            -- mentioned, numeric
233     , (enumClass_RDR,           enumClassKey)           -- derivable
234     , (monadClass_RDR,          monadClassKey)
235     , (monadPlusClass_RDR,      monadPlusClassKey)
236     , (functorClass_RDR,        functorClassKey)
237     , (showClass_RDR,           showClassKey)           -- derivable
238     , (realClass_RDR,           realClassKey)           -- numeric
239     , (integralClass_RDR,       integralClassKey)       -- numeric
240     , (fractionalClass_RDR,     fractionalClassKey)     -- numeric
241     , (floatingClass_RDR,       floatingClassKey)       -- numeric
242     , (realFracClass_RDR,       realFracClassKey)       -- numeric
243     , (realFloatClass_RDR,      realFloatClassKey)      -- numeric
244     , (readClass_RDR,           readClassKey)           -- derivable
245     , (ixClass_RDR,             ixClassKey)             -- derivable (but it isn't Prelude.Ix; hmmm)
246     , (ccallableClass_RDR,      cCallableClassKey)      -- mentioned, ccallish
247     , (creturnableClass_RDR,    cReturnableClassKey)    -- mentioned, ccallish
248
249         -- ClassOps 
250     , (fromInt_RDR,             fromIntClassOpKey)
251     , (fromInteger_RDR,         fromIntegerClassOpKey)
252     , (ge_RDR,                  geClassOpKey) 
253     , (minus_RDR,               minusClassOpKey)
254     , (enumFrom_RDR,            enumFromClassOpKey)
255     , (enumFromThen_RDR,        enumFromThenClassOpKey)
256     , (enumFromTo_RDR,          enumFromToClassOpKey)
257     , (enumFromThenTo_RDR,      enumFromThenToClassOpKey)
258     , (fromEnum_RDR,            fromEnumClassOpKey)
259     , (toEnum_RDR,              toEnumClassOpKey)
260     , (eq_RDR,                  eqClassOpKey)
261     , (thenM_RDR,               thenMClassOpKey)
262     , (returnM_RDR,             returnMClassOpKey)
263     , (failM_RDR,               failMClassOpKey)
264     , (fromRational_RDR,        fromRationalClassOpKey)
265     
266     , (deRefStablePtr_RDR,      deRefStablePtrIdKey)
267     , (makeStablePtr_RDR,       makeStablePtrIdKey)
268     , (bindIO_RDR,              bindIOIdKey)
269
270     , (map_RDR,                 mapIdKey)
271     , (append_RDR,              appendIdKey)
272
273         -- List operations
274     , (concat_RDR,              concatIdKey)
275     , (filter_RDR,              filterIdKey)
276     , (zip_RDR,                 zipIdKey)
277     , (build_RDR,               buildIdKey)
278     , (augment_RDR,             augmentIdKey)
279
280         -- FFI primitive types that are not wired-in.
281     , (int8TyCon_RDR,           int8TyConKey)
282     , (int16TyCon_RDR,          int16TyConKey)
283     , (int32TyCon_RDR,          int32TyConKey)
284     , (int64TyCon_RDR,          int64TyConKey)
285     , (word8TyCon_RDR,          word8TyConKey)
286     , (word16TyCon_RDR,         word16TyConKey)
287     , (word32TyCon_RDR,         word32TyConKey)
288     , (word64TyCon_RDR,         word64TyConKey)
289
290         -- Others
291     , (otherwiseId_RDR,         otherwiseIdKey)
292     , (assert_RDR,              assertIdKey)
293     , (runSTRep_RDR,            runSTRepIdKey)
294     ]
295 \end{code}
296
297 ToDo: make it do the ``like'' part properly (as in 0.26 and before).
298
299 \begin{code}
300 maybeCharLikeCon, maybeIntLikeCon :: DataCon -> Bool
301 maybeCharLikeCon con = getUnique con == charDataConKey
302 maybeIntLikeCon  con = getUnique con == intDataConKey
303 \end{code}
304
305 %************************************************************************
306 %*                                                                      *
307 \subsection{Commonly-used RdrNames}
308 %*                                                                      *
309 %************************************************************************
310
311 These RdrNames are not really "built in", but some parts of the compiler
312 (notably the deriving mechanism) need to mention their names, and it's convenient
313 to write them all down in one place.
314
315 \begin{code}
316 main_RDR                = varQual mAIN_Name      SLIT("main")
317 otherwiseId_RDR         = varQual pREL_BASE_Name SLIT("otherwise")
318
319 intTyCon_RDR            = nameRdrName (getName intTyCon)
320 ioTyCon_RDR             = tcQual   pREL_IO_BASE_Name SLIT("IO")
321 ioDataCon_RDR           = dataQual pREL_IO_BASE_Name SLIT("IO")
322 bindIO_RDR              = varQual  pREL_IO_BASE_Name SLIT("bindIO")
323
324 orderingTyCon_RDR       = tcQual   pREL_BASE_Name SLIT("Ordering")
325
326 rationalTyCon_RDR       = tcQual   pREL_REAL_Name  SLIT("Rational")
327 ratioTyCon_RDR          = tcQual   pREL_REAL_Name  SLIT("Ratio")
328 ratioDataCon_RDR        = dataQual pREL_REAL_Name  SLIT(":%")
329
330 byteArrayTyCon_RDR              = tcQual pREL_BYTEARR_Name  SLIT("ByteArray")
331 mutableByteArrayTyCon_RDR       = tcQual pREL_BYTEARR_Name  SLIT("MutableByteArray")
332
333 foreignObjTyCon_RDR     = tcQual   pREL_IO_BASE_Name SLIT("ForeignObj")
334 stablePtrTyCon_RDR      = tcQual   pREL_STABLE_Name SLIT("StablePtr")
335 stablePtrDataCon_RDR    = dataQual pREL_STABLE_Name SLIT("StablePtr")
336 deRefStablePtr_RDR      = varQual  pREL_STABLE_Name SLIT("deRefStablePtr")
337 makeStablePtr_RDR       = varQual  pREL_STABLE_Name SLIT("makeStablePtr")
338
339 -- Random PrelBase data constructors
340 mkInt_RDR          = dataQual pREL_BASE_Name SLIT("I#")
341 false_RDR          = dataQual pREL_BASE_Name SLIT("False")
342 true_RDR           = dataQual pREL_BASE_Name SLIT("True")
343
344 -- Random PrelBase functions
345 and_RDR            = varQual pREL_BASE_Name SLIT("&&")
346 not_RDR            = varQual pREL_BASE_Name SLIT("not")
347 compose_RDR        = varQual pREL_BASE_Name SLIT(".")
348 append_RDR         = varQual pREL_BASE_Name SLIT("++")
349 map_RDR            = varQual pREL_BASE_Name SLIT("map")
350 build_RDR          = varQual pREL_BASE_Name SLIT("build")
351 augment_RDR        = varQual pREL_BASE_Name SLIT("augment")
352
353 -- Classes Eq and Ord
354 eqClass_RDR             = clsQual pREL_BASE_Name SLIT("Eq")
355 ordClass_RDR            = clsQual pREL_BASE_Name SLIT("Ord")
356 eq_RDR             = varQual pREL_BASE_Name SLIT("==")
357 ne_RDR             = varQual pREL_BASE_Name SLIT("/=")
358 le_RDR             = varQual pREL_BASE_Name SLIT("<=")
359 lt_RDR             = varQual pREL_BASE_Name SLIT("<")
360 ge_RDR             = varQual pREL_BASE_Name SLIT(">=")
361 gt_RDR             = varQual pREL_BASE_Name SLIT(">")
362 ltTag_RDR          = dataQual pREL_BASE_Name SLIT("LT")
363 eqTag_RDR          = dataQual pREL_BASE_Name SLIT("EQ")
364 gtTag_RDR          = dataQual pREL_BASE_Name SLIT("GT")
365 max_RDR            = varQual pREL_BASE_Name SLIT("max")
366 min_RDR            = varQual pREL_BASE_Name SLIT("min")
367 compare_RDR        = varQual pREL_BASE_Name SLIT("compare")
368
369 -- Class Monad
370 monadClass_RDR     = clsQual pREL_BASE_Name SLIT("Monad")
371 monadPlusClass_RDR = clsQual pREL_BASE_Name SLIT("MonadPlus")
372 thenM_RDR          = varQual pREL_BASE_Name SLIT(">>=")
373 returnM_RDR        = varQual pREL_BASE_Name SLIT("return")
374 failM_RDR          = varQual pREL_BASE_Name SLIT("fail")
375
376 -- Class Functor
377 functorClass_RDR        = clsQual pREL_BASE_Name SLIT("Functor")
378
379 -- Class Show
380 showClass_RDR      = clsQual pREL_SHOW_Name SLIT("Show")
381 showList___RDR     = varQual pREL_SHOW_Name SLIT("showList__")
382 showsPrec_RDR      = varQual pREL_SHOW_Name SLIT("showsPrec")
383 showList_RDR       = varQual pREL_SHOW_Name SLIT("showList")
384 showSpace_RDR      = varQual pREL_SHOW_Name SLIT("showSpace")
385 showString_RDR     = varQual pREL_SHOW_Name SLIT("showString")
386 showParen_RDR      = varQual pREL_SHOW_Name SLIT("showParen")
387
388
389 -- Class Read
390 readClass_RDR      = clsQual pREL_READ_Name SLIT("Read")
391 readsPrec_RDR      = varQual pREL_READ_Name SLIT("readsPrec")
392 readList_RDR       = varQual pREL_READ_Name SLIT("readList")
393 readParen_RDR      = varQual pREL_READ_Name SLIT("readParen")
394 lex_RDR            = varQual pREL_READ_Name SLIT("lex")
395 readList___RDR     = varQual pREL_READ_Name SLIT("readList__")
396
397
398 -- Class Num
399 numClass_RDR       = clsQual pREL_NUM_Name SLIT("Num")
400 fromInt_RDR        = varQual pREL_NUM_Name SLIT("fromInt")
401 fromInteger_RDR    = varQual pREL_NUM_Name SLIT("fromInteger")
402 minus_RDR          = varQual pREL_NUM_Name SLIT("-")
403 negate_RDR         = varQual pREL_NUM_Name SLIT("negate")
404 plus_RDR           = varQual pREL_NUM_Name SLIT("+")
405 times_RDR          = varQual pREL_NUM_Name SLIT("*")
406
407 -- Other numberic classes
408 realClass_RDR           = clsQual pREL_REAL_Name  SLIT("Real")
409 integralClass_RDR       = clsQual pREL_REAL_Name  SLIT("Integral")
410 realFracClass_RDR       = clsQual pREL_REAL_Name  SLIT("RealFrac")
411 fractionalClass_RDR     = clsQual pREL_REAL_Name  SLIT("Fractional")
412 fromRational_RDR        = varQual pREL_REAL_Name  SLIT("fromRational")
413
414 floatingClass_RDR       = clsQual pREL_FLOAT_Name  SLIT("Floating")
415 realFloatClass_RDR      = clsQual pREL_FLOAT_Name  SLIT("RealFloat")
416
417 -- Class Ix
418 ixClass_RDR        = clsQual iX_Name      SLIT("Ix")
419 range_RDR          = varQual iX_Name   SLIT("range")
420 index_RDR          = varQual iX_Name   SLIT("index")
421 inRange_RDR        = varQual iX_Name   SLIT("inRange")
422
423 -- Class CCallable and CReturnable
424 ccallableClass_RDR      = clsQual pREL_GHC_Name  SLIT("CCallable")
425 creturnableClass_RDR    = clsQual pREL_GHC_Name  SLIT("CReturnable")
426
427 -- Class Enum
428 enumClass_RDR      = clsQual pREL_ENUM_Name SLIT("Enum")
429 succ_RDR           = varQual pREL_ENUM_Name SLIT("succ")
430 pred_RDR           = varQual pREL_ENUM_Name SLIT("pred")
431 toEnum_RDR         = varQual pREL_ENUM_Name SLIT("toEnum")
432 fromEnum_RDR       = varQual pREL_ENUM_Name SLIT("fromEnum")
433 enumFrom_RDR       = varQual pREL_ENUM_Name SLIT("enumFrom")
434 enumFromTo_RDR     = varQual pREL_ENUM_Name SLIT("enumFromTo")
435 enumFromThen_RDR   = varQual pREL_ENUM_Name SLIT("enumFromThen")
436 enumFromThenTo_RDR = varQual pREL_ENUM_Name SLIT("enumFromThenTo")
437
438 -- Class Bounded
439 boundedClass_RDR   = clsQual pREL_ENUM_Name SLIT("Bounded")
440 minBound_RDR       = varQual pREL_ENUM_Name SLIT("minBound")
441 maxBound_RDR       = varQual pREL_ENUM_Name SLIT("maxBound")
442
443
444 -- List functions
445 concat_RDR         = varQual pREL_LIST_Name SLIT("concat")
446 filter_RDR         = varQual pREL_LIST_Name SLIT("filter")
447 zip_RDR            = varQual pREL_LIST_Name SLIT("zip")
448
449 int8TyCon_RDR    = tcQual iNT_Name       SLIT("Int8")
450 int16TyCon_RDR   = tcQual iNT_Name       SLIT("Int16")
451 int32TyCon_RDR   = tcQual iNT_Name       SLIT("Int32")
452 int64TyCon_RDR   = tcQual pREL_ADDR_Name SLIT("Int64")
453
454 word8TyCon_RDR    = tcQual wORD_Name      SLIT("Word8")
455 word16TyCon_RDR   = tcQual wORD_Name      SLIT("Word16")
456 word32TyCon_RDR   = tcQual wORD_Name      SLIT("Word32")
457 word64TyCon_RDR   = tcQual pREL_ADDR_Name SLIT("Word64")
458
459 error_RDR          = varQual pREL_ERR_Name SLIT("error")
460 assert_RDR         = varQual pREL_GHC_Name SLIT("assert")
461 assertErr_RDR      = varQual pREL_ERR_Name SLIT("assertError")
462 runSTRep_RDR       = varQual pREL_ST_Name  SLIT("runSTRep")
463
464 eqH_Char_RDR    = primOpRdrName CharEqOp
465 ltH_Char_RDR    = primOpRdrName CharLtOp
466 eqH_Word_RDR    = primOpRdrName WordEqOp
467 ltH_Word_RDR    = primOpRdrName WordLtOp
468 eqH_Addr_RDR    = primOpRdrName AddrEqOp
469 ltH_Addr_RDR    = primOpRdrName AddrLtOp
470 eqH_Float_RDR   = primOpRdrName FloatEqOp
471 ltH_Float_RDR   = primOpRdrName FloatLtOp
472 eqH_Double_RDR  = primOpRdrName DoubleEqOp
473 ltH_Double_RDR  = primOpRdrName DoubleLtOp
474 eqH_Int_RDR     = primOpRdrName IntEqOp
475 ltH_Int_RDR     = primOpRdrName IntLtOp
476 geH_RDR         = primOpRdrName IntGeOp
477 leH_RDR         = primOpRdrName IntLeOp
478 minusH_RDR      = primOpRdrName IntSubOp
479
480 tagToEnumH_RDR  = primOpRdrName TagToEnumOp
481 getTag_RDR      = varQual pREL_GHC_Name SLIT("getTag#")
482 \end{code}
483
484 \begin{code}
485 mkTupConRdrName :: Int -> RdrName 
486 mkTupConRdrName arity = case mkTupNameStr arity of
487                           (mod, occ) -> dataQual mod occ
488
489 mkUbxTupConRdrName :: Int -> RdrName
490 mkUbxTupConRdrName arity = case mkUbxTupNameStr arity of
491                                 (mod, occ) -> dataQual mod occ
492 \end{code}
493
494
495 %************************************************************************
496 %*                                                                      *
497 \subsection[Class-std-groups]{Standard groups of Prelude classes}
498 %*                                                                      *
499 %************************************************************************
500
501 @derivableClassKeys@ is also used in checking \tr{deriving} constructs
502 (@TcDeriv@).
503
504 @derivingOccurrences@ maps a class name to a list of the (qualified) occurrences
505 that will be mentioned by  the derived code for the class when it is later generated.
506 We don't need to put in things that are WiredIn (because they are already mapped to their
507 correct name by the @NameSupply@.  The class itself, and all its class ops, is
508 already flagged as an occurrence so we don't need to mention that either.
509
510 @derivingOccurrences@ has an item for every derivable class, even if that item is empty,
511 because we treat lookup failure as indicating that the class is illegal in a deriving clause.
512
513 \begin{code}
514 derivingOccurrences :: UniqFM [RdrName]
515 derivingOccurrences = listToUFM deriving_occ_info
516
517 derivableClassKeys  = map fst deriving_occ_info
518
519 deriving_occ_info
520   = [ (eqClassKey,      [intTyCon_RDR, and_RDR, not_RDR])
521     , (ordClassKey,     [intTyCon_RDR, compose_RDR, eqTag_RDR])
522                                 -- EQ (from Ordering) is needed to force in the constructors
523                                 -- as well as the type constructor.
524     , (enumClassKey,    [intTyCon_RDR, eq_RDR, ge_RDR, and_RDR, map_RDR, plus_RDR, showsPrec_RDR, append_RDR]) 
525                                 -- The last two Enum deps are only used to produce better
526                                 -- error msgs for derived toEnum methods.
527     , (boundedClassKey, [intTyCon_RDR])
528     , (showClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, compose_RDR, showString_RDR, 
529                          showParen_RDR, showSpace_RDR, showList___RDR])
530     , (readClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, append_RDR, 
531                          lex_RDR, readParen_RDR, readList___RDR, thenM_RDR])
532                              -- returnM (and the rest of the Monad class decl) 
533                              -- will be forced in as result of depending
534                              -- on thenM.   -- SOF 1/99
535     , (ixClassKey,      [intTyCon_RDR, numClass_RDR, and_RDR, map_RDR, enumFromTo_RDR, 
536                          returnM_RDR, failM_RDR])
537                              -- the last two are needed to force returnM, thenM and failM
538                              -- in before typechecking the list(monad) comprehension
539                              -- generated for derived Ix instances (range method)
540                              -- of single constructor types.  -- SOF 8/97
541     ]
542         -- intTyCon: Practically any deriving needs Int, either for index calculations, 
543         --              or for taggery.
544         -- ordClass: really it's the methods that are actually used.
545         -- numClass: for Int literals
546 \end{code}
547
548
549 NOTE: @Eq@ and @Text@ do need to appear in @standardClasses@
550 even though every numeric class has these two as a superclass,
551 because the list of ambiguous dictionaries hasn't been simplified.
552
553 \begin{code}
554 isCcallishClass, isCreturnableClass, isNoDictClass, 
555   isNumericClass, isStandardClass :: Class -> Bool
556
557 isFractionalClass  clas = classKey clas `is_elem` fractionalClassKeys
558 isNumericClass     clas = classKey clas `is_elem` numericClassKeys
559 isStandardClass    clas = classKey clas `is_elem` standardClassKeys
560 isCcallishClass    clas = classKey clas `is_elem` cCallishClassKeys
561 isCreturnableClass clas = classKey clas == cReturnableClassKey
562 isNoDictClass      clas = classKey clas `is_elem` noDictClassKeys
563 is_elem = isIn "is_X_Class"
564
565 numericClassKeys =
566         [ numClassKey
567         , realClassKey
568         , integralClassKey
569         ]
570         ++ fractionalClassKeys
571
572 fractionalClassKeys = 
573         [ fractionalClassKey
574         , floatingClassKey
575         , realFracClassKey
576         , realFloatClassKey
577         ]
578
579         -- the strictness analyser needs to know about numeric types
580         -- (see SaAbsInt.lhs)
581 numericTyKeys = 
582         [ addrTyConKey
583         , wordTyConKey
584         , intTyConKey
585         , integerTyConKey
586         , doubleTyConKey
587         , floatTyConKey
588         ]
589
590 needsDataDeclCtxtClassKeys = -- see comments in TcDeriv
591         [ readClassKey
592         ]
593
594 cCallishClassKeys = 
595         [ cCallableClassKey
596         , cReturnableClassKey
597         ]
598
599         -- Renamer always imports these data decls replete with constructors
600         -- so that desugarer can always see their constructors.  Ugh!
601 cCallishTyKeys = 
602         [ addrTyConKey
603         , wordTyConKey
604         , byteArrayTyConKey
605         , mutableByteArrayTyConKey
606         , foreignObjTyConKey
607         , stablePtrTyConKey
608         , int8TyConKey
609         , int16TyConKey
610         , int32TyConKey
611         , int64TyConKey
612         , word8TyConKey
613         , word16TyConKey
614         , word32TyConKey
615         , word64TyConKey
616         ]
617
618 standardClassKeys
619   = derivableClassKeys ++ numericClassKeys ++ cCallishClassKeys
620     --
621     -- We have to have "CCallable" and "CReturnable" in the standard
622     -- classes, so that if you go...
623     --
624     --      _ccall_ foo ... 93{-numeric literal-} ...
625     --
626     -- ... it can do The Right Thing on the 93.
627
628 noDictClassKeys         -- These classes are used only for type annotations;
629                         -- they are not implemented by dictionaries, ever.
630   = cCallishClassKeys
631 \end{code}
632
633
634 %************************************************************************
635 %*                                                                      *
636 \subsection{Local helpers}
637 %*                                                                      *
638 %************************************************************************
639
640 \begin{code}
641 varQual  = mkPreludeQual varName
642 dataQual = mkPreludeQual dataName
643 tcQual   = mkPreludeQual tcName
644 clsQual  = mkPreludeQual clsName
645 \end{code}
646