[project @ 1999-04-06 09:44:27 by simonm]
[ghc-hetmet.git] / ghc / compiler / basicTypes / Id.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[Id]{@Ids@: Value and constructor identifiers}
5
6 \begin{code}
7 module Id (
8         Id, DictId,
9
10         -- Simple construction
11         mkVanillaId, mkImportedId, mkSysLocal, mkUserLocal,
12         mkTemplateLocals, mkTemplateLocal, mkWildId, mkUserId,
13
14         -- Taking an Id apart
15         idName, idType, idUnique, idInfo, idDetails,
16         idPrimRep, isId,
17         recordSelectorFieldLabel,
18
19         -- Modifying an Id
20         setIdName, setIdUnique, setIdType, setIdInfo,
21
22         -- Predicates
23         omitIfaceSigForId,
24         externallyVisibleId,
25         idFreeTyVars, 
26
27         -- Inline pragma stuff
28         getInlinePragma, setInlinePragma, modifyInlinePragma, 
29         idWantsToBeINLINEd, idMustBeINLINEd, idMustNotBeINLINEd,
30         isSpecPragmaId,
31         
32
33         isRecordSelector,
34         isPrimitiveId_maybe, isDataConId_maybe,
35         isConstantId,
36         isBottomingId, idAppIsBottom,
37
38         -- IdInfo stuff
39         setIdUnfolding,
40         setIdArity,
41         setIdDemandInfo,
42         setIdStrictness,
43         setIdSpecialisation,
44         setIdUpdateInfo,
45         setIdCafInfo,
46
47         getIdArity,
48         getIdDemandInfo,
49         getIdStrictness,
50         getIdUnfolding,
51         getIdSpecialisation,
52         getIdUpdateInfo,
53         getIdCafInfo
54
55     ) where
56
57 #include "HsVersions.h"
58
59 import {-# SOURCE #-} CoreUnfold ( Unfolding )
60
61 import Var              ( Id, DictId, VarDetails(..), 
62                           isId, mkId, 
63                           idName, idType, idUnique, idInfo, idDetails,
64                           setIdName, setVarType, setIdUnique, setIdInfo, modifyIdInfo,
65                           externallyVisibleId
66                         )
67 import VarSet
68 import Type             ( Type, tyVarsOfType, typePrimRep, addFreeTyVars )
69 import IdInfo
70 import Demand           ( Demand )
71 import Name             ( Name, OccName,
72                           mkSysLocalName, mkLocalName,
73                           isWiredInName
74                         ) 
75 import Const            ( Con(..) )
76 import PrimRep          ( PrimRep )
77 import PrimOp           ( PrimOp )
78 import FieldLabel       ( FieldLabel(..) )
79 import SrcLoc           ( SrcLoc )
80 import Unique           ( Unique, mkBuiltinUnique, getBuiltinUniques )
81 import Outputable
82
83 infixl  1 `setIdUnfolding`,
84           `setIdArity`,
85           `setIdDemandInfo`,
86           `setIdStrictness`,
87           `setIdSpecialisation`,
88           `setIdUpdateInfo`,
89           `setInlinePragma`
90         -- infixl so you can say (id `set` a `set` b)
91 \end{code}
92
93
94
95 %************************************************************************
96 %*                                                                      *
97 \subsection{Simple Id construction}
98 %*                                                                      *
99 %************************************************************************
100
101 \begin{code}
102 mkVanillaId :: Name -> Type -> Id
103 mkVanillaId name ty = mkId name (addFreeTyVars ty) VanillaId noIdInfo
104
105 mkImportedId :: Name -> Type -> IdInfo -> Id
106 mkImportedId name ty info = mkId name (addFreeTyVars ty) VanillaId info
107
108 mkUserId :: Name -> Type -> Id
109 mkUserId name ty = mkVanillaId name ty
110
111 -- SysLocal: for an Id being created by the compiler out of thin air...
112 -- UserLocal: an Id with a name the user might recognize...
113 mkUserLocal :: OccName     -> Unique -> Type -> SrcLoc -> Id
114 mkSysLocal  :: FAST_STRING -> Unique -> Type -> Id
115
116 mkSysLocal  fs uniq ty      = mkVanillaId (mkSysLocalName uniq fs)      ty
117 mkUserLocal occ uniq ty loc = mkVanillaId (mkLocalName    uniq occ loc) ty
118 \end{code}
119
120 Make some local @Ids@ for a template @CoreExpr@.  These have bogus
121 @Uniques@, but that's OK because the templates are supposed to be
122 instantiated before use.
123
124 \begin{code}
125 -- "Wild Id" typically used when you need a binder that you don't expect to use
126 mkWildId :: Type -> Id
127 mkWildId ty = mkSysLocal SLIT("wild") (mkBuiltinUnique 1) ty
128
129 -- "Template locals" typically used in unfoldings
130 mkTemplateLocals :: [Type] -> [Id]
131 mkTemplateLocals tys = zipWith (mkSysLocal SLIT("tpl"))
132                                (getBuiltinUniques (length tys))
133                                tys
134
135 mkTemplateLocal :: Int -> Type -> Id
136 mkTemplateLocal i ty = mkSysLocal SLIT("tpl") (mkBuiltinUnique i) ty
137 \end{code}
138
139
140 %************************************************************************
141 %*                                                                      *
142 \subsection[Id-general-funs]{General @Id@-related functions}
143 %*                                                                      *
144 %************************************************************************
145
146 \begin{code}
147 idFreeTyVars :: Id -> TyVarSet
148 idFreeTyVars id = tyVarsOfType (idType id)
149
150 setIdType :: Id -> Type -> Id
151         -- Add free tyvar info to the type
152 setIdType id ty = setVarType id (addFreeTyVars ty)
153
154 idPrimRep :: Id -> PrimRep
155 idPrimRep id = typePrimRep (idType id)
156 \end{code}
157
158 omitIfaceSigForId tells whether an Id's info is implied by other declarations,
159 so we don't need to put its signature in an interface file, even if it's mentioned
160 in some other interface unfolding.
161
162 \begin{code}
163 omitIfaceSigForId :: Id -> Bool
164 omitIfaceSigForId id
165   | isWiredInName (idName id)
166   = True
167
168   | otherwise
169   = case idDetails id of
170         RecordSelId _  -> True  -- Includes dictionary selectors
171         ConstantId _   -> True
172                 -- ConstantIds are implied by their type or class decl;
173                 -- remember that all type and class decls appear in the interface file.
174                 -- The dfun id must *not* be omitted, because it carries version info for
175                 -- the instance decl
176
177         other          -> False -- Don't omit!
178 \end{code}
179
180 %************************************************************************
181 %*                                                                      *
182 \subsection{Special Ids}
183 %*                                                                      *
184 %************************************************************************
185
186 \begin{code}
187 recordSelectorFieldLabel :: Id -> FieldLabel
188 recordSelectorFieldLabel id = case idDetails id of
189                                 RecordSelId lbl -> lbl
190
191 isRecordSelector id = case idDetails id of
192                         RecordSelId lbl -> True
193                         other           -> False
194
195 isPrimitiveId_maybe id = case idDetails id of
196                             ConstantId (PrimOp op) -> Just op
197                             other                  -> Nothing
198
199 isDataConId_maybe id = case idDetails id of
200                           ConstantId (DataCon con) -> Just con
201                           other                    -> Nothing
202
203 isConstantId id = case idDetails id of
204                     ConstantId _ -> True
205                     other        -> False
206 \end{code}
207
208
209 %************************************************************************
210 %*                                                                      *
211 \subsection{IdInfo stuff}
212 %*                                                                      *
213 %************************************************************************
214
215 \begin{code}
216         ---------------------------------
217         -- ARITY
218 getIdArity :: Id -> ArityInfo
219 getIdArity id = arityInfo (idInfo id)
220
221 setIdArity :: Id -> ArityInfo -> Id
222 setIdArity id arity = modifyIdInfo id (arity `setArityInfo`)
223
224         ---------------------------------
225         -- STRICTNESS
226 getIdStrictness :: Id -> StrictnessInfo
227 getIdStrictness id = strictnessInfo (idInfo id)
228
229 setIdStrictness :: Id -> StrictnessInfo -> Id
230 setIdStrictness id strict_info = modifyIdInfo id (strict_info `setStrictnessInfo`)
231
232 -- isBottomingId returns true if an application to n args would diverge
233 isBottomingId :: Id -> Bool
234 isBottomingId id = isBottomingStrictness (strictnessInfo (idInfo id))
235
236 idAppIsBottom :: Id -> Int -> Bool
237 idAppIsBottom id n = appIsBottom (strictnessInfo (idInfo id)) n
238
239         ---------------------------------
240         -- UNFOLDING
241 getIdUnfolding :: Id -> Unfolding
242 getIdUnfolding id = unfoldingInfo (idInfo id)
243
244 setIdUnfolding :: Id -> Unfolding -> Id
245 setIdUnfolding id unfolding = modifyIdInfo id (unfolding `setUnfoldingInfo`)
246
247         ---------------------------------
248         -- DEMAND
249 getIdDemandInfo :: Id -> Demand
250 getIdDemandInfo id = demandInfo (idInfo id)
251
252 setIdDemandInfo :: Id -> Demand -> Id
253 setIdDemandInfo id demand_info = modifyIdInfo id (demand_info `setDemandInfo`)
254
255         ---------------------------------
256         -- UPDATE INFO
257 getIdUpdateInfo :: Id -> UpdateInfo
258 getIdUpdateInfo id = updateInfo (idInfo id)
259
260 setIdUpdateInfo :: Id -> UpdateInfo -> Id
261 setIdUpdateInfo id upd_info = modifyIdInfo id (upd_info `setUpdateInfo`)
262
263         ---------------------------------
264         -- SPECIALISATION
265 getIdSpecialisation :: Id -> IdSpecEnv
266 getIdSpecialisation id = specInfo (idInfo id)
267
268 setIdSpecialisation :: Id -> IdSpecEnv -> Id
269 setIdSpecialisation id spec_info = modifyIdInfo id (spec_info `setSpecInfo`)
270
271         ---------------------------------
272         -- CAF INFO
273 getIdCafInfo :: Id -> CafInfo
274 getIdCafInfo id = cafInfo (idInfo id)
275
276 setIdCafInfo :: Id -> CafInfo -> Id
277 setIdCafInfo id caf_info = modifyIdInfo id (caf_info `setCafInfo`)
278 \end{code}
279
280
281         ---------------------------------
282         -- INLINING
283 The inline pragma tells us to be very keen to inline this Id, but it's still
284 OK not to if optimisation is switched off.
285
286 \begin{code}
287 getInlinePragma :: Id -> InlinePragInfo
288 getInlinePragma id = inlinePragInfo (idInfo id)
289
290 setInlinePragma :: Id -> InlinePragInfo -> Id
291 setInlinePragma id prag = modifyIdInfo id (setInlinePragInfo prag)
292
293 modifyInlinePragma :: Id -> (InlinePragInfo -> InlinePragInfo) -> Id
294 modifyInlinePragma id fn = modifyIdInfo id (\info -> setInlinePragInfo (fn (inlinePragInfo info)) info)
295
296 idWantsToBeINLINEd :: Id -> Bool
297 idWantsToBeINLINEd id = case getInlinePragma id of
298                           IWantToBeINLINEd -> True
299                           IMustBeINLINEd   -> True
300                           other            -> False
301
302 idMustNotBeINLINEd id = case getInlinePragma id of
303                           IMustNotBeINLINEd -> True
304                           IAmASpecPragmaId  -> True
305                           IAmALoopBreaker   -> True
306                           other             -> False
307
308 idMustBeINLINEd id =  case getInlinePragma id of
309                         IMustBeINLINEd -> True
310                         other          -> False
311
312 isSpecPragmaId id = case getInlinePragma id of
313                         IAmASpecPragmaId -> True
314                         other            -> False
315 \end{code}