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