[project @ 2004-01-05 10:41:04 by simonpj]
[ghc-hetmet.git] / ghc / compiler / basicTypes / Var.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section{@Vars@: Variables}
5
6 \begin{code}
7 module Var (
8         Var, 
9         varName, varUnique, 
10         setVarName, setVarUnique, setVarOcc,
11
12         -- TyVars
13         TyVar, mkTyVar, mkTcTyVar,
14         tyVarName, tyVarKind,
15         setTyVarName, setTyVarUnique,
16         tcTyVarRef, tcTyVarDetails,
17
18         -- Ids
19         Id, DictId,
20         idName, idType, idUnique, idInfo, modifyIdInfo, maybeModifyIdInfo,
21         setIdName, setIdUnique, setIdType, setIdInfo, lazySetIdInfo, 
22         setIdLocalExported, zapSpecPragmaId,
23
24         globalIdDetails, globaliseId, 
25
26         mkLocalId, mkExportedLocalId, mkSpecPragmaId,
27         mkGlobalId, 
28
29         isTyVar, isTcTyVar, isId, isLocalVar, isLocalId,
30         isGlobalId, isExportedId, isSpecPragmaId,
31         mustHaveLocalBinding
32     ) where
33
34 #include "HsVersions.h"
35
36 import {-# SOURCE #-}   TypeRep( Type )
37 import {-# SOURCE #-}   TcType( TyVarDetails )
38 import {-# SOURCE #-}   IdInfo( GlobalIdDetails, notGlobalId,
39                                 IdInfo, seqIdInfo )
40
41 import Name             ( Name, OccName, NamedThing(..),
42                           setNameUnique, setNameOcc, nameUnique
43                         )
44 import Kind             ( Kind )
45 import Unique           ( Unique, Uniquable(..), mkUniqueGrimily, getKey# )
46 import FastTypes
47 import Outputable
48 import DATA_IOREF
49 \end{code}
50
51
52 %************************************************************************
53 %*                                                                      *
54 \subsection{The main data type declarations}
55 %*                                                                      *
56 %************************************************************************
57
58
59 Every @Var@ has a @Unique@, to uniquify it and for fast comparison, a
60 @Type@, and an @IdInfo@ (non-essential info about it, e.g.,
61 strictness).  The essential info about different kinds of @Vars@ is
62 in its @VarDetails@.
63
64 \begin{code}
65 data Var
66   = TyVar {
67         varName    :: !Name,
68         realUnique :: FastInt,          -- Key for fast comparison
69                                         -- Identical to the Unique in the name,
70                                         -- cached here for speed
71         tyVarKind :: Kind }
72
73   | TcTyVar {                   -- Used only during type inference
74         varName        :: !Name,        -- Could we get away without a Name?
75         realUnique     :: FastInt,
76         tyVarKind      :: Kind,
77         tcTyVarRef     :: IORef (Maybe Type),
78         tcTyVarDetails :: TyVarDetails }
79
80   | GlobalId {                  -- Used for imported Ids, dict selectors etc
81         varName    :: !Name,
82         realUnique :: FastInt,
83         idType     :: Type,
84         idInfo     :: IdInfo,
85         gblDetails :: GlobalIdDetails }
86
87   | LocalId {                   -- Used for locally-defined Ids (see NOTE below)
88         varName    :: !Name,
89         realUnique :: FastInt,
90         idType     :: Type,
91         idInfo     :: IdInfo,
92         lclDetails :: LocalIdDetails }
93
94 data LocalIdDetails 
95   = NotExported -- Not exported
96   | Exported    -- Exported
97   | SpecPragma  -- Not exported, but not to be discarded either
98                 -- It's unclean that this is so deeply built in
99 \end{code}
100
101 LocalId and GlobalId
102 ~~~~~~~~~~~~~~~~~~~~
103 A GlobalId is
104   * always a constant (top-level)
105   * imported, or data constructor, or primop, or record selector
106   * has a Unique that is globally unique across the whole
107     GHC invocation (a single invocation may compile multiple modules)
108
109 A LocalId is 
110   * bound within an expression (lambda, case, local let(rec))
111   * or defined at top level in the module being compiled
112
113 After CoreTidy, top-level LocalIds are turned into GlobalIds
114  
115
116 \begin{code}
117 instance Outputable Var where
118   ppr var = ppr (varName var)
119
120 instance Show Var where
121   showsPrec p var = showsPrecSDoc p (ppr var)
122
123 instance NamedThing Var where
124   getName = varName
125
126 instance Uniquable Var where
127   getUnique = varUnique
128
129 instance Eq Var where
130     a == b = realUnique a ==# realUnique b
131
132 instance Ord Var where
133     a <= b = realUnique a <=# realUnique b
134     a <  b = realUnique a <#  realUnique b
135     a >= b = realUnique a >=# realUnique b
136     a >  b = realUnique a >#  realUnique b
137     a `compare` b = varUnique a `compare` varUnique b
138 \end{code}
139
140
141 \begin{code}
142 varUnique :: Var -> Unique
143 varUnique var = mkUniqueGrimily (iBox (realUnique var))
144
145 setVarUnique :: Var -> Unique -> Var
146 setVarUnique var uniq 
147   = var { realUnique = getKey# uniq, 
148           varName = setNameUnique (varName var) uniq }
149
150 setVarName :: Var -> Name -> Var
151 setVarName var new_name
152   = var { realUnique = getKey# (getUnique new_name), 
153           varName = new_name }
154
155 setVarOcc :: Var -> OccName -> Var
156 setVarOcc var new_occ
157   = var { varName = setNameOcc (varName var) new_occ }
158 \end{code}
159
160
161 %************************************************************************
162 %*                                                                      *
163 \subsection{Type variables}
164 %*                                                                      *
165 %************************************************************************
166
167 \begin{code}
168 type TyVar = Var
169
170 tyVarName = varName
171
172 setTyVarUnique = setVarUnique
173 setTyVarName   = setVarName
174 \end{code}
175
176 \begin{code}
177 mkTyVar :: Name -> Kind -> TyVar
178 mkTyVar name kind = TyVar { varName    = name
179                           , realUnique = getKey# (nameUnique name)
180                           , tyVarKind  = kind
181                         }
182
183 mkTcTyVar :: Name -> Kind -> TyVarDetails -> IORef (Maybe Type) -> TyVar
184 mkTcTyVar name kind details ref
185   = TcTyVar {   varName    = name,
186                 realUnique = getKey# (nameUnique name),
187                 tyVarKind  = kind,
188                 tcTyVarRef = ref,
189                 tcTyVarDetails = details
190         }
191 \end{code}
192
193
194 %************************************************************************
195 %*                                                                      *
196 \subsection{Id Construction}
197 %*                                                                      *
198 %************************************************************************
199
200 Most Id-related functions are in Id.lhs and MkId.lhs
201
202 \begin{code}
203 type Id     = Var
204 type DictId = Id
205 \end{code}
206
207 \begin{code}
208 idName    = varName
209 idUnique  = varUnique
210
211 setIdUnique :: Id -> Unique -> Id
212 setIdUnique = setVarUnique
213
214 setIdName :: Id -> Name -> Id
215 setIdName = setVarName
216
217 setIdType :: Id -> Type -> Id
218 setIdType id ty = id {idType = ty}
219
220 setIdLocalExported :: Id -> Id
221 -- It had better be a LocalId already
222 setIdLocalExported id = id { lclDetails = Exported }
223
224 globaliseId :: GlobalIdDetails -> Id -> Id
225 -- If it's a local, make it global
226 globaliseId details id = GlobalId { varName    = varName id,
227                                     realUnique = realUnique id,
228                                     idType     = idType id,
229                                     idInfo     = idInfo id,
230                                     gblDetails = details }
231
232 zapSpecPragmaId :: Id -> Id
233 zapSpecPragmaId id
234   | isSpecPragmaId id = id {lclDetails = NotExported}
235   | otherwise         = id
236
237 lazySetIdInfo :: Id -> IdInfo -> Id
238 lazySetIdInfo id info = id {idInfo = info}
239
240 setIdInfo :: Id -> IdInfo -> Id
241 setIdInfo id info = seqIdInfo info `seq` id {idInfo = info}
242         -- Try to avoid spack leaks by seq'ing
243
244 modifyIdInfo :: (IdInfo -> IdInfo) -> Id -> Id
245 modifyIdInfo fn id
246   = seqIdInfo new_info `seq` id {idInfo = new_info}
247   where
248     new_info = fn (idInfo id)
249
250 -- maybeModifyIdInfo tries to avoid unnecesary thrashing
251 maybeModifyIdInfo :: (IdInfo -> Maybe IdInfo) -> Id -> Id
252 maybeModifyIdInfo fn id
253   = case fn (idInfo id) of
254         Nothing       -> id
255         Just new_info -> id {idInfo = new_info}
256 \end{code}
257
258 %************************************************************************
259 %*                                                                      *
260 \subsection{Predicates over variables
261 %*                                                                      *
262 %************************************************************************
263
264 \begin{code}
265 mkGlobalId :: GlobalIdDetails -> Name -> Type -> IdInfo -> Id
266 mkGlobalId details name ty info 
267   = GlobalId {  varName    = name, 
268                 realUnique = getKey# (nameUnique name),         -- Cache the unique
269                 idType     = ty,        
270                 gblDetails = details,
271                 idInfo     = info }
272
273 mk_local_id :: Name -> Type -> LocalIdDetails -> IdInfo -> Id
274 mk_local_id name ty details info
275   = LocalId {   varName    = name, 
276                 realUnique = getKey# (nameUnique name),         -- Cache the unique
277                 idType     = ty,        
278                 lclDetails = details,
279                 idInfo     = info }
280
281 mkLocalId :: Name -> Type -> IdInfo -> Id
282 mkLocalId name ty info = mk_local_id name ty NotExported info
283
284 mkExportedLocalId :: Name -> Type -> IdInfo -> Id
285 mkExportedLocalId name ty info = mk_local_id name ty Exported info
286
287 mkSpecPragmaId :: Name -> Type -> IdInfo -> Id
288 mkSpecPragmaId name ty info = mk_local_id name ty SpecPragma info
289 \end{code}
290
291 \begin{code}
292 isTyVar, isTcTyVar                       :: Var -> Bool
293 isId, isLocalVar, isLocalId              :: Var -> Bool
294 isGlobalId, isExportedId, isSpecPragmaId :: Var -> Bool
295 mustHaveLocalBinding                     :: Var -> Bool
296
297 isTyVar (TyVar {})   = True
298 isTyVar (TcTyVar {}) = True
299 isTyVar other        = False
300
301 isTcTyVar (TcTyVar {}) = True
302 isTcTyVar other        = False
303
304 isId (LocalId {})  = True
305 isId (GlobalId {}) = True
306 isId other         = False
307
308 isLocalId (LocalId {}) = True
309 isLocalId other        = False
310
311 -- isLocalVar returns True for type variables as well as local Ids
312 -- These are the variables that we need to pay attention to when finding free
313 -- variables, or doing dependency analysis.
314 isLocalVar (GlobalId {}) = False 
315 isLocalVar other         = True
316
317 -- mustHaveLocalBinding returns True of Ids and TyVars
318 -- that must have a binding in this module.  The converse
319 -- is not quite right: there are some GlobalIds that must have
320 -- bindings, such as record selectors.  But that doesn't matter,
321 -- because it's only used for assertions
322 mustHaveLocalBinding var = isLocalVar var
323
324 isGlobalId (GlobalId {}) = True
325 isGlobalId other         = False
326
327 -- isExportedId means "don't throw this away"
328 isExportedId (GlobalId {}) = True
329 isExportedId (LocalId {lclDetails = details}) 
330   = case details of
331         Exported   -> True
332         SpecPragma -> True
333         other      -> False
334 isExportedId other = False
335
336 isSpecPragmaId (LocalId {lclDetails = SpecPragma}) = True
337 isSpecPragmaId other = False
338 \end{code}
339
340 \begin{code}
341 globalIdDetails :: Var -> GlobalIdDetails
342 -- Works OK on local Ids too, returning notGlobalId
343 globalIdDetails (GlobalId {gblDetails = details}) = details
344 globalIdDetails other                             = notGlobalId
345 \end{code}
346