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