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