553da13e635fe808378d5eefd69366e8224757ea
[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
72         -- types: Integer, Rational (= Ratio Integer)
73         integerTy, rationalTy,
74         integerTyCon, integerDataCon,
75         rationalTyCon, ratioDataCon,
76
77         -- type: Lift
78         liftTyCon, liftDataCon, mkLiftTy,
79
80         -- type: List
81         listTyCon, mkListTy, nilDataCon, consDataCon,
82
83         -- type: tuples
84         mkTupleTy, unitTy,
85
86         -- for compilation of List Comprehensions and foldr
87         foldlId, foldrId,
88         mkBuild, buildId, augmentId, appendId
89
90         -- and, finally, we must put in some (abstract) data types,
91         -- to make the interface self-sufficient
92     ) where
93
94 import Ubiq
95 import PrelLoop         ( primOpNameInfo )
96
97 -- friends:
98 import PrelMods         -- Prelude module names
99 import PrelVals         -- VALUES
100 import PrimOp           ( PrimOp(..), allThePrimOps )
101 import PrimRep          ( PrimRep(..) )
102 import TysPrim          -- TYPES
103 import TysWiredIn
104
105 -- others:
106 import CmdLineOpts      ( opt_HideBuiltinNames,
107                           opt_HideMostBuiltinNames,
108                           opt_ForConcurrent
109                         )
110 import FiniteMap        ( FiniteMap, emptyFM, listToFM )
111 import Id               ( mkTupleCon, GenId, Id(..) )
112 import Maybes           ( catMaybes )
113 import Name             ( getOrigName )
114 import RnHsSyn          ( RnName(..) )
115 import TyCon            ( tyConDataCons, mkFunTyCon, mkTupleTyCon, TyCon )
116 import Type
117 import UniqFM           ( UniqFM, emptyUFM, listToUFM )
118 import Unique           -- *Key stuff
119 import Util             ( nOfThem, panic )
120 \end{code}
121
122 %************************************************************************
123 %*                                                                      *
124 \subsection[builtinNameInfo]{Lookup built-in names}
125 %*                                                                      *
126 %************************************************************************
127
128 We have two ``builtin name funs,'' one to look up @TyCons@ and
129 @Classes@, the other to look up values.
130
131 \begin{code}
132 builtinNameInfo :: ( BuiltinNames, BuiltinKeys, BuiltinIdInfos )
133
134 type BuiltinNames   = FiniteMap FAST_STRING RnName   -- WiredIn Ids/TyCons
135 type BuiltinKeys    = FiniteMap FAST_STRING Unique   -- Names with known uniques
136 type BuiltinIdInfos = UniqFM IdInfo                  -- Info for known unique Ids
137
138 builtinNameInfo
139   = if opt_HideBuiltinNames then
140         (
141          emptyFM,
142          emptyFM,
143          emptyUFM
144         )
145     else if opt_HideMostBuiltinNames then
146         (
147          listToFM min_assoc_wired,
148          emptyFM,
149          emptyUFM
150         )
151     else
152         (
153          listToFM assoc_wired,
154          listToFM assoc_keys,
155          listToUFM assoc_id_infos
156         )
157
158   where
159     min_assoc_wired     -- min needed when compiling bits of Prelude
160         = concat
161           [
162             -- tycons
163             map pcTyConWiredInInfo prim_tycons,
164             map pcTyConWiredInInfo g_tycons,
165             map pcTyConWiredInInfo min_nonprim_tycon_list,
166
167             -- data constrs
168             concat (map pcDataConWiredInInfo g_con_tycons),
169             concat (map pcDataConWiredInInfo min_nonprim_tycon_list),
170
171             -- values
172             map pcIdWiredInInfo wired_in_ids,
173             primop_ids
174           ]
175
176     assoc_wired
177         = concat
178           [
179             -- tycons
180             map pcTyConWiredInInfo prim_tycons,
181             map pcTyConWiredInInfo g_tycons,
182             map pcTyConWiredInInfo data_tycons,
183             map pcTyConWiredInInfo synonym_tycons,
184
185             -- data consts
186             concat (map pcDataConWiredInInfo g_con_tycons),
187             concat (map pcDataConWiredInInfo data_tycons),
188
189             -- values
190             map pcIdWiredInInfo wired_in_ids,
191             map pcIdWiredInInfo parallel_ids,
192             primop_ids
193           ]
194
195     assoc_keys
196         = concat
197           [
198             id_keys,
199             tysyn_keys,
200             class_keys,
201             class_op_keys
202           ]
203
204     id_keys = map id_key id_keys_infos
205     id_key (str, uniq, info) = (str, uniq)
206
207     assoc_id_infos = catMaybes (map assoc_info id_keys_infos)
208     assoc_info (str, uniq, Just info) = Just (uniq, info)
209     assoc_info (str, uniq, Nothing)   = Nothing
210 \end{code}
211
212
213 We let a lot of "non-standard" values be visible, so that we can make
214 sense of them in interface pragmas. It's cool, though they all have
215 "non-standard" names, so they won't get past the parser in user code.
216
217 The WiredIn TyCons and DataCons ...
218 \begin{code}
219
220 prim_tycons
221   = [addrPrimTyCon,
222      arrayPrimTyCon,
223      byteArrayPrimTyCon,
224      charPrimTyCon,
225      doublePrimTyCon,
226      floatPrimTyCon,
227      intPrimTyCon,
228      mallocPtrPrimTyCon,
229      mutableArrayPrimTyCon,
230      mutableByteArrayPrimTyCon,
231      synchVarPrimTyCon,
232      realWorldTyCon,
233      stablePtrPrimTyCon,
234      statePrimTyCon,
235      wordPrimTyCon
236     ]
237
238 g_tycons
239   = mkFunTyCon : g_con_tycons
240
241 g_con_tycons
242   = listTyCon : mkTupleTyCon 0 : [mkTupleTyCon i | i <- [2..32] ]
243
244 min_nonprim_tycon_list  -- used w/ HideMostBuiltinNames
245   = [ boolTyCon,
246       orderingTyCon,
247       charTyCon,
248       intTyCon,
249       floatTyCon,
250       doubleTyCon,
251       integerTyCon,
252       ratioTyCon,
253       liftTyCon,
254       return2GMPsTyCon, -- ADR asked for these last two (WDP 94/11)
255       returnIntAndGMPTyCon
256     ]
257
258
259 data_tycons
260   = [
261      addrTyCon,
262      boolTyCon,
263      charTyCon,
264      orderingTyCon,
265      doubleTyCon,
266      floatTyCon,
267      intTyCon,
268      integerTyCon,
269      liftTyCon,
270      mallocPtrTyCon,
271      ratioTyCon,
272      return2GMPsTyCon,
273      returnIntAndGMPTyCon,
274      stablePtrTyCon,
275      stateAndAddrPrimTyCon,
276      stateAndArrayPrimTyCon,
277      stateAndByteArrayPrimTyCon,
278      stateAndCharPrimTyCon,
279      stateAndDoublePrimTyCon,
280      stateAndFloatPrimTyCon,
281      stateAndIntPrimTyCon,
282      stateAndMallocPtrPrimTyCon,
283      stateAndMutableArrayPrimTyCon,
284      stateAndMutableByteArrayPrimTyCon,
285      stateAndSynchVarPrimTyCon,
286      stateAndPtrPrimTyCon,
287      stateAndStablePtrPrimTyCon,
288      stateAndWordPrimTyCon,
289      stateTyCon,
290      wordTyCon
291     ]
292
293 synonym_tycons
294   = [
295      primIoTyCon,
296      rationalTyCon,
297      stTyCon,
298      stringTyCon
299     ]
300
301 pcTyConWiredInInfo :: TyCon -> (FAST_STRING, RnName)
302 pcTyConWiredInInfo tc = (snd (getOrigName tc), WiredInTyCon tc)
303
304 pcDataConWiredInInfo :: TyCon -> [(FAST_STRING, RnName)]
305 pcDataConWiredInInfo tycon
306   = [ (snd (getOrigName con), WiredInId con) | con <- tyConDataCons tycon ]
307 \end{code}
308
309 The WiredIn Ids ...
310 ToDo: Some of these should be moved to id_keys_infos!
311 \begin{code}
312 wired_in_ids
313   = [eRROR_ID,
314      pAT_ERROR_ID,      -- occurs in i/faces
315      pAR_ERROR_ID,      -- ditto
316      tRACE_ID,
317
318      runSTId,
319      seqId,
320      realWorldPrimId,
321      
322      -- foldr/build Ids have magic unfoldings
323      buildId,
324      augmentId,
325      foldlId,
326      foldrId,
327      unpackCStringAppendId,
328      unpackCStringFoldrId
329     ]
330
331 parallel_ids
332   = if not opt_ForConcurrent then
333         []
334     else
335         [parId,
336          forkId
337 #ifdef GRAN
338          ,parLocalId
339          ,parGlobalId
340             -- Add later:
341             -- ,parAtId
342             -- ,parAtForNowId
343             -- ,copyableId
344             -- ,noFollowId
345 #endif {-GRAN-}
346         ]
347
348 pcIdWiredInInfo :: Id -> (FAST_STRING, RnName)
349 pcIdWiredInInfo id = (snd (getOrigName id), WiredInId id)
350 \end{code}
351
352 WiredIn primitive numeric operations ...
353 \begin{code}
354 primop_ids
355   =  map primOpNameInfo allThePrimOps ++ map fn funny_name_primops
356   where
357     fn (op,s) = case (primOpNameInfo op) of (_,n) -> (s,n)
358
359 funny_name_primops
360   = [
361      (IntAddOp,      SLIT("+#")),
362      (IntSubOp,      SLIT("-#")),
363      (IntMulOp,      SLIT("*#")),
364      (IntGtOp,       SLIT(">#")),
365      (IntGeOp,       SLIT(">=#")),
366      (IntEqOp,       SLIT("==#")),
367      (IntNeOp,       SLIT("/=#")),
368      (IntLtOp,       SLIT("<#")),
369      (IntLeOp,       SLIT("<=#")),
370      (DoubleAddOp,   SLIT("+##")),
371      (DoubleSubOp,   SLIT("-##")),
372      (DoubleMulOp,   SLIT("*##")),
373      (DoubleDivOp,   SLIT("/##")),
374      (DoublePowerOp, SLIT("**##")),
375      (DoubleGtOp,    SLIT(">##")),
376      (DoubleGeOp,    SLIT(">=##")),
377      (DoubleEqOp,    SLIT("==##")),
378      (DoubleNeOp,    SLIT("/=##")),
379      (DoubleLtOp,    SLIT("<##")),
380      (DoubleLeOp,    SLIT("<=##"))
381     ]
382 \end{code}
383
384
385 Ids, Synonyms, Classes and ClassOps with builtin keys.
386 For the Ids we may also have some builtin IdInfo.
387 \begin{code}
388 id_keys_infos :: [(FAST_STRING, Unique, Maybe IdInfo)]
389 id_keys_infos
390   = [
391     ]
392
393 tysyn_keys
394   = [
395      (SLIT("IO"), iOTyConKey)   -- SLIT("PreludeMonadicIO")
396     ]
397
398 class_keys
399   = [
400      (SLIT("Eq"),               eqClassKey),
401      (SLIT("Ord"),              ordClassKey),
402      (SLIT("Num"),              numClassKey),
403      (SLIT("Real"),             realClassKey),
404      (SLIT("Integral"),         integralClassKey),
405      (SLIT("Fractional"),       fractionalClassKey),
406      (SLIT("Floating"),         floatingClassKey),
407      (SLIT("RealFrac"),         realFracClassKey),
408      (SLIT("RealFloat"),        realFloatClassKey),
409      (SLIT("Ix"),               ixClassKey),
410      (SLIT("Enum"),             enumClassKey),
411      (SLIT("Show"),             showClassKey),
412      (SLIT("Read"),             readClassKey),
413      (SLIT("Monad"),            monadClassKey),
414      (SLIT("MonadZero"),        monadZeroClassKey),
415      (SLIT("Binary"),           binaryClassKey),
416      (SLIT("_CCallable"),       cCallableClassKey),
417      (SLIT("_CReturnable"),     cReturnableClassKey)
418     ]
419
420 class_op_keys
421   = [
422      (SLIT("fromInt"),          fromIntClassOpKey),
423      (SLIT("fromInteger"),      fromIntegerClassOpKey),
424      (SLIT("fromRational"),     fromRationalClassOpKey),
425      (SLIT("enumFrom"),         enumFromClassOpKey),
426      (SLIT("enumFromThen"),     enumFromThenClassOpKey),
427      (SLIT("enumFromTo"),       enumFromToClassOpKey),
428      (SLIT("enumFromThenTo"),   enumFromThenToClassOpKey),
429      (SLIT("=="),               eqClassOpKey),
430      (SLIT(">="),               geClassOpKey)
431     ]
432 \end{code}