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