[project @ 2000-09-22 15:56:12 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 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, mkKnownKeyGlobal, getName )
50 import Class            ( Class, classKey )
51 import TyCon            ( tyConDataConsIfAvailable, TyCon )
52 import Type             ( funTyCon )
53 import Bag
54 import BasicTypes       ( Boxity(..) )
55 import Unique           -- *Key stuff
56 import UniqFM           ( UniqFM, listToUFM )
57 import Util             ( isIn )
58 \end{code}
59
60 %************************************************************************
61 %*                                                                      *
62 \subsection[builtinNameInfo]{Lookup built-in names}
63 %*                                                                      *
64 %************************************************************************
65
66 We have two ``builtin name funs,'' one to look up @TyCons@ and
67 @Classes@, the other to look up values.
68
69 \begin{code}
70 builtinNames :: Bag Name
71 builtinNames
72   = unionManyBags
73         [       -- Wired in TyCons
74           unionManyBags (map getTyConNames wired_in_tycons)
75
76                 -- Wired in Ids
77         , listToBag (map getName wiredInIds)
78
79                 -- PrimOps
80         , listToBag (map (getName . mkPrimOpId) allThePrimOps)
81
82                 -- Other names with magic keys
83         , listToBag knownKeyNames
84         ]
85 \end{code}
86
87
88 \begin{code}
89 getTyConNames :: TyCon -> Bag Name
90 getTyConNames tycon
91     = getName tycon `consBag` 
92       unionManyBags (map get_data_con_names (tyConDataConsIfAvailable tycon))
93         -- Synonyms return empty list of constructors
94     where
95       get_data_con_names dc = listToBag [getName (dataConId dc),        -- Worker
96                                          getName (dataConWrapId dc)]    -- Wrapper
97 \end{code}
98
99 We let a lot of "non-standard" values be visible, so that we can make
100 sense of them in interface pragmas. It's cool, though they all have
101 "non-standard" names, so they won't get past the parser in user code.
102
103
104 %************************************************************************
105 %*                                                                      *
106 \subsection{RdrNames for the primops}
107 %*                                                                      *
108 %************************************************************************
109
110 These can't be in PrelNames, because we get the RdrName from the PrimOp,
111 which is above PrelNames in the module hierarchy.
112
113 \begin{code}
114 eqH_Char_RDR    = primOpRdrName CharEqOp
115 ltH_Char_RDR    = primOpRdrName CharLtOp
116 eqH_Word_RDR    = primOpRdrName WordEqOp
117 ltH_Word_RDR    = primOpRdrName WordLtOp
118 eqH_Addr_RDR    = primOpRdrName AddrEqOp
119 ltH_Addr_RDR    = primOpRdrName AddrLtOp
120 eqH_Float_RDR   = primOpRdrName FloatEqOp
121 ltH_Float_RDR   = primOpRdrName FloatLtOp
122 eqH_Double_RDR  = primOpRdrName DoubleEqOp
123 ltH_Double_RDR  = primOpRdrName DoubleLtOp
124 eqH_Int_RDR     = primOpRdrName IntEqOp
125 ltH_Int_RDR     = primOpRdrName IntLtOp
126 geH_RDR         = primOpRdrName IntGeOp
127 leH_RDR         = primOpRdrName IntLeOp
128 minusH_RDR      = primOpRdrName IntSubOp
129
130 tagToEnumH_RDR  = primOpRdrName TagToEnumOp
131 \end{code}
132
133 %************************************************************************
134 %*                                                                      *
135 \subsection{Wired in TyCons}
136 %*                                                                      *
137 %************************************************************************
138
139 \begin{code}
140 wired_in_tycons = [funTyCon] ++
141                   prim_tycons ++
142                   tuple_tycons ++
143                   unboxed_tuple_tycons ++
144                   data_tycons
145
146 prim_tycons
147   = [ addrPrimTyCon
148     , arrayPrimTyCon
149     , byteArrayPrimTyCon
150     , charPrimTyCon
151     , doublePrimTyCon
152     , floatPrimTyCon
153     , intPrimTyCon
154     , int64PrimTyCon
155     , foreignObjPrimTyCon
156     , bcoPrimTyCon
157     , weakPrimTyCon
158     , mutableArrayPrimTyCon
159     , mutableByteArrayPrimTyCon
160     , mVarPrimTyCon
161     , mutVarPrimTyCon
162     , realWorldTyCon
163     , stablePtrPrimTyCon
164     , stableNamePrimTyCon
165     , statePrimTyCon
166     , threadIdPrimTyCon
167     , wordPrimTyCon
168     , word64PrimTyCon
169     ]
170
171 tuple_tycons = unitTyCon : [tupleTyCon Boxed i | i <- [2..37] ]
172 unboxed_tuple_tycons = [tupleTyCon Unboxed i | i <- [1..37] ]
173
174 data_tycons
175   = [ addrTyCon
176     , boolTyCon
177     , charTyCon
178     , doubleTyCon
179     , floatTyCon
180     , intTyCon
181     , integerTyCon
182     , listTyCon
183     , wordTyCon
184     ]
185 \end{code}
186
187
188 %************************************************************************
189 %*                                                                      *
190 \subsection{Built-in keys}
191 %*                                                                      *
192 %************************************************************************
193
194 Ids, Synonyms, Classes and ClassOps with builtin keys. 
195
196 \begin{code}
197 knownKeyNames :: [Name]
198 knownKeyNames
199   = map mkKnownKeyGlobal
200     [
201         -- Type constructors (synonyms especially)
202       (ioTyCon_RDR,             ioTyConKey)
203     , (main_RDR,                mainKey)
204     , (orderingTyCon_RDR,       orderingTyConKey)
205     , (rationalTyCon_RDR,       rationalTyConKey)
206     , (ratioDataCon_RDR,        ratioDataConKey)
207     , (ratioTyCon_RDR,          ratioTyConKey)
208     , (byteArrayTyCon_RDR,      byteArrayTyConKey)
209     , (mutableByteArrayTyCon_RDR, mutableByteArrayTyConKey)
210     , (foreignObjTyCon_RDR,     foreignObjTyConKey)
211     , (bcoPrimTyCon_RDR,        bcoPrimTyConKey)
212     , (stablePtrTyCon_RDR,      stablePtrTyConKey)
213     , (stablePtrDataCon_RDR,    stablePtrDataConKey)
214
215         --  Classes.  *Must* include:
216         --      classes that are grabbed by key (e.g., eqClassKey)
217         --      classes in "Class.standardClassKeys" (quite a few)
218     , (eqClass_RDR,             eqClassKey)             -- mentioned, derivable
219     , (ordClass_RDR,            ordClassKey)            -- derivable
220     , (boundedClass_RDR,        boundedClassKey)        -- derivable
221     , (numClass_RDR,            numClassKey)            -- mentioned, numeric
222     , (enumClass_RDR,           enumClassKey)           -- derivable
223     , (monadClass_RDR,          monadClassKey)
224     , (monadPlusClass_RDR,      monadPlusClassKey)
225     , (functorClass_RDR,        functorClassKey)
226     , (showClass_RDR,           showClassKey)           -- derivable
227     , (realClass_RDR,           realClassKey)           -- numeric
228     , (integralClass_RDR,       integralClassKey)       -- numeric
229     , (fractionalClass_RDR,     fractionalClassKey)     -- numeric
230     , (floatingClass_RDR,       floatingClassKey)       -- numeric
231     , (realFracClass_RDR,       realFracClassKey)       -- numeric
232     , (realFloatClass_RDR,      realFloatClassKey)      -- numeric
233     , (readClass_RDR,           readClassKey)           -- derivable
234     , (ixClass_RDR,             ixClassKey)             -- derivable (but it isn't Prelude.Ix; hmmm)
235     , (ccallableClass_RDR,      cCallableClassKey)      -- mentioned, ccallish
236     , (creturnableClass_RDR,    cReturnableClassKey)    -- mentioned, ccallish
237
238         -- ClassOps 
239     , (fromInt_RDR,             fromIntClassOpKey)
240     , (fromInteger_RDR,         fromIntegerClassOpKey)
241     , (ge_RDR,                  geClassOpKey) 
242     , (minus_RDR,               minusClassOpKey)
243     , (enumFrom_RDR,            enumFromClassOpKey)
244     , (enumFromThen_RDR,        enumFromThenClassOpKey)
245     , (enumFromTo_RDR,          enumFromToClassOpKey)
246     , (enumFromThenTo_RDR,      enumFromThenToClassOpKey)
247     , (fromEnum_RDR,            fromEnumClassOpKey)
248     , (toEnum_RDR,              toEnumClassOpKey)
249     , (eq_RDR,                  eqClassOpKey)
250     , (thenM_RDR,               thenMClassOpKey)
251     , (returnM_RDR,             returnMClassOpKey)
252     , (failM_RDR,               failMClassOpKey)
253     , (fromRational_RDR,        fromRationalClassOpKey)
254     
255     , (deRefStablePtr_RDR,      deRefStablePtrIdKey)
256     , (makeStablePtr_RDR,       makeStablePtrIdKey)
257     , (bindIO_RDR,              bindIOIdKey)
258     , (returnIO_RDR,            returnIOIdKey)
259     , (addr2Integer_RDR,        addr2IntegerIdKey)
260
261         -- Strings and lists
262     , (map_RDR,                 mapIdKey)
263     , (append_RDR,              appendIdKey)
264     , (unpackCString_RDR,       unpackCStringIdKey)
265     , (unpackCStringAppend_RDR, unpackCStringAppendIdKey)
266     , (unpackCStringFoldr_RDR,  unpackCStringFoldrIdKey)
267     , (unpackCStringUtf8_RDR,   unpackCStringUtf8IdKey)
268
269         -- List operations
270     , (concat_RDR,              concatIdKey)
271     , (filter_RDR,              filterIdKey)
272     , (zip_RDR,                 zipIdKey)
273     , (foldr_RDR,               foldrIdKey)
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     , (plusInteger_RDR,         plusIntegerIdKey)
290     , (timesInteger_RDR,        timesIntegerIdKey)
291     , (eqString_RDR,            eqStringIdKey)
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 = con `hasKey` charDataConKey
302 maybeIntLikeCon  con = con `hasKey` intDataConKey
303 \end{code}
304
305 %************************************************************************
306 %*                                                                      *
307 \subsection[Class-std-groups]{Standard groups of Prelude classes}
308 %*                                                                      *
309 %************************************************************************
310
311 @derivableClassKeys@ is also used in checking \tr{deriving} constructs
312 (@TcDeriv@).
313
314 @derivingOccurrences@ maps a class name to a list of the (qualified) occurrences
315 that will be mentioned by  the derived code for the class when it is later generated.
316 We don't need to put in things that are WiredIn (because they are already mapped to their
317 correct name by the @NameSupply@.  The class itself, and all its class ops, is
318 already flagged as an occurrence so we don't need to mention that either.
319
320 @derivingOccurrences@ has an item for every derivable class, even if that item is empty,
321 because we treat lookup failure as indicating that the class is illegal in a deriving clause.
322
323 \begin{code}
324 derivingOccurrences :: UniqFM [RdrName]
325 derivingOccurrences = listToUFM deriving_occ_info
326
327 derivableClassKeys  = map fst deriving_occ_info
328
329 deriving_occ_info
330   = [ (eqClassKey,      [intTyCon_RDR, and_RDR, not_RDR])
331     , (ordClassKey,     [intTyCon_RDR, compose_RDR, eqTag_RDR])
332                                 -- EQ (from Ordering) is needed to force in the constructors
333                                 -- as well as the type constructor.
334     , (enumClassKey,    [intTyCon_RDR, eq_RDR, ge_RDR, and_RDR, map_RDR, plus_RDR, showsPrec_RDR, append_RDR]) 
335                                 -- The last two Enum deps are only used to produce better
336                                 -- error msgs for derived toEnum methods.
337     , (boundedClassKey, [intTyCon_RDR])
338     , (showClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, compose_RDR, showString_RDR, 
339                          showParen_RDR, showSpace_RDR, showList___RDR])
340     , (readClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, append_RDR,
341                          foldr_RDR, build_RDR,
342                              -- foldr and build required for list comprehension
343                              -- KSW 2000-06
344                          lex_RDR, readParen_RDR, readList___RDR, thenM_RDR])
345                              -- returnM (and the rest of the Monad class decl) 
346                              -- will be forced in as result of depending
347                              -- on thenM.   -- SOF 1/99
348     , (ixClassKey,      [intTyCon_RDR, numClass_RDR, and_RDR, map_RDR, enumFromTo_RDR,
349                          foldr_RDR, build_RDR,
350                              -- foldr and build required for list comprehension used
351                              -- with single constructor types  -- KSW 2000-06
352                          returnM_RDR, failM_RDR])
353                              -- the last two are needed to force returnM, thenM and failM
354                              -- in before typechecking the list(monad) comprehension
355                              -- generated for derived Ix instances (range method)
356                              -- of single constructor types.  -- SOF 8/97
357     ]
358         -- intTyCon: Practically any deriving needs Int, either for index calculations, 
359         --              or for taggery.
360         -- ordClass: really it's the methods that are actually used.
361         -- numClass: for Int literals
362 \end{code}
363
364
365 NOTE: @Eq@ and @Text@ do need to appear in @standardClasses@
366 even though every numeric class has these two as a superclass,
367 because the list of ambiguous dictionaries hasn't been simplified.
368
369 \begin{code}
370 isCcallishClass, isCreturnableClass, isNoDictClass, 
371   isNumericClass, isStandardClass :: Class -> Bool
372
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