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