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