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