[project @ 1996-12-19 09:39:49 by simonpj]
[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         -- Globals only
261 setNameProvenance (Global uniq mod occ def _) prov = Global uniq mod occ def prov
262
263 -- When we renumber/rename things, we need to be
264 -- able to change a Name's Unique to match the cached
265 -- one in the thing it's the name of.  If you know what I mean.
266 changeUnique (Local      _ n l)  u = Local u n l
267 changeUnique (Global   _ mod occ def prov) u = Global u mod occ def prov
268
269 setNameVisibility :: Module -> Name -> Name
270 -- setNameVisibility is applied to top-level names in the final program
271 -- The "visibility" here concerns whether the .o file's symbol table
272 -- mentions the thing; if so, it needs a module name in its symbol,
273 -- otherwise we just use its unique.  The Global things are "visible"
274 -- and the local ones are not
275
276 setNameVisibility _ (Global uniq mod occ def (LocalDef NotExported loc))
277   | not all_toplev_ids_visible
278   = Local uniq occ loc
279
280 setNameVisibility mod (Local uniq occ loc)
281   | all_toplev_ids_visible
282   = Global uniq mod 
283            (VarOcc (showUnique uniq))   -- It's local name must be unique!
284            VanillaDefn (LocalDef NotExported loc)
285
286 setNameVisibility mod name = name
287
288 all_toplev_ids_visible = not opt_OmitInterfacePragmas ||  -- Pragmas can make them visible
289                          opt_EnsureSplittableC            -- Splitting requires visiblilty
290 \end{code}
291
292 %************************************************************************
293 %*                                                                      *
294 \subsection{Predicates and selectors}
295 %*                                                                      *
296 %************************************************************************
297
298 \begin{code}
299 nameUnique              :: Name -> Unique
300 nameModAndOcc           :: Name -> (Module, OccName)    -- Globals only
301 nameOccName             :: Name -> OccName 
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 nameModAndOcc (Global _ mod occ _ _) = (mod,occ)
318
319 nameString (Local _ occ _)        = occNameString occ
320 nameString (Global _ mod occ _ _) = mod _APPEND_ SLIT(".") _APPEND_ occNameString occ
321
322 isExportedName (Global _ _ _ _ (LocalDef Exported _)) = True
323 isExportedName other                                  = False
324
325 nameSrcLoc (Local _ _ loc)     = loc
326 nameSrcLoc (Global _ _ _ _ (LocalDef _ loc)) = loc
327 nameSrcLoc (Global _ _ _ _ (Imported _ loc)) = loc
328 nameSrcLoc other                             = noSrcLoc
329   
330 isLocallyDefinedName (Local  _ _ _)                  = True
331 isLocallyDefinedName (Global _ _ _ _ (LocalDef _ _)) = True
332 isLocallyDefinedName other                           = False
333
334 -- Things the compiler "knows about" are in some sense
335 -- "imported".  When we are compiling the module where
336 -- the entities are defined, we need to be able to pick
337 -- them out, often in combination with isLocallyDefined.
338 isWiredInName (Global _ _ _ (WiredInTyCon _) _) = True
339 isWiredInName (Global _ _ _ (WiredInId    _) _) = True
340 isWiredInName _                                   = False
341
342 maybeWiredInIdName :: Name -> Maybe Id
343 maybeWiredInIdName (Global _ _ _ (WiredInId id) _) = Just id
344 maybeWiredInIdName other                           = Nothing
345
346 maybeWiredInTyConName :: Name -> Maybe TyCon
347 maybeWiredInTyConName (Global _ _ _ (WiredInTyCon tc) _) = Just tc
348 maybeWiredInTyConName other                              = Nothing
349
350
351 isLocalName (Local _ _ _) = True
352 isLocalName _             = False
353 \end{code}
354
355
356 %************************************************************************
357 %*                                                                      *
358 \subsection[Name-instances]{Instance declarations}
359 %*                                                                      *
360 %************************************************************************
361
362 \begin{code}
363 cmpName n1 n2 = c n1 n2
364   where
365     c (Local  u1 _ _)   (Local  u2 _ _)       = cmp u1 u2
366     c (Local   _ _ _)     _                   = LT_
367     c (Global u1 _ _ _ _) (Global u2 _ _ _ _) = cmp u1 u2
368     c (Global  _ _ _ _ _)   _                 = GT_
369 \end{code}
370
371 \begin{code}
372 instance Eq Name where
373     a == b = case (a `cmp` b) of { EQ_ -> True;  _ -> False }
374     a /= b = case (a `cmp` b) of { EQ_ -> False; _ -> True }
375
376 instance Ord Name where
377     a <= b = case (a `cmp` b) of { LT_ -> True;  EQ_ -> True;  GT__ -> False }
378     a <  b = case (a `cmp` b) of { LT_ -> True;  EQ_ -> False; GT__ -> False }
379     a >= b = case (a `cmp` b) of { LT_ -> False; EQ_ -> True;  GT__ -> True  }
380     a >  b = case (a `cmp` b) of { LT_ -> False; EQ_ -> False; GT__ -> True  }
381
382 instance Ord3 Name where
383     cmp = cmpName
384
385 instance Uniquable Name where
386     uniqueOf = nameUnique
387
388 instance NamedThing Name where
389     getName n = n
390 \end{code}
391
392
393
394 %************************************************************************
395 %*                                                                      *
396 \subsection{Pretty printing}
397 %*                                                                      *
398 %************************************************************************
399
400 \begin{code}
401 instance Outputable Name where
402     ppr sty (Local u n _) | codeStyle sty ||
403                             ifaceStyle sty = pprUnique u
404     ppr PprForUser (Local _ n _) = ppPStr (occNameString n)
405     ppr other_sty  (Local u n _) = ppBesides [ppPStr (occNameString n), ppPStr SLIT("_"), pprUnique u]
406
407     ppr sty (Global u m n _ _) = ppBesides [pp_name, pp_uniq sty u]
408                                where
409                                  pp_name | codeStyle sty = identToC qual_name
410                                          | otherwise     = ppPStr qual_name
411                                  qual_name = m _APPEND_ SLIT(".") _APPEND_ occNameString n
412
413 pp_uniq PprDebug uniq = ppBesides [ppStr "{-", pprUnique uniq, ppStr "-}"]
414 pp_uniq other    uniq = ppNil
415
416 -- pprNameProvenance is used in error messages to say where a name came from
417 pprNameProvenance :: PprStyle -> Name -> Pretty
418 pprNameProvenance sty (Local _ _ loc)       = pprProvenance sty (LocalDef NotExported loc)
419 pprNameProvenance sty (Global _ _ _ _ prov) = pprProvenance sty prov
420
421 pprProvenance :: PprStyle -> Provenance -> Pretty
422 pprProvenance sty (Imported mod loc)
423   = ppSep [ppStr "Imported from", pprModule sty mod, ppStr "at", ppr sty loc]
424 pprProvenance sty (LocalDef _ loc) 
425   = ppSep [ppStr "Defined at", ppr sty loc]
426 pprProvenance sty Implicit
427   = panic "pprNameProvenance: Implicit"
428 \end{code}
429
430
431 %************************************************************************
432 %*                                                                      *
433 \subsection[Sets of names}
434 %*                                                                      *
435 %************************************************************************
436
437 \begin{code}
438 type NameSet = UniqSet Name
439 emptyNameSet      :: NameSet
440 unitNameSet       :: Name -> NameSet
441 addListToNameSet  :: NameSet -> [Name] -> NameSet
442 mkNameSet         :: [Name] -> NameSet
443 unionNameSets     :: NameSet -> NameSet -> NameSet
444 unionManyNameSets :: [NameSet] -> NameSet
445 minusNameSet      :: NameSet -> NameSet -> NameSet
446 elemNameSet       :: Name -> NameSet -> Bool
447 nameSetToList     :: NameSet -> [Name]
448
449 emptyNameSet      = emptyUniqSet
450 unitNameSet       = unitUniqSet
451 mkNameSet         = mkUniqSet
452 addListToNameSet  = addListToUniqSet
453 unionNameSets     = unionUniqSets
454 unionManyNameSets = unionManyUniqSets
455 minusNameSet      = minusUniqSet
456 elemNameSet       = elementOfUniqSet
457 nameSetToList     = uniqSetToList
458 \end{code}
459
460
461
462 %************************************************************************
463 %*                                                                      *
464 \subsection{Overloaded functions related to Names}
465 %*                                                                      *
466 %************************************************************************
467
468 \begin{code}
469 class NamedThing a where
470     getOccName :: a -> OccName          -- Even RdrNames can do this!
471     getName    :: a -> Name
472
473     getOccName n = nameOccName (getName n)      -- Default method
474 \end{code}
475
476 \begin{code}
477 modAndOcc           :: NamedThing a => a -> (Module, OccName)
478 getSrcLoc           :: NamedThing a => a -> SrcLoc
479 isLocallyDefined    :: NamedThing a => a -> Bool
480 isExported          :: NamedThing a => a -> Bool
481 getOccString        :: NamedThing a => a -> String
482
483 modAndOcc           = nameModAndOcc        . getName
484 isExported          = isExportedName       . getName
485 getSrcLoc           = nameSrcLoc           . getName
486 isLocallyDefined    = isLocallyDefinedName . getName
487 pprSym sty          = pprSymOcc sty        . getOccName
488 pprNonSym sty       = pprNonSymOcc sty     . getOccName
489 getOccString x      = _UNPK_ (occNameString (getOccName x))
490 \end{code}
491
492 \begin{code}
493 {-# SPECIALIZE isLocallyDefined
494         :: Name     -> Bool
495   #-}
496 \end{code}