fd8f2cfd4835583eadc2354ab2b6d869942bf66d
[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, mkSystemVarNameEncoded, 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 )
42 import SrcLoc           ( noSrcLoc, wiredInSrcLoc, SrcLoc )
43 import Unique           ( Unique, Uniquable(..), getKey, pprUnique )
44 import Maybes           ( orElse, isJust )
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 isImplicitName :: Name -> Bool
163 -- An Implicit Name is one has a parent; that is, one whose definition
164 -- derives from the parent thing
165 isImplicitName name = isJust (nameParent_maybe name)
166
167 nameModule name = nameModule_maybe name `orElse` pprPanic "nameModule" (ppr name)
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 isTyVarName :: Name -> Bool
177 isTyVarName name = isTvOcc (nameOccName name)
178
179 isSystemName (Name {n_sort = System}) = True
180 isSystemName other                    = False
181 \end{code}
182
183
184 %************************************************************************
185 %*                                                                      *
186 \subsection{Making names}
187 %*                                                                      *
188 %************************************************************************
189
190 \begin{code}
191 mkInternalName :: Unique -> OccName -> SrcLoc -> Name
192 mkInternalName uniq occ loc = Name { n_uniq = uniq, n_sort = Internal, n_occ = occ, n_loc = loc }
193         -- NB: You might worry that after lots of huffing and
194         -- puffing we might end up with two local names with distinct
195         -- uniques, but the same OccName.  Indeed we can, but that's ok
196         --      * the insides of the compiler don't care: they use the Unique
197         --      * when printing for -ddump-xxx you can switch on -dppr-debug to get the
198         --        uniques if you get confused
199         --      * for interface files we tidyCore first, which puts the uniques
200         --        into the print name (see setNameVisibility below)
201
202 mkExternalName :: Unique -> Module -> OccName -> Maybe Name -> SrcLoc -> Name
203 mkExternalName uniq mod occ mb_parent loc 
204   = Name { n_uniq = uniq, n_sort = External mod mb_parent,
205            n_occ = occ, n_loc = loc }
206
207 mkWiredInName :: Module -> OccName -> Unique 
208               -> Maybe Name -> TyThing -> BuiltInSyntax -> Name
209 mkWiredInName mod occ uniq mb_parent thing built_in
210   = Name { n_uniq = uniq,
211            n_sort = WiredIn mod mb_parent thing built_in,
212            n_occ = occ, n_loc = wiredInSrcLoc }
213
214 mkSystemName :: Unique -> OccName -> Name
215 mkSystemName uniq occ = Name { n_uniq = uniq, n_sort = System, 
216                                n_occ = occ, n_loc = noSrcLoc }
217
218 mkSystemVarName :: Unique -> UserFS -> Name
219 mkSystemVarName uniq fs = mkSystemName uniq (mkVarOcc fs)
220
221 -- Use this version when the string is already encoded.  Avoids duplicating
222 -- the string each time a new name is created.
223 mkSystemVarNameEncoded :: Unique -> EncodedFS -> Name
224 mkSystemVarNameEncoded uniq fs = mkSystemName uniq (mkSysOccFS varName fs) 
225
226 mkSysTvName :: Unique -> EncodedFS -> Name
227 mkSysTvName uniq fs = mkSystemName uniq (mkSysOccFS tvName fs) 
228
229 mkFCallName :: Unique -> EncodedString -> Name
230         -- The encoded string completely describes the ccall
231 mkFCallName uniq str =  Name { n_uniq = uniq, n_sort = Internal, 
232                                n_occ = mkFCallOcc str, n_loc = noSrcLoc }
233
234 mkIPName :: Unique -> OccName -> Name
235 mkIPName uniq occ
236   = Name { n_uniq = uniq,
237            n_sort = Internal,
238            n_occ  = occ,
239            n_loc = noSrcLoc }
240 \end{code}
241
242 \begin{code}
243 -- When we renumber/rename things, we need to be
244 -- able to change a Name's Unique to match the cached
245 -- one in the thing it's the name of.  If you know what I mean.
246 setNameUnique name uniq = name {n_uniq = uniq}
247
248 setNameOcc :: Name -> OccName -> Name
249 setNameOcc name occ = name {n_occ = occ}
250
251 localiseName :: Name -> Name
252 localiseName n = n { n_sort = Internal }
253 \end{code}
254
255
256 %************************************************************************
257 %*                                                                      *
258 \subsection{Predicates and selectors}
259 %*                                                                      *
260 %************************************************************************
261
262 \begin{code}
263 hashName :: Name -> Int
264 hashName name = getKey (nameUnique name)
265 \end{code}
266
267
268 %************************************************************************
269 %*                                                                      *
270 \subsection[Name-instances]{Instance declarations}
271 %*                                                                      *
272 %************************************************************************
273
274 \begin{code}
275 cmpName n1 n2 = n_uniq n1 `compare` n_uniq n2
276 \end{code}
277
278 \begin{code}
279 instance Eq Name where
280     a == b = case (a `compare` b) of { EQ -> True;  _ -> False }
281     a /= b = case (a `compare` b) of { EQ -> False; _ -> True }
282
283 instance Ord Name where
284     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
285     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
286     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
287     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
288     compare a b = cmpName a b
289
290 instance Uniquable Name where
291     getUnique = nameUnique
292
293 instance NamedThing Name where
294     getName n = n
295 \end{code}
296
297
298 %************************************************************************
299 %*                                                                      *
300 \subsection{Pretty printing}
301 %*                                                                      *
302 %************************************************************************
303
304 \begin{code}
305 instance Outputable Name where
306     ppr name = pprName name
307
308 instance OutputableBndr Name where
309     pprBndr _ name = pprName name
310
311 pprName (Name {n_sort = sort, n_uniq = uniq, n_occ = occ})
312   = getPprStyle $ \ sty ->
313     case sort of
314       WiredIn mod _ _ builtin -> pprExternal sty uniq mod occ True  builtin
315       External mod _          -> pprExternal sty uniq mod occ False UserSyntax
316       System                  -> pprSystem sty uniq occ
317       Internal                -> pprInternal sty uniq occ
318
319 pprExternal sty uniq mod occ is_wired is_builtin
320   | codeStyle sty        = ppr mod <> char '_' <> ppr_occ_name occ
321         -- In code style, always qualify
322         -- ToDo: maybe we could print all wired-in things unqualified
323         --       in code style, to reduce symbol table bloat?
324   | debugStyle sty       = ppr mod <> dot <> ppr_occ_name occ
325                            <> braces (hsep [if is_wired then ptext SLIT("(w)") else empty,
326                                             text (briefOccNameFlavour occ), 
327                                             pprUnique uniq])
328   | BuiltInSyntax <- is_builtin  = ppr_occ_name occ
329         -- never qualify builtin syntax
330   | unqualStyle sty mod occ = ppr_occ_name occ
331   | otherwise               = ppr mod <> dot <> ppr_occ_name occ
332
333 pprInternal sty uniq occ
334   | codeStyle sty  = pprUnique uniq
335   | debugStyle sty = ppr_occ_name occ <> braces (hsep [text (briefOccNameFlavour occ), 
336                                                        pprUnique uniq])
337   | dumpStyle sty  = ppr_occ_name occ <> char '_' <> pprUnique uniq
338                         -- For debug dumps, we're not necessarily dumping
339                         -- tidied code, so we need to print the uniques.
340   | otherwise      = ppr_occ_name occ   -- User style
341
342 -- Like Internal, except that we only omit the unique in Iface style
343 pprSystem sty uniq occ
344   | codeStyle sty  = pprUnique uniq
345   | debugStyle sty = ppr_occ_name occ <> char '_' <> pprUnique uniq
346                      <> braces (text (briefOccNameFlavour occ))
347   | otherwise      = ppr_occ_name occ <> char '_' <> pprUnique uniq
348                                 -- If the tidy phase hasn't run, the OccName
349                                 -- is unlikely to be informative (like 's'),
350                                 -- so print the unique
351
352 ppr_occ_name occ = pprEncodedFS (occNameFS occ)
353         -- Don't use pprOccName; instead, just print the string of the OccName; 
354         -- we print the namespace in the debug stuff above
355 \end{code}
356
357 %************************************************************************
358 %*                                                                      *
359 \subsection{Overloaded functions related to Names}
360 %*                                                                      *
361 %************************************************************************
362
363 \begin{code}
364 class NamedThing a where
365     getOccName :: a -> OccName
366     getName    :: a -> Name
367
368     getOccName n = nameOccName (getName n)      -- Default method
369 \end{code}
370
371 \begin{code}
372 getSrcLoc           :: NamedThing a => a -> SrcLoc
373 getOccString        :: NamedThing a => a -> String
374
375 getSrcLoc           = nameSrcLoc           . getName
376 getOccString        = occNameString        . getOccName
377 \end{code}
378