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