[project @ 1996-05-17 16:02:43 by partain]
[ghc-hetmet.git] / ghc / compiler / prelude / PrelInfo.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
3 %
4 \section[PrelInfo]{The @PrelInfo@ interface to the compiler's prelude knowledge}
5
6 \begin{code}
7 #include "HsVersions.h"
8
9 module PrelInfo (
10
11         -- finite maps for built-in things (for the renamer and typechecker):
12         builtinNameInfo, BuiltinNames(..),
13         BuiltinKeys(..), BuiltinIdInfos(..),
14
15         maybeCharLikeTyCon, maybeIntLikeTyCon
16     ) where
17
18 import Ubiq
19 import PrelLoop         ( primOpNameInfo )
20
21 -- friends:
22 import PrelMods         -- Prelude module names
23 import PrelVals         -- VALUES
24 import PrimOp           ( PrimOp(..), allThePrimOps )
25 import PrimRep          ( PrimRep(..) )
26 import TysPrim          -- TYPES
27 import TysWiredIn
28
29 -- others:
30 import CmdLineOpts      ( opt_HideBuiltinNames,
31                           opt_HideMostBuiltinNames,
32                           opt_ForConcurrent
33                         )
34 import FiniteMap        ( FiniteMap, emptyFM, listToFM )
35 import Id               ( mkTupleCon, GenId, Id(..) )
36 import Maybes           ( catMaybes )
37 import Name             ( origName, nameOf )
38 import RnHsSyn          ( RnName(..) )
39 import TyCon            ( tyConDataCons, mkFunTyCon, mkTupleTyCon, TyCon )
40 import Type
41 import UniqFM           ( UniqFM, emptyUFM, listToUFM )
42 import Unique           -- *Key stuff
43 import Util             ( nOfThem, panic )
44 \end{code}
45
46 %************************************************************************
47 %*                                                                      *
48 \subsection[builtinNameInfo]{Lookup built-in names}
49 %*                                                                      *
50 %************************************************************************
51
52 We have two ``builtin name funs,'' one to look up @TyCons@ and
53 @Classes@, the other to look up values.
54
55 \begin{code}
56 builtinNameInfo :: ( BuiltinNames, BuiltinKeys, BuiltinIdInfos )
57
58 type BuiltinNames   = (FiniteMap FAST_STRING RnName, -- WiredIn Ids
59                        FiniteMap FAST_STRING RnName) -- WiredIn TyCons
60                         -- Two maps because "[]" is in both...
61 type BuiltinKeys    = FiniteMap FAST_STRING (Unique, Name -> RnName)
62                                                     -- Names with known uniques
63 type BuiltinIdInfos = UniqFM IdInfo                  -- Info for known unique Ids
64
65 builtinNameInfo
66   = if opt_HideBuiltinNames then
67         (
68          (emptyFM, emptyFM),
69          emptyFM,
70          emptyUFM
71         )
72     else if opt_HideMostBuiltinNames then
73         (
74          (listToFM min_assoc_val_wired, listToFM min_assoc_tc_wired),
75          emptyFM,
76          emptyUFM
77         )
78     else
79         (
80          (listToFM assoc_val_wired, listToFM assoc_tc_wired),
81          listToFM assoc_keys,
82          listToUFM assoc_id_infos
83         )
84
85   where
86     min_assoc_val_wired -- min needed when compiling bits of Prelude
87       = concat [
88             -- data constrs
89             concat (map pcDataConWiredInInfo g_con_tycons),
90             concat (map pcDataConWiredInInfo min_nonprim_tycon_list),
91
92             -- values
93             map pcIdWiredInInfo wired_in_ids,
94             primop_ids
95          ]
96     min_assoc_tc_wired
97       = concat [
98             -- tycons
99             map pcTyConWiredInInfo prim_tycons,
100             map pcTyConWiredInInfo g_tycons,
101             map pcTyConWiredInInfo min_nonprim_tycon_list
102          ]
103
104     assoc_val_wired
105         = concat [
106             -- data constrs
107             concat (map pcDataConWiredInInfo g_con_tycons),
108             concat (map pcDataConWiredInInfo data_tycons),
109
110             -- values
111             map pcIdWiredInInfo wired_in_ids,
112             map pcIdWiredInInfo parallel_ids,
113             primop_ids
114           ]
115     assoc_tc_wired
116         = concat [
117             -- tycons
118             map pcTyConWiredInInfo prim_tycons,
119             map pcTyConWiredInInfo g_tycons,
120             map pcTyConWiredInInfo data_tycons,
121             map pcTyConWiredInInfo synonym_tycons
122           ]
123
124     assoc_keys
125         = concat
126           [
127             id_keys,
128             tysyn_keys,
129             class_keys,
130             class_op_keys
131           ]
132
133     id_keys = map id_key id_keys_infos
134     id_key (str, uniq, info) = (str, (uniq, RnImplicit))
135
136     assoc_id_infos = catMaybes (map assoc_info id_keys_infos)
137     assoc_info (str, uniq, Just info) = Just (uniq, info)
138     assoc_info (str, uniq, Nothing)   = Nothing
139 \end{code}
140
141
142 We let a lot of "non-standard" values be visible, so that we can make
143 sense of them in interface pragmas. It's cool, though they all have
144 "non-standard" names, so they won't get past the parser in user code.
145
146 The WiredIn TyCons and DataCons ...
147 \begin{code}
148
149 prim_tycons
150   = [ addrPrimTyCon
151     , arrayPrimTyCon
152     , byteArrayPrimTyCon
153     , charPrimTyCon
154     , doublePrimTyCon
155     , floatPrimTyCon
156     , intPrimTyCon
157     , foreignObjPrimTyCon
158     , mutableArrayPrimTyCon
159     , mutableByteArrayPrimTyCon
160     , synchVarPrimTyCon
161     , realWorldTyCon
162     , stablePtrPrimTyCon
163     , statePrimTyCon
164     , wordPrimTyCon
165     ]
166
167 g_tycons
168   = mkFunTyCon : g_con_tycons
169
170 g_con_tycons
171   = listTyCon : mkTupleTyCon 0 : [mkTupleTyCon i | i <- [2..32] ]
172
173 min_nonprim_tycon_list  -- used w/ HideMostBuiltinNames
174   = [ boolTyCon
175     , orderingTyCon
176     , charTyCon
177     , intTyCon
178     , floatTyCon
179     , doubleTyCon
180     , integerTyCon
181     , ratioTyCon
182     , liftTyCon
183     , return2GMPsTyCon  -- ADR asked for these last two (WDP 94/11)
184     , returnIntAndGMPTyCon
185     ]
186
187
188 data_tycons
189   = [ addrTyCon
190     , boolTyCon
191     , charTyCon
192     , orderingTyCon
193     , doubleTyCon
194     , floatTyCon
195     , intTyCon
196     , integerTyCon
197     , liftTyCon
198     , foreignObjTyCon
199     , ratioTyCon
200     , return2GMPsTyCon
201     , returnIntAndGMPTyCon
202     , stablePtrTyCon
203     , stateAndAddrPrimTyCon
204     , stateAndArrayPrimTyCon
205     , stateAndByteArrayPrimTyCon
206     , stateAndCharPrimTyCon
207     , stateAndDoublePrimTyCon
208     , stateAndFloatPrimTyCon
209     , stateAndIntPrimTyCon
210     , stateAndForeignObjPrimTyCon
211     , stateAndMutableArrayPrimTyCon
212     , stateAndMutableByteArrayPrimTyCon
213     , stateAndSynchVarPrimTyCon
214     , stateAndPtrPrimTyCon
215     , stateAndStablePtrPrimTyCon
216     , stateAndWordPrimTyCon
217     , stateTyCon
218     , wordTyCon
219     ]
220
221 synonym_tycons
222   = [ primIoTyCon
223     , rationalTyCon
224     , stTyCon
225     , stringTyCon
226     ]
227
228 pcTyConWiredInInfo :: TyCon -> (FAST_STRING, RnName)
229 pcTyConWiredInInfo tc = (nameOf (origName tc), WiredInTyCon tc)
230
231 pcDataConWiredInInfo :: TyCon -> [(FAST_STRING, RnName)]
232 pcDataConWiredInInfo tycon
233   = [ (nameOf (origName con), WiredInId con) | con <- tyConDataCons tycon ]
234 \end{code}
235
236 The WiredIn Ids ...
237 ToDo: Some of these should be moved to id_keys_infos!
238 \begin{code}
239 wired_in_ids
240   = [ eRROR_ID
241     , pAT_ERROR_ID      -- occurs in i/faces
242     , pAR_ERROR_ID      -- ditto
243     , tRACE_ID
244  
245     , runSTId
246     , seqId
247     , realWorldPrimId
248
249       -- foldr/build Ids have magic unfoldings
250     , buildId
251     , augmentId
252     , foldlId
253     , foldrId
254     , unpackCStringAppendId
255     , unpackCStringFoldrId
256     ]
257
258 parallel_ids
259   = if not opt_ForConcurrent then
260         []
261     else
262         [ parId
263         , forkId
264         , copyableId
265         , noFollowId
266         , parAtAbsId
267         , parAtForNowId
268         , parAtId
269         , parAtRelId
270         , parGlobalId
271         , parLocalId
272         ]
273
274 pcIdWiredInInfo :: Id -> (FAST_STRING, RnName)
275 pcIdWiredInInfo id = (nameOf (origName id), WiredInId id)
276 \end{code}
277
278 WiredIn primitive numeric operations ...
279 \begin{code}
280 primop_ids
281   =  map primOpNameInfo allThePrimOps ++ map fn funny_name_primops
282   where
283     fn (op,s) = case (primOpNameInfo op) of (_,n) -> (s,n)
284
285 funny_name_primops
286   = [ (IntAddOp,      SLIT("+#"))
287     , (IntSubOp,      SLIT("-#"))
288     , (IntMulOp,      SLIT("*#"))
289     , (IntGtOp,       SLIT(">#"))
290     , (IntGeOp,       SLIT(">=#"))
291     , (IntEqOp,       SLIT("==#"))
292     , (IntNeOp,       SLIT("/=#"))
293     , (IntLtOp,       SLIT("<#"))
294     , (IntLeOp,       SLIT("<=#"))
295     , (DoubleAddOp,   SLIT("+##"))
296     , (DoubleSubOp,   SLIT("-##"))
297     , (DoubleMulOp,   SLIT("*##"))
298     , (DoubleDivOp,   SLIT("/##"))
299     , (DoublePowerOp, SLIT("**##"))
300     , (DoubleGtOp,    SLIT(">##"))
301     , (DoubleGeOp,    SLIT(">=##"))
302     , (DoubleEqOp,    SLIT("==##"))
303     , (DoubleNeOp,    SLIT("/=##"))
304     , (DoubleLtOp,    SLIT("<##"))
305     , (DoubleLeOp,    SLIT("<=##"))
306     ]
307 \end{code}
308
309
310 Ids, Synonyms, Classes and ClassOps with builtin keys.
311 For the Ids we may also have some builtin IdInfo.
312 \begin{code}
313 id_keys_infos :: [(FAST_STRING, Unique, Maybe IdInfo)]
314 id_keys_infos
315   = [ (SLIT("main"),        mainIdKey,          Nothing)
316     , (SLIT("mainPrimIO"),  mainPrimIOIdKey,    Nothing)
317     ]
318
319 tysyn_keys
320   = [ (SLIT("IO"), (iOTyConKey, RnImplicitTyCon))
321     ]
322
323 -- this "class_keys" list *must* include:
324 --  classes that are grabbed by key (e.g., eqClassKey)
325 --  classes in "Class.standardClassKeys" (quite a few)
326
327 class_keys
328   = [ (s, (k, RnImplicitClass)) | (s,k) <-
329     [ (SLIT("Eq"),              eqClassKey)             -- mentioned, derivable
330     , (SLIT("Eval"),            evalClassKey)           -- mentioned
331     , (SLIT("Ord"),             ordClassKey)            -- derivable
332     , (SLIT("Num"),             numClassKey)            -- mentioned, numeric
333     , (SLIT("Real"),            realClassKey)           -- numeric
334     , (SLIT("Integral"),        integralClassKey)       -- numeric
335     , (SLIT("Fractional"),      fractionalClassKey)     -- numeric
336     , (SLIT("Floating"),        floatingClassKey)       -- numeric
337     , (SLIT("RealFrac"),        realFracClassKey)       -- numeric
338     , (SLIT("RealFloat"),       realFloatClassKey)      -- numeric
339 --  , (SLIT("Ix"),              ixClassKey)             -- derivable (but it isn't Prelude.Ix; hmmm)
340         -- see *hack* in Rename
341     , (SLIT("Bounded"),         boundedClassKey)        -- derivable
342     , (SLIT("Enum"),            enumClassKey)           -- derivable
343     , (SLIT("Show"),            showClassKey)           -- derivable
344     , (SLIT("Read"),            readClassKey)           -- derivable
345     , (SLIT("Monad"),           monadClassKey)
346     , (SLIT("MonadZero"),       monadZeroClassKey)
347     , (SLIT("MonadPlus"),       monadPlusClassKey)
348     , (SLIT("Functor"),         functorClassKey)
349     , (SLIT("CCallable"),       cCallableClassKey)      -- mentioned, ccallish
350     , (SLIT("CReturnable"),     cReturnableClassKey)    -- mentioned, ccallish
351     ]]
352
353 class_op_keys
354   = [ (s, (k, RnImplicit)) | (s,k) <-
355     [ (SLIT("fromInt"),         fromIntClassOpKey)
356     , (SLIT("fromInteger"),     fromIntegerClassOpKey)
357     , (SLIT("fromRational"),    fromRationalClassOpKey)
358     , (SLIT("enumFrom"),        enumFromClassOpKey)
359     , (SLIT("enumFromThen"),    enumFromThenClassOpKey)
360     , (SLIT("enumFromTo"),      enumFromToClassOpKey)
361     , (SLIT("enumFromThenTo"),  enumFromThenToClassOpKey)
362     , (SLIT("=="),              eqClassOpKey)
363     ]]
364 \end{code}
365
366 ToDo: make it do the ``like'' part properly (as in 0.26 and before).
367 \begin{code}
368 maybeCharLikeTyCon tc = if (uniqueOf tc == charDataConKey) then Just charDataCon else Nothing
369 maybeIntLikeTyCon  tc = if (uniqueOf tc == intDataConKey)  then Just intDataCon  else Nothing
370 \end{code}