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