Make various assertions work when !DEBUG
[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 = getKey# uniq, 
170           varName = setNameUnique (varName var) uniq }
171
172 setVarName :: Var -> Name -> Var
173 setVarName var new_name
174   = var { realUnique = getKey# (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 = getKey# (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 = getKey# (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 = getKey# (nameUnique name)
236                           , varType  = kind
237                           , isCoercionVar    = True
238                         }
239
240 mkWildCoVar :: Kind -> TyVar
241 -- A type variable that is never referred to,
242 -- so its unique doesn't matter
243 mkWildCoVar kind 
244   = ASSERT( isCoercionKind kind )
245     TyVar { varName = mkSysTvName wild_uniq FSLIT("co_wild"),
246             realUnique = _ILIT(1),
247             varType = kind,
248             isCoercionVar = True }
249   where
250     wild_uniq = mkBuiltinUnique 1
251 \end{code}
252
253 %************************************************************************
254 %*                                                                      *
255 \subsection{Id Construction}
256 %*                                                                      *
257 %************************************************************************
258
259 Most Id-related functions are in Id.lhs and MkId.lhs
260
261 \begin{code}
262 type Id     = Var
263 type DictId = Id
264 \end{code}
265
266 \begin{code}
267 idName    = varName
268 idUnique  = varUnique
269 idType    = varType
270
271 setIdUnique :: Id -> Unique -> Id
272 setIdUnique = setVarUnique
273
274 setIdName :: Id -> Name -> Id
275 setIdName = setVarName
276
277 setIdType :: Id -> Type -> Id
278 setIdType id ty = id {varType = ty}
279
280 setIdExported :: Id -> Id
281 -- Can be called on GlobalIds, such as data cons and class ops,
282 -- which are "born" as GlobalIds and automatically exported
283 setIdExported id@(LocalId {}) = id { lclDetails = Exported }
284 setIdExported other_id        = ASSERT( isId other_id ) other_id
285
286 setIdNotExported :: Id -> Id
287 -- We can only do this to LocalIds
288 setIdNotExported id = ASSERT( isLocalId id ) id { lclDetails = NotExported }
289
290 globaliseId :: GlobalIdDetails -> Id -> Id
291 -- If it's a local, make it global
292 globaliseId details id = GlobalId { varName    = varName id,
293                                     realUnique = realUnique id,
294                                     varType    = varType id,
295                                     idInfo_    = idInfo id,
296                                     gblDetails = details }
297
298 idInfo :: Id -> IdInfo
299 idInfo (GlobalId {idInfo_ = info}) = info
300 idInfo (LocalId  {idInfo_ = info}) = info
301 idInfo other_var                   = pprPanic "idInfo" (ppr other_var)
302
303 lazySetIdInfo :: Id -> IdInfo -> Id
304 lazySetIdInfo id info = id {idInfo_ = info}
305
306 setIdInfo :: Id -> IdInfo -> Id
307 setIdInfo id info = seqIdInfo info `seq` id {idInfo_ = info}
308         -- Try to avoid spack leaks by seq'ing
309
310 modifyIdInfo :: (IdInfo -> IdInfo) -> Id -> Id
311 modifyIdInfo fn id
312   = seqIdInfo new_info `seq` id {idInfo_ = new_info}
313   where
314     new_info = fn (idInfo id)
315
316 -- maybeModifyIdInfo tries to avoid unnecesary thrashing
317 maybeModifyIdInfo :: Maybe IdInfo -> Id -> Id
318 maybeModifyIdInfo (Just new_info) id = id {idInfo_ = new_info}
319 maybeModifyIdInfo Nothing         id = id
320 \end{code}
321
322 %************************************************************************
323 %*                                                                      *
324 \subsection{Predicates over variables
325 %*                                                                      *
326 %************************************************************************
327
328 \begin{code}
329 mkGlobalId :: GlobalIdDetails -> Name -> Type -> IdInfo -> Id
330 mkGlobalId details name ty info 
331   = GlobalId {  varName    = name, 
332                 realUnique = getKey# (nameUnique name),         -- Cache the unique
333                 varType     = ty,       
334                 gblDetails = details,
335                 idInfo_    = info }
336
337 mk_local_id :: Name -> Type -> LocalIdDetails -> IdInfo -> Id
338 mk_local_id name ty details info
339   = LocalId {   varName    = name, 
340                 realUnique = getKey# (nameUnique name),         -- Cache the unique
341                 varType     = ty,       
342                 lclDetails = details,
343                 idInfo_    = info }
344
345 mkLocalId :: Name -> Type -> IdInfo -> Id
346 mkLocalId name ty info = mk_local_id name ty NotExported info
347
348 mkExportedLocalId :: Name -> Type -> IdInfo -> Id
349 mkExportedLocalId name ty info = mk_local_id name ty Exported info
350 \end{code}
351
352 \begin{code}
353 isTyVar, isTcTyVar          :: Var -> Bool
354 isId, isLocalVar, isLocalId :: Var -> Bool
355 isGlobalId, isExportedId    :: Var -> Bool
356 mustHaveLocalBinding        :: Var -> Bool
357
358 isTyVar (TyVar {})   = True
359 isTyVar (TcTyVar {}) = True
360 isTyVar other        = False
361
362 isTcTyVar (TcTyVar {}) = True
363 isTcTyVar other        = False
364
365 isId (LocalId {})  = True
366 isId (GlobalId {}) = True
367 isId other         = False
368
369 isLocalId (LocalId {}) = True
370 isLocalId other        = False
371
372 isCoVar (v@(TyVar {})) = isCoercionVar v
373 isCoVar other          = False
374
375 -- isLocalVar returns True for type variables as well as local Ids
376 -- These are the variables that we need to pay attention to when finding free
377 -- variables, or doing dependency analysis.
378 isLocalVar (GlobalId {}) = False 
379 isLocalVar other         = True
380
381 -- mustHaveLocalBinding returns True of Ids and TyVars
382 -- that must have a binding in this module.  The converse
383 -- is not quite right: there are some GlobalIds that must have
384 -- bindings, such as record selectors.  But that doesn't matter,
385 -- because it's only used for assertions
386 mustHaveLocalBinding var = isLocalVar var
387
388 isGlobalId (GlobalId {}) = True
389 isGlobalId other         = False
390
391 -- isExportedId means "don't throw this away"
392 isExportedId (GlobalId {}) = True
393 isExportedId (LocalId {lclDetails = details}) 
394   = case details of
395         Exported   -> True
396         other      -> False
397 isExportedId other = False
398 \end{code}
399
400 \begin{code}
401 globalIdDetails :: Var -> GlobalIdDetails
402 -- Works OK on local Ids too, returning notGlobalId
403 globalIdDetails (GlobalId {gblDetails = details}) = details
404 globalIdDetails other                             = notGlobalId
405 \end{code}
406