[project @ 2002-10-18 13:35:46 by simonpj]
[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 PrelNames,
9         module MkId,
10
11         wiredInThings,  -- Names of wired in things
12         wiredInThingEnv,
13         ghcPrimExports,
14         cCallableClassDecl, cReturnableClassDecl,
15         knownKeyNames,
16         
17         -- Random other things
18         maybeCharLikeCon, maybeIntLikeCon,
19
20         -- Class categories
21         isCcallishClass, isCreturnableClass, isNoDictClass, 
22         isNumericClass, isStandardClass
23
24     ) where
25
26 #include "HsVersions.h"
27
28 import PrelNames        ( basicKnownKeyNames, 
29                           cCallableClassName, cReturnableClassName,
30                           hasKey, charDataConKey, intDataConKey,
31                           numericClassKeys, standardClassKeys, cCallishClassKeys,
32                           noDictClassKeys )
33 #ifdef GHCI
34 import DsMeta           ( templateHaskellNames )
35 import NameSet          ( nameSetToList )
36 #endif
37
38 import PrimOp           ( allThePrimOps, primOpOcc )
39 import DataCon          ( DataCon )
40 import Id               ( idName )
41 import MkId             ( mkPrimOpId, wiredInIds )
42 import MkId             -- All of it, for re-export
43 import Name             ( Name, nameOccName )
44 import RdrName          ( mkRdrUnqual, getRdrName )
45 import HsSyn            ( HsTyVarBndr(..) )
46 import OccName          ( mkVarOcc )
47 import TysPrim          ( primTyCons )
48 import TysWiredIn       ( wiredInTyCons )
49 import RdrHsSyn         ( mkClassDecl )
50 import HscTypes         ( TyThing(..), implicitTyThingIds, TypeEnv, mkTypeEnv,
51                           GenAvailInfo(..), RdrAvailInfo )
52 import Class            ( Class, classKey, className )
53 import Type             ( funTyCon, openTypeKind, liftedTypeKind )
54 import TyCon            ( tyConName )
55 import SrcLoc           ( noSrcLoc )
56 import Util             ( isIn )
57 \end{code}
58
59 %************************************************************************
60 %*                                                                      *
61 \subsection[builtinNameInfo]{Lookup built-in names}
62 %*                                                                      *
63 %************************************************************************
64
65 We have two ``builtin name funs,'' one to look up @TyCons@ and
66 @Classes@, the other to look up values.
67
68 \begin{code}
69 wiredInThings :: [TyThing]
70 wiredInThings
71   = concat
72     [           -- Wired in TyCons and their implicit Ids
73           tycon_things
74         , map AnId (implicitTyThingIds tycon_things)
75
76                 -- Wired in Ids
77         , map AnId wiredInIds
78
79                 -- PrimOps
80         , map (AnId . mkPrimOpId) allThePrimOps
81     ]
82   where
83     tycon_things = map ATyCon ([funTyCon] ++ primTyCons ++ wiredInTyCons)
84
85 wiredInThingEnv :: TypeEnv
86 wiredInThingEnv = mkTypeEnv wiredInThings
87
88 knownKeyNames :: [Name]
89 knownKeyNames 
90   = basicKnownKeyNames
91 #ifdef GHCI
92     ++ nameSetToList templateHaskellNames
93 #endif
94 \end{code}
95
96 We let a lot of "non-standard" values be visible, so that we can make
97 sense of them in interface pragmas. It's cool, though they all have
98 "non-standard" names, so they won't get past the parser in user code.
99
100 %************************************************************************
101 %*                                                                      *
102 \subsection{Export lists for pseudo-modules (GHC.Prim)}
103 %*                                                                      *
104 %************************************************************************
105
106 GHC.Prim "exports" all the primops and primitive types, some 
107 wired-in Ids, and the CCallable & CReturnable classes.
108
109 \begin{code}
110 ghcPrimExports :: [RdrAvailInfo]
111  = AvailTC cCallableOcc [ cCallableOcc ] :
112    AvailTC cReturnableOcc [ cReturnableOcc ] :
113    map (Avail . nameOccName . idName) ghcPrimIds ++
114    map (Avail . primOpOcc) allThePrimOps ++
115    [ AvailTC occ [occ] |
116      n <- funTyCon : primTyCons, let occ = nameOccName (tyConName n) 
117    ]
118  where
119    cCallableOcc = nameOccName cCallableClassName
120    cReturnableOcc = nameOccName cReturnableClassName
121
122 cCallableClassDecl
123   = mkClassDecl
124     ([], getRdrName cCallableClassName, [openAlpha])
125     [] -- no fds
126     [] -- no sigs
127     Nothing -- no mbinds
128     noSrcLoc
129
130 cReturnableClassDecl
131   = mkClassDecl
132     ([], getRdrName cReturnableClassName, [openAlpha])
133     [] -- no fds
134     [] -- no sigs
135     Nothing -- no mbinds
136     noSrcLoc
137
138 alpha = mkRdrUnqual (mkVarOcc FSLIT("a"))
139 openAlpha = IfaceTyVar alpha openTypeKind
140 liftedAlpha = IfaceTyVar alpha liftedTypeKind
141 \end{code}
142
143
144 %************************************************************************
145 %*                                                                      *
146 \subsection{Built-in keys}
147 %*                                                                      *
148 %************************************************************************
149
150 ToDo: make it do the ``like'' part properly (as in 0.26 and before).
151
152 \begin{code}
153 maybeCharLikeCon, maybeIntLikeCon :: DataCon -> Bool
154 maybeCharLikeCon con = con `hasKey` charDataConKey
155 maybeIntLikeCon  con = con `hasKey` intDataConKey
156 \end{code}
157
158
159 %************************************************************************
160 %*                                                                      *
161 \subsection{Class predicates}
162 %*                                                                      *
163 %************************************************************************
164
165 \begin{code}
166 isCcallishClass, isCreturnableClass, isNoDictClass, 
167   isNumericClass, isStandardClass :: Class -> Bool
168
169 isNumericClass     clas = classKey clas `is_elem` numericClassKeys
170 isStandardClass    clas = classKey clas `is_elem` standardClassKeys
171 isCcallishClass    clas = classKey clas `is_elem` cCallishClassKeys
172 isCreturnableClass clas = className clas == cReturnableClassName
173 isNoDictClass      clas = classKey clas `is_elem` noDictClassKeys
174 is_elem = isIn "is_X_Class"
175 \end{code}