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