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