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