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