Major refactoring of the type inference engine
[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 -- |
9 -- #name_types#
10 -- GHC uses several kinds of name internally:
11 --
12 -- * 'OccName.OccName': see "OccName#name_types"
13 --
14 -- * 'RdrName.RdrName': see "RdrName#name_types"
15 --
16 -- * 'Name.Name': see "Name#name_types"
17 --
18 -- * 'Id.Id': see "Id#name_types"
19 --
20 -- * 'Var.Var' is a synonym for the 'Id.Id' type but it may additionally potentially contain type variables, 
21 --   which have a 'TypeRep.Kind' rather than a 'TypeRep.Type' and only contain some extra details during typechecking.
22 --   These 'Var.Var' names may either be global or local, see "Var#globalvslocal"
23 --
24 -- #globalvslocal#
25 -- Global 'Id's and 'Var's are those that are imported or correspond to a data constructor, primitive operation, or record selectors.
26 -- Local 'Id's and 'Var's are those bound within an expression (e.g. by a lambda) or at the top level of the module being compiled.
27 module Var (
28         -- * The main data type and synonyms
29         Var, TyVar, CoVar, Id, DictId, DFunId, EvVar, EvId, IpId,
30
31         -- ** Taking 'Var's apart
32         varName, varUnique, varType, 
33
34         -- ** Modifying 'Var's
35         setVarName, setVarUnique, setVarType,
36
37         -- ** Constructing, taking apart, modifying 'Id's
38         mkGlobalVar, mkLocalVar, mkExportedLocalVar, 
39         idInfo, idDetails,
40         lazySetIdInfo, setIdDetails, globaliseId,
41         setIdExported, setIdNotExported,
42
43         -- ** Predicates
44         isCoVar, isId, isTyCoVar, isTyVar, isTcTyVar,
45         isLocalVar, isLocalId,
46         isGlobalId, isExportedId,
47         mustHaveLocalBinding,
48
49         -- ** Constructing 'TyVar's
50         mkTyVar, mkTcTyVar, mkWildCoVar,
51
52         -- ** Taking 'TyVar's apart
53         tyVarName, tyVarKind, tcTyVarDetails, setTcTyVarDetails,
54
55         -- ** Modifying 'TyVar's
56         setTyVarName, setTyVarUnique, setTyVarKind,
57
58         -- ** Constructing 'CoVar's
59         mkCoVar,
60
61         -- ** Taking 'CoVar's apart
62         coVarName,
63
64         -- ** Modifying 'CoVar's
65         setCoVarUnique, setCoVarName
66
67     ) where
68
69 #include "HsVersions.h"
70 #include "Typeable.h"
71
72 import {-# SOURCE #-}   TypeRep( Type, Kind )
73 import {-# SOURCE #-}   TcType( TcTyVarDetails, pprTcTyVarDetails )
74 import {-# SOURCE #-}   IdInfo( IdDetails, IdInfo, pprIdDetails )
75 import {-# SOURCE #-}   TypeRep( isCoercionKind )
76
77 import Name hiding (varName)
78 import Unique
79 import Util
80 import FastTypes
81 import FastString
82 import Outputable
83
84 import Data.Data
85 \end{code}
86
87
88 %************************************************************************
89 %*                                                                      *
90                      Synonyms                                                                   
91 %*                                                                      *
92 %************************************************************************
93 -- These synonyms are here and not in Id because otherwise we need a very
94 -- large number of SOURCE imports of Id.hs :-(
95
96 \begin{code}
97 type EvVar = Var        -- An evidence variable: dictionary or equality constraint
98                         -- Could be an DictId or a CoVar
99
100 type Id     = Var       -- A term-level identifier
101 type DFunId = Id        -- A dictionary function
102 type EvId   = Id        -- Term-level evidence: DictId or IpId
103 type DictId = EvId      -- A dictionary variable
104 type IpId   = EvId      -- A term-level implicit parameter
105
106 type TyVar = Var
107 type CoVar = TyVar      -- A coercion variable is simply a type 
108                         -- variable of kind @ty1 ~ ty2@. Hence its
109                         -- 'varType' is always @PredTy (EqPred t1 t2)@
110 \end{code}
111
112 %************************************************************************
113 %*                                                                      *
114 \subsection{The main data type declarations}
115 %*                                                                      *
116 %************************************************************************
117
118
119 Every @Var@ has a @Unique@, to uniquify it and for fast comparison, a
120 @Type@, and an @IdInfo@ (non-essential info about it, e.g.,
121 strictness).  The essential info about different kinds of @Vars@ is
122 in its @VarDetails@.
123
124 \begin{code}
125 -- | Essentially a typed 'Name', that may also contain some additional information
126 -- about the 'Var' and it's use sites.
127 data Var
128   = TyVar {
129         varName    :: !Name,
130         realUnique :: FastInt,          -- Key for fast comparison
131                                         -- Identical to the Unique in the name,
132                                         -- cached here for speed
133         varType       :: Kind,          -- ^ The type or kind of the 'Var' in question
134         isCoercionVar :: Bool
135  }
136
137   | TcTyVar {                           -- Used only during type inference
138                                         -- Used for kind variables during 
139                                         -- inference, as well
140         varName        :: !Name,
141         realUnique     :: FastInt,
142         varType        :: Kind,
143         tc_tv_details  :: TcTyVarDetails }
144
145   | Id {
146         varName    :: !Name,
147         realUnique :: FastInt,
148         varType    :: Type,
149         idScope    :: IdScope,
150         id_details :: IdDetails,        -- Stable, doesn't change
151         id_info    :: IdInfo }          -- Unstable, updated by simplifier
152
153 data IdScope    -- See Note [GlobalId/LocalId]
154   = GlobalId 
155   | LocalId ExportFlag
156
157 data ExportFlag 
158   = NotExported -- ^ Not exported: may be discarded as dead code.
159   | Exported    -- ^ Exported: kept alive
160 \end{code}
161
162 Note [GlobalId/LocalId]
163 ~~~~~~~~~~~~~~~~~~~~~~~
164 A GlobalId is
165   * always a constant (top-level)
166   * imported, or data constructor, or primop, or record selector
167   * has a Unique that is globally unique across the whole
168     GHC invocation (a single invocation may compile multiple modules)
169   * never treated as a candidate by the free-variable finder;
170         it's a constant!
171
172 A LocalId is 
173   * bound within an expression (lambda, case, local let(rec))
174   * or defined at top level in the module being compiled
175   * always treated as a candidate by the free-variable finder
176
177 After CoreTidy, top-level LocalIds are turned into GlobalIds
178
179 \begin{code}
180 instance Outputable Var where
181   ppr var = ppr (varName var) <+> ifPprDebug (brackets (ppr_debug var))
182
183 ppr_debug :: Var -> SDoc
184 ppr_debug (TyVar { isCoercionVar = False })   = ptext (sLit "tv")
185 ppr_debug (TyVar { isCoercionVar = True })    = ptext (sLit "co")
186 ppr_debug (TcTyVar {tc_tv_details = d})       = pprTcTyVarDetails d
187 ppr_debug (Id { idScope = s, id_details = d }) = ppr_id_scope s <> pprIdDetails d
188
189 ppr_id_scope :: IdScope -> SDoc
190 ppr_id_scope GlobalId              = ptext (sLit "gid")
191 ppr_id_scope (LocalId Exported)    = ptext (sLit "lidx")
192 ppr_id_scope (LocalId NotExported) = ptext (sLit "lid")
193
194 instance Show Var where
195   showsPrec p var = showsPrecSDoc p (ppr var)
196
197 instance NamedThing Var where
198   getName = varName
199
200 instance Uniquable Var where
201   getUnique = varUnique
202
203 instance Eq Var where
204     a == b = realUnique a ==# realUnique b
205
206 instance Ord Var where
207     a <= b = realUnique a <=# realUnique b
208     a <  b = realUnique a <#  realUnique b
209     a >= b = realUnique a >=# realUnique b
210     a >  b = realUnique a >#  realUnique b
211     a `compare` b = varUnique a `compare` varUnique b
212
213 INSTANCE_TYPEABLE0(Var,varTc,"Var")
214
215 instance Data Var where
216   -- don't traverse?
217   toConstr _   = abstractConstr "Var"
218   gunfold _ _  = error "gunfold"
219   dataTypeOf _ = mkNoRepType "Var"
220 \end{code}
221
222
223 \begin{code}
224 varUnique :: Var -> Unique
225 varUnique var = mkUniqueGrimily (iBox (realUnique var))
226
227 setVarUnique :: Var -> Unique -> Var
228 setVarUnique var uniq 
229   = var { realUnique = getKeyFastInt uniq, 
230           varName = setNameUnique (varName var) uniq }
231
232 setVarName :: Var -> Name -> Var
233 setVarName var new_name
234   = var { realUnique = getKeyFastInt (getUnique new_name), 
235           varName = new_name }
236
237 setVarType :: Id -> Type -> Id
238 setVarType id ty = id { varType = ty }
239 \end{code}
240
241
242 %************************************************************************
243 %*                                                                      *
244 \subsection{Type variables}
245 %*                                                                      *
246 %************************************************************************
247
248 \begin{code}
249 tyVarName :: TyVar -> Name
250 tyVarName = varName
251
252 tyVarKind :: TyVar -> Kind
253 tyVarKind = varType
254
255 setTyVarUnique :: TyVar -> Unique -> TyVar
256 setTyVarUnique = setVarUnique
257
258 setTyVarName :: TyVar -> Name -> TyVar
259 setTyVarName   = setVarName
260
261 setTyVarKind :: TyVar -> Kind -> TyVar
262 setTyVarKind tv k = tv {varType = k}
263 \end{code}
264
265 \begin{code}
266 mkTyVar :: Name -> Kind -> TyVar
267 mkTyVar name kind = ASSERT( not (isCoercionKind kind ) )
268                     TyVar { varName    = name
269                           , realUnique = getKeyFastInt (nameUnique name)
270                           , varType  = kind
271                           , isCoercionVar    = False
272                         }
273
274 mkTcTyVar :: Name -> Kind -> TcTyVarDetails -> TyVar
275 mkTcTyVar name kind details
276   = -- NB: 'kind' may be a coercion kind; cf, 'TcMType.newMetaCoVar'
277     TcTyVar {   varName    = name,
278                 realUnique = getKeyFastInt (nameUnique name),
279                 varType  = kind,
280                 tc_tv_details = details
281         }
282
283 tcTyVarDetails :: TyVar -> TcTyVarDetails
284 tcTyVarDetails (TcTyVar { tc_tv_details = details }) = details
285 tcTyVarDetails var = pprPanic "tcTyVarDetails" (ppr var)
286
287 setTcTyVarDetails :: TyVar -> TcTyVarDetails -> TyVar
288 setTcTyVarDetails tv details = tv { tc_tv_details = details }
289 \end{code}
290
291 %************************************************************************
292 %*                                                                      *
293 \subsection{Coercion variables}
294 %*                                                                      *
295 %************************************************************************
296
297 \begin{code}
298 coVarName :: CoVar -> Name
299 coVarName = varName
300
301 setCoVarUnique :: CoVar -> Unique -> CoVar
302 setCoVarUnique = setVarUnique
303
304 setCoVarName :: CoVar -> Name -> CoVar
305 setCoVarName   = setVarName
306
307 mkCoVar :: Name -> Kind -> CoVar
308 mkCoVar name kind = ASSERT( isCoercionKind kind )
309                     TyVar { varName       = name
310                           , realUnique    = getKeyFastInt (nameUnique name)
311                           , varType       = kind
312                           , isCoercionVar = True
313                         }
314
315 mkWildCoVar :: Kind -> TyVar
316 -- ^ Create a type variable that is never referred to, so its unique doesn't 
317 -- matter
318 mkWildCoVar = mkCoVar (mkSysTvName (mkBuiltinUnique 1) (fsLit "co_wild"))
319 \end{code}
320
321 %************************************************************************
322 %*                                                                      *
323 \subsection{Ids}
324 %*                                                                      *
325 %************************************************************************
326
327 \begin{code}
328 idInfo :: Id -> IdInfo
329 idInfo (Id { id_info = info }) = info
330 idInfo other                   = pprPanic "idInfo" (ppr other)
331
332 idDetails :: Id -> IdDetails
333 idDetails (Id { id_details = details }) = details
334 idDetails other                         = pprPanic "idDetails" (ppr other)
335
336 -- The next three have a 'Var' suffix even though they always build
337 -- Ids, becuase Id.lhs uses 'mkGlobalId' etc with different types
338 mkGlobalVar :: IdDetails -> Name -> Type -> IdInfo -> Id
339 mkGlobalVar details name ty info
340   = mk_id name ty GlobalId details info
341
342 mkLocalVar :: IdDetails -> Name -> Type -> IdInfo -> Id
343 mkLocalVar details name ty info
344   = mk_id name ty (LocalId NotExported) details  info
345
346 -- | Exported 'Var's will not be removed as dead code
347 mkExportedLocalVar :: IdDetails -> Name -> Type -> IdInfo -> Id
348 mkExportedLocalVar details name ty info 
349   = mk_id name ty (LocalId Exported) details info
350
351 mk_id :: Name -> Type -> IdScope -> IdDetails -> IdInfo -> Id
352 mk_id name ty scope details info
353   = Id { varName    = name, 
354          realUnique = getKeyFastInt (nameUnique name),
355          varType    = ty,       
356          idScope    = scope,
357          id_details = details,
358          id_info    = info }
359
360 -------------------
361 lazySetIdInfo :: Id -> IdInfo -> Var
362 lazySetIdInfo id info = id { id_info = info }
363
364 setIdDetails :: Id -> IdDetails -> Id
365 setIdDetails id details = id { id_details = details }
366
367 globaliseId :: Id -> Id
368 -- ^ If it's a local, make it global
369 globaliseId id = id { idScope = GlobalId }
370
371 setIdExported :: Id -> Id
372 -- ^ Exports the given local 'Id'. Can also be called on global 'Id's, such as data constructors
373 -- and class operations, which are born as global 'Id's and automatically exported
374 setIdExported id@(Id { idScope = LocalId {} }) = id { idScope = LocalId Exported }
375 setIdExported id@(Id { idScope = GlobalId })   = id
376 setIdExported tv                               = pprPanic "setIdExported" (ppr tv)
377
378 setIdNotExported :: Id -> Id
379 -- ^ We can only do this to LocalIds
380 setIdNotExported id = ASSERT( isLocalId id ) 
381                       id { idScope = LocalId NotExported }
382 \end{code}
383
384 %************************************************************************
385 %*                                                                      *
386 \subsection{Predicates over variables}
387 %*                                                                      *
388 %************************************************************************
389
390 \begin{code}
391 isTyCoVar :: Var -> Bool        -- True of both type and coercion variables
392 isTyCoVar (TyVar {})   = True
393 isTyCoVar (TcTyVar {}) = True
394 isTyCoVar _            = False
395
396 isTyVar :: Var -> Bool          -- True of both type variables only
397 isTyVar v@(TyVar {}) = not (isCoercionVar v)
398 isTyVar (TcTyVar {}) = True
399 isTyVar _            = False
400
401 isCoVar :: Var -> Bool          -- Only works after type checking (sigh)
402 isCoVar v@(TyVar {}) = isCoercionVar v
403 isCoVar _            = False
404
405 isTcTyVar :: Var -> Bool
406 isTcTyVar (TcTyVar {}) = True
407 isTcTyVar _            = False
408
409 isId :: Var -> Bool
410 isId (Id {}) = True
411 isId _       = False
412
413 isLocalId :: Var -> Bool
414 isLocalId (Id { idScope = LocalId _ }) = True
415 isLocalId _                            = False
416
417 -- | 'isLocalVar' returns @True@ for type variables as well as local 'Id's
418 -- These are the variables that we need to pay attention to when finding free
419 -- variables, or doing dependency analysis.
420 isLocalVar :: Var -> Bool
421 isLocalVar v = not (isGlobalId v)
422
423 isGlobalId :: Var -> Bool
424 isGlobalId (Id { idScope = GlobalId }) = True
425 isGlobalId _                           = False
426
427 -- | 'mustHaveLocalBinding' returns @True@ of 'Id's and 'TyVar's
428 -- that must have a binding in this module.  The converse
429 -- is not quite right: there are some global 'Id's that must have
430 -- bindings, such as record selectors.  But that doesn't matter,
431 -- because it's only used for assertions
432 mustHaveLocalBinding        :: Var -> Bool
433 mustHaveLocalBinding var = isLocalVar var
434
435 -- | 'isExportedIdVar' means \"don't throw this away\"
436 isExportedId :: Var -> Bool
437 isExportedId (Id { idScope = GlobalId })        = True
438 isExportedId (Id { idScope = LocalId Exported}) = True
439 isExportedId _ = False
440 \end{code}