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