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