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