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