[project @ 2004-11-26 16:19:45 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         BuiltInSyntax(..), 
14         mkInternalName, mkSystemName, 
15         mkSystemNameEncoded, 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,
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 )
42 import SrcLoc           ( noSrcLoc, wiredInSrcLoc, SrcLoc )
43 import Unique           ( Unique, Uniquable(..), getKey, pprUnique )
44 import Maybes           ( orElse )
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 (Maybe Name)
68         -- (Just parent) => this Name is a subordinate name of 'parent'
69         -- e.g. data constructor of a data type, method of a class
70         -- Nothing => not a subordinate
71  
72   | WiredIn Module (Maybe Name) TyThing BuiltInSyntax
73         -- A variant of External, for wired-in things
74
75   | Internal            -- A user-defined Id or TyVar
76                         -- defined in the module being compiled
77
78   | System              -- A system-defined Id or TyVar.  Typically the
79                         -- OccName is very uninformative (like 's')
80
81 data BuiltInSyntax = BuiltInSyntax | UserSyntax
82 -- BuiltInSyntax is for things like (:), [], tuples etc, 
83 -- which have special syntactic forms.  They aren't "in scope"
84 -- as such.
85 \end{code}
86
87 Notes about the NameSorts:
88
89 1.  Initially, top-level Ids (including locally-defined ones) get External names, 
90     and all other local Ids get Internal names
91
92 2.  Things with a External name are given C static labels, so they finally
93     appear in the .o file's symbol table.  They appear in the symbol table
94     in the form M.n.  If originally-local things have this property they
95     must be made @External@ first.
96
97 3.  In the tidy-core phase, a External that is not visible to an importer
98     is changed to Internal, and a Internal that is visible is changed to External
99
100 4.  A System Name differs in the following ways:
101         a) has unique attached when printing dumps
102         b) unifier eliminates sys tyvars in favour of user provs where possible
103
104     Before anything gets printed in interface files or output code, it's
105     fed through a 'tidy' processor, which zaps the OccNames to have
106     unique names; and converts all sys-locals to user locals
107     If any desugarer sys-locals have survived that far, they get changed to
108     "ds1", "ds2", etc.
109
110 Built-in syntax => It's a syntactic form, not "in scope" (e.g. [])
111
112 Wired-in thing  => The thing (Id, TyCon) is fully known to the compiler, 
113                    not read from an interface file. 
114                    E.g. Bool, True, Int, Float, and many others
115
116 All built-in syntax is for wired-in things.
117
118 \begin{code}
119 nameUnique              :: Name -> Unique
120 nameOccName             :: Name -> OccName 
121 nameModule              :: Name -> Module
122 nameSrcLoc              :: Name -> SrcLoc
123
124 nameUnique  name = n_uniq name
125 nameOccName name = n_occ  name
126 nameSrcLoc  name = n_loc  name
127 \end{code}
128
129 \begin{code}
130 nameIsLocalOrFrom :: Module -> Name -> Bool
131 isInternalName    :: Name -> Bool
132 isExternalName    :: Name -> Bool
133 isSystemName      :: Name -> Bool
134 isWiredInName     :: Name -> Bool
135
136 isWiredInName (Name {n_sort = WiredIn _ _ _ _}) = True
137 isWiredInName other                             = False
138
139 wiredInNameTyThing_maybe :: Name -> Maybe TyThing
140 wiredInNameTyThing_maybe (Name {n_sort = WiredIn _ _ thing _}) = Just thing
141 wiredInNameTyThing_maybe other                                 = Nothing
142
143 isBuiltInSyntax (Name {n_sort = WiredIn _ _ _ BuiltInSyntax}) = True
144 isBuiltInSyntax other                                         = False
145
146 isExternalName (Name {n_sort = External _ _})    = True
147 isExternalName (Name {n_sort = WiredIn _ _ _ _}) = True
148 isExternalName other                             = False
149
150 isInternalName name = not (isExternalName name)
151
152 nameParent_maybe :: Name -> Maybe Name
153 nameParent_maybe (Name {n_sort = External _ p})    = p
154 nameParent_maybe (Name {n_sort = WiredIn _ p _ _}) = p
155 nameParent_maybe other                             = Nothing
156
157 nameParent :: Name -> Name
158 nameParent name = case nameParent_maybe name of
159                         Just parent -> parent
160                         Nothing     -> name
161
162 nameModule name = nameModule_maybe name `orElse` pprPanic "nameModule" (ppr name)
163 nameModule_maybe (Name { n_sort = External mod _})    = Just mod
164 nameModule_maybe (Name { n_sort = WiredIn mod _ _ _}) = Just mod
165 nameModule_maybe name                                 = Nothing
166
167 nameIsLocalOrFrom from name
168   | isExternalName name = from == nameModule name
169   | otherwise           = True
170
171 isTyVarName :: Name -> Bool
172 isTyVarName name = isTvOcc (nameOccName name)
173
174 isSystemName (Name {n_sort = System}) = True
175 isSystemName other                    = False
176 \end{code}
177
178
179 %************************************************************************
180 %*                                                                      *
181 \subsection{Making names}
182 %*                                                                      *
183 %************************************************************************
184
185 \begin{code}
186 mkInternalName :: Unique -> OccName -> SrcLoc -> Name
187 mkInternalName uniq occ loc = Name { n_uniq = uniq, n_sort = Internal, n_occ = occ, n_loc = loc }
188         -- NB: You might worry that after lots of huffing and
189         -- puffing we might end up with two local names with distinct
190         -- uniques, but the same OccName.  Indeed we can, but that's ok
191         --      * the insides of the compiler don't care: they use the Unique
192         --      * when printing for -ddump-xxx you can switch on -dppr-debug to get the
193         --        uniques if you get confused
194         --      * for interface files we tidyCore first, which puts the uniques
195         --        into the print name (see setNameVisibility below)
196
197 mkExternalName :: Unique -> Module -> OccName -> Maybe Name -> SrcLoc -> Name
198 mkExternalName uniq mod occ mb_parent loc 
199   = Name { n_uniq = uniq, n_sort = External mod mb_parent,
200            n_occ = occ, n_loc = loc }
201
202 mkWiredInName :: Module -> OccName -> Unique 
203               -> Maybe Name -> TyThing -> BuiltInSyntax -> Name
204 mkWiredInName mod occ uniq mb_parent thing built_in
205   = Name { n_uniq = uniq,
206            n_sort = WiredIn mod mb_parent thing built_in,
207            n_occ = occ, n_loc = wiredInSrcLoc }
208
209 mkSystemName :: Unique -> UserFS -> Name
210 mkSystemName uniq fs = Name { n_uniq = uniq, n_sort = System, 
211                               n_occ = mkVarOcc fs, n_loc = noSrcLoc }
212
213 -- Use this version when the string is already encoded.  Avoids duplicating
214 -- the string each time a new name is created.
215 mkSystemNameEncoded :: Unique -> EncodedFS -> Name
216 mkSystemNameEncoded uniq fs = Name { n_uniq = uniq, n_sort = System, 
217                                      n_occ = mkSysOccFS varName fs, 
218                                      n_loc = noSrcLoc }
219
220 mkSysTvName :: Unique -> EncodedFS -> Name
221 mkSysTvName uniq fs = Name { n_uniq = uniq, n_sort = System, 
222                              n_occ = mkSysOccFS tvName fs, 
223                              n_loc = noSrcLoc }
224
225 mkFCallName :: Unique -> EncodedString -> Name
226         -- The encoded string completely describes the ccall
227 mkFCallName uniq str =  Name { n_uniq = uniq, n_sort = Internal, 
228                                n_occ = mkFCallOcc 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         -- When printing interfaces, all Internals have been given nice print-names
303     ppr name = pprName name
304
305 instance OutputableBndr Name where
306     pprBndr _ name = pprName name
307
308 pprName (Name {n_sort = sort, n_uniq = uniq, n_occ = occ})
309   = getPprStyle $ \ sty ->
310     case sort of
311       WiredIn mod _ _ builtin -> pprExternal sty uniq mod occ True  builtin
312       External mod _          -> pprExternal sty uniq mod occ False UserSyntax
313       System                  -> pprSystem sty uniq occ
314       Internal                -> pprInternal sty uniq occ
315
316 pprExternal sty uniq mod occ is_wired is_builtin
317   | codeStyle sty        = ppr mod <> char '_' <> ppr_occ_name occ
318         -- In code style, always qualify
319         -- ToDo: maybe we could print all wired-in things unqualified
320         --       in code style, to reduce symbol table bloat?
321   | debugStyle sty       = ppr mod <> dot <> ppr_occ_name occ
322                            <> braces (hsep [if is_wired then ptext SLIT("(w)") else empty,
323                                             text (briefOccNameFlavour occ), 
324                                             pprUnique uniq])
325   | BuiltInSyntax <- is_builtin  = ppr_occ_name occ
326         -- never qualify builtin syntax
327   | unqualStyle sty mod occ = ppr_occ_name occ
328   | otherwise               = ppr mod <> dot <> ppr_occ_name occ
329
330 pprInternal sty uniq occ
331   | codeStyle sty  = pprUnique uniq
332   | debugStyle sty = ppr_occ_name occ <> braces (hsep [text (briefOccNameFlavour occ), 
333                                                        pprUnique uniq])
334   | otherwise      = ppr_occ_name occ   -- User style
335
336 -- Like Internal, except that we only omit the unique in Iface style
337 pprSystem sty uniq occ
338   | codeStyle sty  = pprUnique uniq
339   | debugStyle sty = ppr_occ_name occ <> char '_' <> pprUnique uniq
340                      <> braces (text (briefOccNameFlavour occ))
341   | otherwise      = ppr_occ_name occ <> char '_' <> pprUnique uniq
342                                 -- If the tidy phase hasn't run, the OccName
343                                 -- is unlikely to be informative (like 's'),
344                                 -- so print the unique
345
346 ppr_occ_name occ = pprEncodedFS (occNameFS occ)
347         -- Don't use pprOccName; instead, just print the string of the OccName; 
348         -- we print the namespace in the debug stuff above
349 \end{code}
350
351 %************************************************************************
352 %*                                                                      *
353 \subsection{Overloaded functions related to Names}
354 %*                                                                      *
355 %************************************************************************
356
357 \begin{code}
358 class NamedThing a where
359     getOccName :: a -> OccName
360     getName    :: a -> Name
361
362     getOccName n = nameOccName (getName n)      -- Default method
363 \end{code}
364
365 \begin{code}
366 getSrcLoc           :: NamedThing a => a -> SrcLoc
367 getOccString        :: NamedThing a => a -> String
368
369 getSrcLoc           = nameSrcLoc           . getName
370 getOccString        = occNameString        . getOccName
371 \end{code}
372