Split the Id related functions out from Var into Id, document Var and some of Id
[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
29         Var,
30
31         -- ** Constructing 'Var's
32         mkLocalIdVar, mkExportedLocalIdVar, mkGlobalIdVar, 
33
34         -- ** Taking 'Var's apart
35         varName, varUnique, varType, varIdInfo, globalIdVarDetails,
36
37         -- ** Modifying 'Var's
38         setVarName, setVarUnique, setVarType,
39         setIdVarExported, setIdVarNotExported, 
40         globaliseIdVar, lazySetVarIdInfo,
41
42         -- ** Predicates
43         isCoVar, isIdVar, isTyVar, isTcTyVar,
44         isLocalVar, isLocalIdVar,
45         isGlobalIdVar, isExportedIdVar,
46         mustHaveLocalBinding,
47
48         -- * Type variable data type
49         TyVar,
50
51         -- ** Constructing 'TyVar's
52         mkTyVar, mkTcTyVar, mkWildCoVar,
53
54         -- ** Taking 'TyVar's apart
55         tyVarName, tyVarKind, tcTyVarDetails,
56
57         -- ** Modifying 'TyVar's
58         setTyVarName, setTyVarUnique, setTyVarKind,
59
60         -- * Coercion variable data type
61         CoVar,
62
63         -- ** Constructing 'CoVar's
64         mkCoVar,
65
66         -- ** Taking 'CoVar's apart
67         coVarName,
68
69         -- ** Modifying 'CoVar's
70         setCoVarUnique, setCoVarName,
71
72         -- * 'Var' type synonyms
73         Id, DictId
74     ) where
75
76 #include "HsVersions.h"
77
78 import {-# SOURCE #-}   TypeRep( Type, Kind )
79 import {-# SOURCE #-}   TcType( TcTyVarDetails, pprTcTyVarDetails )
80 import {-# SOURCE #-}   IdInfo( GlobalIdDetails, notGlobalId, 
81                                 IdInfo )
82 import {-# SOURCE #-}   TypeRep( isCoercionKind )
83
84 import Name hiding (varName)
85 import Unique
86 import FastTypes
87 import FastString
88 import Outputable
89 \end{code}
90
91
92 %************************************************************************
93 %*                                                                      *
94 \subsection{The main data type declarations}
95 %*                                                                      *
96 %************************************************************************
97
98
99 Every @Var@ has a @Unique@, to uniquify it and for fast comparison, a
100 @Type@, and an @IdInfo@ (non-essential info about it, e.g.,
101 strictness).  The essential info about different kinds of @Vars@ is
102 in its @VarDetails@.
103
104 \begin{code}
105 -- | Essentially a typed 'Name', that may also contain some additional information
106 -- about the 'Var' and it's use sites.
107 data Var
108   = TyVar {
109         varName    :: !Name,
110         realUnique :: FastInt,          -- Key for fast comparison
111                                         -- Identical to the Unique in the name,
112                                         -- cached here for speed
113         varType       :: Kind,          -- ^ The type or kind of the 'Var' in question
114         isCoercionVar :: Bool
115  }
116
117   | TcTyVar {                           -- Used only during type inference
118                                         -- Used for kind variables during 
119                                         -- inference, as well
120         varName        :: !Name,
121         realUnique     :: FastInt,
122         varType        :: Kind,
123         tcTyVarDetails :: TcTyVarDetails }
124
125   | GlobalId {                  -- Used for imported Ids, dict selectors etc
126                                 -- See Note [GlobalId/LocalId] below
127         varName    :: !Name,    -- Always an External or WiredIn Name
128         realUnique :: FastInt,
129         varType    :: Type,
130         idInfo_    :: IdInfo,
131         gblDetails :: GlobalIdDetails }
132
133   | LocalId {                   -- Used for locally-defined Ids 
134                                 -- See Note [GlobalId/LocalId] below
135         varName    :: !Name,
136         realUnique :: FastInt,
137         varType    :: Type,
138         idInfo_    :: IdInfo,
139         lclDetails :: LocalIdDetails }
140
141 data LocalIdDetails 
142   = NotExported -- ^ Not exported: may be discarded as dead code.
143   | Exported    -- ^ Exported: kept alive
144 \end{code}
145
146 Note [GlobalId/LocalId]
147 ~~~~~~~~~~~~~~~~~~~~~~~
148 A GlobalId is
149   * always a constant (top-level)
150   * imported, or data constructor, or primop, or record selector
151   * has a Unique that is globally unique across the whole
152     GHC invocation (a single invocation may compile multiple modules)
153   * never treated as a candidate by the free-variable finder;
154         it's a constant!
155
156 A LocalId is 
157   * bound within an expression (lambda, case, local let(rec))
158   * or defined at top level in the module being compiled
159   * always treated as a candidate by the free-variable finder
160
161 After CoreTidy, top-level LocalIds are turned into GlobalIds
162
163 \begin{code}
164 instance Outputable Var where
165   ppr var = ppr (varName var) <+> ifPprDebug (brackets extra)
166         where
167           extra = case var of
168                         GlobalId {} -> ptext (sLit "gid")
169                         LocalId  {} -> ptext (sLit "lid")
170                         TyVar    {} -> ptext (sLit "tv")
171                         TcTyVar {tcTyVarDetails = details} -> pprTcTyVarDetails details
172
173 instance Show Var where
174   showsPrec p var = showsPrecSDoc p (ppr var)
175
176 instance NamedThing Var where
177   getName = varName
178
179 instance Uniquable Var where
180   getUnique = varUnique
181
182 instance Eq Var where
183     a == b = realUnique a ==# realUnique b
184
185 instance Ord Var where
186     a <= b = realUnique a <=# realUnique b
187     a <  b = realUnique a <#  realUnique b
188     a >= b = realUnique a >=# realUnique b
189     a >  b = realUnique a >#  realUnique b
190     a `compare` b = varUnique a `compare` varUnique b
191 \end{code}
192
193
194 \begin{code}
195 varUnique :: Var -> Unique
196 varUnique var = mkUniqueGrimily (iBox (realUnique var))
197
198 setVarUnique :: Var -> Unique -> Var
199 setVarUnique var uniq 
200   = var { realUnique = getKeyFastInt uniq, 
201           varName = setNameUnique (varName var) uniq }
202
203 setVarName :: Var -> Name -> Var
204 setVarName var new_name
205   = var { realUnique = getKeyFastInt (getUnique new_name), 
206           varName = new_name }
207
208 setVarType :: Id -> Type -> Id
209 setVarType id ty = id { varType = ty }
210
211 setIdVarExported :: Var -> Var
212 -- ^ Exports the given local 'Id'. Can also be called on global 'Id's, such as data constructors
213 -- and class operations, which are born as global 'Id's and automatically exported
214 setIdVarExported id@(LocalId {}) = id { lclDetails = Exported }
215 setIdVarExported other_id             = ASSERT( isIdVar other_id ) other_id
216
217 setIdVarNotExported :: Id -> Id
218 -- ^ We can only do this to LocalIds
219 setIdVarNotExported id = ASSERT( isLocalIdVar id ) id { lclDetails = NotExported }
220
221 globaliseIdVar :: GlobalIdDetails -> Var -> Var
222 -- ^ If it's a local, make it global
223 globaliseIdVar details id = GlobalId { varName    = varName id,
224                                     realUnique = realUnique id,
225                                     varType    = varType id,
226                                     idInfo_    = varIdInfo id,
227                                     gblDetails = details }
228
229 -- | Extract 'Id' information from the 'Var' if it represents a global or local 'Id', otherwise panic
230 varIdInfo :: Var -> IdInfo
231 varIdInfo (GlobalId {idInfo_ = info}) = info
232 varIdInfo (LocalId  {idInfo_ = info}) = info
233 varIdInfo other_var                = pprPanic "idInfo" (ppr other_var)
234
235 lazySetVarIdInfo :: Var -> IdInfo -> Var
236 lazySetVarIdInfo id info = id { idInfo_ = info }
237 \end{code}
238
239
240 %************************************************************************
241 %*                                                                      *
242 \subsection{Type variables}
243 %*                                                                      *
244 %************************************************************************
245
246 \begin{code}
247 type TyVar = Var
248
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   = -- TOM: no longer valid assertion? 
277     -- ASSERT( not (isCoercionKind kind) )
278     TcTyVar {   varName    = name,
279                 realUnique = getKeyFastInt (nameUnique name),
280                 varType  = kind,
281                 tcTyVarDetails = details
282         }
283 \end{code}
284
285 %************************************************************************
286 %*                                                                      *
287 \subsection{Coercion variables}
288 %*                                                                      *
289 %************************************************************************
290
291 \begin{code}
292 type CoVar = Var        -- ^ A coercion variable is simply a type 
293                         -- variable of kind @ty1 :=: ty2@. Hence its
294                         -- 'varType' is always @PredTy (EqPred t1 t2)@
295
296 coVarName :: CoVar -> Name
297 coVarName = varName
298
299 setCoVarUnique :: CoVar -> Unique -> CoVar
300 setCoVarUnique = setVarUnique
301
302 setCoVarName :: CoVar -> Name -> CoVar
303 setCoVarName   = setVarName
304
305 mkCoVar :: Name -> Kind -> CoVar
306 mkCoVar name kind = ASSERT( isCoercionKind kind )
307                     TyVar { varName       = name
308                           , realUnique    = getKeyFastInt (nameUnique name)
309                           , varType       = kind
310                           , isCoercionVar = True
311                         }
312
313 mkWildCoVar :: Kind -> TyVar
314 -- ^ Create a type variable that is never referred to, so its unique doesn't matter
315 mkWildCoVar kind 
316   = ASSERT( isCoercionKind kind )
317     TyVar { varName = mkSysTvName wild_uniq (fsLit "co_wild"),
318             realUnique = _ILIT(1),
319             varType = kind,
320             isCoercionVar = True }
321   where
322     wild_uniq = mkBuiltinUnique 1
323
324 \end{code}
325
326 %************************************************************************
327 %*                                                                      *
328 \subsection{Ids}
329 %*                                                                      *
330 %************************************************************************
331
332 \begin{code}
333
334 -- These synonyms are here and not in Id because otherwise we need a very
335 -- large number of SOURCE imports of Id.hs :-(
336 type Id = Var
337 type DictId = Var
338
339 \end{code}
340
341 %************************************************************************
342 %*                                                                      *
343 \subsection{Predicates over variables}
344 %*                                                                      *
345 %************************************************************************
346
347 \begin{code}
348 -- | For an explanation of global vs. local 'Var's, see "Var#globalvslocal"
349 mkGlobalIdVar :: GlobalIdDetails -> Name -> Type -> IdInfo -> Var
350 mkGlobalIdVar details name ty info 
351   = GlobalId {  varName    = name, 
352                 realUnique = getKeyFastInt (nameUnique name),   -- Cache the unique
353                 varType     = ty,       
354                 gblDetails = details,
355                 idInfo_    = info }
356
357 mkLocalIdVar' :: Name -> Type -> LocalIdDetails -> IdInfo -> Var
358 mkLocalIdVar' name ty details info
359   = LocalId {   varName    = name, 
360                 realUnique = getKeyFastInt (nameUnique name),   -- Cache the unique
361                 varType     = ty,       
362                 lclDetails = details,
363                 idInfo_    = info }
364
365 -- | For an explanation of global vs. local 'Var's, see "Var#globalvslocal"
366 mkLocalIdVar :: Name -> Type -> IdInfo -> Var
367 mkLocalIdVar name ty info = mkLocalIdVar' name ty NotExported info
368
369 -- | Exported 'Var's will not be removed as dead code
370 mkExportedLocalIdVar :: Name -> Type -> IdInfo -> Var
371 mkExportedLocalIdVar name ty info = mkLocalIdVar' name ty Exported info
372 \end{code}
373
374 \begin{code}
375 isTyVar :: Var -> Bool
376 isTyVar (TyVar {})   = True
377 isTyVar (TcTyVar {}) = True
378 isTyVar _            = False
379
380 isTcTyVar :: Var -> Bool
381 isTcTyVar (TcTyVar {}) = True
382 isTcTyVar _            = False
383
384 isIdVar :: Var -> Bool
385 isIdVar (LocalId {})  = True
386 isIdVar (GlobalId {}) = True
387 isIdVar _             = False
388
389 isLocalIdVar :: Var -> Bool
390 isLocalIdVar (LocalId {}) = True
391 isLocalIdVar _            = False
392
393 isCoVar :: Var -> Bool
394 isCoVar (v@(TyVar {})) = isCoercionVar v
395 isCoVar _              = False
396
397 -- | 'isLocalVar' returns @True@ for type variables as well as local 'Id's
398 -- These are the variables that we need to pay attention to when finding free
399 -- variables, or doing dependency analysis.
400 isLocalVar :: Var -> Bool
401 isLocalVar (GlobalId {}) = False 
402 isLocalVar _             = True
403
404 -- | 'mustHaveLocalBinding' returns @True@ of 'Id's and 'TyVar's
405 -- that must have a binding in this module.  The converse
406 -- is not quite right: there are some global 'Id's that must have
407 -- bindings, such as record selectors.  But that doesn't matter,
408 -- because it's only used for assertions
409 mustHaveLocalBinding        :: Var -> Bool
410 mustHaveLocalBinding var = isLocalVar var
411
412 isGlobalIdVar :: Var -> Bool
413 isGlobalIdVar (GlobalId {}) = True
414 isGlobalIdVar _             = False
415
416 -- | 'isExportedIdVar' means \"don't throw this away\"
417 isExportedIdVar :: Var -> Bool
418 isExportedIdVar (GlobalId {}) = True
419 isExportedIdVar (LocalId {lclDetails = details}) 
420   = case details of
421         Exported   -> True
422         _          -> False
423 isExportedIdVar _ = False
424 \end{code}
425
426 \begin{code}
427 globalIdVarDetails :: Var -> GlobalIdDetails
428 -- ^ Find the global 'Id' information if the 'Var' is a global 'Id', otherwise returns 'notGlobalId'
429 globalIdVarDetails (GlobalId {gblDetails = details}) = details
430 globalIdVarDetails _                                 = notGlobalId
431 \end{code}