948b910f8be064d357f77f828eb22a127263e18f
[ghc-hetmet.git] / ghc / compiler / basicTypes / Var.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section{@Vars@: Variables}
5
6 \begin{code}
7 module Var (
8         Var, 
9         varName, varUnique, 
10         setVarName, setVarUnique, setVarOcc,
11
12         -- TyVars
13         TyVar, mkTyVar, mkTcTyVar,
14         tyVarName, tyVarKind,
15         setTyVarName, setTyVarUnique,
16         tcTyVarDetails,
17
18         -- Ids
19         Id, DictId,
20         idName, idType, idUnique, idInfo, modifyIdInfo, maybeModifyIdInfo,
21         setIdName, setIdUnique, setIdType, setIdInfo, lazySetIdInfo, 
22         setIdExported, setIdNotExported, 
23
24         globalIdDetails, globaliseId, 
25
26         mkLocalId, mkExportedLocalId, mkGlobalId, 
27
28         isTyVar, isTcTyVar, isId, isLocalVar, isLocalId,
29         isGlobalId, isExportedId, 
30         mustHaveLocalBinding
31     ) where
32
33 #include "HsVersions.h"
34
35 import {-# SOURCE #-}   TypeRep( Type )
36 import {-# SOURCE #-}   TcType( TcTyVarDetails )
37 import {-# SOURCE #-}   IdInfo( GlobalIdDetails, notGlobalId, IdInfo, seqIdInfo )
38
39 import Name             ( Name, OccName, NamedThing(..),
40                           setNameUnique, setNameOcc, nameUnique
41                         )
42 import Kind             ( Kind )
43 import Unique           ( Unique, Uniquable(..), mkUniqueGrimily, getKey# )
44 import FastTypes
45 import Outputable
46 \end{code}
47
48
49 %************************************************************************
50 %*                                                                      *
51 \subsection{The main data type declarations}
52 %*                                                                      *
53 %************************************************************************
54
55
56 Every @Var@ has a @Unique@, to uniquify it and for fast comparison, a
57 @Type@, and an @IdInfo@ (non-essential info about it, e.g.,
58 strictness).  The essential info about different kinds of @Vars@ is
59 in its @VarDetails@.
60
61 \begin{code}
62 data Var
63   = TyVar {
64         varName    :: !Name,
65         realUnique :: FastInt,          -- Key for fast comparison
66                                         -- Identical to the Unique in the name,
67                                         -- cached here for speed
68         tyVarKind :: Kind }
69
70   | TcTyVar {                           -- Used only during type inference
71         varName        :: !Name,
72         realUnique     :: FastInt,
73         tyVarKind      :: Kind,
74         tcTyVarDetails :: TcTyVarDetails }
75
76   | GlobalId {                  -- Used for imported Ids, dict selectors etc
77         varName    :: !Name,
78         realUnique :: FastInt,
79         idType     :: Type,
80         idInfo     :: IdInfo,
81         gblDetails :: GlobalIdDetails }
82
83   | LocalId {                   -- Used for locally-defined Ids (see NOTE below)
84         varName    :: !Name,
85         realUnique :: FastInt,
86         idType     :: Type,
87         idInfo     :: IdInfo,
88         lclDetails :: LocalIdDetails }
89
90 data LocalIdDetails 
91   = NotExported -- Not exported
92   | Exported    -- Exported
93   -- Exported Ids are kept alive; 
94   -- NotExported things may be discarded as dead code.
95 \end{code}
96
97 LocalId and GlobalId
98 ~~~~~~~~~~~~~~~~~~~~
99 A GlobalId is
100   * always a constant (top-level)
101   * imported, or data constructor, or primop, or record selector
102   * has a Unique that is globally unique across the whole
103     GHC invocation (a single invocation may compile multiple modules)
104
105 A LocalId is 
106   * bound within an expression (lambda, case, local let(rec))
107   * or defined at top level in the module being compiled
108
109 After CoreTidy, top-level LocalIds are turned into GlobalIds
110  
111
112 \begin{code}
113 instance Outputable Var where
114   ppr var = ppr (varName var)
115
116 instance Show Var where
117   showsPrec p var = showsPrecSDoc p (ppr var)
118
119 instance NamedThing Var where
120   getName = varName
121
122 instance Uniquable Var where
123   getUnique = varUnique
124
125 instance Eq Var where
126     a == b = realUnique a ==# realUnique b
127
128 instance Ord Var where
129     a <= b = realUnique a <=# realUnique b
130     a <  b = realUnique a <#  realUnique b
131     a >= b = realUnique a >=# realUnique b
132     a >  b = realUnique a >#  realUnique b
133     a `compare` b = varUnique a `compare` varUnique b
134 \end{code}
135
136
137 \begin{code}
138 varUnique :: Var -> Unique
139 varUnique var = mkUniqueGrimily (iBox (realUnique var))
140
141 setVarUnique :: Var -> Unique -> Var
142 setVarUnique var uniq 
143   = var { realUnique = getKey# uniq, 
144           varName = setNameUnique (varName var) uniq }
145
146 setVarName :: Var -> Name -> Var
147 setVarName var new_name
148   = var { realUnique = getKey# (getUnique new_name), 
149           varName = new_name }
150
151 setVarOcc :: Var -> OccName -> Var
152 setVarOcc var new_occ
153   = var { varName = setNameOcc (varName var) new_occ }
154 \end{code}
155
156
157 %************************************************************************
158 %*                                                                      *
159 \subsection{Type variables}
160 %*                                                                      *
161 %************************************************************************
162
163 \begin{code}
164 type TyVar = Var
165
166 tyVarName = varName
167
168 setTyVarUnique = setVarUnique
169 setTyVarName   = setVarName
170 \end{code}
171
172 \begin{code}
173 mkTyVar :: Name -> Kind -> TyVar
174 mkTyVar name kind = TyVar { varName    = name
175                           , realUnique = getKey# (nameUnique name)
176                           , tyVarKind  = kind
177                         }
178
179 mkTcTyVar :: Name -> Kind -> TcTyVarDetails -> TyVar
180 mkTcTyVar name kind details
181   = TcTyVar {   varName    = name,
182                 realUnique = getKey# (nameUnique name),
183                 tyVarKind  = kind,
184                 tcTyVarDetails = details
185         }
186 \end{code}
187
188
189 %************************************************************************
190 %*                                                                      *
191 \subsection{Id Construction}
192 %*                                                                      *
193 %************************************************************************
194
195 Most Id-related functions are in Id.lhs and MkId.lhs
196
197 \begin{code}
198 type Id     = Var
199 type DictId = Id
200 \end{code}
201
202 \begin{code}
203 idName    = varName
204 idUnique  = varUnique
205
206 setIdUnique :: Id -> Unique -> Id
207 setIdUnique = setVarUnique
208
209 setIdName :: Id -> Name -> Id
210 setIdName = setVarName
211
212 setIdType :: Id -> Type -> Id
213 setIdType id ty = id {idType = ty}
214
215 setIdExported :: Id -> Id
216 -- Can be called on GlobalIds, such as data cons and class ops,
217 -- which are "born" as GlobalIds and automatically exported
218 setIdExported id@(LocalId {}) = id { lclDetails = Exported }
219 setIdExported other_id        = ASSERT( isId other_id ) other_id
220
221 setIdNotExported :: Id -> Id
222 -- We can only do this to LocalIds
223 setIdNotExported id = ASSERT( isLocalId id ) id { lclDetails = NotExported }
224
225 globaliseId :: GlobalIdDetails -> Id -> Id
226 -- If it's a local, make it global
227 globaliseId details id = GlobalId { varName    = varName id,
228                                     realUnique = realUnique id,
229                                     idType     = idType id,
230                                     idInfo     = idInfo id,
231                                     gblDetails = details }
232
233 lazySetIdInfo :: Id -> IdInfo -> Id
234 lazySetIdInfo id info = id {idInfo = info}
235
236 setIdInfo :: Id -> IdInfo -> Id
237 setIdInfo id info = seqIdInfo info `seq` id {idInfo = info}
238         -- Try to avoid spack leaks by seq'ing
239
240 modifyIdInfo :: (IdInfo -> IdInfo) -> Id -> Id
241 modifyIdInfo fn id
242   = seqIdInfo new_info `seq` id {idInfo = new_info}
243   where
244     new_info = fn (idInfo id)
245
246 -- maybeModifyIdInfo tries to avoid unnecesary thrashing
247 maybeModifyIdInfo :: (IdInfo -> Maybe IdInfo) -> Id -> Id
248 maybeModifyIdInfo fn id
249   = case fn (idInfo id) of
250         Nothing       -> id
251         Just new_info -> id {idInfo = new_info}
252 \end{code}
253
254 %************************************************************************
255 %*                                                                      *
256 \subsection{Predicates over variables
257 %*                                                                      *
258 %************************************************************************
259
260 \begin{code}
261 mkGlobalId :: GlobalIdDetails -> Name -> Type -> IdInfo -> Id
262 mkGlobalId details name ty info 
263   = GlobalId {  varName    = name, 
264                 realUnique = getKey# (nameUnique name),         -- Cache the unique
265                 idType     = ty,        
266                 gblDetails = details,
267                 idInfo     = info }
268
269 mk_local_id :: Name -> Type -> LocalIdDetails -> IdInfo -> Id
270 mk_local_id name ty details info
271   = LocalId {   varName    = name, 
272                 realUnique = getKey# (nameUnique name),         -- Cache the unique
273                 idType     = ty,        
274                 lclDetails = details,
275                 idInfo     = info }
276
277 mkLocalId :: Name -> Type -> IdInfo -> Id
278 mkLocalId name ty info = mk_local_id name ty NotExported info
279
280 mkExportedLocalId :: Name -> Type -> IdInfo -> Id
281 mkExportedLocalId name ty info = mk_local_id name ty Exported info
282 \end{code}
283
284 \begin{code}
285 isTyVar, isTcTyVar          :: Var -> Bool
286 isId, isLocalVar, isLocalId :: Var -> Bool
287 isGlobalId, isExportedId    :: Var -> Bool
288 mustHaveLocalBinding        :: Var -> Bool
289
290 isTyVar (TyVar {})   = True
291 isTyVar (TcTyVar {}) = True
292 isTyVar other        = False
293
294 isTcTyVar (TcTyVar {}) = True
295 isTcTyVar other        = False
296
297 isId (LocalId {})  = True
298 isId (GlobalId {}) = True
299 isId other         = False
300
301 isLocalId (LocalId {}) = True
302 isLocalId other        = False
303
304 -- isLocalVar returns True for type variables as well as local Ids
305 -- These are the variables that we need to pay attention to when finding free
306 -- variables, or doing dependency analysis.
307 isLocalVar (GlobalId {}) = False 
308 isLocalVar other         = True
309
310 -- mustHaveLocalBinding returns True of Ids and TyVars
311 -- that must have a binding in this module.  The converse
312 -- is not quite right: there are some GlobalIds that must have
313 -- bindings, such as record selectors.  But that doesn't matter,
314 -- because it's only used for assertions
315 mustHaveLocalBinding var = isLocalVar var
316
317 isGlobalId (GlobalId {}) = True
318 isGlobalId other         = False
319
320 -- isExportedId means "don't throw this away"
321 isExportedId (GlobalId {}) = True
322 isExportedId (LocalId {lclDetails = details}) 
323   = case details of
324         Exported   -> True
325         other      -> False
326 isExportedId other = False
327 \end{code}
328
329 \begin{code}
330 globalIdDetails :: Var -> GlobalIdDetails
331 -- Works OK on local Ids too, returning notGlobalId
332 globalIdDetails (GlobalId {gblDetails = details}) = details
333 globalIdDetails other                             = notGlobalId
334 \end{code}
335