[project @ 1996-05-16 09:42:08 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         pRELUDE, pRELUDE_BUILTIN, pRELUDE_CORE, pRELUDE_RATIO,
12         pRELUDE_LIST, pRELUDE_TEXT,
13         pRELUDE_PRIMIO, pRELUDE_IO, pRELUDE_PS,
14         gLASGOW_ST, gLASGOW_MISC,
15
16         -- finite maps for built-in things (for the renamer and typechecker):
17         builtinNameInfo, BuiltinNames(..),
18         BuiltinKeys(..), BuiltinIdInfos(..),
19
20         -- *odd* values that need to be reached out and grabbed:
21         eRROR_ID,
22         pAT_ERROR_ID,
23         rEC_CON_ERROR_ID,
24         rEC_UPD_ERROR_ID,
25         iRREFUT_PAT_ERROR_ID,
26         nON_EXHAUSTIVE_GUARDS_ERROR_ID,
27         aBSENT_ERROR_ID,
28         packStringForCId,
29         unpackCStringId, unpackCString2Id,
30         unpackCStringAppendId, unpackCStringFoldrId,
31         integerZeroId, integerPlusOneId,
32         integerPlusTwoId, integerMinusOneId,
33
34         -----------------------------------------------------
35         -- the rest of the export list is organised by *type*
36         -----------------------------------------------------
37
38         -- type: Bool
39         boolTyCon, boolTy, falseDataCon, trueDataCon,
40
41         -- types: Char#, Char, String (= [Char])
42         charPrimTy, charTy, stringTy,
43         charPrimTyCon, charTyCon, charDataCon,
44
45         -- type: Ordering (used in deriving)
46         orderingTy, ltDataCon, eqDataCon, gtDataCon,
47
48         -- types: Double#, Double
49         doublePrimTy, doubleTy,
50         doublePrimTyCon, doubleTyCon, doubleDataCon,
51
52         -- types: Float#, Float
53         floatPrimTy, floatTy,
54         floatPrimTyCon, floatTyCon, floatDataCon,
55
56         -- types: Glasgow *primitive* arrays, sequencing and I/O
57         mkPrimIoTy, -- to typecheck "mainPrimIO" & for _ccall_s
58         realWorldStatePrimTy, realWorldStateTy{-boxed-},
59         realWorldTy, realWorldTyCon, realWorldPrimId,
60         statePrimTyCon, stateDataCon, getStatePairingConInfo,
61
62         byteArrayPrimTy,
63
64         -- types: Void# (only used within the compiler)
65         voidPrimTy, voidPrimId,
66
67         -- types: Addr#, Int#, Word#, Int
68         intPrimTy, intTy, intPrimTyCon, intTyCon, intDataCon,
69         wordPrimTyCon, wordPrimTy, wordTy, wordTyCon, wordDataCon,
70         addrPrimTyCon, addrPrimTy, addrTy, addrTyCon, addrDataCon,
71         maybeIntLikeTyCon, maybeCharLikeTyCon,
72
73         -- types: Integer, Rational (= Ratio Integer)
74         integerTy, rationalTy,
75         integerTyCon, integerDataCon,
76         rationalTyCon, ratioDataCon,
77
78         -- type: Lift
79         liftTyCon, liftDataCon, mkLiftTy,
80
81         -- type: List
82         listTyCon, mkListTy, nilDataCon, consDataCon,
83
84         -- type: tuples
85         mkTupleTy, unitTy,
86
87         -- for compilation of List Comprehensions and foldr
88         foldlId, foldrId,
89         mkBuild, buildId, augmentId, appendId
90
91         -- and, finally, we must put in some (abstract) data types,
92         -- to make the interface self-sufficient
93     ) where
94
95 import Ubiq
96 import PrelLoop         ( primOpNameInfo )
97
98 -- friends:
99 import PrelMods         -- Prelude module names
100 import PrelVals         -- VALUES
101 import PrimOp           ( PrimOp(..), allThePrimOps )
102 import PrimRep          ( PrimRep(..) )
103 import TysPrim          -- TYPES
104 import TysWiredIn
105
106 -- others:
107 import CmdLineOpts      ( opt_HideBuiltinNames,
108                           opt_HideMostBuiltinNames,
109                           opt_ForConcurrent
110                         )
111 import FiniteMap        ( FiniteMap, emptyFM, listToFM )
112 import Id               ( mkTupleCon, GenId, Id(..) )
113 import Maybes           ( catMaybes )
114 import Name             ( origName, nameOf )
115 import RnHsSyn          ( RnName(..) )
116 import TyCon            ( tyConDataCons, mkFunTyCon, mkTupleTyCon, TyCon )
117 import Type
118 import UniqFM           ( UniqFM, emptyUFM, listToUFM )
119 import Unique           -- *Key stuff
120 import Util             ( nOfThem, panic )
121 \end{code}
122
123 %************************************************************************
124 %*                                                                      *
125 \subsection[builtinNameInfo]{Lookup built-in names}
126 %*                                                                      *
127 %************************************************************************
128
129 We have two ``builtin name funs,'' one to look up @TyCons@ and
130 @Classes@, the other to look up values.
131
132 \begin{code}
133 builtinNameInfo :: ( BuiltinNames, BuiltinKeys, BuiltinIdInfos )
134
135 type BuiltinNames   = (FiniteMap FAST_STRING RnName, -- WiredIn Ids
136                        FiniteMap FAST_STRING RnName) -- WiredIn TyCons
137                         -- Two maps because "[]" is in both...
138 type BuiltinKeys    = FiniteMap FAST_STRING (Unique, Name -> RnName)
139                                                     -- Names with known uniques
140 type BuiltinIdInfos = UniqFM IdInfo                  -- Info for known unique Ids
141
142 builtinNameInfo
143   = if opt_HideBuiltinNames then
144         (
145          (emptyFM, emptyFM),
146          emptyFM,
147          emptyUFM
148         )
149     else if opt_HideMostBuiltinNames then
150         (
151          (listToFM min_assoc_val_wired, listToFM min_assoc_tc_wired),
152          emptyFM,
153          emptyUFM
154         )
155     else
156         (
157          (listToFM assoc_val_wired, listToFM assoc_tc_wired),
158          listToFM assoc_keys,
159          listToUFM assoc_id_infos
160         )
161
162   where
163     min_assoc_val_wired -- min needed when compiling bits of Prelude
164       = concat [
165             -- data constrs
166             concat (map pcDataConWiredInInfo g_con_tycons),
167             concat (map pcDataConWiredInInfo min_nonprim_tycon_list),
168
169             -- values
170             map pcIdWiredInInfo wired_in_ids,
171             primop_ids
172          ]
173     min_assoc_tc_wired
174       = concat [
175             -- tycons
176             map pcTyConWiredInInfo prim_tycons,
177             map pcTyConWiredInInfo g_tycons,
178             map pcTyConWiredInInfo min_nonprim_tycon_list
179          ]
180
181     assoc_val_wired
182         = concat [
183             -- data constrs
184             concat (map pcDataConWiredInInfo g_con_tycons),
185             concat (map pcDataConWiredInInfo data_tycons),
186
187             -- values
188             map pcIdWiredInInfo wired_in_ids,
189             map pcIdWiredInInfo parallel_ids,
190             primop_ids
191           ]
192     assoc_tc_wired
193         = concat [
194             -- tycons
195             map pcTyConWiredInInfo prim_tycons,
196             map pcTyConWiredInInfo g_tycons,
197             map pcTyConWiredInInfo data_tycons,
198             map pcTyConWiredInInfo synonym_tycons
199           ]
200
201     assoc_keys
202         = concat
203           [
204             id_keys,
205             tysyn_keys,
206             class_keys,
207             class_op_keys
208           ]
209
210     id_keys = map id_key id_keys_infos
211     id_key (str, uniq, info) = (str, (uniq, RnImplicit))
212
213     assoc_id_infos = catMaybes (map assoc_info id_keys_infos)
214     assoc_info (str, uniq, Just info) = Just (uniq, info)
215     assoc_info (str, uniq, Nothing)   = Nothing
216 \end{code}
217
218
219 We let a lot of "non-standard" values be visible, so that we can make
220 sense of them in interface pragmas. It's cool, though they all have
221 "non-standard" names, so they won't get past the parser in user code.
222
223 The WiredIn TyCons and DataCons ...
224 \begin{code}
225
226 prim_tycons
227   = [ addrPrimTyCon
228     , arrayPrimTyCon
229     , byteArrayPrimTyCon
230     , charPrimTyCon
231     , doublePrimTyCon
232     , floatPrimTyCon
233     , intPrimTyCon
234     , mallocPtrPrimTyCon
235     , mutableArrayPrimTyCon
236     , mutableByteArrayPrimTyCon
237     , synchVarPrimTyCon
238     , realWorldTyCon
239     , stablePtrPrimTyCon
240     , statePrimTyCon
241     , wordPrimTyCon
242     ]
243
244 g_tycons
245   = mkFunTyCon : g_con_tycons
246
247 g_con_tycons
248   = listTyCon : mkTupleTyCon 0 : [mkTupleTyCon i | i <- [2..32] ]
249
250 min_nonprim_tycon_list  -- used w/ HideMostBuiltinNames
251   = [ boolTyCon
252     , orderingTyCon
253     , charTyCon
254     , intTyCon
255     , floatTyCon
256     , doubleTyCon
257     , integerTyCon
258     , ratioTyCon
259     , liftTyCon
260     , return2GMPsTyCon  -- ADR asked for these last two (WDP 94/11)
261     , returnIntAndGMPTyCon
262     ]
263
264
265 data_tycons
266   = [ addrTyCon
267     , boolTyCon
268     , charTyCon
269     , orderingTyCon
270     , doubleTyCon
271     , floatTyCon
272     , intTyCon
273     , integerTyCon
274     , liftTyCon
275     , mallocPtrTyCon
276     , ratioTyCon
277     , return2GMPsTyCon
278     , returnIntAndGMPTyCon
279     , stablePtrTyCon
280     , stateAndAddrPrimTyCon
281     , stateAndArrayPrimTyCon
282     , stateAndByteArrayPrimTyCon
283     , stateAndCharPrimTyCon
284     , stateAndDoublePrimTyCon
285     , stateAndFloatPrimTyCon
286     , stateAndIntPrimTyCon
287     , stateAndMallocPtrPrimTyCon
288     , stateAndMutableArrayPrimTyCon
289     , stateAndMutableByteArrayPrimTyCon
290     , stateAndSynchVarPrimTyCon
291     , stateAndPtrPrimTyCon
292     , stateAndStablePtrPrimTyCon
293     , stateAndWordPrimTyCon
294     , stateTyCon
295     , wordTyCon
296     ]
297
298 synonym_tycons
299   = [ primIoTyCon
300     , rationalTyCon
301     , stTyCon
302     , stringTyCon
303     ]
304
305 pcTyConWiredInInfo :: TyCon -> (FAST_STRING, RnName)
306 pcTyConWiredInInfo tc = (nameOf (origName tc), WiredInTyCon tc)
307
308 pcDataConWiredInInfo :: TyCon -> [(FAST_STRING, RnName)]
309 pcDataConWiredInInfo tycon
310   = [ (nameOf (origName con), WiredInId con) | con <- tyConDataCons tycon ]
311 \end{code}
312
313 The WiredIn Ids ...
314 ToDo: Some of these should be moved to id_keys_infos!
315 \begin{code}
316 wired_in_ids
317   = [ eRROR_ID
318     , pAT_ERROR_ID      -- occurs in i/faces
319     , pAR_ERROR_ID      -- ditto
320     , tRACE_ID
321  
322     , runSTId
323     , seqId
324     , realWorldPrimId
325
326       -- foldr/build Ids have magic unfoldings
327     , buildId
328     , augmentId
329     , foldlId
330     , foldrId
331     , unpackCStringAppendId
332     , unpackCStringFoldrId
333     ]
334
335 parallel_ids
336   = if not opt_ForConcurrent then
337         []
338     else
339         [ parId
340         , forkId
341 #ifdef GRAN
342         , parLocalId
343         , parGlobalId
344             -- Add later:
345             -- ,parAtId
346             -- ,parAtForNowId
347             -- ,copyableId
348             -- ,noFollowId
349 #endif {-GRAN-}
350         ]
351
352 pcIdWiredInInfo :: Id -> (FAST_STRING, RnName)
353 pcIdWiredInInfo id = (nameOf (origName id), WiredInId id)
354 \end{code}
355
356 WiredIn primitive numeric operations ...
357 \begin{code}
358 primop_ids
359   =  map primOpNameInfo allThePrimOps ++ map fn funny_name_primops
360   where
361     fn (op,s) = case (primOpNameInfo op) of (_,n) -> (s,n)
362
363 funny_name_primops
364   = [ (IntAddOp,      SLIT("+#"))
365     , (IntSubOp,      SLIT("-#"))
366     , (IntMulOp,      SLIT("*#"))
367     , (IntGtOp,       SLIT(">#"))
368     , (IntGeOp,       SLIT(">=#"))
369     , (IntEqOp,       SLIT("==#"))
370     , (IntNeOp,       SLIT("/=#"))
371     , (IntLtOp,       SLIT("<#"))
372     , (IntLeOp,       SLIT("<=#"))
373     , (DoubleAddOp,   SLIT("+##"))
374     , (DoubleSubOp,   SLIT("-##"))
375     , (DoubleMulOp,   SLIT("*##"))
376     , (DoubleDivOp,   SLIT("/##"))
377     , (DoublePowerOp, SLIT("**##"))
378     , (DoubleGtOp,    SLIT(">##"))
379     , (DoubleGeOp,    SLIT(">=##"))
380     , (DoubleEqOp,    SLIT("==##"))
381     , (DoubleNeOp,    SLIT("/=##"))
382     , (DoubleLtOp,    SLIT("<##"))
383     , (DoubleLeOp,    SLIT("<=##"))
384     ]
385 \end{code}
386
387
388 Ids, Synonyms, Classes and ClassOps with builtin keys.
389 For the Ids we may also have some builtin IdInfo.
390 \begin{code}
391 id_keys_infos :: [(FAST_STRING, Unique, Maybe IdInfo)]
392 id_keys_infos
393   = [ (SLIT("main"),        mainIdKey,          Nothing)
394     , (SLIT("mainPrimIO"),  mainPrimIOIdKey,    Nothing)
395     ]
396
397 tysyn_keys
398   = [ (SLIT("IO"), (iOTyConKey, RnImplicitTyCon))
399     ]
400
401 -- this "class_keys" list *must* include:
402 --  classes that are grabbed by key (e.g., eqClassKey)
403 --  classes in "Class.standardClassKeys" (quite a few)
404
405 class_keys
406   = [ (s, (k, RnImplicitClass)) | (s,k) <-
407     [ (SLIT("Eq"),              eqClassKey)             -- mentioned, derivable
408     , (SLIT("Ord"),             ordClassKey)            -- derivable
409     , (SLIT("Num"),             numClassKey)            -- mentioned, numeric
410     , (SLIT("Real"),            realClassKey)           -- numeric
411     , (SLIT("Integral"),        integralClassKey)       -- numeric
412     , (SLIT("Fractional"),      fractionalClassKey)     -- numeric
413     , (SLIT("Floating"),        floatingClassKey)       -- numeric
414     , (SLIT("RealFrac"),        realFracClassKey)       -- numeric
415     , (SLIT("RealFloat"),       realFloatClassKey)      -- numeric
416 --  , (SLIT("Ix"),              ixClassKey)             -- derivable (but it isn't Prelude.Ix; hmmm)
417     , (SLIT("Bounded"),         boundedClassKey)        -- derivable
418     , (SLIT("Enum"),            enumClassKey)           -- derivable
419     , (SLIT("Show"),            showClassKey)           -- derivable
420     , (SLIT("Read"),            readClassKey)           -- derivable
421     , (SLIT("Monad"),           monadClassKey)
422     , (SLIT("MonadZero"),       monadZeroClassKey)
423     , (SLIT("MonadPlus"),       monadPlusClassKey)
424     , (SLIT("Functor"),         functorClassKey)
425     , (SLIT("CCallable"),       cCallableClassKey)      -- mentioned, ccallish
426     , (SLIT("CReturnable"),     cReturnableClassKey)    -- mentioned, ccallish
427     ]]
428
429 class_op_keys
430   = [ (s, (k, RnImplicit)) | (s,k) <-
431     [ (SLIT("fromInt"),         fromIntClassOpKey)
432     , (SLIT("fromInteger"),     fromIntegerClassOpKey)
433     , (SLIT("fromRational"),    fromRationalClassOpKey)
434     , (SLIT("enumFrom"),        enumFromClassOpKey)
435     , (SLIT("enumFromThen"),    enumFromThenClassOpKey)
436     , (SLIT("enumFromTo"),      enumFromToClassOpKey)
437     , (SLIT("enumFromThenTo"),  enumFromThenToClassOpKey)
438     , (SLIT("=="),              eqClassOpKey)
439     ]]
440 \end{code}
441
442 ToDo: make it do the ``like'' part properly (as in 0.26 and before).
443 \begin{code}
444 maybeCharLikeTyCon tc = if (uniqueOf tc == charDataConKey) then Just charDataCon else Nothing
445 maybeIntLikeTyCon  tc = if (uniqueOf tc == intDataConKey)  then Just intDataCon  else Nothing
446 \end{code}