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