[project @ 2002-07-29 10:50:43 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         mkInternalName, mkSystemName, 
14         mkSystemNameEncoded, mkSystemTvNameEncoded, mkFCallName,
15         mkIPName,
16         mkExternalName, mkKnownKeyExternalName, mkWiredInName,
17
18         nameUnique, setNameUnique,
19         nameOccName, nameModule, nameModule_maybe,
20         setNameOcc, nameRdrName, setNameModuleAndLoc, 
21         toRdrName, hashName, 
22         externaliseName, localiseName,
23
24         nameSrcLoc, 
25
26         isSystemName, isInternalName, isExternalName,
27         isTyVarName, isDllName, 
28         nameIsLocalOrFrom, isHomePackageName,
29         
30         -- Class NamedThing and overloaded friends
31         NamedThing(..),
32         getSrcLoc, getOccString, toRdrName
33     ) where
34
35 #include "HsVersions.h"
36
37 import OccName          -- All of it
38 import Module           ( Module, moduleName, mkVanillaModule, isHomeModule )
39 import RdrName          ( RdrName, mkRdrOrig, mkRdrUnqual, rdrNameOcc, rdrNameModule )
40 import CmdLineOpts      ( opt_Static )
41 import SrcLoc           ( builtinSrcLoc, noSrcLoc, SrcLoc )
42 import Unique           ( Unique, Uniquable(..), getKey, 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   = External 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   | Internal            -- 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 External names, 
82     and all other local Ids get Internal names
83
84 2.  Things with a External 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 @External@ first.
88
89 3.  In the tidy-core phase, a External that is not visible to an importer
90     is changed to Internal, and a Internal that is visible is changed to External
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 = External mod }) = mod
113 nameModule name                           = pprPanic "nameModule" (ppr name)
114
115 nameModule_maybe (Name { n_sort = External mod }) = Just mod
116 nameModule_maybe name                           = Nothing
117 \end{code}
118
119 \begin{code}
120 nameIsLocalOrFrom :: Module -> Name -> Bool
121 isInternalName    :: Name -> Bool
122 isExternalName    :: Name -> Bool
123 isSystemName      :: Name -> Bool
124 isHomePackageName :: Name -> Bool
125
126 isExternalName (Name {n_sort = External _}) = True
127 isExternalName other                    = False
128
129 isInternalName name = not (isExternalName name)
130
131 nameIsLocalOrFrom from (Name {n_sort = External mod}) = mod == from
132 nameIsLocalOrFrom from other                          = True
133
134 isHomePackageName (Name {n_sort = External mod}) = isHomeModule mod
135 isHomePackageName other                          = True         -- Internal and system names
136
137 isDllName :: Name -> Bool       -- Does this name refer to something in a different DLL?
138 isDllName nm = not opt_Static && not (isHomePackageName nm)
139
140 isTyVarName :: Name -> Bool
141 isTyVarName name = isTvOcc (nameOccName 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 mkInternalName :: Unique -> OccName -> SrcLoc -> Name
156 mkInternalName uniq occ loc = Name { n_uniq = uniq, n_sort = Internal, 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 mkExternalName :: Unique -> Module -> OccName -> SrcLoc -> Name
167 mkExternalName uniq mod occ loc = Name { n_uniq = uniq, n_sort = External mod,
168                                        n_occ = occ, n_loc = loc }
169
170 mkKnownKeyExternalName :: RdrName -> Unique -> Name
171 mkKnownKeyExternalName rdr_name uniq
172   = mkExternalName uniq (mkVanillaModule (rdrNameModule rdr_name))
173                       (rdrNameOcc rdr_name)
174                       builtinSrcLoc
175
176 mkWiredInName :: Module -> OccName -> Unique -> Name
177 mkWiredInName mod occ uniq = mkExternalName uniq mod occ builtinSrcLoc
178
179 mkSystemName :: Unique -> UserFS -> Name
180 mkSystemName uniq fs = Name { n_uniq = uniq, n_sort = System, 
181                               n_occ = mkVarOcc fs, n_loc = noSrcLoc }
182
183 -- Use this version when the string is already encoded.  Avoids duplicating
184 -- the string each time a new name is created.
185 mkSystemNameEncoded :: Unique -> EncodedFS -> Name
186 mkSystemNameEncoded uniq fs = Name { n_uniq = uniq, n_sort = System, 
187                                      n_occ = mkSysOccFS varName fs, 
188                                      n_loc = noSrcLoc }
189
190 mkSystemTvNameEncoded :: Unique -> EncodedFS -> Name
191 mkSystemTvNameEncoded uniq fs = Name { n_uniq = uniq, n_sort = System, 
192                                        n_occ = mkSysOccFS tvName fs, 
193                                        n_loc = noSrcLoc }
194
195 mkFCallName :: Unique -> EncodedString -> Name
196         -- The encoded string completely describes the ccall
197 mkFCallName uniq str =  Name { n_uniq = uniq, n_sort = Internal, 
198                                n_occ = mkFCallOcc str, n_loc = noSrcLoc }
199
200 mkIPName :: Unique -> OccName -> Name
201 mkIPName uniq occ
202   = Name { n_uniq = uniq,
203            n_sort = Internal,
204            n_occ  = occ,
205            n_loc = noSrcLoc }
206 \end{code}
207
208 \begin{code}
209 -- When we renumber/rename things, we need to be
210 -- able to change a Name's Unique to match the cached
211 -- one in the thing it's the name of.  If you know what I mean.
212 setNameUnique name uniq = name {n_uniq = uniq}
213
214 setNameOcc :: Name -> OccName -> Name
215 setNameOcc name occ = name {n_occ = occ}
216
217 externaliseName :: Name -> Module -> Name
218 externaliseName n mod = n { n_sort = External mod }
219                                 
220 localiseName :: Name -> Name
221 localiseName n = n { n_sort = Internal }
222                                 
223 setNameModuleAndLoc :: Name -> Module -> SrcLoc -> Name
224 setNameModuleAndLoc name mod loc = name {n_sort = set (n_sort name), n_loc = loc}
225                        where
226                          set (External _) = External mod
227 \end{code}
228
229
230 %************************************************************************
231 %*                                                                      *
232 \subsection{Predicates and selectors}
233 %*                                                                      *
234 %************************************************************************
235
236 \begin{code}
237 hashName :: Name -> Int
238 hashName name = iBox (getKey (nameUnique name))
239
240
241 nameRdrName :: Name -> RdrName
242 -- Makes a qualified name for top-level (External) names, 
243 -- whether locally defined or not and an unqualified name just for Internals
244 nameRdrName (Name { n_occ = occ, n_sort = External mod }) = mkRdrOrig (moduleName mod) occ
245 nameRdrName (Name { n_occ = occ })                        = mkRdrUnqual occ
246 \end{code}
247
248
249 %************************************************************************
250 %*                                                                      *
251 \subsection[Name-instances]{Instance declarations}
252 %*                                                                      *
253 %************************************************************************
254
255 \begin{code}
256 cmpName n1 n2 = n_uniq n1 `compare` n_uniq n2
257 \end{code}
258
259 \begin{code}
260 instance Eq Name where
261     a == b = case (a `compare` b) of { EQ -> True;  _ -> False }
262     a /= b = case (a `compare` b) of { EQ -> False; _ -> True }
263
264 instance Ord Name where
265     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
266     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
267     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
268     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
269     compare a b = cmpName a b
270
271 instance Uniquable Name where
272     getUnique = nameUnique
273
274 instance NamedThing Name where
275     getName n = n
276 \end{code}
277
278 %************************************************************************
279 %*                                                                      *
280 \subsection{Binary output}
281 %*                                                                      *
282 %************************************************************************
283
284 \begin{code}
285 instance Binary Name where
286   -- we must print these as RdrNames, because that's how they will be read in
287   put_ bh Name {n_sort = sort, n_uniq = uniq, n_occ = occ} =
288    case sort of
289     External mod
290         | this_mod == mod -> put_ bh (mkRdrUnqual occ)
291         | otherwise       -> put_ bh (mkRdrOrig (moduleName mod) occ)
292         where (this_mod,_,_,_) = getUserData bh
293     _ -> do 
294         put_ bh (mkRdrUnqual occ)
295
296   get bh = error "can't Binary.get a Name"    
297 \end{code}
298
299 %************************************************************************
300 %*                                                                      *
301 \subsection{Pretty printing}
302 %*                                                                      *
303 %************************************************************************
304
305 \begin{code}
306 instance Outputable Name where
307         -- When printing interfaces, all Internals have been given nice print-names
308     ppr name = pprName name
309
310 pprName name@(Name {n_sort = sort, n_uniq = uniq, n_occ = occ})
311   = getPprStyle $ \ sty ->
312     case sort of
313       External mod -> pprExternal sty name uniq mod occ
314       System       -> pprSystem sty uniq occ
315       Internal     -> pprInternal sty uniq occ
316
317 pprExternal sty name uniq mod occ
318   | codeStyle sty        = ppr (moduleName mod) <> char '_' <> pprOccName occ
319
320   | debugStyle sty       = ppr (moduleName mod) <> dot <> pprOccName occ <> 
321                             text "{-" <> pprUnique uniq <> text "-}"
322
323   | unqualStyle sty name = pprOccName occ
324   | otherwise            = ppr (moduleName mod) <> dot <> pprOccName occ
325
326 pprInternal sty uniq occ
327   | codeStyle sty  = pprUnique uniq
328   | debugStyle sty = pprOccName occ <> 
329                      text "{-" <> pprUnique uniq <> text "-}"
330   | otherwise      = pprOccName occ     -- User style
331
332 -- Like Internal, except that we only omit the unique in Iface style
333 pprSystem sty uniq occ
334   | codeStyle sty  = pprUnique uniq
335   | otherwise      = pprOccName occ <> char '_' <> pprUnique uniq
336                                 -- If the tidy phase hasn't run, the OccName
337                                 -- is unlikely to be informative (like 's'),
338                                 -- so print the unique
339 \end{code}
340
341 %************************************************************************
342 %*                                                                      *
343 \subsection{Overloaded functions related to Names}
344 %*                                                                      *
345 %************************************************************************
346
347 \begin{code}
348 class NamedThing a where
349     getOccName :: a -> OccName
350     getName    :: a -> Name
351
352     getOccName n = nameOccName (getName n)      -- Default method
353 \end{code}
354
355 \begin{code}
356 getSrcLoc           :: NamedThing a => a -> SrcLoc
357 getOccString        :: NamedThing a => a -> String
358 toRdrName           :: NamedThing a => a -> RdrName
359
360 getSrcLoc           = nameSrcLoc           . getName
361 getOccString        = occNameString        . getOccName
362 toRdrName           = nameRdrName          . getName
363 \end{code}
364