3aeb03b8bf49e7c87fc875418a2b26fd3bdbef10
[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         mkSystemVarName, mkSysTvName, 
16         mkFCallName, mkIPName,
17         mkExternalName, mkWiredInName,
18
19         nameUnique, setNameUnique,
20         nameOccName, nameModule, nameModule_maybe,
21         setNameOcc, 
22         hashName, localiseName,
23
24         nameSrcLoc, nameParent, nameParent_maybe, isImplicitName, 
25
26         isSystemName, isInternalName, isExternalName,
27         isTyVarName, isWiredInName, isBuiltInSyntax,
28         wiredInNameTyThing_maybe, 
29         nameIsLocalOrFrom,
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, moduleFS )
42 import SrcLoc           ( noSrcLoc, wiredInSrcLoc, SrcLoc )
43 import Unique           ( Unique, Uniquable(..), getKey, pprUnique )
44 import Maybes           ( orElse, isJust )
45 import FastString       ( FastString, zEncodeFS )
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 nameSrcLoc              :: Name -> SrcLoc
124
125 nameUnique  name = n_uniq name
126 nameOccName name = n_occ  name
127 nameSrcLoc  name = n_loc  name
128 \end{code}
129
130 \begin{code}
131 nameIsLocalOrFrom :: Module -> Name -> Bool
132 isInternalName    :: Name -> Bool
133 isExternalName    :: Name -> Bool
134 isSystemName      :: Name -> Bool
135 isWiredInName     :: Name -> Bool
136
137 isWiredInName (Name {n_sort = WiredIn _ _ _ _}) = True
138 isWiredInName other                             = False
139
140 wiredInNameTyThing_maybe :: Name -> Maybe TyThing
141 wiredInNameTyThing_maybe (Name {n_sort = WiredIn _ _ thing _}) = Just thing
142 wiredInNameTyThing_maybe other                                 = Nothing
143
144 isBuiltInSyntax (Name {n_sort = WiredIn _ _ _ BuiltInSyntax}) = True
145 isBuiltInSyntax other                                         = False
146
147 isExternalName (Name {n_sort = External _ _})    = True
148 isExternalName (Name {n_sort = WiredIn _ _ _ _}) = True
149 isExternalName other                             = False
150
151 isInternalName name = not (isExternalName name)
152
153 nameParent_maybe :: Name -> Maybe Name
154 nameParent_maybe (Name {n_sort = External _ p})    = p
155 nameParent_maybe (Name {n_sort = WiredIn _ p _ _}) = p
156 nameParent_maybe other                             = Nothing
157
158 nameParent :: Name -> Name
159 nameParent name = case nameParent_maybe name of
160                         Just parent -> parent
161                         Nothing     -> name
162
163 isImplicitName :: Name -> Bool
164 -- An Implicit Name is one has a parent; that is, one whose definition
165 -- derives from the parent thing
166 isImplicitName name = isJust (nameParent_maybe name)
167
168 nameModule name = nameModule_maybe name `orElse` pprPanic "nameModule" (ppr name)
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 isTyVarName :: Name -> Bool
178 isTyVarName name = isTvOcc (nameOccName name)
179
180 isSystemName (Name {n_sort = System}) = True
181 isSystemName other                    = False
182 \end{code}
183
184
185 %************************************************************************
186 %*                                                                      *
187 \subsection{Making names}
188 %*                                                                      *
189 %************************************************************************
190
191 \begin{code}
192 mkInternalName :: Unique -> OccName -> SrcLoc -> Name
193 mkInternalName uniq occ loc = Name { n_uniq = uniq, n_sort = Internal, n_occ = occ, n_loc = loc }
194         -- NB: You might worry that after lots of huffing and
195         -- puffing we might end up with two local names with distinct
196         -- uniques, but the same OccName.  Indeed we can, but that's ok
197         --      * the insides of the compiler don't care: they use the Unique
198         --      * when printing for -ddump-xxx you can switch on -dppr-debug to get the
199         --        uniques if you get confused
200         --      * for interface files we tidyCore first, which puts the uniques
201         --        into the print name (see setNameVisibility below)
202
203 mkExternalName :: Unique -> Module -> OccName -> Maybe Name -> SrcLoc -> Name
204 mkExternalName uniq mod occ mb_parent loc 
205   = Name { n_uniq = uniq, n_sort = External mod mb_parent,
206            n_occ = occ, n_loc = loc }
207
208 mkWiredInName :: Module -> OccName -> Unique 
209               -> Maybe Name -> TyThing -> BuiltInSyntax -> Name
210 mkWiredInName mod occ uniq mb_parent thing built_in
211   = Name { n_uniq = uniq,
212            n_sort = WiredIn mod mb_parent thing built_in,
213            n_occ = occ, n_loc = wiredInSrcLoc }
214
215 mkSystemName :: Unique -> OccName -> Name
216 mkSystemName uniq occ = Name { n_uniq = uniq, n_sort = System, 
217                                n_occ = occ, n_loc = noSrcLoc }
218
219 mkSystemVarName :: Unique -> FastString -> Name
220 mkSystemVarName uniq fs = mkSystemName uniq (mkVarOccFS fs)
221
222 mkSysTvName :: Unique -> FastString -> Name
223 mkSysTvName uniq fs = mkSystemName uniq (mkOccNameFS tvName fs) 
224
225 mkFCallName :: Unique -> String -> Name
226         -- The encoded string completely describes the ccall
227 mkFCallName uniq str =  Name { n_uniq = uniq, n_sort = Internal, 
228                                n_occ = mkVarOcc str, n_loc = noSrcLoc }
229
230 mkIPName :: Unique -> OccName -> Name
231 mkIPName uniq occ
232   = Name { n_uniq = uniq,
233            n_sort = Internal,
234            n_occ  = occ,
235            n_loc = noSrcLoc }
236 \end{code}
237
238 \begin{code}
239 -- When we renumber/rename things, we need to be
240 -- able to change a Name's Unique to match the cached
241 -- one in the thing it's the name of.  If you know what I mean.
242 setNameUnique name uniq = name {n_uniq = uniq}
243
244 setNameOcc :: Name -> OccName -> Name
245 setNameOcc name occ = name {n_occ = occ}
246
247 localiseName :: Name -> Name
248 localiseName n = n { n_sort = Internal }
249 \end{code}
250
251
252 %************************************************************************
253 %*                                                                      *
254 \subsection{Predicates and selectors}
255 %*                                                                      *
256 %************************************************************************
257
258 \begin{code}
259 hashName :: Name -> Int
260 hashName name = getKey (nameUnique name)
261 \end{code}
262
263
264 %************************************************************************
265 %*                                                                      *
266 \subsection[Name-instances]{Instance declarations}
267 %*                                                                      *
268 %************************************************************************
269
270 \begin{code}
271 cmpName n1 n2 = n_uniq n1 `compare` n_uniq n2
272 \end{code}
273
274 \begin{code}
275 instance Eq Name where
276     a == b = case (a `compare` b) of { EQ -> True;  _ -> False }
277     a /= b = case (a `compare` b) of { EQ -> False; _ -> True }
278
279 instance Ord Name where
280     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
281     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
282     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
283     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
284     compare a b = cmpName a b
285
286 instance Uniquable Name where
287     getUnique = nameUnique
288
289 instance NamedThing Name where
290     getName n = n
291 \end{code}
292
293
294 %************************************************************************
295 %*                                                                      *
296 \subsection{Pretty printing}
297 %*                                                                      *
298 %************************************************************************
299
300 \begin{code}
301 instance Outputable Name where
302     ppr name = pprName name
303
304 instance OutputableBndr Name where
305     pprBndr _ name = pprName name
306
307 pprName (Name {n_sort = sort, n_uniq = uniq, n_occ = occ})
308   = getPprStyle $ \ sty ->
309     case sort of
310       WiredIn mod _ _ builtin -> pprExternal sty uniq mod occ True  builtin
311       External mod _          -> pprExternal sty uniq mod occ False UserSyntax
312       System                  -> pprSystem sty uniq occ
313       Internal                -> pprInternal sty uniq occ
314
315 pprExternal sty uniq mod occ is_wired is_builtin
316   | codeStyle sty        = ppr_z_module mod <> char '_' <> ppr_z_occ_name occ
317         -- In code style, always qualify
318         -- ToDo: maybe we could print all wired-in things unqualified
319         --       in code style, to reduce symbol table bloat?
320   | debugStyle sty       = ppr mod <> dot <> ppr_occ_name occ
321                            <> braces (hsep [if is_wired then ptext SLIT("(w)") else empty,
322                                             pprNameSpaceBrief (occNameSpace occ), 
323                                             pprUnique uniq])
324   | BuiltInSyntax <- is_builtin  = ppr_occ_name occ
325         -- never qualify builtin syntax
326   | unqualStyle sty mod occ = ppr_occ_name occ
327   | otherwise               = ppr mod <> dot <> ppr_occ_name occ
328
329 pprInternal sty uniq occ
330   | codeStyle sty  = pprUnique uniq
331   | debugStyle sty = ppr_occ_name occ <> braces (hsep [pprNameSpaceBrief (occNameSpace occ), 
332                                                        pprUnique uniq])
333   | dumpStyle sty  = ppr_occ_name occ <> char '_' <> pprUnique uniq
334                         -- For debug dumps, we're not necessarily dumping
335                         -- tidied code, so we need to print the uniques.
336   | otherwise      = ppr_occ_name occ   -- User style
337
338 -- Like Internal, except that we only omit the unique in Iface style
339 pprSystem sty uniq occ
340   | codeStyle sty  = pprUnique uniq
341   | debugStyle sty = ppr_occ_name occ <> char '_' <> pprUnique uniq
342                      <> braces (pprNameSpaceBrief (occNameSpace occ))
343   | otherwise      = ppr_occ_name occ <> char '_' <> pprUnique uniq
344                                 -- If the tidy phase hasn't run, the OccName
345                                 -- is unlikely to be informative (like 's'),
346                                 -- so print the unique
347
348 ppr_occ_name occ = ftext (occNameFS occ)
349         -- Don't use pprOccName; instead, just print the string of the OccName; 
350         -- we print the namespace in the debug stuff above
351
352 -- In code style, we Z-encode the strings.  The results of Z-encoding each FastString are
353 -- cached behind the scenes in the FastString implementation.
354 ppr_z_occ_name occ = ftext (zEncodeFS (occNameFS occ))
355 ppr_z_module   mod = ftext (zEncodeFS (moduleFS mod))
356
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