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