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