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