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