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