Safe Haskell | None |
---|---|
Language | Haskell98 |
- data RdrName
- mkRdrUnqual :: OccName -> RdrName
- mkRdrQual :: ModuleName -> OccName -> RdrName
- mkUnqual :: NameSpace -> FastString -> RdrName
- mkVarUnqual :: FastString -> RdrName
- mkQual :: NameSpace -> (FastString, FastString) -> RdrName
- mkOrig :: Module -> OccName -> RdrName
- nameRdrName :: Name -> RdrName
- getRdrName :: NamedThing thing => thing -> RdrName
- rdrNameOcc :: RdrName -> OccName
- rdrNameSpace :: RdrName -> NameSpace
- setRdrNameSpace :: RdrName -> NameSpace -> RdrName
- demoteRdrName :: RdrName -> Maybe RdrName
- 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
- data LocalRdrEnv
- emptyLocalRdrEnv :: LocalRdrEnv
- extendLocalRdrEnv :: LocalRdrEnv -> Name -> LocalRdrEnv
- extendLocalRdrEnvList :: LocalRdrEnv -> [Name] -> LocalRdrEnv
- lookupLocalRdrEnv :: LocalRdrEnv -> RdrName -> Maybe Name
- lookupLocalRdrOcc :: LocalRdrEnv -> OccName -> Maybe Name
- elemLocalRdrEnv :: RdrName -> LocalRdrEnv -> Bool
- inLocalRdrEnvScope :: Name -> LocalRdrEnv -> Bool
- localRdrEnvElts :: LocalRdrEnv -> [Name]
- delLocalRdrEnvList :: LocalRdrEnv -> [OccName] -> LocalRdrEnv
- type GlobalRdrEnv = OccEnv [GlobalRdrElt]
- emptyGlobalRdrEnv :: GlobalRdrEnv
- mkGlobalRdrEnv :: [GlobalRdrElt] -> GlobalRdrEnv
- plusGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrEnv -> GlobalRdrEnv
- lookupGlobalRdrEnv :: GlobalRdrEnv -> OccName -> [GlobalRdrElt]
- extendGlobalRdrEnv :: Bool -> GlobalRdrEnv -> [AvailInfo] -> GlobalRdrEnv
- pprGlobalRdrEnv :: Bool -> GlobalRdrEnv -> SDoc
- globalRdrEnvElts :: GlobalRdrEnv -> [GlobalRdrElt]
- lookupGRE_RdrName :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt]
- lookupGRE_Name :: GlobalRdrEnv -> Name -> [GlobalRdrElt]
- getGRE_NameQualifier_maybes :: GlobalRdrEnv -> Name -> [Maybe [ModuleName]]
- transformGREs :: (GlobalRdrElt -> GlobalRdrElt) -> [OccName] -> GlobalRdrEnv -> GlobalRdrEnv
- findLocalDupsRdrEnv :: GlobalRdrEnv -> [Name] -> [[GlobalRdrElt]]
- pickGREs :: RdrName -> [GlobalRdrElt] -> [GlobalRdrElt]
- gresFromAvails :: Provenance -> [AvailInfo] -> [GlobalRdrElt]
- gresFromAvail :: (Name -> Provenance) -> AvailInfo -> [GlobalRdrElt]
- data GlobalRdrElt = GRE {}
- isLocalGRE :: GlobalRdrElt -> Bool
- unQualOK :: GlobalRdrElt -> Bool
- qualSpecOK :: ModuleName -> ImportSpec -> Bool
- unQualSpecOK :: ImportSpec -> Bool
- data Provenance
- = LocalDef
- | Imported [ImportSpec]
- pprNameProvenance :: GlobalRdrElt -> SDoc
- data Parent
- data ImportSpec = ImpSpec {}
- data ImpDeclSpec = ImpDeclSpec {
- is_mod :: ModuleName
- is_as :: ModuleName
- is_qual :: Bool
- is_dloc :: SrcSpan
- data ImpItemSpec
- importSpecLoc :: ImportSpec -> SrcSpan
- importSpecModule :: ImportSpec -> ModuleName
- isExplicitItem :: ImpItemSpec -> Bool
The main type
Do not use the data constructors of RdrName directly: prefer the family
of functions that creates them, such as mkRdrUnqual
Unqual OccName | Used for ordinary, unqualified occurrences, e.g. |
Qual ModuleName OccName | A qualified name written by the user in
source code. The module isn't necessarily
the module where the thing is defined;
just the one from which it is imported.
Examples are |
Orig Module OccName | An original name; the module is the defining module.
This is used when GHC generates code that will be fed
into the renamer (e.g. from deriving clauses), but where
we want to say "Use Prelude.map dammit". One of these
can be created with |
Exact Name | We know exactly the
Such a |
Construction
mkRdrUnqual :: OccName -> RdrName Source
mkRdrQual :: ModuleName -> OccName -> RdrName Source
mkUnqual :: NameSpace -> FastString -> RdrName Source
mkVarUnqual :: FastString -> RdrName Source
mkQual :: NameSpace -> (FastString, FastString) -> RdrName Source
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
nameRdrName :: Name -> RdrName Source
getRdrName :: NamedThing thing => thing -> RdrName Source
Destruction
rdrNameOcc :: RdrName -> OccName Source
rdrNameSpace :: RdrName -> NameSpace Source
setRdrNameSpace :: RdrName -> NameSpace -> RdrName Source
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.
demoteRdrName :: RdrName -> Maybe RdrName Source
isRdrDataCon :: RdrName -> Bool Source
isRdrTyVar :: RdrName -> Bool Source
isQual_maybe :: RdrName -> Maybe (ModuleName, OccName) Source
isExact_maybe :: RdrName -> Maybe Name Source
isSrcRdrName :: RdrName -> Bool Source
Local mapping of RdrName
to Name
data LocalRdrEnv Source
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
We keep the current mapping, *and* the set of all Names in scope
Reason: see Note [Splicing Exact Names] in RnEnv
extendLocalRdrEnv :: LocalRdrEnv -> Name -> LocalRdrEnv Source
extendLocalRdrEnvList :: LocalRdrEnv -> [Name] -> LocalRdrEnv Source
lookupLocalRdrEnv :: LocalRdrEnv -> RdrName -> Maybe Name Source
lookupLocalRdrOcc :: LocalRdrEnv -> OccName -> Maybe Name Source
elemLocalRdrEnv :: RdrName -> LocalRdrEnv -> Bool Source
inLocalRdrEnvScope :: Name -> LocalRdrEnv -> Bool Source
localRdrEnvElts :: LocalRdrEnv -> [Name] Source
delLocalRdrEnvList :: LocalRdrEnv -> [OccName] -> LocalRdrEnv Source
Global mapping of RdrName
to GlobalRdrElt
s
type GlobalRdrEnv = OccEnv [GlobalRdrElt] Source
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]
mkGlobalRdrEnv :: [GlobalRdrElt] -> GlobalRdrEnv Source
lookupGlobalRdrEnv :: GlobalRdrEnv -> OccName -> [GlobalRdrElt] Source
extendGlobalRdrEnv :: Bool -> GlobalRdrEnv -> [AvailInfo] -> GlobalRdrEnv Source
pprGlobalRdrEnv :: Bool -> GlobalRdrEnv -> SDoc Source
lookupGRE_RdrName :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt] Source
lookupGRE_Name :: GlobalRdrEnv -> Name -> [GlobalRdrElt] Source
getGRE_NameQualifier_maybes :: GlobalRdrEnv -> Name -> [Maybe [ModuleName]] Source
transformGREs :: (GlobalRdrElt -> GlobalRdrElt) -> [OccName] -> GlobalRdrEnv -> GlobalRdrEnv Source
Apply a transformation function to the GREs for these OccNames
findLocalDupsRdrEnv :: GlobalRdrEnv -> [Name] -> [[GlobalRdrElt]] Source
For each OccName
, see if there are multiple local definitions
for it; return a list of all such
and return a list of the duplicate bindings
pickGREs :: RdrName -> [GlobalRdrElt] -> [GlobalRdrElt] Source
Take a list of GREs which have the right OccName Pick those GREs that are suitable for this RdrName And for those, keep only only the Provenances that are suitable Only used for Qual and Unqual, not Orig or Exact
Consider:
module A ( f ) where import qualified Foo( f ) import Baz( f ) f = undefined
Let's suppose that Foo.f
and Baz.f
are the same entity really.
The export of f
is ambiguous because it's in scope from the local def
and the import. The lookup of Unqual f
should return a GRE for
the locally-defined f
, and a GRE for the imported f
, with a single
provenance, namely the one for Baz(f)
.
GlobalRdrElts
gresFromAvails :: Provenance -> [AvailInfo] -> [GlobalRdrElt] Source
make a GlobalRdrEnv
where all the elements point to the same
Provenance (useful for "hiding" imports, or imports with
no details).
gresFromAvail :: (Name -> Provenance) -> AvailInfo -> [GlobalRdrElt] Source
Global RdrName
mapping elements: GlobalRdrElt
, Provenance
, ImportSpec
data GlobalRdrElt Source
An element of the GlobalRdrEnv
isLocalGRE :: GlobalRdrElt -> Bool Source
unQualOK :: GlobalRdrElt -> Bool Source
Test if an unqualifed version of this thing would be in scope
qualSpecOK :: ModuleName -> ImportSpec -> Bool Source
Is in scope qualified with the given module?
unQualSpecOK :: ImportSpec -> Bool Source
Is in scope unqualified?
data Provenance Source
The Provenance
of something says how it came to be in scope.
It's quite elaborate so that we can give accurate unused-name warnings.
LocalDef | The thing was defined locally |
Imported [ImportSpec] | The thing was imported. INVARIANT: the list of |
pprNameProvenance :: GlobalRdrElt -> SDoc Source
Print out the place where the name was imported
The children of a Name are the things that are abbreviated by the ".." notation in export lists. See Note [Parents]
data ImportSpec Source
data ImpDeclSpec Source
Describes a particular import declaration and is
shared among all the Provenance
s for that decl
ImpDeclSpec | |
|
data ImpItemSpec Source
Describes import info a particular Name
ImpAll | The import had no import list, or had a hiding list |
ImpSome | The import had an import list.
The import C( T(..) ) Here the constructors of |
|
importSpecLoc :: ImportSpec -> SrcSpan Source
isExplicitItem :: ImpItemSpec -> Bool Source