94666c7101ed3719dd805d082b066e190c9c898e
[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     , weakPrimTyCon
161     , mutableArrayPrimTyCon
162     , mutableByteArrayPrimTyCon
163     , mVarPrimTyCon
164     , mutVarPrimTyCon
165     , realWorldTyCon
166     , stablePtrPrimTyCon
167     , stableNamePrimTyCon
168     , statePrimTyCon
169     , threadIdPrimTyCon
170     , wordPrimTyCon
171     , word64PrimTyCon
172     ]
173
174 tuple_tycons = unitTyCon : [tupleTyCon Boxed i | i <- [2..37] ]
175 unboxed_tuple_tycons = [tupleTyCon Unboxed i | i <- [1..37] ]
176
177 data_tycons
178   = [ addrTyCon
179     , boolTyCon
180     , charTyCon
181     , doubleTyCon
182     , floatTyCon
183     , intTyCon
184     , integerTyCon
185     , listTyCon
186     , wordTyCon
187     ]
188 \end{code}
189
190
191 %************************************************************************
192 %*                                                                      *
193 \subsection{Built-in keys}
194 %*                                                                      *
195 %************************************************************************
196
197 Ids, Synonyms, Classes and ClassOps with builtin keys. 
198
199 \begin{code}
200 knownKeyNames :: [Name]
201 knownKeyNames
202   = map mkKnownKeyGlobal
203     [
204         -- Type constructors (synonyms especially)
205       (ioTyCon_RDR,             ioTyConKey)
206     , (main_RDR,                mainKey)
207     , (orderingTyCon_RDR,       orderingTyConKey)
208     , (rationalTyCon_RDR,       rationalTyConKey)
209     , (ratioDataCon_RDR,        ratioDataConKey)
210     , (ratioTyCon_RDR,          ratioTyConKey)
211     , (byteArrayTyCon_RDR,      byteArrayTyConKey)
212     , (mutableByteArrayTyCon_RDR, mutableByteArrayTyConKey)
213     , (foreignObjTyCon_RDR,     foreignObjTyConKey)
214     , (stablePtrTyCon_RDR,      stablePtrTyConKey)
215     , (stablePtrDataCon_RDR,    stablePtrDataConKey)
216
217         --  Classes.  *Must* include:
218         --      classes that are grabbed by key (e.g., eqClassKey)
219         --      classes in "Class.standardClassKeys" (quite a few)
220     , (eqClass_RDR,             eqClassKey)             -- mentioned, derivable
221     , (ordClass_RDR,            ordClassKey)            -- derivable
222     , (boundedClass_RDR,        boundedClassKey)        -- derivable
223     , (numClass_RDR,            numClassKey)            -- mentioned, numeric
224     , (enumClass_RDR,           enumClassKey)           -- derivable
225     , (monadClass_RDR,          monadClassKey)
226     , (monadPlusClass_RDR,      monadPlusClassKey)
227     , (functorClass_RDR,        functorClassKey)
228     , (showClass_RDR,           showClassKey)           -- derivable
229     , (realClass_RDR,           realClassKey)           -- numeric
230     , (integralClass_RDR,       integralClassKey)       -- numeric
231     , (fractionalClass_RDR,     fractionalClassKey)     -- numeric
232     , (floatingClass_RDR,       floatingClassKey)       -- numeric
233     , (realFracClass_RDR,       realFracClassKey)       -- numeric
234     , (realFloatClass_RDR,      realFloatClassKey)      -- numeric
235     , (readClass_RDR,           readClassKey)           -- derivable
236     , (ixClass_RDR,             ixClassKey)             -- derivable (but it isn't Prelude.Ix; hmmm)
237     , (ccallableClass_RDR,      cCallableClassKey)      -- mentioned, ccallish
238     , (creturnableClass_RDR,    cReturnableClassKey)    -- mentioned, ccallish
239
240         -- ClassOps 
241     , (fromInt_RDR,             fromIntClassOpKey)
242     , (fromInteger_RDR,         fromIntegerClassOpKey)
243     , (ge_RDR,                  geClassOpKey) 
244     , (minus_RDR,               minusClassOpKey)
245     , (enumFrom_RDR,            enumFromClassOpKey)
246     , (enumFromThen_RDR,        enumFromThenClassOpKey)
247     , (enumFromTo_RDR,          enumFromToClassOpKey)
248     , (enumFromThenTo_RDR,      enumFromThenToClassOpKey)
249     , (fromEnum_RDR,            fromEnumClassOpKey)
250     , (toEnum_RDR,              toEnumClassOpKey)
251     , (eq_RDR,                  eqClassOpKey)
252     , (thenM_RDR,               thenMClassOpKey)
253     , (returnM_RDR,             returnMClassOpKey)
254     , (failM_RDR,               failMClassOpKey)
255     , (fromRational_RDR,        fromRationalClassOpKey)
256     
257     , (deRefStablePtr_RDR,      deRefStablePtrIdKey)
258     , (makeStablePtr_RDR,       makeStablePtrIdKey)
259     , (bindIO_RDR,              bindIOIdKey)
260     , (returnIO_RDR,            returnIOIdKey)
261     , (addr2Integer_RDR,        addr2IntegerIdKey)
262
263         -- Strings and lists
264     , (map_RDR,                 mapIdKey)
265     , (append_RDR,              appendIdKey)
266     , (unpackCString_RDR,       unpackCStringIdKey)
267     , (unpackCString2_RDR,      unpackCString2IdKey)
268     , (unpackCStringAppend_RDR, unpackCStringAppendIdKey)
269     , (unpackCStringFoldr_RDR,  unpackCStringFoldrIdKey)
270
271         -- List operations
272     , (concat_RDR,              concatIdKey)
273     , (filter_RDR,              filterIdKey)
274     , (zip_RDR,                 zipIdKey)
275     , (foldr_RDR,               foldrIdKey)
276     , (build_RDR,               buildIdKey)
277     , (augment_RDR,             augmentIdKey)
278
279         -- FFI primitive types that are not wired-in.
280     , (int8TyCon_RDR,           int8TyConKey)
281     , (int16TyCon_RDR,          int16TyConKey)
282     , (int32TyCon_RDR,          int32TyConKey)
283     , (int64TyCon_RDR,          int64TyConKey)
284     , (word8TyCon_RDR,          word8TyConKey)
285     , (word16TyCon_RDR,         word16TyConKey)
286     , (word32TyCon_RDR,         word32TyConKey)
287     , (word64TyCon_RDR,         word64TyConKey)
288
289         -- Others
290     , (otherwiseId_RDR,         otherwiseIdKey)
291     , (assert_RDR,              assertIdKey)
292     , (runSTRep_RDR,            runSTRepIdKey)
293     ]
294 \end{code}
295
296 ToDo: make it do the ``like'' part properly (as in 0.26 and before).
297
298 \begin{code}
299 maybeCharLikeCon, maybeIntLikeCon :: DataCon -> Bool
300 maybeCharLikeCon con = con `hasKey` charDataConKey
301 maybeIntLikeCon  con = con `hasKey` intDataConKey
302 \end{code}
303
304 %************************************************************************
305 %*                                                                      *
306 \subsection[Class-std-groups]{Standard groups of Prelude classes}
307 %*                                                                      *
308 %************************************************************************
309
310 @derivableClassKeys@ is also used in checking \tr{deriving} constructs
311 (@TcDeriv@).
312
313 @derivingOccurrences@ maps a class name to a list of the (qualified) occurrences
314 that will be mentioned by  the derived code for the class when it is later generated.
315 We don't need to put in things that are WiredIn (because they are already mapped to their
316 correct name by the @NameSupply@.  The class itself, and all its class ops, is
317 already flagged as an occurrence so we don't need to mention that either.
318
319 @derivingOccurrences@ has an item for every derivable class, even if that item is empty,
320 because we treat lookup failure as indicating that the class is illegal in a deriving clause.
321
322 \begin{code}
323 derivingOccurrences :: UniqFM [RdrName]
324 derivingOccurrences = listToUFM deriving_occ_info
325
326 derivableClassKeys  = map fst deriving_occ_info
327
328 deriving_occ_info
329   = [ (eqClassKey,      [intTyCon_RDR, and_RDR, not_RDR])
330     , (ordClassKey,     [intTyCon_RDR, compose_RDR, eqTag_RDR])
331                                 -- EQ (from Ordering) is needed to force in the constructors
332                                 -- as well as the type constructor.
333     , (enumClassKey,    [intTyCon_RDR, eq_RDR, ge_RDR, and_RDR, map_RDR, plus_RDR, showsPrec_RDR, append_RDR]) 
334                                 -- The last two Enum deps are only used to produce better
335                                 -- error msgs for derived toEnum methods.
336     , (boundedClassKey, [intTyCon_RDR])
337     , (showClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, compose_RDR, showString_RDR, 
338                          showParen_RDR, showSpace_RDR, showList___RDR])
339     , (readClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, append_RDR,
340                          foldr_RDR, build_RDR,
341                              -- foldr and build required for list comprehension
342                              -- KSW 2000-06
343                          lex_RDR, readParen_RDR, readList___RDR, thenM_RDR])
344                              -- returnM (and the rest of the Monad class decl) 
345                              -- will be forced in as result of depending
346                              -- on thenM.   -- SOF 1/99
347     , (ixClassKey,      [intTyCon_RDR, numClass_RDR, and_RDR, map_RDR, enumFromTo_RDR,
348                          foldr_RDR, build_RDR,
349                              -- foldr and build required for list comprehension used
350                              -- with single constructor types  -- KSW 2000-06
351                          returnM_RDR, failM_RDR])
352                              -- the last two are needed to force returnM, thenM and failM
353                              -- in before typechecking the list(monad) comprehension
354                              -- generated for derived Ix instances (range method)
355                              -- of single constructor types.  -- SOF 8/97
356     ]
357         -- intTyCon: Practically any deriving needs Int, either for index calculations, 
358         --              or for taggery.
359         -- ordClass: really it's the methods that are actually used.
360         -- numClass: for Int literals
361 \end{code}
362
363
364 NOTE: @Eq@ and @Text@ do need to appear in @standardClasses@
365 even though every numeric class has these two as a superclass,
366 because the list of ambiguous dictionaries hasn't been simplified.
367
368 \begin{code}
369 isCcallishClass, isCreturnableClass, isNoDictClass, 
370   isNumericClass, isStandardClass :: Class -> Bool
371
372 isFractionalClass  clas = classKey clas `is_elem` fractionalClassKeys
373 isNumericClass     clas = classKey clas `is_elem` numericClassKeys
374 isStandardClass    clas = classKey clas `is_elem` standardClassKeys
375 isCcallishClass    clas = classKey clas `is_elem` cCallishClassKeys
376 isCreturnableClass clas = classKey clas == cReturnableClassKey
377 isNoDictClass      clas = classKey clas `is_elem` noDictClassKeys
378 is_elem = isIn "is_X_Class"
379
380 numericClassKeys =
381         [ numClassKey
382         , realClassKey
383         , integralClassKey
384         ]
385         ++ fractionalClassKeys
386
387 fractionalClassKeys = 
388         [ fractionalClassKey
389         , floatingClassKey
390         , realFracClassKey
391         , realFloatClassKey
392         ]
393
394         -- the strictness analyser needs to know about numeric types
395         -- (see SaAbsInt.lhs)
396 numericTyKeys = 
397         [ addrTyConKey
398         , wordTyConKey
399         , intTyConKey
400         , integerTyConKey
401         , doubleTyConKey
402         , floatTyConKey
403         ]
404
405 needsDataDeclCtxtClassKeys = -- see comments in TcDeriv
406         [ readClassKey
407         ]
408
409 cCallishClassKeys = 
410         [ cCallableClassKey
411         , cReturnableClassKey
412         ]
413
414         -- Renamer always imports these data decls replete with constructors
415         -- so that desugarer can always see their constructors.  Ugh!
416 cCallishTyKeys = 
417         [ addrTyConKey
418         , wordTyConKey
419         , byteArrayTyConKey
420         , mutableByteArrayTyConKey
421         , foreignObjTyConKey
422         , stablePtrTyConKey
423         , int8TyConKey
424         , int16TyConKey
425         , int32TyConKey
426         , int64TyConKey
427         , word8TyConKey
428         , word16TyConKey
429         , word32TyConKey
430         , word64TyConKey
431         ]
432
433 standardClassKeys
434   = derivableClassKeys ++ numericClassKeys ++ cCallishClassKeys
435     --
436     -- We have to have "CCallable" and "CReturnable" in the standard
437     -- classes, so that if you go...
438     --
439     --      _ccall_ foo ... 93{-numeric literal-} ...
440     --
441     -- ... it can do The Right Thing on the 93.
442
443 noDictClassKeys         -- These classes are used only for type annotations;
444                         -- they are not implemented by dictionaries, ever.
445   = cCallishClassKeys
446 \end{code}
447