5ed26fc2f56da1f94b7eabfc9ba9a2a582fe5d48
[ghc-hetmet.git] / ghc / compiler / prelude / PrelInfo.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[PrelInfo]{The @PrelInfo@ interface to the compiler's prelude knowledge}
5
6 \begin{code}
7 module PrelInfo (
8         module MkId,
9
10         ghcPrimExports,
11         wiredInThings, basicKnownKeyNames,
12         primOpId,
13         
14         -- Random other things
15         maybeCharLikeCon, maybeIntLikeCon,
16
17         -- Class categories
18         isNoDictClass, isNumericClass, isStandardClass
19
20     ) where
21
22 #include "HsVersions.h"
23
24 import PrelNames        ( basicKnownKeyNames, 
25                           hasKey, charDataConKey, intDataConKey,
26                           numericClassKeys, standardClassKeys,
27                           noDictClassKeys )
28
29 import PrimOp           ( PrimOp, allThePrimOps, primOpOcc, primOpTag, maxPrimOpTag )
30 import DataCon          ( DataCon )
31 import Id               ( Id, idName )
32 import MkId             ( mkPrimOpId, wiredInIds )
33 import MkId             -- All of it, for re-export
34 import Name             ( nameOccName )
35 import TysPrim          ( primTyCons )
36 import TysWiredIn       ( wiredInTyCons )
37 import HscTypes         ( TyThing(..), implicitTyThings, GenAvailInfo(..), RdrAvailInfo )
38 import Class            ( Class, classKey )
39 import Type             ( funTyCon )
40 import TyCon            ( tyConName )
41 import Util             ( isIn )
42
43 import Array            ( Array, array, (!) )
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 wiredInThings :: [TyThing]
57 wiredInThings           
58   = concat
59     [           -- Wired in TyCons and their implicit Ids
60           tycon_things
61         , concatMap implicitTyThings tycon_things
62
63                 -- Wired in Ids
64         , map AnId wiredInIds
65
66                 -- PrimOps
67         , map (AnId . mkPrimOpId) allThePrimOps
68     ]
69   where
70     tycon_things = map ATyCon ([funTyCon] ++ primTyCons ++ wiredInTyCons)
71 \end{code}
72
73 We let a lot of "non-standard" values be visible, so that we can make
74 sense of them in interface pragmas. It's cool, though they all have
75 "non-standard" names, so they won't get past the parser in user code.
76
77 %************************************************************************
78 %*                                                                      *
79                 PrimOpIds
80 %*                                                                      *
81 %************************************************************************
82
83 \begin{code}
84 primOpIds :: Array Int Id       -- Indexed by PrimOp tag
85 primOpIds = array (1,maxPrimOpTag) [ (primOpTag op, mkPrimOpId op) 
86                                    | op <- allThePrimOps]
87
88 primOpId :: PrimOp -> Id
89 primOpId op = primOpIds ! primOpTag op
90 \end{code}
91
92
93 %************************************************************************
94 %*                                                                      *
95 \subsection{Export lists for pseudo-modules (GHC.Prim)}
96 %*                                                                      *
97 %************************************************************************
98
99 GHC.Prim "exports" all the primops and primitive types, some 
100 wired-in Ids.
101
102 \begin{code}
103 ghcPrimExports :: [RdrAvailInfo]
104 ghcPrimExports
105  = map (Avail . nameOccName . idName) ghcPrimIds ++
106    map (Avail . primOpOcc) allThePrimOps ++
107    [ AvailTC occ [occ] |
108      n <- funTyCon : primTyCons, let occ = nameOccName (tyConName n) 
109    ]
110 \end{code}
111
112
113 %************************************************************************
114 %*                                                                      *
115 \subsection{Built-in keys}
116 %*                                                                      *
117 %************************************************************************
118
119 ToDo: make it do the ``like'' part properly (as in 0.26 and before).
120
121 \begin{code}
122 maybeCharLikeCon, maybeIntLikeCon :: DataCon -> Bool
123 maybeCharLikeCon con = con `hasKey` charDataConKey
124 maybeIntLikeCon  con = con `hasKey` intDataConKey
125 \end{code}
126
127
128 %************************************************************************
129 %*                                                                      *
130 \subsection{Class predicates}
131 %*                                                                      *
132 %************************************************************************
133
134 \begin{code}
135 isNoDictClass, isNumericClass, isStandardClass :: Class -> Bool
136
137 isNumericClass     clas = classKey clas `is_elem` numericClassKeys
138 isStandardClass    clas = classKey clas `is_elem` standardClassKeys
139 isNoDictClass      clas = classKey clas `is_elem` noDictClassKeys
140 is_elem = isIn "is_X_Class"
141 \end{code}