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