466c140b963bc0fb56361c6f6b457f111733925c
[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 IMP_Ubiq()
19 IMPORT_DELOOPER(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, OrigName(..) )
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 OrigName RnName, -- WiredIn Ids
59                        FiniteMap OrigName RnName) -- WiredIn TyCons
60                         -- Two maps because "[]" is in both...
61
62 type BuiltinKeys    = FiniteMap OrigName (Unique, Name -> RnName)
63                                                      -- Names with known uniques
64
65 type BuiltinIdInfos = UniqFM IdInfo                  -- Info for known unique Ids
66
67 builtinNameInfo
68   = if opt_HideBuiltinNames then
69         (
70          (emptyFM, emptyFM),
71          emptyFM,
72          emptyUFM
73         )
74     else if opt_HideMostBuiltinNames then
75         (
76          (listToFM min_assoc_val_wired, listToFM min_assoc_tc_wired),
77          emptyFM,
78          emptyUFM
79         )
80     else
81         (
82          (listToFM assoc_val_wired, listToFM assoc_tc_wired),
83          listToFM assoc_keys,
84          listToUFM assoc_id_infos
85         )
86
87   where
88     min_assoc_val_wired -- min needed when compiling bits of Prelude
89       = concat [
90             -- data constrs
91             concat (map pcDataConWiredInInfo g_con_tycons),
92             concat (map pcDataConWiredInInfo min_nonprim_tycon_list),
93
94             -- values
95             map pcIdWiredInInfo wired_in_ids,
96             primop_ids
97          ]
98     min_assoc_tc_wired
99       = concat [
100             -- tycons
101             map pcTyConWiredInInfo prim_tycons,
102             map pcTyConWiredInInfo g_tycons,
103             map pcTyConWiredInInfo min_nonprim_tycon_list
104          ]
105
106     assoc_val_wired
107         = concat [
108             -- data constrs
109             concat (map pcDataConWiredInInfo g_con_tycons),
110             concat (map pcDataConWiredInInfo data_tycons),
111
112             -- values
113             map pcIdWiredInInfo wired_in_ids,
114             primop_ids
115           ]
116     assoc_tc_wired
117         = concat [
118             -- tycons
119             map pcTyConWiredInInfo prim_tycons,
120             map pcTyConWiredInInfo g_tycons,
121             map pcTyConWiredInInfo data_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_mod, uniq, info) = (str_mod, (uniq, RnImplicit))
135
136     assoc_id_infos = catMaybes (map assoc_info id_keys_infos)
137     assoc_info (str_mod, uniq, Just info) = Just (uniq, info)
138     assoc_info (str_mod, 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     , charTyCon
176     , intTyCon
177     , floatTyCon
178     , doubleTyCon
179     , integerTyCon
180     , liftTyCon
181     , return2GMPsTyCon  -- ADR asked for these last two (WDP 94/11)
182     , returnIntAndGMPTyCon
183     ]
184
185
186 data_tycons
187   = [ addrTyCon
188     , boolTyCon
189     , charTyCon
190     , doubleTyCon
191     , floatTyCon
192     , foreignObjTyCon
193     , intTyCon
194     , integerTyCon
195     , liftTyCon
196     , primIoTyCon
197     , return2GMPsTyCon
198     , returnIntAndGMPTyCon
199     , stTyCon
200     , stablePtrTyCon
201     , stateAndAddrPrimTyCon
202     , stateAndArrayPrimTyCon
203     , stateAndByteArrayPrimTyCon
204     , stateAndCharPrimTyCon
205     , stateAndDoublePrimTyCon
206     , stateAndFloatPrimTyCon
207     , stateAndForeignObjPrimTyCon
208     , stateAndIntPrimTyCon
209     , stateAndMutableArrayPrimTyCon
210     , stateAndMutableByteArrayPrimTyCon
211     , stateAndPtrPrimTyCon
212     , stateAndStablePtrPrimTyCon
213     , stateAndSynchVarPrimTyCon
214     , stateAndWordPrimTyCon
215     , stateTyCon
216     , voidTyCon
217     , wordTyCon
218     ]
219 \end{code}
220
221 The WiredIn Ids ...
222 ToDo: Some of these should be moved to id_keys_infos!
223 \begin{code}
224 wired_in_ids
225   = [ aBSENT_ERROR_ID
226     , augmentId
227     , buildId
228     , copyableId
229     , eRROR_ID
230     , foldlId
231     , foldrId
232     , forkId
233     , iRREFUT_PAT_ERROR_ID
234     , integerMinusOneId
235     , integerPlusOneId
236     , integerPlusTwoId
237     , integerZeroId
238     , nON_EXHAUSTIVE_GUARDS_ERROR_ID
239     , nO_DEFAULT_METHOD_ERROR_ID
240     , nO_EXPLICIT_METHOD_ERROR_ID
241     , noFollowId
242     , pAR_ERROR_ID
243     , pAT_ERROR_ID
244     , packStringForCId
245     , parAtAbsId
246     , parAtForNowId
247     , parAtId
248     , parAtRelId
249     , parGlobalId
250     , parId
251     , parLocalId
252     , rEC_CON_ERROR_ID
253     , rEC_UPD_ERROR_ID
254     , realWorldPrimId
255     , runSTId
256     , seqId
257     , tRACE_ID
258     , tRACE_ID
259     , unpackCString2Id
260     , unpackCStringAppendId
261     , unpackCStringFoldrId
262     , unpackCStringId
263     , voidId
264     ]
265
266 pcTyConWiredInInfo :: TyCon -> (OrigName, RnName)
267 pcTyConWiredInInfo tc = (origName "pcTyConWiredInInfo" tc, WiredInTyCon tc)
268
269 pcDataConWiredInInfo :: TyCon -> [(OrigName, RnName)]
270 pcDataConWiredInInfo tycon
271   = [ (origName "pcDataConWiredInInfo" con, WiredInId con) | con <- tyConDataCons tycon ]
272
273 pcIdWiredInInfo :: Id -> (OrigName, RnName)
274 pcIdWiredInInfo id = (origName "pcIdWiredInInfo" id, WiredInId id)
275 \end{code}
276
277 WiredIn primitive numeric operations ...
278 \begin{code}
279 primop_ids
280   = map prim_fn allThePrimOps ++ map funny_fn funny_name_primops
281   where
282     prim_fn  op     = case (primOpNameInfo op) of (s,n) -> ((OrigName gHC_BUILTINS s),n)
283     funny_fn (op,s) = case (primOpNameInfo op) of (_,n) -> ((OrigName gHC_BUILTINS 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 :: [(OrigName, Unique, Maybe IdInfo)]
314 id_keys_infos
315   = [ -- here so we can check the type of main/mainPrimIO
316       (OrigName SLIT("Main") SLIT("main"),        mainIdKey,      Nothing)
317     , (OrigName SLIT("Main") SLIT("mainPrimIO"), mainPrimIOIdKey, Nothing)
318
319       -- here because we use them in derived instances
320     , (OrigName pRELUDE SLIT("&&"),             andandIdKey,    Nothing)
321     , (OrigName pRELUDE SLIT("."),              composeIdKey,   Nothing)
322     , (OrigName pRELUDE SLIT("lex"),            lexIdKey,       Nothing)
323     , (OrigName pRELUDE SLIT("not"),            notIdKey,       Nothing)
324     , (OrigName pRELUDE SLIT("readParen"),      readParenIdKey, Nothing)
325     , (OrigName pRELUDE SLIT("showParen"),      showParenIdKey, Nothing)
326     , (OrigName pRELUDE SLIT("showString"),     showStringIdKey,Nothing)
327     , (OrigName gHC__   SLIT("readList__"),     ureadListIdKey, Nothing)
328     , (OrigName gHC__   SLIT("showList__"),     ushowListIdKey, Nothing)
329     , (OrigName gHC__   SLIT("showSpace"),      showSpaceIdKey, Nothing)
330     ]
331
332 tysyn_keys
333   = [ (OrigName gHC__   SLIT("IO"),       (iOTyConKey, RnImplicitTyCon))
334     , (OrigName pRELUDE SLIT("Ordering"), (orderingTyConKey, RnImplicitTyCon))
335     , (OrigName rATIO   SLIT("Rational"), (rationalTyConKey, RnImplicitTyCon))
336     , (OrigName rATIO   SLIT("Ratio"),    (ratioTyConKey, RnImplicitTyCon))
337     ]
338
339 -- this "class_keys" list *must* include:
340 --  classes that are grabbed by key (e.g., eqClassKey)
341 --  classes in "Class.standardClassKeys" (quite a few)
342
343 class_keys
344   = [ (str_mod, (k, RnImplicitClass)) | (str_mod,k) <-
345     [ (OrigName pRELUDE SLIT("Eq"),             eqClassKey)             -- mentioned, derivable
346     , (OrigName pRELUDE SLIT("Eval"),           evalClassKey)           -- mentioned
347     , (OrigName pRELUDE SLIT("Ord"),            ordClassKey)            -- derivable
348     , (OrigName pRELUDE SLIT("Num"),            numClassKey)            -- mentioned, numeric
349     , (OrigName pRELUDE SLIT("Real"),           realClassKey)           -- numeric
350     , (OrigName pRELUDE SLIT("Integral"),       integralClassKey)       -- numeric
351     , (OrigName pRELUDE SLIT("Fractional"),     fractionalClassKey)     -- numeric
352     , (OrigName pRELUDE SLIT("Floating"),       floatingClassKey)       -- numeric
353     , (OrigName pRELUDE SLIT("RealFrac"),       realFracClassKey)       -- numeric
354     , (OrigName pRELUDE SLIT("RealFloat"),      realFloatClassKey)      -- numeric
355     , (OrigName iX      SLIT("Ix"),             ixClassKey)             -- derivable (but it isn't Prelude.Ix; hmmm)
356     , (OrigName pRELUDE SLIT("Bounded"),        boundedClassKey)        -- derivable
357     , (OrigName pRELUDE SLIT("Enum"),           enumClassKey)           -- derivable
358     , (OrigName pRELUDE SLIT("Show"),           showClassKey)           -- derivable
359     , (OrigName pRELUDE SLIT("Read"),           readClassKey)           -- derivable
360     , (OrigName pRELUDE SLIT("Monad"),          monadClassKey)
361     , (OrigName pRELUDE SLIT("MonadZero"),      monadZeroClassKey)
362     , (OrigName pRELUDE SLIT("MonadPlus"),      monadPlusClassKey)
363     , (OrigName pRELUDE SLIT("Functor"),        functorClassKey)
364     , (OrigName gHC__   SLIT("CCallable"),      cCallableClassKey)      -- mentioned, ccallish
365     , (OrigName gHC__   SLIT("CReturnable"),    cReturnableClassKey)    -- mentioned, ccallish
366     ]]
367
368 class_op_keys
369   = [ (str_mod, (k, RnImplicit)) | (str_mod,k) <-
370     [ (OrigName pRELUDE SLIT("fromInt"),        fromIntClassOpKey)
371     , (OrigName pRELUDE SLIT("fromInteger"),    fromIntegerClassOpKey)
372     , (OrigName pRELUDE SLIT("fromRational"),   fromRationalClassOpKey)
373     , (OrigName pRELUDE SLIT("enumFrom"),       enumFromClassOpKey)
374     , (OrigName pRELUDE SLIT("enumFromThen"),   enumFromThenClassOpKey)
375     , (OrigName pRELUDE SLIT("enumFromTo"),     enumFromToClassOpKey)
376     , (OrigName pRELUDE SLIT("enumFromThenTo"),enumFromThenToClassOpKey)
377     , (OrigName pRELUDE SLIT("=="),             eqClassOpKey)
378     , (OrigName pRELUDE SLIT(">>="),            thenMClassOpKey)
379     , (OrigName pRELUDE SLIT("zero"),           zeroClassOpKey)
380     ]]
381 \end{code}
382
383 ToDo: make it do the ``like'' part properly (as in 0.26 and before).
384 \begin{code}
385 maybeCharLikeTyCon tc = if (uniqueOf tc == charDataConKey) then Just charDataCon else Nothing
386 maybeIntLikeTyCon  tc = if (uniqueOf tc == intDataConKey)  then Just intDataCon  else Nothing
387 \end{code}