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