[project @ 1996-07-19 18:36:04 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, builtinNameMaps,
13         builtinValNamesMap, builtinTcNamesMap,
14         builtinKeysMap,
15         SYN_IE(BuiltinNames),
16         SYN_IE(BuiltinKeys), SYN_IE(BuiltinIdInfos),
17
18         maybeCharLikeTyCon, maybeIntLikeTyCon
19     ) where
20
21 IMP_Ubiq()
22 IMPORT_DELOOPER(PrelLoop) ( primOpNameInfo )
23 IMPORT_DELOOPER(IdLoop)   ( SpecEnv )
24
25 -- friends:
26 import PrelMods         -- Prelude module names
27 import PrelVals         -- VALUES
28 import PrimOp           ( PrimOp(..), allThePrimOps )
29 import PrimRep          ( PrimRep(..) )
30 import TysPrim          -- TYPES
31 import TysWiredIn
32
33 -- others:
34 import FiniteMap        ( FiniteMap, emptyFM, listToFM )
35 import Id               ( mkTupleCon, GenId, SYN_IE(Id) )
36 import Maybes           ( catMaybes )
37 import Name             ( origName, OrigName(..), Name )
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 builtinNameMaps    = case builtinNameInfo of { (x,_,_) -> x }
68 builtinKeysMap     = case builtinNameInfo of { (_,x,_) -> x }
69 builtinValNamesMap = fst builtinNameMaps
70 builtinTcNamesMap  = snd builtinNameMaps
71
72 builtinNameInfo
73   = ( (listToFM assoc_val_wired, listToFM assoc_tc_wired)
74     , listToFM assoc_keys
75     , listToUFM assoc_id_infos
76     )
77   where
78     assoc_val_wired
79         = concat [
80             -- data constrs
81             concat (map pcDataConWiredInInfo g_con_tycons),
82             concat (map pcDataConWiredInInfo data_tycons),
83
84             -- values
85             map pcIdWiredInInfo wired_in_ids,
86             primop_ids
87           ]
88     assoc_tc_wired
89         = concat [
90             -- tycons
91             map pcTyConWiredInInfo prim_tycons,
92             map pcTyConWiredInInfo g_tycons,
93             map pcTyConWiredInInfo data_tycons
94           ]
95
96     assoc_keys
97         = concat
98           [
99             id_keys,
100             tysyn_keys,
101             class_keys,
102             class_op_keys
103           ]
104
105     id_keys = map id_key id_keys_infos
106     id_key (str_mod, uniq, info) = (str_mod, (uniq, RnImplicit))
107
108     assoc_id_infos = catMaybes (map assoc_info id_keys_infos)
109     assoc_info (str_mod, uniq, Just info) = Just (uniq, info)
110     assoc_info (str_mod, uniq, Nothing)   = Nothing
111 \end{code}
112
113
114 We let a lot of "non-standard" values be visible, so that we can make
115 sense of them in interface pragmas. It's cool, though they all have
116 "non-standard" names, so they won't get past the parser in user code.
117
118 The WiredIn TyCons and DataCons ...
119 \begin{code}
120
121 prim_tycons
122   = [ addrPrimTyCon
123     , arrayPrimTyCon
124     , byteArrayPrimTyCon
125     , charPrimTyCon
126     , doublePrimTyCon
127     , floatPrimTyCon
128     , intPrimTyCon
129     , foreignObjPrimTyCon
130     , mutableArrayPrimTyCon
131     , mutableByteArrayPrimTyCon
132     , synchVarPrimTyCon
133     , realWorldTyCon
134     , stablePtrPrimTyCon
135     , statePrimTyCon
136     , wordPrimTyCon
137     ]
138
139 g_tycons
140   = mkFunTyCon : g_con_tycons
141
142 g_con_tycons
143   = listTyCon : mkTupleTyCon 0 : [mkTupleTyCon i | i <- [2..37] ]
144
145 min_nonprim_tycon_list  -- used w/ HideMostBuiltinNames
146   = [ boolTyCon
147     , charTyCon
148     , intTyCon
149     , floatTyCon
150     , doubleTyCon
151     , integerTyCon
152     , liftTyCon
153     , return2GMPsTyCon  -- ADR asked for these last two (WDP 94/11)
154     , returnIntAndGMPTyCon
155     ]
156
157
158 data_tycons
159   = [ addrTyCon
160     , boolTyCon
161     , charTyCon
162     , doubleTyCon
163     , floatTyCon
164     , foreignObjTyCon
165     , intTyCon
166     , integerTyCon
167     , liftTyCon
168     , primIoTyCon
169     , return2GMPsTyCon
170     , returnIntAndGMPTyCon
171     , stTyCon
172     , stablePtrTyCon
173     , stateAndAddrPrimTyCon
174     , stateAndArrayPrimTyCon
175     , stateAndByteArrayPrimTyCon
176     , stateAndCharPrimTyCon
177     , stateAndDoublePrimTyCon
178     , stateAndFloatPrimTyCon
179     , stateAndForeignObjPrimTyCon
180     , stateAndIntPrimTyCon
181     , stateAndMutableArrayPrimTyCon
182     , stateAndMutableByteArrayPrimTyCon
183     , stateAndPtrPrimTyCon
184     , stateAndStablePtrPrimTyCon
185     , stateAndSynchVarPrimTyCon
186     , stateAndWordPrimTyCon
187     , stateTyCon
188     , voidTyCon
189     , wordTyCon
190     ]
191 \end{code}
192
193 The WiredIn Ids ...
194 ToDo: Some of these should be moved to id_keys_infos!
195 \begin{code}
196 wired_in_ids
197   = [ aBSENT_ERROR_ID
198     , augmentId
199     , buildId
200 --  , copyableId
201     , eRROR_ID
202     , foldlId
203     , foldrId
204 --  , forkId
205     , iRREFUT_PAT_ERROR_ID
206     , integerMinusOneId
207     , integerPlusOneId
208     , integerPlusTwoId
209     , integerZeroId
210     , nON_EXHAUSTIVE_GUARDS_ERROR_ID
211     , nO_DEFAULT_METHOD_ERROR_ID
212     , nO_EXPLICIT_METHOD_ERROR_ID
213 --  , noFollowId
214     , pAR_ERROR_ID
215     , pAT_ERROR_ID
216     , packStringForCId
217 --    , parAtAbsId
218 --    , parAtForNowId
219 --    , parAtId
220 --    , parAtRelId
221 --    , parGlobalId
222 --    , parId
223 --    , parLocalId
224     , rEC_CON_ERROR_ID
225     , rEC_UPD_ERROR_ID
226     , realWorldPrimId
227     , runSTId
228 --    , seqId
229     , tRACE_ID
230     , unpackCString2Id
231     , unpackCStringAppendId
232     , unpackCStringFoldrId
233     , unpackCStringId
234     , voidId
235     ]
236
237 pcTyConWiredInInfo :: TyCon -> (OrigName, RnName)
238 pcTyConWiredInInfo tc = (origName "pcTyConWiredInInfo" tc, WiredInTyCon tc)
239
240 pcDataConWiredInInfo :: TyCon -> [(OrigName, RnName)]
241 pcDataConWiredInInfo tycon
242   = [ (origName "pcDataConWiredInInfo" con, WiredInId con) | con <- tyConDataCons tycon ]
243
244 pcIdWiredInInfo :: Id -> (OrigName, RnName)
245 pcIdWiredInInfo id = (origName "pcIdWiredInInfo" id, WiredInId id)
246 \end{code}
247
248 WiredIn primitive numeric operations ...
249 \begin{code}
250 primop_ids
251   = map prim_fn allThePrimOps ++ map funny_fn funny_name_primops
252   where
253     prim_fn  op     = case (primOpNameInfo op) of (s,n) -> ((OrigName gHC_BUILTINS s),n)
254     funny_fn (op,s) = case (primOpNameInfo op) of (_,n) -> ((OrigName gHC_BUILTINS s),n)
255
256 funny_name_primops
257   = [ (IntAddOp,      SLIT("+#"))
258     , (IntSubOp,      SLIT("-#"))
259     , (IntMulOp,      SLIT("*#"))
260     , (IntGtOp,       SLIT(">#"))
261     , (IntGeOp,       SLIT(">=#"))
262     , (IntEqOp,       SLIT("==#"))
263     , (IntNeOp,       SLIT("/=#"))
264     , (IntLtOp,       SLIT("<#"))
265     , (IntLeOp,       SLIT("<=#"))
266     , (DoubleAddOp,   SLIT("+##"))
267     , (DoubleSubOp,   SLIT("-##"))
268     , (DoubleMulOp,   SLIT("*##"))
269     , (DoubleDivOp,   SLIT("/##"))
270     , (DoublePowerOp, SLIT("**##"))
271     , (DoubleGtOp,    SLIT(">##"))
272     , (DoubleGeOp,    SLIT(">=##"))
273     , (DoubleEqOp,    SLIT("==##"))
274     , (DoubleNeOp,    SLIT("/=##"))
275     , (DoubleLtOp,    SLIT("<##"))
276     , (DoubleLeOp,    SLIT("<=##"))
277     ]
278 \end{code}
279
280
281 Ids, Synonyms, Classes and ClassOps with builtin keys.
282 For the Ids we may also have some builtin IdInfo.
283 \begin{code}
284 id_keys_infos :: [(OrigName, Unique, Maybe IdInfo)]
285 id_keys_infos
286   = [ -- here because we use them in derived instances
287       (OrigName pRELUDE SLIT("&&"),             andandIdKey,    Nothing)
288     , (OrigName pRELUDE SLIT("."),              composeIdKey,   Nothing)
289     , (OrigName gHC__   SLIT("lex"),            lexIdKey,       Nothing)
290     , (OrigName pRELUDE SLIT("not"),            notIdKey,       Nothing)
291     , (OrigName pRELUDE SLIT("readParen"),      readParenIdKey, Nothing)
292     , (OrigName pRELUDE SLIT("showParen"),      showParenIdKey, Nothing)
293     , (OrigName pRELUDE SLIT("showString"),     showStringIdKey,Nothing)
294     , (OrigName gHC__   SLIT("readList__"),     ureadListIdKey, Nothing)
295     , (OrigName gHC__   SLIT("showList__"),     ushowListIdKey, Nothing)
296     , (OrigName gHC__   SLIT("showSpace"),      showSpaceIdKey, Nothing)
297     ]
298
299 tysyn_keys
300   = [ (OrigName gHC__   SLIT("IO"),       (iOTyConKey, RnImplicitTyCon))
301     , (OrigName pRELUDE SLIT("Ordering"), (orderingTyConKey, RnImplicitTyCon))
302     , (OrigName rATIO   SLIT("Rational"), (rationalTyConKey, RnImplicitTyCon))
303     , (OrigName rATIO   SLIT("Ratio"),    (ratioTyConKey, RnImplicitTyCon))
304     ]
305
306 -- this "class_keys" list *must* include:
307 --  classes that are grabbed by key (e.g., eqClassKey)
308 --  classes in "Class.standardClassKeys" (quite a few)
309
310 class_keys
311   = [ (str_mod, (k, RnImplicitClass)) | (str_mod,k) <-
312     [ (OrigName pRELUDE SLIT("Eq"),             eqClassKey)             -- mentioned, derivable
313     , (OrigName pRELUDE SLIT("Eval"),           evalClassKey)           -- mentioned
314     , (OrigName pRELUDE SLIT("Ord"),            ordClassKey)            -- derivable
315     , (OrigName pRELUDE SLIT("Num"),            numClassKey)            -- mentioned, numeric
316     , (OrigName pRELUDE SLIT("Real"),           realClassKey)           -- numeric
317     , (OrigName pRELUDE SLIT("Integral"),       integralClassKey)       -- numeric
318     , (OrigName pRELUDE SLIT("Fractional"),     fractionalClassKey)     -- numeric
319     , (OrigName pRELUDE SLIT("Floating"),       floatingClassKey)       -- numeric
320     , (OrigName pRELUDE SLIT("RealFrac"),       realFracClassKey)       -- numeric
321     , (OrigName pRELUDE SLIT("RealFloat"),      realFloatClassKey)      -- numeric
322     , (OrigName iX      SLIT("Ix"),             ixClassKey)             -- derivable (but it isn't Prelude.Ix; hmmm)
323     , (OrigName pRELUDE SLIT("Bounded"),        boundedClassKey)        -- derivable
324     , (OrigName pRELUDE SLIT("Enum"),           enumClassKey)           -- derivable
325     , (OrigName pRELUDE SLIT("Show"),           showClassKey)           -- derivable
326     , (OrigName pRELUDE SLIT("Read"),           readClassKey)           -- derivable
327     , (OrigName pRELUDE SLIT("Monad"),          monadClassKey)
328     , (OrigName pRELUDE SLIT("MonadZero"),      monadZeroClassKey)
329     , (OrigName pRELUDE SLIT("MonadPlus"),      monadPlusClassKey)
330     , (OrigName pRELUDE SLIT("Functor"),        functorClassKey)
331     , (OrigName gHC__   SLIT("CCallable"),      cCallableClassKey)      -- mentioned, ccallish
332     , (OrigName gHC__   SLIT("CReturnable"),    cReturnableClassKey)    -- mentioned, ccallish
333     ]]
334
335 class_op_keys
336   = [ (str_mod, (k, RnImplicit)) | (str_mod,k) <-
337     [ (OrigName pRELUDE SLIT("fromInt"),        fromIntClassOpKey)
338     , (OrigName pRELUDE SLIT("fromInteger"),    fromIntegerClassOpKey)
339     , (OrigName pRELUDE SLIT("fromRational"),   fromRationalClassOpKey)
340     , (OrigName pRELUDE SLIT("enumFrom"),       enumFromClassOpKey)
341     , (OrigName pRELUDE SLIT("enumFromThen"),   enumFromThenClassOpKey)
342     , (OrigName pRELUDE SLIT("enumFromTo"),     enumFromToClassOpKey)
343     , (OrigName pRELUDE SLIT("enumFromThenTo"),enumFromThenToClassOpKey)
344     , (OrigName pRELUDE SLIT("=="),             eqClassOpKey)
345     , (OrigName pRELUDE SLIT(">>="),            thenMClassOpKey)
346     , (OrigName pRELUDE SLIT("zero"),           zeroClassOpKey)
347     ]]
348 \end{code}
349
350 ToDo: make it do the ``like'' part properly (as in 0.26 and before).
351 \begin{code}
352 maybeCharLikeTyCon tc = if (uniqueOf tc == charDataConKey) then Just charDataCon else Nothing
353 maybeIntLikeTyCon  tc = if (uniqueOf tc == intDataConKey)  then Just intDataCon  else Nothing
354 \end{code}