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