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