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