[project @ 2001-12-10 14:00:35 by simonmar]
[ghc-hetmet.git] / ghc / compiler / basicTypes / Name.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[Name]{@Name@: to transmit name info from renamer to typechecker}
5
6 \begin{code}
7 module Name (
8         -- Re-export the OccName stuff
9         module OccName,
10
11         -- The Name type
12         Name,                                   -- Abstract
13         mkLocalName, mkSysLocalName, mkFCallName,
14         mkIPName,
15         mkGlobalName, mkKnownKeyGlobal, mkWiredInName,
16
17         nameUnique, setNameUnique,
18         nameOccName, nameModule, nameModule_maybe,
19         setNameOcc, nameRdrName, setNameModuleAndLoc, 
20         toRdrName, hashName, 
21         globaliseName, localiseName,
22
23         nameSrcLoc, 
24
25         isSystemName, isLocalName, isGlobalName, isExternallyVisibleName,
26         isTyVarName, isDllName, 
27         nameIsLocalOrFrom, isHomePackageName,
28         
29         -- Class NamedThing and overloaded friends
30         NamedThing(..),
31         getSrcLoc, getOccString, toRdrName
32     ) where
33
34 #include "HsVersions.h"
35
36 import OccName          -- All of it
37 import Module           ( Module, moduleName, mkVanillaModule, isHomeModule )
38 import RdrName          ( RdrName, mkRdrOrig, mkRdrUnqual, rdrNameOcc, rdrNameModule )
39 import CmdLineOpts      ( opt_Static )
40 import SrcLoc           ( builtinSrcLoc, noSrcLoc, SrcLoc )
41 import Unique           ( Unique, Uniquable(..), u2i, pprUnique )
42 import FastTypes
43 import Outputable
44 \end{code}
45
46 %************************************************************************
47 %*                                                                      *
48 \subsection[Name-datatype]{The @Name@ datatype, and name construction}
49 %*                                                                      *
50 %************************************************************************
51  
52 \begin{code}
53 data Name = Name {
54                 n_sort :: NameSort,     -- What sort of name it is
55                 n_occ  :: !OccName,     -- Its occurrence name
56                 n_uniq :: Unique,
57                 n_loc  :: !SrcLoc       -- Definition site
58             }
59
60 -- NOTE: we make the n_loc field strict to eliminate some potential
61 -- (and real!) space leaks, due to the fact that we don't look at
62 -- the SrcLoc in a Name all that often.
63
64 data NameSort
65   = Global Module       -- (a) TyCon, Class, their derived Ids, dfun Id
66                         -- (b) Imported Id
67                         -- (c) Top-level Id in the original source, even if
68                         --      locally defined
69
70   | Local               -- A user-defined Id or TyVar
71                         -- defined in the module being compiled
72
73   | System              -- A system-defined Id or TyVar.  Typically the
74                         -- OccName is very uninformative (like 's')
75 \end{code}
76
77 Notes about the NameSorts:
78
79 1.  Initially, top-level Ids (including locally-defined ones) get Global names, 
80     and all other local Ids get Local names
81
82 2.  Things with a @Global@ name are given C static labels, so they finally
83     appear in the .o file's symbol table.  They appear in the symbol table
84     in the form M.n.  If originally-local things have this property they
85     must be made @Global@ first.
86
87 3.  In the tidy-core phase, a Global that is not visible to an importer
88     is changed to Local, and a Local that is visible is changed to Global
89
90 4.  A System Name differs in the following ways:
91         a) has unique attached when printing dumps
92         b) unifier eliminates sys tyvars in favour of user provs where possible
93
94     Before anything gets printed in interface files or output code, it's
95     fed through a 'tidy' processor, which zaps the OccNames to have
96     unique names; and converts all sys-locals to user locals
97     If any desugarer sys-locals have survived that far, they get changed to
98     "ds1", "ds2", etc.
99
100 \begin{code}
101 nameUnique              :: Name -> Unique
102 nameOccName             :: Name -> OccName 
103 nameModule              :: Name -> Module
104 nameSrcLoc              :: Name -> SrcLoc
105
106 nameUnique  name = n_uniq name
107 nameOccName name = n_occ  name
108 nameSrcLoc  name = n_loc  name
109
110 nameModule (Name { n_sort = Global mod }) = mod
111 nameModule name                           = pprPanic "nameModule" (ppr name)
112
113 nameModule_maybe (Name { n_sort = Global mod }) = Just mod
114 nameModule_maybe name                           = Nothing
115 \end{code}
116
117 \begin{code}
118 nameIsLocalOrFrom       :: Module -> Name -> Bool
119 isLocalName             :: Name -> Bool         -- Not globals
120 isGlobalName            :: Name -> Bool
121 isSystemName            :: Name -> Bool
122 isExternallyVisibleName :: Name -> Bool
123 isHomePackageName       :: Name -> Bool
124
125 isGlobalName (Name {n_sort = Global _}) = True
126 isGlobalName other                      = False
127
128 isLocalName name = not (isGlobalName name)
129
130 nameIsLocalOrFrom from (Name {n_sort = Global mod}) = mod == from
131 nameIsLocalOrFrom from other                        = True
132
133 isHomePackageName (Name {n_sort = Global mod}) = isHomeModule mod
134 isHomePackageName other                        = True   -- Local and system names
135
136 isDllName :: Name -> Bool       -- Does this name refer to something in a different DLL?
137 isDllName nm = not opt_Static && not (isHomePackageName nm)
138
139 isTyVarName :: Name -> Bool
140 isTyVarName name = isTvOcc (nameOccName name)
141
142 -- Global names are by definition those that are visible
143 -- outside the module, *as seen by the linker*.  Externally visible
144 -- does not mean visible at the source level
145 isExternallyVisibleName name = isGlobalName name
146
147 isSystemName (Name {n_sort = System}) = True
148 isSystemName other                    = False
149 \end{code}
150
151
152 %************************************************************************
153 %*                                                                      *
154 \subsection{Making names}
155 %*                                                                      *
156 %************************************************************************
157
158 \begin{code}
159 mkLocalName :: Unique -> OccName -> SrcLoc -> Name
160 mkLocalName uniq occ loc = Name { n_uniq = uniq, n_sort = Local, n_occ = occ, n_loc = loc }
161         -- NB: You might worry that after lots of huffing and
162         -- puffing we might end up with two local names with distinct
163         -- uniques, but the same OccName.  Indeed we can, but that's ok
164         --      * the insides of the compiler don't care: they use the Unique
165         --      * when printing for -ddump-xxx you can switch on -dppr-debug to get the
166         --        uniques if you get confused
167         --      * for interface files we tidyCore first, which puts the uniques
168         --        into the print name (see setNameVisibility below)
169
170 mkGlobalName :: Unique -> Module -> OccName -> SrcLoc -> Name
171 mkGlobalName uniq mod occ loc = Name { n_uniq = uniq, n_sort = Global mod,
172                                        n_occ = occ, n_loc = loc }
173
174 mkKnownKeyGlobal :: RdrName -> Unique -> Name
175 mkKnownKeyGlobal rdr_name uniq
176   = mkGlobalName uniq (mkVanillaModule (rdrNameModule rdr_name))
177                       (rdrNameOcc rdr_name)
178                       builtinSrcLoc
179
180 mkWiredInName :: Module -> OccName -> Unique -> Name
181 mkWiredInName mod occ uniq = mkGlobalName uniq mod occ builtinSrcLoc
182
183 mkSysLocalName :: Unique -> UserFS -> Name
184 mkSysLocalName uniq fs = Name { n_uniq = uniq, n_sort = System, 
185                                 n_occ = mkVarOcc fs, n_loc = noSrcLoc }
186
187 mkFCallName :: Unique -> EncodedString -> Name
188         -- The encoded string completely describes the ccall
189 mkFCallName uniq str =  Name { n_uniq = uniq, n_sort = Local, 
190                                n_occ = mkFCallOcc str, n_loc = noSrcLoc }
191
192 mkIPName :: Unique -> OccName -> Name
193 mkIPName uniq occ
194   = Name { n_uniq = uniq,
195            n_sort = Local,
196            n_occ  = occ,
197            n_loc = noSrcLoc }
198 \end{code}
199
200 \begin{code}
201 -- When we renumber/rename things, we need to be
202 -- able to change a Name's Unique to match the cached
203 -- one in the thing it's the name of.  If you know what I mean.
204 setNameUnique name uniq = name {n_uniq = uniq}
205
206 setNameOcc :: Name -> OccName -> Name
207 setNameOcc name occ = name {n_occ = occ}
208
209 globaliseName :: Name -> Module -> Name
210 globaliseName n mod = n { n_sort = Global mod }
211                                 
212 localiseName :: Name -> Name
213 localiseName n = n { n_sort = Local }
214                                 
215 setNameModuleAndLoc :: Name -> Module -> SrcLoc -> Name
216 setNameModuleAndLoc name mod loc = name {n_sort = set (n_sort name), n_loc = loc}
217                        where
218                          set (Global _) = Global mod
219 \end{code}
220
221
222 %************************************************************************
223 %*                                                                      *
224 \subsection{Predicates and selectors}
225 %*                                                                      *
226 %************************************************************************
227
228 \begin{code}
229 hashName :: Name -> Int
230 hashName name = iBox (u2i (nameUnique name))
231
232
233 nameRdrName :: Name -> RdrName
234 -- Makes a qualified name for top-level (Global) names, whether locally defined or not
235 -- and an unqualified name just for Locals
236 nameRdrName (Name { n_occ = occ, n_sort = Global mod }) = mkRdrOrig (moduleName mod) occ
237 nameRdrName (Name { n_occ = occ })                      = mkRdrUnqual occ
238 \end{code}
239
240
241 %************************************************************************
242 %*                                                                      *
243 \subsection[Name-instances]{Instance declarations}
244 %*                                                                      *
245 %************************************************************************
246
247 \begin{code}
248 cmpName n1 n2 = n_uniq n1 `compare` n_uniq n2
249 \end{code}
250
251 \begin{code}
252 instance Eq Name where
253     a == b = case (a `compare` b) of { EQ -> True;  _ -> False }
254     a /= b = case (a `compare` b) of { EQ -> False; _ -> True }
255
256 instance Ord Name where
257     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
258     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
259     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
260     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
261     compare a b = cmpName a b
262
263 instance Uniquable Name where
264     getUnique = nameUnique
265
266 instance NamedThing Name where
267     getName n = n
268 \end{code}
269
270
271 %************************************************************************
272 %*                                                                      *
273 \subsection{Pretty printing}
274 %*                                                                      *
275 %************************************************************************
276
277 \begin{code}
278 instance Outputable Name where
279         -- When printing interfaces, all Locals have been given nice print-names
280     ppr name = pprName name
281
282 pprName name@(Name {n_sort = sort, n_uniq = uniq, n_occ = occ})
283   = getPprStyle $ \ sty ->
284     case sort of
285       Global mod -> pprGlobal sty name uniq mod occ
286       System     -> pprSysLocal sty uniq occ
287       Local      -> pprLocal sty uniq occ
288
289 pprGlobal sty name uniq mod occ
290   | codeStyle sty        = ppr (moduleName mod) <> char '_' <> pprOccName occ
291
292   | debugStyle sty       = ppr (moduleName mod) <> dot <> pprOccName occ <> 
293                             text "{-" <> pprUnique uniq <> text "-}"
294
295   | unqualStyle sty name = pprOccName occ
296   | otherwise            = ppr (moduleName mod) <> dot <> pprOccName occ
297
298 pprLocal sty uniq occ
299   | codeStyle sty  = pprUnique uniq
300   | debugStyle sty = pprOccName occ <> 
301                      text "{-" <> pprUnique uniq <> text "-}"
302   | otherwise      = pprOccName occ     -- User and Iface styles
303
304 -- Like Local, except that we only omit the unique in Iface style
305 pprSysLocal sty uniq occ
306   | codeStyle sty  = pprUnique uniq
307   | ifaceStyle sty = pprOccName occ     -- The tidy phase has ensured 
308                                         -- that OccNames are enough
309   | otherwise      = pprOccName occ <> char '_' <> pprUnique uniq
310                                 -- If the tidy phase hasn't run, the OccName
311                                 -- is unlikely to be informative (like 's'),
312                                 -- so print the unique
313 \end{code}
314
315 %************************************************************************
316 %*                                                                      *
317 \subsection{Overloaded functions related to Names}
318 %*                                                                      *
319 %************************************************************************
320
321 \begin{code}
322 class NamedThing a where
323     getOccName :: a -> OccName
324     getName    :: a -> Name
325
326     getOccName n = nameOccName (getName n)      -- Default method
327 \end{code}
328
329 \begin{code}
330 getSrcLoc           :: NamedThing a => a -> SrcLoc
331 getOccString        :: NamedThing a => a -> String
332 toRdrName           :: NamedThing a => a -> RdrName
333
334 getSrcLoc           = nameSrcLoc           . getName
335 getOccString        = occNameString        . getOccName
336 toRdrName           = nameRdrName          . getName
337 \end{code}
338