Fix scoped type variables for expression type signatures
[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, 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 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 isTyConName :: Name -> Bool
184 isTyConName name = isTcOcc (nameOccName name)
185
186 isSystemName (Name {n_sort = System}) = True
187 isSystemName other                    = False
188 \end{code}
189
190
191 %************************************************************************
192 %*                                                                      *
193 \subsection{Making names}
194 %*                                                                      *
195 %************************************************************************
196
197 \begin{code}
198 mkInternalName :: Unique -> OccName -> SrcLoc -> Name
199 mkInternalName uniq occ loc = Name { n_uniq = getKey# uniq, n_sort = Internal, n_occ = occ, n_loc = loc }
200         -- NB: You might worry that after lots of huffing and
201         -- puffing we might end up with two local names with distinct
202         -- uniques, but the same OccName.  Indeed we can, but that's ok
203         --      * the insides of the compiler don't care: they use the Unique
204         --      * when printing for -ddump-xxx you can switch on -dppr-debug to get the
205         --        uniques if you get confused
206         --      * for interface files we tidyCore first, which puts the uniques
207         --        into the print name (see setNameVisibility below)
208
209 mkExternalName :: Unique -> Module -> OccName -> Maybe Name -> SrcLoc -> Name
210 mkExternalName uniq mod occ mb_parent loc 
211   = Name { n_uniq = getKey# uniq, n_sort = External mod mb_parent,
212            n_occ = occ, n_loc = loc }
213
214 mkWiredInName :: Module -> OccName -> Unique 
215               -> Maybe Name -> TyThing -> BuiltInSyntax -> Name
216 mkWiredInName mod occ uniq mb_parent thing built_in
217   = Name { n_uniq = getKey# uniq,
218            n_sort = WiredIn mod mb_parent thing built_in,
219            n_occ = occ, n_loc = wiredInSrcLoc }
220
221 mkSystemName :: Unique -> OccName -> Name
222 mkSystemName uniq occ = Name { n_uniq = getKey# uniq, n_sort = System, 
223                                n_occ = occ, n_loc = noSrcLoc }
224
225 mkSystemVarName :: Unique -> FastString -> Name
226 mkSystemVarName uniq fs = mkSystemName uniq (mkVarOccFS fs)
227
228 mkSysTvName :: Unique -> FastString -> Name
229 mkSysTvName uniq fs = mkSystemName uniq (mkOccNameFS tvName fs) 
230
231 mkFCallName :: Unique -> String -> Name
232         -- The encoded string completely describes the ccall
233 mkFCallName uniq str =  Name { n_uniq = getKey# uniq, n_sort = Internal, 
234                                n_occ = mkVarOcc str, n_loc = noSrcLoc }
235
236 mkIPName :: Unique -> OccName -> Name
237 mkIPName uniq occ
238   = Name { n_uniq = getKey# uniq,
239            n_sort = Internal,
240            n_occ  = occ,
241            n_loc = noSrcLoc }
242 \end{code}
243
244 \begin{code}
245 -- When we renumber/rename things, we need to be
246 -- able to change a Name's Unique to match the cached
247 -- one in the thing it's the name of.  If you know what I mean.
248 setNameUnique :: Name -> Unique -> Name
249 setNameUnique name uniq = name {n_uniq = getKey# uniq}
250
251 tidyNameOcc :: Name -> OccName -> Name
252 -- We set the OccName of a Name when tidying
253 -- In doing so, we change System --> Internal, so that when we print
254 -- it we don't get the unique by default.  It's tidy now!
255 tidyNameOcc name@(Name { n_sort = System }) occ = name { n_occ = occ, n_sort = Internal}
256 tidyNameOcc name                            occ = name { n_occ = occ }
257
258 localiseName :: Name -> Name
259 localiseName n = n { n_sort = Internal }
260 \end{code}
261
262
263 %************************************************************************
264 %*                                                                      *
265 \subsection{Predicates and selectors}
266 %*                                                                      *
267 %************************************************************************
268
269 \begin{code}
270 hashName :: Name -> Int
271 hashName name = getKey (nameUnique name)
272 \end{code}
273
274
275 %************************************************************************
276 %*                                                                      *
277 \subsection[Name-instances]{Instance declarations}
278 %*                                                                      *
279 %************************************************************************
280
281 \begin{code}
282 cmpName n1 n2 = I# (n_uniq n1) `compare` I# (n_uniq n2)
283 \end{code}
284
285 \begin{code}
286 instance Eq Name where
287     a == b = case (a `compare` b) of { EQ -> True;  _ -> False }
288     a /= b = case (a `compare` b) of { EQ -> False; _ -> True }
289
290 instance Ord Name where
291     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
292     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
293     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
294     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
295     compare a b = cmpName a b
296
297 instance Uniquable Name where
298     getUnique = nameUnique
299
300 instance NamedThing Name where
301     getName n = n
302 \end{code}
303
304
305 %************************************************************************
306 %*                                                                      *
307 \subsection{Pretty printing}
308 %*                                                                      *
309 %************************************************************************
310
311 \begin{code}
312 instance Outputable Name where
313     ppr name = pprName name
314
315 instance OutputableBndr Name where
316     pprBndr _ name = pprName name
317
318 pprName name@(Name {n_sort = sort, n_uniq = u#, n_occ = occ})
319   = getPprStyle $ \ sty ->
320     case sort of
321       WiredIn mod _ _ builtin -> pprExternal sty uniq mod occ True  builtin
322       External mod _          -> pprExternal sty uniq mod occ False UserSyntax
323       System                  -> pprSystem sty uniq occ
324       Internal                -> pprInternal sty uniq occ
325   where uniq = mkUniqueGrimily (I# u#)
326
327 pprExternal sty uniq mod occ is_wired is_builtin
328   | codeStyle sty        = ppr mod <> char '_' <> ppr_z_occ_name occ
329         -- In code style, always qualify
330         -- ToDo: maybe we could print all wired-in things unqualified
331         --       in code style, to reduce symbol table bloat?
332  | debugStyle sty       = ppr mod <> dot <> ppr_occ_name occ
333                 <> braces (hsep [if is_wired then ptext SLIT("(w)") else empty,
334                                  pprNameSpaceBrief (occNameSpace occ), 
335                                  pprUnique uniq])
336   | BuiltInSyntax <- is_builtin  = ppr_occ_name occ
337         -- never qualify builtin syntax
338   | Just mod <- qualName sty mod occ = ppr mod <> dot <> ppr_occ_name occ
339         -- the PrintUnqualified tells us how to qualify this Name, if at all
340   | otherwise                     = ppr_occ_name occ
341
342 pprInternal sty uniq occ
343   | codeStyle sty  = pprUnique uniq
344   | debugStyle sty = ppr_occ_name occ <> braces (hsep [pprNameSpaceBrief (occNameSpace occ), 
345                                                        pprUnique uniq])
346   | dumpStyle sty  = ppr_occ_name occ <> char '_' <> pprUnique uniq
347                         -- For debug dumps, we're not necessarily dumping
348                         -- tidied code, so we need to print the uniques.
349   | otherwise      = ppr_occ_name occ   -- User style
350
351 -- Like Internal, except that we only omit the unique in Iface style
352 pprSystem sty uniq occ
353   | codeStyle sty  = pprUnique uniq
354   | debugStyle sty = ppr_occ_name occ <> char '_' <> pprUnique uniq
355                      <> braces (pprNameSpaceBrief (occNameSpace occ))
356   | otherwise      = ppr_occ_name occ <> char '_' <> pprUnique uniq
357                                 -- If the tidy phase hasn't run, the OccName
358                                 -- is unlikely to be informative (like 's'),
359                                 -- so print the unique
360
361 ppr_occ_name occ = ftext (occNameFS occ)
362         -- Don't use pprOccName; instead, just print the string of the OccName; 
363         -- we print the namespace in the debug stuff above
364
365 -- In code style, we Z-encode the strings.  The results of Z-encoding each FastString are
366 -- cached behind the scenes in the FastString implementation.
367 ppr_z_occ_name occ = ftext (zEncodeFS (occNameFS occ))
368 \end{code}
369
370 %************************************************************************
371 %*                                                                      *
372 \subsection{Overloaded functions related to Names}
373 %*                                                                      *
374 %************************************************************************
375
376 \begin{code}
377 class NamedThing a where
378     getOccName :: a -> OccName
379     getName    :: a -> Name
380
381     getOccName n = nameOccName (getName n)      -- Default method
382 \end{code}
383
384 \begin{code}
385 getSrcLoc           :: NamedThing a => a -> SrcLoc
386 getOccString        :: NamedThing a => a -> String
387
388 getSrcLoc           = nameSrcLoc           . getName
389 getOccString        = occNameString        . getOccName
390 \end{code}
391