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