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