cd21b9dd9fc95fde223a6ea21ca19da5a0c30a94
[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   = ASSERT( not (isCoercionKind kind) )
205     TcTyVar {   varName    = name,
206                 realUnique = getKey# (nameUnique name),
207                 varType  = kind,
208                 tcTyVarDetails = details
209         }
210 \end{code}
211
212 %************************************************************************
213 %*                                                                      *
214 \subsection{Coercion variables}
215 %*                                                                      *
216 %************************************************************************
217
218 \begin{code}
219 type CoVar = Var        -- A coercion variable is simply a type 
220                         -- variable of kind (ty1 :=: ty2)
221 coVarName = varName
222
223 setCoVarUnique = setVarUnique
224 setCoVarName   = setVarName
225
226 mkCoVar :: Name -> Kind -> CoVar
227 mkCoVar name kind = ASSERT( isCoercionKind kind )
228                     TyVar { varName    = name
229                           , realUnique = getKey# (nameUnique name)
230                           , varType  = kind
231                           , isCoercionVar    = True
232                         }
233
234 mkWildCoVar :: Kind -> TyVar
235 -- A type variable that is never referred to,
236 -- so its unique doesn't matter
237 mkWildCoVar kind 
238   = ASSERT( isCoercionKind kind )
239     TyVar { varName = mkSysTvName wild_uniq FSLIT("co_wild"),
240             realUnique = _ILIT(1),
241             varType = kind,
242             isCoercionVar = True }
243   where
244     wild_uniq = mkBuiltinUnique 1
245 \end{code}
246
247 %************************************************************************
248 %*                                                                      *
249 \subsection{Id Construction}
250 %*                                                                      *
251 %************************************************************************
252
253 Most Id-related functions are in Id.lhs and MkId.lhs
254
255 \begin{code}
256 type Id     = Var
257 type DictId = Id
258 \end{code}
259
260 \begin{code}
261 idName    = varName
262 idUnique  = varUnique
263 idType    = varType
264
265 setIdUnique :: Id -> Unique -> Id
266 setIdUnique = setVarUnique
267
268 setIdName :: Id -> Name -> Id
269 setIdName = setVarName
270
271 setIdType :: Id -> Type -> Id
272 setIdType id ty = id {varType = ty}
273
274 setIdExported :: Id -> Id
275 -- Can be called on GlobalIds, such as data cons and class ops,
276 -- which are "born" as GlobalIds and automatically exported
277 setIdExported id@(LocalId {}) = id { lclDetails = Exported }
278 setIdExported other_id        = ASSERT( isId other_id ) other_id
279
280 setIdNotExported :: Id -> Id
281 -- We can only do this to LocalIds
282 setIdNotExported id = ASSERT( isLocalId id ) id { lclDetails = NotExported }
283
284 globaliseId :: GlobalIdDetails -> Id -> Id
285 -- If it's a local, make it global
286 globaliseId details id = GlobalId { varName    = varName id,
287                                     realUnique = realUnique id,
288                                     varType    = varType id,
289                                     idInfo_    = idInfo id,
290                                     gblDetails = details }
291
292 idInfo :: Id -> IdInfo
293 idInfo (GlobalId {idInfo_ = info}) = info
294 idInfo (LocalId  {idInfo_ = info}) = info
295 idInfo other_var                   = pprPanic "idInfo" (ppr other_var)
296
297 lazySetIdInfo :: Id -> IdInfo -> Id
298 lazySetIdInfo id info = id {idInfo_ = info}
299
300 setIdInfo :: Id -> IdInfo -> Id
301 setIdInfo id info = seqIdInfo info `seq` id {idInfo_ = info}
302         -- Try to avoid spack leaks by seq'ing
303
304 modifyIdInfo :: (IdInfo -> IdInfo) -> Id -> Id
305 modifyIdInfo fn id
306   = seqIdInfo new_info `seq` id {idInfo_ = new_info}
307   where
308     new_info = fn (idInfo id)
309
310 -- maybeModifyIdInfo tries to avoid unnecesary thrashing
311 maybeModifyIdInfo :: Maybe IdInfo -> Id -> Id
312 maybeModifyIdInfo (Just new_info) id = id {idInfo_ = new_info}
313 maybeModifyIdInfo Nothing         id = id
314 \end{code}
315
316 %************************************************************************
317 %*                                                                      *
318 \subsection{Predicates over variables
319 %*                                                                      *
320 %************************************************************************
321
322 \begin{code}
323 mkGlobalId :: GlobalIdDetails -> Name -> Type -> IdInfo -> Id
324 mkGlobalId details name ty info 
325   = GlobalId {  varName    = name, 
326                 realUnique = getKey# (nameUnique name),         -- Cache the unique
327                 varType     = ty,       
328                 gblDetails = details,
329                 idInfo_    = info }
330
331 mk_local_id :: Name -> Type -> LocalIdDetails -> IdInfo -> Id
332 mk_local_id name ty details info
333   = LocalId {   varName    = name, 
334                 realUnique = getKey# (nameUnique name),         -- Cache the unique
335                 varType     = ty,       
336                 lclDetails = details,
337                 idInfo_    = info }
338
339 mkLocalId :: Name -> Type -> IdInfo -> Id
340 mkLocalId name ty info = mk_local_id name ty NotExported info
341
342 mkExportedLocalId :: Name -> Type -> IdInfo -> Id
343 mkExportedLocalId name ty info = mk_local_id name ty Exported info
344 \end{code}
345
346 \begin{code}
347 isTyVar, isTcTyVar          :: Var -> Bool
348 isId, isLocalVar, isLocalId :: Var -> Bool
349 isGlobalId, isExportedId    :: Var -> Bool
350 mustHaveLocalBinding        :: Var -> Bool
351
352 isTyVar (TyVar {})   = True
353 isTyVar (TcTyVar {}) = True
354 isTyVar other        = False
355
356 isTcTyVar (TcTyVar {}) = True
357 isTcTyVar other        = False
358
359 isId (LocalId {})  = True
360 isId (GlobalId {}) = True
361 isId other         = False
362
363 isLocalId (LocalId {}) = True
364 isLocalId other        = False
365
366 isCoVar (v@(TyVar {})) = isCoercionVar v
367 isCoVar other          = False
368
369 -- isLocalVar returns True for type variables as well as local Ids
370 -- These are the variables that we need to pay attention to when finding free
371 -- variables, or doing dependency analysis.
372 isLocalVar (GlobalId {}) = False 
373 isLocalVar other         = True
374
375 -- mustHaveLocalBinding returns True of Ids and TyVars
376 -- that must have a binding in this module.  The converse
377 -- is not quite right: there are some GlobalIds that must have
378 -- bindings, such as record selectors.  But that doesn't matter,
379 -- because it's only used for assertions
380 mustHaveLocalBinding var = isLocalVar var
381
382 isGlobalId (GlobalId {}) = True
383 isGlobalId other         = False
384
385 -- isExportedId means "don't throw this away"
386 isExportedId (GlobalId {}) = True
387 isExportedId (LocalId {lclDetails = details}) 
388   = case details of
389         Exported   -> True
390         other      -> False
391 isExportedId other = False
392 \end{code}
393
394 \begin{code}
395 globalIdDetails :: Var -> GlobalIdDetails
396 -- Works OK on local Ids too, returning notGlobalId
397 globalIdDetails (GlobalId {gblDetails = details}) = details
398 globalIdDetails other                             = notGlobalId
399 \end{code}
400