593d61bb53060691ef680834838951ba8797e8bd
[ghc-hetmet.git] / ghc / compiler / basicTypes / Name.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
3 %
4 \section[Name]{@Name@: to transmit name info from renamer to typechecker}
5
6 \begin{code}
7 #include "HsVersions.h"
8
9 module Name (
10         -- The Module type
11         SYN_IE(Module),
12         pprModule, moduleString,
13
14         -- The OccName type
15         OccName(..),
16         pprOccName, pprSymOcc, pprNonSymOcc, occNameString, occNameFlavour, isTvOcc, 
17         quoteInText, parenInCode,
18
19         -- The Name type
20         Name,                                   -- Abstract
21         mkLocalName, mkSysLocalName, 
22
23         mkCompoundName, mkGlobalName, mkInstDeclName,
24
25         mkWiredInIdName,   mkWiredInTyConName,
26         maybeWiredInIdName, maybeWiredInTyConName,
27         isWiredInName,
28
29         nameUnique, changeUnique, setNameProvenance, setNameVisibility,
30         nameOccName, nameString,
31         isExportedName, nameSrcLoc,
32         isLocallyDefinedName,
33
34         isLocalName, 
35
36         pprNameProvenance,
37
38         -- Sets of Names
39         NameSet(..),
40         emptyNameSet, unitNameSet, mkNameSet, unionNameSets, unionManyNameSets,
41         minusNameSet, elemNameSet, nameSetToList, addListToNameSet,
42
43         -- Misc
44         DefnInfo(..),
45         Provenance(..), pprProvenance,
46         ExportFlag(..),
47
48         -- Class NamedThing and overloaded friends
49         NamedThing(..),
50         modAndOcc, isExported, 
51         getSrcLoc, isLocallyDefined, getOccString,
52
53         pprSym, pprNonSym
54     ) where
55
56 IMP_Ubiq()
57 import TyLoop           ( GenId, Id(..), TyCon )                        -- Used inside Names
58 import CStrings         ( identToC, modnameToC, cSEP )
59 import CmdLineOpts      ( opt_OmitInterfacePragmas, opt_EnsureSplittableC )
60
61 import Outputable       ( Outputable(..) )
62 import PprStyle         ( PprStyle(..), codeStyle, ifaceStyle )
63 import PrelMods         ( gHC__ )
64 import Pretty
65 import Lex              ( isLexSym, isLexConId )
66 import SrcLoc           ( noSrcLoc, SrcLoc )
67 import Unique           ( pprUnique, showUnique, Unique )
68 import UniqSet          ( UniqSet(..), emptyUniqSet, unitUniqSet, unionUniqSets, uniqSetToList,
69                           unionManyUniqSets, minusUniqSet, mkUniqSet, elementOfUniqSet, addListToUniqSet )
70 import UniqFM           ( UniqFM )
71 import Util             ( cmpPString, panic, assertPanic {-, pprTrace ToDo:rm-} )
72 \end{code}
73
74
75 %************************************************************************
76 %*                                                                      *
77 \subsection[Name-pieces-datatypes]{The @Module@, @OccName@ datatypes}
78 %*                                                                      *
79 %************************************************************************
80
81 \begin{code}
82 type Module   = FAST_STRING
83
84 data OccName  = VarOcc  FAST_STRING     -- Variables and data constructors
85               | TvOcc   FAST_STRING     -- Type variables
86               | TCOcc   FAST_STRING     -- Type constructors and classes
87
88 moduleString :: Module -> String
89 moduleString mod = _UNPK_ mod
90
91 pprModule :: PprStyle -> Module -> Pretty
92 pprModule sty m = ppPStr m
93
94 pprOccName :: PprStyle -> OccName -> Pretty
95 pprOccName PprDebug n = ppCat [ppPStr (occNameString n), ppBracket (ppStr (occNameFlavour n))]
96 pprOccName sty      n = if codeStyle sty 
97                         then identToC (occNameString n)
98                         else ppPStr (occNameString n)
99
100 occNameString :: OccName -> FAST_STRING
101 occNameString (VarOcc s)  = s
102 occNameString (TvOcc s)   = s
103 occNameString (TCOcc s)   = s
104
105 -- occNameFlavour is used only to generate good error messages, so it doesn't matter
106 -- that the VarOcc case isn't mega-efficient.  We could have different Occ constructors for
107 -- data constructors and values, but that makes everything else a bit more complicated.
108 occNameFlavour :: OccName -> String
109 occNameFlavour (VarOcc s) | isLexConId s = "data constructor"
110                           | otherwise    = "value"
111 occNameFlavour (TvOcc s)  = "type variable"
112 occNameFlavour (TCOcc s)  = "type constructor or class"
113
114 isTvOcc :: OccName -> Bool
115 isTvOcc (TvOcc s) = True
116 isTvOcc other     = False
117
118 instance Eq OccName where
119     a == b = case (a `cmp` b) of { EQ_ -> True;  _ -> False }
120     a /= b = case (a `cmp` b) of { EQ_ -> False; _ -> True }
121
122 instance Ord OccName where
123     a <= b = case (a `cmp` b) of { LT_ -> True;  EQ_ -> True;  GT__ -> False }
124     a <  b = case (a `cmp` b) of { LT_ -> True;  EQ_ -> False; GT__ -> False }
125     a >= b = case (a `cmp` b) of { LT_ -> False; EQ_ -> True;  GT__ -> True  }
126     a >  b = case (a `cmp` b) of { LT_ -> False; EQ_ -> False; GT__ -> True  }
127
128 instance Ord3 OccName where
129     cmp = cmpOcc
130
131 (VarOcc s1) `cmpOcc` (VarOcc s2) = s1 `_CMP_STRING_` s2
132 (VarOcc s1) `cmpOcc` other2      = LT_
133
134 (TvOcc s1)  `cmpOcc` (VarOcc s2) = GT_
135 (TvOcc s1)  `cmpOcc` (TvOcc s2)  = s1 `_CMP_STRING_` s2
136 (TvOcc s1)  `cmpOcc` other       = LT_
137
138 (TCOcc s1) `cmpOcc` (TCOcc s2) = s1 `_CMP_STRING_` s2
139 (TCOcc s1) `cmpOcc` other      = GT_
140
141 instance Outputable OccName where
142   ppr = pprOccName
143 \end{code}
144
145
146 \begin{code}
147 parenInCode, quoteInText :: OccName -> Bool
148 parenInCode occ = isLexSym (occNameString occ)
149
150 quoteInText occ = not (isLexSym (occNameString occ))
151
152 -- print `vars`, (op) correctly
153 pprSymOcc, pprNonSymOcc :: PprStyle -> OccName -> Pretty
154
155 pprSymOcc sty var
156   = if quoteInText var
157     then ppQuote (pprOccName sty var)
158     else pprOccName sty var
159
160 pprNonSymOcc sty var
161   = if parenInCode var
162     then ppParens (pprOccName sty var)
163     else pprOccName sty var
164 \end{code}
165
166 %************************************************************************
167 %*                                                                      *
168 \subsection[Name-datatype]{The @Name@ datatype, and name construction}
169 %*                                                                      *
170 %************************************************************************
171  
172 \begin{code}
173 data Name
174   = Local    Unique
175              OccName
176              SrcLoc
177
178   | Global   Unique
179              Module             -- The defining module
180              OccName            -- Its name in that module
181              DefnInfo           -- How it is defined
182              Provenance         -- How it was brought into scope
183 \end{code}
184
185 Things with a @Global@ name are given C static labels, so they finally
186 appear in the .o file's symbol table.  They appear in the symbol table
187 in the form M.n.  If originally-local things have this property they
188 must be made @Global@ first.
189
190 \begin{code}
191 data DefnInfo = VanillaDefn     
192               | WiredInTyCon TyCon      -- There's a wired-in version
193               | WiredInId    Id         -- ...ditto...
194
195 data Provenance
196   = LocalDef ExportFlag SrcLoc  -- Locally defined
197   | Imported Module SrcLoc      -- Directly imported from M; gives locn of import statement
198   | Implicit                    -- Implicitly imported
199 \end{code}
200
201 Something is "Exported" if it may be mentioned by another module without
202 warning.  The crucial thing about Exported things is that they must
203 never be dropped as dead code, even if they aren't used in this module.
204 Furthermore, being Exported means that we can't see all call sites of the thing.
205
206 Exported things include:
207         - explicitly exported Ids, including data constructors, class method selectors
208         - dfuns from instance decls
209
210 Being Exported is *not* the same as finally appearing in the .o file's 
211 symbol table.  For example, a local Id may be mentioned in an Exported
212 Id's unfolding in the interface file, in which case the local Id goes
213 out too.
214
215 \begin{code}
216 data ExportFlag = Exported  | NotExported
217 \end{code}
218
219 \begin{code}
220 mkLocalName    :: Unique -> OccName -> SrcLoc -> Name
221 mkLocalName = Local
222
223 mkGlobalName :: Unique -> Module -> OccName -> DefnInfo -> Provenance -> Name
224 mkGlobalName = Global
225
226 mkSysLocalName :: Unique -> FAST_STRING -> SrcLoc -> Name
227 mkSysLocalName uniq str loc = Local uniq (VarOcc str) loc
228
229 mkWiredInIdName :: Unique -> Module -> FAST_STRING -> Id -> Name
230 mkWiredInIdName uniq mod occ id 
231   = Global uniq mod (VarOcc occ) (WiredInId id) Implicit
232
233 mkWiredInTyConName :: Unique -> Module -> FAST_STRING -> TyCon -> Name
234 mkWiredInTyConName uniq mod occ tycon
235   = Global uniq mod (TCOcc occ) (WiredInTyCon tycon) Implicit
236
237
238 mkCompoundName :: (FAST_STRING -> FAST_STRING)  -- Occurrence-name modifier
239                -> Unique                        -- New unique
240                -> Name                          -- Base name (must be a Global)
241                -> Name          -- Result is always a value name
242
243 mkCompoundName str_fn uniq (Global _ mod occ defn prov)
244   = Global uniq mod new_occ defn prov
245   where    
246     new_occ = VarOcc (str_fn (occNameString occ))               -- Always a VarOcc
247
248 mkCompoundName str_fn uniq (Local _ occ loc)
249   = Local uniq (VarOcc (str_fn (occNameString occ))) loc
250
251         -- Rather a wierd one that's used for names generated for instance decls
252 mkInstDeclName :: Unique -> Module -> OccName -> SrcLoc -> Bool -> Name
253 mkInstDeclName uniq mod occ loc from_here
254   = Global uniq mod occ VanillaDefn prov
255   where
256     prov | from_here = LocalDef Exported loc
257          | otherwise = Implicit
258
259
260 setNameProvenance :: Name -> Provenance -> Name         -- Implicit Globals only
261 setNameProvenance (Global uniq mod occ def Implicit) prov = Global uniq mod occ def prov
262 setNameProvenance other_name                         prov = other_name
263
264 -- When we renumber/rename things, we need to be
265 -- able to change a Name's Unique to match the cached
266 -- one in the thing it's the name of.  If you know what I mean.
267 changeUnique (Local      _ n l)  u = Local u n l
268 changeUnique (Global   _ mod occ def prov) u = Global u mod occ def prov
269
270 setNameVisibility :: Module -> Name -> Name
271 -- setNameVisibility is applied to top-level names in the final program
272 -- The "visibility" here concerns whether the .o file's symbol table
273 -- mentions the thing; if so, it needs a module name in its symbol,
274 -- otherwise we just use its unique.  The Global things are "visible"
275 -- and the local ones are not
276
277 setNameVisibility _ (Global uniq mod occ def (LocalDef NotExported loc))
278   | not all_toplev_ids_visible
279   = Local uniq occ loc
280
281 setNameVisibility mod (Local uniq occ loc)
282   | all_toplev_ids_visible
283   = Global uniq mod 
284            (VarOcc (showUnique uniq))   -- It's local name must be unique!
285            VanillaDefn (LocalDef NotExported loc)
286
287 setNameVisibility mod name = name
288
289 all_toplev_ids_visible = not opt_OmitInterfacePragmas ||  -- Pragmas can make them visible
290                          opt_EnsureSplittableC            -- Splitting requires visiblilty
291 \end{code}
292
293 %************************************************************************
294 %*                                                                      *
295 \subsection{Predicates and selectors}
296 %*                                                                      *
297 %************************************************************************
298
299 \begin{code}
300 nameUnique              :: Name -> Unique
301 nameModAndOcc           :: Name -> (Module, OccName)    -- Globals only
302 nameOccName             :: Name -> OccName 
303 nameString              :: Name -> FAST_STRING          -- A.b form
304 nameSrcLoc              :: Name -> SrcLoc
305 isLocallyDefinedName    :: Name -> Bool
306 isExportedName          :: Name -> Bool
307 isWiredInName           :: Name -> Bool
308 isLocalName             :: Name -> Bool
309
310
311
312 nameUnique (Local  u _ _)   = u
313 nameUnique (Global u _ _ _ _) = u
314
315 nameOccName (Local _ occ _)      = occ
316 nameOccName (Global _ _ occ _ _) = occ
317
318 nameModAndOcc (Global _ mod occ _ _) = (mod,occ)
319
320 nameString (Local _ occ _)        = occNameString occ
321 nameString (Global _ mod occ _ _) = mod _APPEND_ SLIT(".") _APPEND_ occNameString occ
322
323 isExportedName (Global _ _ _ _ (LocalDef Exported _)) = True
324 isExportedName other                                  = False
325
326 nameSrcLoc (Local _ _ loc)     = loc
327 nameSrcLoc (Global _ _ _ _ (LocalDef _ loc)) = loc
328 nameSrcLoc (Global _ _ _ _ (Imported _ loc)) = loc
329 nameSrcLoc other                             = noSrcLoc
330   
331 isLocallyDefinedName (Local  _ _ _)                  = True
332 isLocallyDefinedName (Global _ _ _ _ (LocalDef _ _)) = True
333 isLocallyDefinedName other                           = False
334
335 -- Things the compiler "knows about" are in some sense
336 -- "imported".  When we are compiling the module where
337 -- the entities are defined, we need to be able to pick
338 -- them out, often in combination with isLocallyDefined.
339 isWiredInName (Global _ _ _ (WiredInTyCon _) _) = True
340 isWiredInName (Global _ _ _ (WiredInId    _) _) = True
341 isWiredInName _                                   = False
342
343 maybeWiredInIdName :: Name -> Maybe Id
344 maybeWiredInIdName (Global _ _ _ (WiredInId id) _) = Just id
345 maybeWiredInIdName other                           = Nothing
346
347 maybeWiredInTyConName :: Name -> Maybe TyCon
348 maybeWiredInTyConName (Global _ _ _ (WiredInTyCon tc) _) = Just tc
349 maybeWiredInTyConName other                              = Nothing
350
351
352 isLocalName (Local _ _ _) = True
353 isLocalName _             = False
354 \end{code}
355
356
357 %************************************************************************
358 %*                                                                      *
359 \subsection[Name-instances]{Instance declarations}
360 %*                                                                      *
361 %************************************************************************
362
363 \begin{code}
364 cmpName n1 n2 = c n1 n2
365   where
366     c (Local  u1 _ _)   (Local  u2 _ _)       = cmp u1 u2
367     c (Local   _ _ _)     _                   = LT_
368     c (Global u1 _ _ _ _) (Global u2 _ _ _ _) = cmp u1 u2
369     c (Global  _ _ _ _ _)   _                 = GT_
370 \end{code}
371
372 \begin{code}
373 instance Eq Name where
374     a == b = case (a `cmp` b) of { EQ_ -> True;  _ -> False }
375     a /= b = case (a `cmp` b) of { EQ_ -> False; _ -> True }
376
377 instance Ord Name where
378     a <= b = case (a `cmp` b) of { LT_ -> True;  EQ_ -> True;  GT__ -> False }
379     a <  b = case (a `cmp` b) of { LT_ -> True;  EQ_ -> False; GT__ -> False }
380     a >= b = case (a `cmp` b) of { LT_ -> False; EQ_ -> True;  GT__ -> True  }
381     a >  b = case (a `cmp` b) of { LT_ -> False; EQ_ -> False; GT__ -> True  }
382
383 instance Ord3 Name where
384     cmp = cmpName
385
386 instance Uniquable Name where
387     uniqueOf = nameUnique
388
389 instance NamedThing Name where
390     getName n = n
391 \end{code}
392
393
394
395 %************************************************************************
396 %*                                                                      *
397 \subsection{Pretty printing}
398 %*                                                                      *
399 %************************************************************************
400
401 \begin{code}
402 instance Outputable Name where
403     ppr sty (Local u n _) | codeStyle sty ||
404                             ifaceStyle sty = pprUnique u
405     ppr PprForUser (Local _ n _) = ppPStr (occNameString n)
406     ppr other_sty  (Local u n _) = ppBesides [ppPStr (occNameString n), ppPStr SLIT("_"), pprUnique u]
407
408     ppr sty name@(Global u m n _ _) = ppBesides [pp_name, pp_debug sty name]
409                                where
410                                  pp_name | codeStyle sty = identToC qual_name
411                                          | otherwise     = ppPStr qual_name
412                                  qual_name = m _APPEND_ SLIT(".") _APPEND_ occNameString n
413
414 pp_debug PprDebug (Global uniq m n _ prov) = ppBesides [ppStr "{-", pprUnique uniq, ppStr ",", 
415                                                         pp_prov prov, ppStr "-}"]
416                                         where
417                                                 pp_prov (LocalDef _ _) = ppChar 'l'
418                                                 pp_prov (Imported _ _) = ppChar 'i'
419                                                 pp_prov Implicit       = ppChar 'p'
420 pp_debug other    name                  = ppNil
421
422 -- pprNameProvenance is used in error messages to say where a name came from
423 pprNameProvenance :: PprStyle -> Name -> Pretty
424 pprNameProvenance sty (Local _ _ loc)       = pprProvenance sty (LocalDef NotExported loc)
425 pprNameProvenance sty (Global _ _ _ _ prov) = pprProvenance sty prov
426
427 pprProvenance :: PprStyle -> Provenance -> Pretty
428 pprProvenance sty (Imported mod loc)
429   = ppSep [ppStr "Imported from", pprModule sty mod, ppStr "at", ppr sty loc]
430 pprProvenance sty (LocalDef _ loc) 
431   = ppSep [ppStr "Defined at", ppr sty loc]
432 pprProvenance sty Implicit
433   = panic "pprNameProvenance: Implicit"
434 \end{code}
435
436
437 %************************************************************************
438 %*                                                                      *
439 \subsection[Sets of names}
440 %*                                                                      *
441 %************************************************************************
442
443 \begin{code}
444 type NameSet = UniqSet Name
445 emptyNameSet      :: NameSet
446 unitNameSet       :: Name -> NameSet
447 addListToNameSet  :: NameSet -> [Name] -> NameSet
448 mkNameSet         :: [Name] -> NameSet
449 unionNameSets     :: NameSet -> NameSet -> NameSet
450 unionManyNameSets :: [NameSet] -> NameSet
451 minusNameSet      :: NameSet -> NameSet -> NameSet
452 elemNameSet       :: Name -> NameSet -> Bool
453 nameSetToList     :: NameSet -> [Name]
454
455 emptyNameSet      = emptyUniqSet
456 unitNameSet       = unitUniqSet
457 mkNameSet         = mkUniqSet
458 addListToNameSet  = addListToUniqSet
459 unionNameSets     = unionUniqSets
460 unionManyNameSets = unionManyUniqSets
461 minusNameSet      = minusUniqSet
462 elemNameSet       = elementOfUniqSet
463 nameSetToList     = uniqSetToList
464 \end{code}
465
466
467
468 %************************************************************************
469 %*                                                                      *
470 \subsection{Overloaded functions related to Names}
471 %*                                                                      *
472 %************************************************************************
473
474 \begin{code}
475 class NamedThing a where
476     getOccName :: a -> OccName          -- Even RdrNames can do this!
477     getName    :: a -> Name
478
479     getOccName n = nameOccName (getName n)      -- Default method
480 \end{code}
481
482 \begin{code}
483 modAndOcc           :: NamedThing a => a -> (Module, OccName)
484 getSrcLoc           :: NamedThing a => a -> SrcLoc
485 isLocallyDefined    :: NamedThing a => a -> Bool
486 isExported          :: NamedThing a => a -> Bool
487 getOccString        :: NamedThing a => a -> String
488
489 modAndOcc           = nameModAndOcc        . getName
490 isExported          = isExportedName       . getName
491 getSrcLoc           = nameSrcLoc           . getName
492 isLocallyDefined    = isLocallyDefinedName . getName
493 pprSym sty          = pprSymOcc sty        . getOccName
494 pprNonSym sty       = pprNonSymOcc sty     . getOccName
495 getOccString x      = _UNPK_ (occNameString (getOccName x))
496 \end{code}
497
498 \begin{code}
499 {-# SPECIALIZE isLocallyDefined
500         :: Name     -> Bool
501   #-}
502 \end{code}