ae88f95dd64904a5db2cbf0db12d1160225cd569
[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 PrelNames,
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         
22         -- Primop RdrNames
23         eqH_Char_RDR,   ltH_Char_RDR,   eqH_Word_RDR,  ltH_Word_RDR, 
24         eqH_Addr_RDR,   ltH_Addr_RDR,   eqH_Float_RDR, ltH_Float_RDR, 
25         eqH_Double_RDR, ltH_Double_RDR, eqH_Int_RDR,   ltH_Int_RDR,
26         geH_RDR, leH_RDR, minusH_RDR, tagToEnumH_RDR, 
27
28         -- Random other things
29         maybeCharLikeCon, maybeIntLikeCon,
30         needsDataDeclCtxtClassKeys, cCallishClassKeys, cCallishTyKeys, 
31         isNoDictClass, isNumericClass, isStandardClass, isCcallishClass, 
32         isCreturnableClass, numericTyKeys, fractionalClassKeys,
33
34     ) where
35
36 #include "HsVersions.h"
37
38 -- friends:
39 import MkId             -- Ditto
40 import PrelNames        -- Prelude module names
41
42 import PrimOp           ( PrimOp(..), allThePrimOps, primOpRdrName )
43 import DataCon          ( DataCon, dataConId, dataConWrapId )
44 import TysPrim          -- TYPES
45 import TysWiredIn
46
47 -- others:
48 import RdrName          ( RdrName )
49 import Name             ( Name, OccName, Provenance(..), 
50                           NameSpace, tcName, clsName, varName, dataName,
51                           mkKnownKeyGlobal,
52                           getName, mkGlobalName, nameRdrName
53                         )
54 import Class            ( Class, classKey )
55 import TyCon            ( tyConDataConsIfAvailable, TyCon )
56 import Type             ( funTyCon )
57 import Bag
58 import BasicTypes       ( Boxity(..) )
59 import Unique           -- *Key stuff
60 import UniqFM           ( UniqFM, listToUFM )
61 import Util             ( isIn )
62 \end{code}
63
64 %************************************************************************
65 %*                                                                      *
66 \subsection[builtinNameInfo]{Lookup built-in names}
67 %*                                                                      *
68 %************************************************************************
69
70 We have two ``builtin name funs,'' one to look up @TyCons@ and
71 @Classes@, the other to look up values.
72
73 \begin{code}
74 builtinNames :: Bag Name
75 builtinNames
76   = unionManyBags
77         [       -- Wired in TyCons
78           unionManyBags (map getTyConNames wired_in_tycons)
79
80                 -- Wired in Ids
81         , listToBag (map getName wiredInIds)
82
83                 -- PrimOps
84         , listToBag (map (getName . mkPrimOpId) allThePrimOps)
85
86                 -- Other names with magic keys
87         , listToBag knownKeyNames
88         ]
89 \end{code}
90
91
92 \begin{code}
93 getTyConNames :: TyCon -> Bag Name
94 getTyConNames tycon
95     = getName tycon `consBag` 
96       unionManyBags (map get_data_con_names (tyConDataConsIfAvailable tycon))
97         -- Synonyms return empty list of constructors
98     where
99       get_data_con_names dc = listToBag [getName (dataConId dc),        -- Worker
100                                          getName (dataConWrapId dc)]    -- Wrapper
101 \end{code}
102
103 We let a lot of "non-standard" values be visible, so that we can make
104 sense of them in interface pragmas. It's cool, though they all have
105 "non-standard" names, so they won't get past the parser in user code.
106
107
108 %************************************************************************
109 %*                                                                      *
110 \subsection{RdrNames for the primops}
111 %*                                                                      *
112 %************************************************************************
113
114 These can't be in PrelNames, because we get the RdrName from the PrimOp,
115 which is above PrelNames in the module hierarchy.
116
117 \begin{code}
118 eqH_Char_RDR    = primOpRdrName CharEqOp
119 ltH_Char_RDR    = primOpRdrName CharLtOp
120 eqH_Word_RDR    = primOpRdrName WordEqOp
121 ltH_Word_RDR    = primOpRdrName WordLtOp
122 eqH_Addr_RDR    = primOpRdrName AddrEqOp
123 ltH_Addr_RDR    = primOpRdrName AddrLtOp
124 eqH_Float_RDR   = primOpRdrName FloatEqOp
125 ltH_Float_RDR   = primOpRdrName FloatLtOp
126 eqH_Double_RDR  = primOpRdrName DoubleEqOp
127 ltH_Double_RDR  = primOpRdrName DoubleLtOp
128 eqH_Int_RDR     = primOpRdrName IntEqOp
129 ltH_Int_RDR     = primOpRdrName IntLtOp
130 geH_RDR         = primOpRdrName IntGeOp
131 leH_RDR         = primOpRdrName IntLeOp
132 minusH_RDR      = primOpRdrName IntSubOp
133
134 tagToEnumH_RDR  = primOpRdrName TagToEnumOp
135 \end{code}
136
137 %************************************************************************
138 %*                                                                      *
139 \subsection{Wired in TyCons}
140 %*                                                                      *
141 %************************************************************************
142
143 \begin{code}
144 wired_in_tycons = [funTyCon] ++
145                   prim_tycons ++
146                   tuple_tycons ++
147                   unboxed_tuple_tycons ++
148                   data_tycons
149
150 prim_tycons
151   = [ addrPrimTyCon
152     , arrayPrimTyCon
153     , byteArrayPrimTyCon
154     , charPrimTyCon
155     , doublePrimTyCon
156     , floatPrimTyCon
157     , intPrimTyCon
158     , int64PrimTyCon
159     , foreignObjPrimTyCon
160     , bcoPrimTyCon
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 Boxed i | i <- [2..37] ]
176 unboxed_tuple_tycons = [tupleTyCon Unboxed 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 knownKeyNames :: [Name]
202 knownKeyNames
203   = map mkKnownKeyGlobal
204     [
205         -- Type constructors (synonyms especially)
206       (ioTyCon_RDR,             ioTyConKey)
207     , (main_RDR,                mainKey)
208     , (orderingTyCon_RDR,       orderingTyConKey)
209     , (rationalTyCon_RDR,       rationalTyConKey)
210     , (ratioDataCon_RDR,        ratioDataConKey)
211     , (ratioTyCon_RDR,          ratioTyConKey)
212     , (byteArrayTyCon_RDR,      byteArrayTyConKey)
213     , (mutableByteArrayTyCon_RDR, mutableByteArrayTyConKey)
214     , (foreignObjTyCon_RDR,     foreignObjTyConKey)
215     , (bcoPrimTyCon_RDR,        bcoPrimTyConKey)
216     , (stablePtrTyCon_RDR,      stablePtrTyConKey)
217     , (stablePtrDataCon_RDR,    stablePtrDataConKey)
218
219         --  Classes.  *Must* include:
220         --      classes that are grabbed by key (e.g., eqClassKey)
221         --      classes in "Class.standardClassKeys" (quite a few)
222     , (eqClass_RDR,             eqClassKey)             -- mentioned, derivable
223     , (ordClass_RDR,            ordClassKey)            -- derivable
224     , (boundedClass_RDR,        boundedClassKey)        -- derivable
225     , (numClass_RDR,            numClassKey)            -- mentioned, numeric
226     , (enumClass_RDR,           enumClassKey)           -- derivable
227     , (monadClass_RDR,          monadClassKey)
228     , (monadPlusClass_RDR,      monadPlusClassKey)
229     , (functorClass_RDR,        functorClassKey)
230     , (showClass_RDR,           showClassKey)           -- derivable
231     , (realClass_RDR,           realClassKey)           -- numeric
232     , (integralClass_RDR,       integralClassKey)       -- numeric
233     , (fractionalClass_RDR,     fractionalClassKey)     -- numeric
234     , (floatingClass_RDR,       floatingClassKey)       -- numeric
235     , (realFracClass_RDR,       realFracClassKey)       -- numeric
236     , (realFloatClass_RDR,      realFloatClassKey)      -- numeric
237     , (readClass_RDR,           readClassKey)           -- derivable
238     , (ixClass_RDR,             ixClassKey)             -- derivable (but it isn't Prelude.Ix; hmmm)
239     , (ccallableClass_RDR,      cCallableClassKey)      -- mentioned, ccallish
240     , (creturnableClass_RDR,    cReturnableClassKey)    -- mentioned, ccallish
241
242         -- ClassOps 
243     , (fromInt_RDR,             fromIntClassOpKey)
244     , (fromInteger_RDR,         fromIntegerClassOpKey)
245     , (ge_RDR,                  geClassOpKey) 
246     , (minus_RDR,               minusClassOpKey)
247     , (enumFrom_RDR,            enumFromClassOpKey)
248     , (enumFromThen_RDR,        enumFromThenClassOpKey)
249     , (enumFromTo_RDR,          enumFromToClassOpKey)
250     , (enumFromThenTo_RDR,      enumFromThenToClassOpKey)
251     , (fromEnum_RDR,            fromEnumClassOpKey)
252     , (toEnum_RDR,              toEnumClassOpKey)
253     , (eq_RDR,                  eqClassOpKey)
254     , (thenM_RDR,               thenMClassOpKey)
255     , (returnM_RDR,             returnMClassOpKey)
256     , (failM_RDR,               failMClassOpKey)
257     , (fromRational_RDR,        fromRationalClassOpKey)
258     
259     , (deRefStablePtr_RDR,      deRefStablePtrIdKey)
260     , (makeStablePtr_RDR,       makeStablePtrIdKey)
261     , (bindIO_RDR,              bindIOIdKey)
262     , (returnIO_RDR,            returnIOIdKey)
263     , (addr2Integer_RDR,        addr2IntegerIdKey)
264
265         -- Strings and lists
266     , (map_RDR,                 mapIdKey)
267     , (append_RDR,              appendIdKey)
268     , (unpackCString_RDR,       unpackCStringIdKey)
269     , (unpackCString2_RDR,      unpackCString2IdKey)
270     , (unpackCStringAppend_RDR, unpackCStringAppendIdKey)
271     , (unpackCStringFoldr_RDR,  unpackCStringFoldrIdKey)
272
273         -- List operations
274     , (concat_RDR,              concatIdKey)
275     , (filter_RDR,              filterIdKey)
276     , (zip_RDR,                 zipIdKey)
277     , (foldr_RDR,               foldrIdKey)
278     , (build_RDR,               buildIdKey)
279     , (augment_RDR,             augmentIdKey)
280
281         -- FFI primitive types that are not wired-in.
282     , (int8TyCon_RDR,           int8TyConKey)
283     , (int16TyCon_RDR,          int16TyConKey)
284     , (int32TyCon_RDR,          int32TyConKey)
285     , (int64TyCon_RDR,          int64TyConKey)
286     , (word8TyCon_RDR,          word8TyConKey)
287     , (word16TyCon_RDR,         word16TyConKey)
288     , (word32TyCon_RDR,         word32TyConKey)
289     , (word64TyCon_RDR,         word64TyConKey)
290
291         -- Others
292     , (otherwiseId_RDR,         otherwiseIdKey)
293     , (assert_RDR,              assertIdKey)
294     , (runSTRep_RDR,            runSTRepIdKey)
295     ]
296 \end{code}
297
298 ToDo: make it do the ``like'' part properly (as in 0.26 and before).
299
300 \begin{code}
301 maybeCharLikeCon, maybeIntLikeCon :: DataCon -> Bool
302 maybeCharLikeCon con = con `hasKey` charDataConKey
303 maybeIntLikeCon  con = con `hasKey` intDataConKey
304 \end{code}
305
306 %************************************************************************
307 %*                                                                      *
308 \subsection[Class-std-groups]{Standard groups of Prelude classes}
309 %*                                                                      *
310 %************************************************************************
311
312 @derivableClassKeys@ is also used in checking \tr{deriving} constructs
313 (@TcDeriv@).
314
315 @derivingOccurrences@ maps a class name to a list of the (qualified) occurrences
316 that will be mentioned by  the derived code for the class when it is later generated.
317 We don't need to put in things that are WiredIn (because they are already mapped to their
318 correct name by the @NameSupply@.  The class itself, and all its class ops, is
319 already flagged as an occurrence so we don't need to mention that either.
320
321 @derivingOccurrences@ has an item for every derivable class, even if that item is empty,
322 because we treat lookup failure as indicating that the class is illegal in a deriving clause.
323
324 \begin{code}
325 derivingOccurrences :: UniqFM [RdrName]
326 derivingOccurrences = listToUFM deriving_occ_info
327
328 derivableClassKeys  = map fst deriving_occ_info
329
330 deriving_occ_info
331   = [ (eqClassKey,      [intTyCon_RDR, and_RDR, not_RDR])
332     , (ordClassKey,     [intTyCon_RDR, compose_RDR, eqTag_RDR])
333                                 -- EQ (from Ordering) is needed to force in the constructors
334                                 -- as well as the type constructor.
335     , (enumClassKey,    [intTyCon_RDR, eq_RDR, ge_RDR, and_RDR, map_RDR, plus_RDR, showsPrec_RDR, append_RDR]) 
336                                 -- The last two Enum deps are only used to produce better
337                                 -- error msgs for derived toEnum methods.
338     , (boundedClassKey, [intTyCon_RDR])
339     , (showClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, compose_RDR, showString_RDR, 
340                          showParen_RDR, showSpace_RDR, showList___RDR])
341     , (readClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, append_RDR,
342                          foldr_RDR, build_RDR,
343                              -- foldr and build required for list comprehension
344                              -- KSW 2000-06
345                          lex_RDR, readParen_RDR, readList___RDR, thenM_RDR])
346                              -- returnM (and the rest of the Monad class decl) 
347                              -- will be forced in as result of depending
348                              -- on thenM.   -- SOF 1/99
349     , (ixClassKey,      [intTyCon_RDR, numClass_RDR, and_RDR, map_RDR, enumFromTo_RDR,
350                          foldr_RDR, build_RDR,
351                              -- foldr and build required for list comprehension used
352                              -- with single constructor types  -- KSW 2000-06
353                          returnM_RDR, failM_RDR])
354                              -- the last two are needed to force returnM, thenM and failM
355                              -- in before typechecking the list(monad) comprehension
356                              -- generated for derived Ix instances (range method)
357                              -- of single constructor types.  -- SOF 8/97
358     ]
359         -- intTyCon: Practically any deriving needs Int, either for index calculations, 
360         --              or for taggery.
361         -- ordClass: really it's the methods that are actually used.
362         -- numClass: for Int literals
363 \end{code}
364
365
366 NOTE: @Eq@ and @Text@ do need to appear in @standardClasses@
367 even though every numeric class has these two as a superclass,
368 because the list of ambiguous dictionaries hasn't been simplified.
369
370 \begin{code}
371 isCcallishClass, isCreturnableClass, isNoDictClass, 
372   isNumericClass, isStandardClass :: Class -> Bool
373
374 isFractionalClass  clas = classKey clas `is_elem` fractionalClassKeys
375 isNumericClass     clas = classKey clas `is_elem` numericClassKeys
376 isStandardClass    clas = classKey clas `is_elem` standardClassKeys
377 isCcallishClass    clas = classKey clas `is_elem` cCallishClassKeys
378 isCreturnableClass clas = classKey clas == cReturnableClassKey
379 isNoDictClass      clas = classKey clas `is_elem` noDictClassKeys
380 is_elem = isIn "is_X_Class"
381
382 numericClassKeys =
383         [ numClassKey
384         , realClassKey
385         , integralClassKey
386         ]
387         ++ fractionalClassKeys
388
389 fractionalClassKeys = 
390         [ fractionalClassKey
391         , floatingClassKey
392         , realFracClassKey
393         , realFloatClassKey
394         ]
395
396         -- the strictness analyser needs to know about numeric types
397         -- (see SaAbsInt.lhs)
398 numericTyKeys = 
399         [ addrTyConKey
400         , wordTyConKey
401         , intTyConKey
402         , integerTyConKey
403         , doubleTyConKey
404         , floatTyConKey
405         ]
406
407 needsDataDeclCtxtClassKeys = -- see comments in TcDeriv
408         [ readClassKey
409         ]
410
411 cCallishClassKeys = 
412         [ cCallableClassKey
413         , cReturnableClassKey
414         ]
415
416         -- Renamer always imports these data decls replete with constructors
417         -- so that desugarer can always see their constructors.  Ugh!
418 cCallishTyKeys = 
419         [ addrTyConKey
420         , wordTyConKey
421         , byteArrayTyConKey
422         , mutableByteArrayTyConKey
423         , foreignObjTyConKey
424         , stablePtrTyConKey
425         , int8TyConKey
426         , int16TyConKey
427         , int32TyConKey
428         , int64TyConKey
429         , word8TyConKey
430         , word16TyConKey
431         , word32TyConKey
432         , word64TyConKey
433         ]
434
435 standardClassKeys
436   = derivableClassKeys ++ numericClassKeys ++ cCallishClassKeys
437     --
438     -- We have to have "CCallable" and "CReturnable" in the standard
439     -- classes, so that if you go...
440     --
441     --      _ccall_ foo ... 93{-numeric literal-} ...
442     --
443     -- ... it can do The Right Thing on the 93.
444
445 noDictClassKeys         -- These classes are used only for type annotations;
446                         -- they are not implemented by dictionaries, ever.
447   = cCallishClassKeys
448 \end{code}
449