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