[project @ 2002-03-14 16:22:31 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, 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,
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   = 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 -> EncodedFS -> Name
180 mkSystemName 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 = Internal, 
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 = Internal,
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 externaliseName :: Name -> Module -> Name
206 externaliseName n mod = n { n_sort = External mod }
207                                 
208 localiseName :: Name -> Name
209 localiseName n = n { n_sort = Internal }
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 (External _) = External 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 (External) names, 
231 -- whether locally defined or not and an unqualified name just for Internals
232 nameRdrName (Name { n_occ = occ, n_sort = External 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 \subsection{Binary output}
269 %*                                                                      *
270 %************************************************************************
271
272 \begin{code}
273 instance Binary Name where
274   -- we must print these as RdrNames, because that's how they will be read in
275   put_ bh Name {n_sort = sort, n_uniq = uniq, n_occ = occ} =
276    case sort of
277     External mod
278         | this_mod == mod -> put_ bh (mkRdrUnqual occ)
279         | otherwise       -> put_ bh (mkRdrOrig (moduleName mod) occ)
280         where (this_mod,_,_,_) = getUserData bh
281     _ -> do 
282         put_ bh (mkRdrUnqual occ)
283
284   get bh = error "can't Binary.get a Name"    
285 \end{code}
286
287 %************************************************************************
288 %*                                                                      *
289 \subsection{Pretty printing}
290 %*                                                                      *
291 %************************************************************************
292
293 \begin{code}
294 instance Outputable Name where
295         -- When printing interfaces, all Internals have been given nice print-names
296     ppr name = pprName name
297
298 pprName name@(Name {n_sort = sort, n_uniq = uniq, n_occ = occ})
299   = getPprStyle $ \ sty ->
300     case sort of
301       External mod -> pprExternal sty name uniq mod occ
302       System       -> pprSystem sty uniq occ
303       Internal     -> pprInternal sty uniq occ
304
305 pprExternal sty name uniq mod occ
306   | codeStyle sty        = ppr (moduleName mod) <> char '_' <> pprOccName occ
307
308   | debugStyle sty       = ppr (moduleName mod) <> dot <> pprOccName occ <> 
309                             text "{-" <> pprUnique uniq <> text "-}"
310
311   | unqualStyle sty name = pprOccName occ
312   | otherwise            = ppr (moduleName mod) <> dot <> pprOccName occ
313
314 pprInternal sty uniq occ
315   | codeStyle sty  = pprUnique uniq
316   | debugStyle sty = pprOccName occ <> 
317                      text "{-" <> pprUnique uniq <> text "-}"
318   | otherwise      = pprOccName occ     -- User style
319
320 -- Like Internal, except that we only omit the unique in Iface style
321 pprSystem sty uniq occ
322   | codeStyle sty  = pprUnique uniq
323   | otherwise      = pprOccName occ <> char '_' <> pprUnique uniq
324                                 -- If the tidy phase hasn't run, the OccName
325                                 -- is unlikely to be informative (like 's'),
326                                 -- so print the unique
327 \end{code}
328
329 %************************************************************************
330 %*                                                                      *
331 \subsection{Overloaded functions related to Names}
332 %*                                                                      *
333 %************************************************************************
334
335 \begin{code}
336 class NamedThing a where
337     getOccName :: a -> OccName
338     getName    :: a -> Name
339
340     getOccName n = nameOccName (getName n)      -- Default method
341 \end{code}
342
343 \begin{code}
344 getSrcLoc           :: NamedThing a => a -> SrcLoc
345 getOccString        :: NamedThing a => a -> String
346 toRdrName           :: NamedThing a => a -> RdrName
347
348 getSrcLoc           = nameSrcLoc           . getName
349 getOccString        = occNameString        . getOccName
350 toRdrName           = nameRdrName          . getName
351 \end{code}
352