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