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