[project @ 1998-12-18 17:40:31 by simonpj]
[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 -> Unique -> Id -> Id
178 mkIdVisible mod u id 
179   = setIdName id (mkNameVisible mod u (idName id))
180 \end{code}
181
182 %************************************************************************
183 %*                                                                      *
184 \subsection{Special Ids}
185 %*                                                                      *
186 %************************************************************************
187
188 \begin{code}
189 recordSelectorFieldLabel :: Id -> FieldLabel
190 recordSelectorFieldLabel id = case idDetails id of
191                                 RecordSelId lbl -> lbl
192
193 isRecordSelector id = case idDetails id of
194                         RecordSelId lbl -> True
195                         other           -> False
196
197 isPrimitiveId_maybe id = case idDetails id of
198                             ConstantId (PrimOp op) -> Just op
199                             other                  -> Nothing
200
201 isDataConId_maybe id = case idDetails id of
202                           ConstantId (DataCon con) -> Just con
203                           other                    -> Nothing
204
205 isConstantId id = case idDetails id of
206                     ConstantId _ -> True
207                     other        -> False
208 \end{code}
209
210
211 %************************************************************************
212 %*                                                                      *
213 \subsection{IdInfo stuff}
214 %*                                                                      *
215 %************************************************************************
216
217 \begin{code}
218         ---------------------------------
219         -- ARITY
220 getIdArity :: Id -> ArityInfo
221 getIdArity id = arityInfo (idInfo id)
222
223 setIdArity :: Id -> ArityInfo -> Id
224 setIdArity id arity = modifyIdInfo id (arity `setArityInfo`)
225
226         ---------------------------------
227         -- STRICTNESS
228 getIdStrictness :: Id -> StrictnessInfo
229 getIdStrictness id = strictnessInfo (idInfo id)
230
231 setIdStrictness :: Id -> StrictnessInfo -> Id
232 setIdStrictness id strict_info = modifyIdInfo id (strict_info `setStrictnessInfo`)
233
234 -- isBottomingId returns true if an application to n args would diverge
235 isBottomingId :: Id -> Bool
236 isBottomingId id = isBottomingStrictness (strictnessInfo (idInfo id))
237
238 idAppIsBottom :: Id -> Int -> Bool
239 idAppIsBottom id n = appIsBottom (strictnessInfo (idInfo id)) n
240
241         ---------------------------------
242         -- UNFOLDING
243 getIdUnfolding :: Id -> Unfolding
244 getIdUnfolding id = unfoldingInfo (idInfo id)
245
246 setIdUnfolding :: Id -> Unfolding -> Id
247 setIdUnfolding id unfolding = modifyIdInfo id (unfolding `setUnfoldingInfo`)
248
249         ---------------------------------
250         -- DEMAND
251 getIdDemandInfo :: Id -> Demand
252 getIdDemandInfo id = demandInfo (idInfo id)
253
254 setIdDemandInfo :: Id -> Demand -> Id
255 setIdDemandInfo id demand_info = modifyIdInfo id (demand_info `setDemandInfo`)
256
257         ---------------------------------
258         -- UPDATE INFO
259 getIdUpdateInfo :: Id -> UpdateInfo
260 getIdUpdateInfo id = updateInfo (idInfo id)
261
262 setIdUpdateInfo :: Id -> UpdateInfo -> Id
263 setIdUpdateInfo id upd_info = modifyIdInfo id (upd_info `setUpdateInfo`)
264
265         ---------------------------------
266         -- SPECIALISATION
267 getIdSpecialisation :: Id -> IdSpecEnv
268 getIdSpecialisation id = specInfo (idInfo id)
269
270 setIdSpecialisation :: Id -> IdSpecEnv -> Id
271 setIdSpecialisation id spec_info = modifyIdInfo id (spec_info `setSpecInfo`)
272
273         ---------------------------------
274         -- CAF INFO
275 getIdCafInfo :: Id -> CafInfo
276 getIdCafInfo id = cafInfo (idInfo id)
277
278 setIdCafInfo :: Id -> CafInfo -> Id
279 setIdCafInfo id caf_info = modifyIdInfo id (caf_info `setCafInfo`)
280 \end{code}
281
282
283         ---------------------------------
284         -- INLINING
285 The inline pragma tells us to be very keen to inline this Id, but it's still
286 OK not to if optimisation is switched off.
287
288 \begin{code}
289 getInlinePragma :: Id -> InlinePragInfo
290 getInlinePragma id = inlinePragInfo (idInfo id)
291
292 setInlinePragma :: Id -> InlinePragInfo -> Id
293 setInlinePragma id prag = modifyIdInfo id (setInlinePragInfo prag)
294
295 modifyInlinePragma :: Id -> (InlinePragInfo -> InlinePragInfo) -> Id
296 modifyInlinePragma id fn = modifyIdInfo id (\info -> setInlinePragInfo (fn (inlinePragInfo info)) info)
297
298 idWantsToBeINLINEd :: Id -> Bool
299 idWantsToBeINLINEd id = case getInlinePragma id of
300                           IWantToBeINLINEd -> True
301                           IMustBeINLINEd   -> True
302                           other            -> False
303
304 idMustNotBeINLINEd id = case getInlinePragma id of
305                           IMustNotBeINLINEd -> True
306                           IAmASpecPragmaId  -> True
307                           IAmALoopBreaker   -> True
308                           other             -> False
309
310 idMustBeINLINEd id =  case getInlinePragma id of
311                         IMustBeINLINEd -> True
312                         other          -> False
313
314 isSpecPragmaId id = case getInlinePragma id of
315                         IAmASpecPragmaId -> True
316                         other            -> False
317 \end{code}