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