| |||||||||||||||||
| |||||||||||||||||
| |||||||||||||||||
Description | |||||||||||||||||
GHC uses several kinds of name internally:
| |||||||||||||||||
Synopsis | |||||||||||||||||
The main type | |||||||||||||||||
data RdrName | |||||||||||||||||
| |||||||||||||||||
Construction | |||||||||||||||||
mkRdrUnqual :: OccName -> RdrName | |||||||||||||||||
mkRdrQual :: ModuleName -> OccName -> RdrName | |||||||||||||||||
mkUnqual :: NameSpace -> FastString -> RdrName | |||||||||||||||||
mkVarUnqual :: FastString -> RdrName | |||||||||||||||||
mkQual :: NameSpace -> (FastString, FastString) -> RdrName | |||||||||||||||||
Make a qualified RdrName in the given namespace and where the ModuleName and the OccName are taken from the first and second elements of the tuple respectively | |||||||||||||||||
mkOrig :: Module -> OccName -> RdrName | |||||||||||||||||
nameRdrName :: Name -> RdrName | |||||||||||||||||
getRdrName :: NamedThing thing => thing -> RdrName | |||||||||||||||||
mkDerivedRdrName :: Name -> (OccName -> OccName) -> RdrName | |||||||||||||||||
Produce an original RdrName whose module that of a parent Name but its OccName is derived from that of it's parent using the supplied function | |||||||||||||||||
Destruction | |||||||||||||||||
rdrNameOcc :: RdrName -> OccName | |||||||||||||||||
rdrNameSpace :: RdrName -> NameSpace | |||||||||||||||||
setRdrNameSpace :: RdrName -> NameSpace -> RdrName | |||||||||||||||||
This rather gruesome function is used mainly by the parser. When parsing: data T a = T | T1 Int we parse the data constructors as types because of parser ambiguities, so then we need to change the type constr to a data constr The exact-name case can occur when parsing: data [] a = [] | a : [a] For the exact-name case we return an original name. | |||||||||||||||||
isRdrDataCon :: RdrName -> Bool | |||||||||||||||||
isRdrTyVar :: RdrName -> Bool | |||||||||||||||||
isRdrTc :: RdrName -> Bool | |||||||||||||||||
isQual :: RdrName -> Bool | |||||||||||||||||
isQual_maybe :: RdrName -> Maybe (ModuleName, OccName) | |||||||||||||||||
isUnqual :: RdrName -> Bool | |||||||||||||||||
isOrig :: RdrName -> Bool | |||||||||||||||||
isOrig_maybe :: RdrName -> Maybe (Module, OccName) | |||||||||||||||||
isExact :: RdrName -> Bool | |||||||||||||||||
isExact_maybe :: RdrName -> Maybe Name | |||||||||||||||||
isSrcRdrName :: RdrName -> Bool | |||||||||||||||||
Printing | |||||||||||||||||
showRdrName :: RdrName -> String | |||||||||||||||||
Local mapping of RdrName to Name | |||||||||||||||||
type LocalRdrEnv = OccEnv Name | |||||||||||||||||
This environment is used to store local bindings (let, where, lambda, case). It is keyed by OccName, because we never use it for qualified names | |||||||||||||||||
emptyLocalRdrEnv :: LocalRdrEnv | |||||||||||||||||
extendLocalRdrEnv :: LocalRdrEnv -> [Name] -> LocalRdrEnv | |||||||||||||||||
lookupLocalRdrEnv :: LocalRdrEnv -> RdrName -> Maybe Name | |||||||||||||||||
lookupLocalRdrOcc :: LocalRdrEnv -> OccName -> Maybe Name | |||||||||||||||||
elemLocalRdrEnv :: RdrName -> LocalRdrEnv -> Bool | |||||||||||||||||
Global mapping of RdrName to GlobalRdrElts | |||||||||||||||||
type GlobalRdrEnv = OccEnv [GlobalRdrElt] | |||||||||||||||||
Keyed by OccName; when looking up a qualified name we look up the OccName part, and then check the Provenance to see if the appropriate qualification is valid. This saves routinely doubling the size of the env by adding both qualified and unqualified names to the domain. The list in the codomain is required because there may be name clashes These only get reported on lookup, not on construction INVARIANT: All the members of the list have distinct gre_name fields; that is, no duplicate Names INVARIANT: Imported provenance => Name is an ExternalName However LocalDefs can have an InternalName. This happens only when type-checking a [d| ... |] Template Haskell quotation; see this note in RnNames Note [Top-level Names in Template Haskell decl quotes] | |||||||||||||||||
emptyGlobalRdrEnv :: GlobalRdrEnv | |||||||||||||||||
mkGlobalRdrEnv :: [GlobalRdrElt] -> GlobalRdrEnv | |||||||||||||||||
plusGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrEnv -> GlobalRdrEnv | |||||||||||||||||
lookupGlobalRdrEnv :: GlobalRdrEnv -> OccName -> [GlobalRdrElt] | |||||||||||||||||
extendGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrElt -> GlobalRdrEnv | |||||||||||||||||
pprGlobalRdrEnv :: GlobalRdrEnv -> SDoc | |||||||||||||||||
globalRdrEnvElts :: GlobalRdrEnv -> [GlobalRdrElt] | |||||||||||||||||
lookupGRE_RdrName :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt] | |||||||||||||||||
lookupGRE_Name :: GlobalRdrEnv -> Name -> [GlobalRdrElt] | |||||||||||||||||
getGRE_NameQualifier_maybes :: GlobalRdrEnv -> Name -> [Maybe [ModuleName]] | |||||||||||||||||
hideSomeUnquals :: GlobalRdrEnv -> [OccName] -> GlobalRdrEnv | |||||||||||||||||
Hide any unqualified bindings for the specified OccNames This is used in TH, when renaming a declaration bracket [d| foo = ... |] We want unqualified foo in ... to mean this foo, not the one from the enclosing module. But the qualified name from the enclosing module must certainly still be available | |||||||||||||||||
findLocalDupsRdrEnv :: GlobalRdrEnv -> [OccName] -> (GlobalRdrEnv, [[Name]]) | |||||||||||||||||
For each OccName, see if there are multiple local definitions for it. If so, remove all but one (to suppress subsequent error messages) and return a list of the duplicate bindings | |||||||||||||||||
Global RdrName mapping elements: GlobalRdrElt, Provenance, ImportSpec | |||||||||||||||||
data GlobalRdrElt | |||||||||||||||||
| |||||||||||||||||
isLocalGRE :: GlobalRdrElt -> Bool | |||||||||||||||||
unQualOK :: GlobalRdrElt -> Bool | |||||||||||||||||
Test if an unqualifed version of this thing would be in scope | |||||||||||||||||
qualSpecOK :: ModuleName -> ImportSpec -> Bool | |||||||||||||||||
Is in scope qualified with the given module? | |||||||||||||||||
unQualSpecOK :: ImportSpec -> Bool | |||||||||||||||||
Is in scope unqualified? | |||||||||||||||||
data Provenance | |||||||||||||||||
| |||||||||||||||||
pprNameProvenance :: GlobalRdrElt -> SDoc | |||||||||||||||||
Print out the place where the name was imported | |||||||||||||||||
data Parent | |||||||||||||||||
| |||||||||||||||||
data ImportSpec | |||||||||||||||||
| |||||||||||||||||
data ImpDeclSpec | |||||||||||||||||
| |||||||||||||||||
data ImpItemSpec | |||||||||||||||||
| |||||||||||||||||
importSpecLoc :: ImportSpec -> SrcSpan | |||||||||||||||||
importSpecModule :: ImportSpec -> ModuleName | |||||||||||||||||
isExplicitItem :: ImpItemSpec -> Bool | |||||||||||||||||
Produced by Haddock version 2.4.2 |