Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
GHC uses several kinds of name internally:
OccName
: see GHC.Types.Name.OccurrenceRdrName
is the type of names that come directly from the parser. They have not yet had their scoping and binding resolved by the renamer and can be thought of to a first approximation as anOccName
with an optional module qualifierName
: see GHC.Types.NameId
: see GHC.Types.IdVar
: see GHC.Types.Var
Synopsis
- 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
- demoteRdrName :: RdrName -> Maybe RdrName
- promoteRdrName :: 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]
- minusLocalRdrEnv :: LocalRdrEnv -> OccEnv a -> LocalRdrEnv
- type GlobalRdrEnv = OccEnv [GlobalRdrElt]
- emptyGlobalRdrEnv :: GlobalRdrEnv
- mkGlobalRdrEnv :: [GlobalRdrElt] -> GlobalRdrEnv
- plusGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrEnv -> GlobalRdrEnv
- lookupGlobalRdrEnv :: GlobalRdrEnv -> OccName -> [GlobalRdrElt]
- extendGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrElt -> GlobalRdrEnv
- greOccName :: GlobalRdrElt -> OccName
- shadowNames :: GlobalRdrEnv -> OccEnv a -> GlobalRdrEnv
- pprGlobalRdrEnv :: Bool -> GlobalRdrEnv -> SDoc
- globalRdrEnvElts :: GlobalRdrEnv -> [GlobalRdrElt]
- lookupGRE_RdrName :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt]
- lookupGRE_RdrName' :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt]
- lookupGRE_Name :: GlobalRdrEnv -> Name -> Maybe GlobalRdrElt
- lookupGRE_GreName :: GlobalRdrEnv -> GreName -> Maybe GlobalRdrElt
- lookupGRE_FieldLabel :: GlobalRdrEnv -> FieldLabel -> Maybe GlobalRdrElt
- lookupGRE_Name_OccName :: GlobalRdrEnv -> Name -> OccName -> Maybe GlobalRdrElt
- getGRE_NameQualifier_maybes :: GlobalRdrEnv -> Name -> [Maybe [ModuleName]]
- transformGREs :: (GlobalRdrElt -> GlobalRdrElt) -> [OccName] -> GlobalRdrEnv -> GlobalRdrEnv
- pickGREs :: RdrName -> [GlobalRdrElt] -> [GlobalRdrElt]
- pickGREsModExp :: ModuleName -> [GlobalRdrElt] -> [(GlobalRdrElt, GlobalRdrElt)]
- gresFromAvails :: Maybe ImportSpec -> [AvailInfo] -> [GlobalRdrElt]
- gresFromAvail :: (Name -> Maybe ImportSpec) -> AvailInfo -> [GlobalRdrElt]
- localGREsFromAvail :: AvailInfo -> [GlobalRdrElt]
- availFromGRE :: GlobalRdrElt -> AvailInfo
- greRdrNames :: GlobalRdrElt -> [RdrName]
- greSrcSpan :: GlobalRdrElt -> SrcSpan
- greQualModName :: GlobalRdrElt -> ModuleName
- gresToAvailInfo :: [GlobalRdrElt] -> [AvailInfo]
- greDefinitionModule :: GlobalRdrElt -> Maybe Module
- greDefinitionSrcSpan :: GlobalRdrElt -> SrcSpan
- greMangledName :: GlobalRdrElt -> Name
- grePrintableName :: GlobalRdrElt -> Name
- greFieldLabel :: GlobalRdrElt -> Maybe FieldLabel
- data GlobalRdrElt = GRE {}
- isLocalGRE :: GlobalRdrElt -> Bool
- isRecFldGRE :: GlobalRdrElt -> Bool
- isDuplicateRecFldGRE :: GlobalRdrElt -> Bool
- isNoFieldSelectorGRE :: GlobalRdrElt -> Bool
- isFieldSelectorGRE :: GlobalRdrElt -> Bool
- unQualOK :: GlobalRdrElt -> Bool
- qualSpecOK :: ModuleName -> ImportSpec -> Bool
- unQualSpecOK :: ImportSpec -> Bool
- pprNameProvenance :: GlobalRdrElt -> SDoc
- data GreName
- greNameSrcSpan :: GreName -> SrcSpan
- data Parent
- greParent_maybe :: GlobalRdrElt -> Maybe Name
- 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
- bestImport :: [ImportSpec] -> ImportSpec
- opIsAt :: RdrName -> Bool
The main type
Reader Name
Do not use the data constructors of RdrName directly: prefer the family
of functions that creates them, such as mkRdrUnqual
- Note: A Located RdrName will only have API Annotations if it is a compound one, e.g.
`bar` ( ~ )
AnnKeywordId
:AnnType
,AnnOpen
'('
or'['
or'[:'
,AnnClose
')'
or']'
or':]'
,,AnnBackquote
'`'
,AnnVal
AnnTilde
,
Unqual OccName | Unqualified name Used for ordinary, unqualified occurrences, e.g. |
Qual ModuleName OccName | Qualified name 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 | Original name 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 | Exact name We know exactly the
Such a |
Instances
Data RdrName Source # | |
Defined in GHC.Types.Name.Reader gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RdrName -> c RdrName Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RdrName Source # toConstr :: RdrName -> Constr Source # dataTypeOf :: RdrName -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RdrName) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RdrName) Source # gmapT :: (forall b. Data b => b -> b) -> RdrName -> RdrName Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RdrName -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RdrName -> r Source # gmapQ :: (forall d. Data d => d -> u) -> RdrName -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> RdrName -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName Source # | |
DisambInfixOp RdrName Source # | |
Defined in GHC.Parser.PostProcess | |
HasOccName RdrName Source # | |
Outputable RdrName Source # | |
OutputableBndr RdrName Source # | |
Defined in GHC.Types.Name.Reader | |
Eq RdrName Source # | |
Ord RdrName Source # | |
type Anno RdrName Source # | |
Defined in GHC.Hs.Extension | |
type Anno (LocatedN RdrName) Source # | |
Defined in GHC.Hs.Binds | |
type Anno [LocatedN RdrName] Source # | |
Defined in GHC.Hs.Binds |
Construction
mkRdrUnqual :: OccName -> 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 #
isRdrDataCon :: RdrName -> Bool Source #
isRdrTyVar :: RdrName -> Bool Source #
isQual_maybe :: RdrName -> Maybe (ModuleName, OccName) Source #
isSrcRdrName :: RdrName -> Bool Source #
Local mapping of RdrName
to Name
data LocalRdrEnv Source #
Local Reader Environment See Note [LocalRdrEnv]
Instances
Outputable LocalRdrEnv Source # | |
Defined in GHC.Types.Name.Reader ppr :: LocalRdrEnv -> SDoc Source # |
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 #
minusLocalRdrEnv :: LocalRdrEnv -> OccEnv a -> LocalRdrEnv Source #
Global mapping of RdrName
to GlobalRdrElt
s
type GlobalRdrEnv = OccEnv [GlobalRdrElt] Source #
Global Reader Environment
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 1: All the members of the list have distinct
gre_name
fields; that is, no duplicate Names
INVARIANT 2: 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 GHC.Rename.Names Note [Top-level Names in Template Haskell decl quotes]
INVARIANT 3: If the GlobalRdrEnv maps [occ -> gre], then greOccName gre = occ
NB: greOccName gre is usually the same as nameOccName (greMangledName gre), but not always in the case of record selectors; see Note [GreNames]
mkGlobalRdrEnv :: [GlobalRdrElt] -> GlobalRdrEnv Source #
lookupGlobalRdrEnv :: GlobalRdrEnv -> OccName -> [GlobalRdrElt] Source #
greOccName :: GlobalRdrElt -> OccName Source #
See Note [GreNames]
shadowNames :: GlobalRdrEnv -> OccEnv a -> GlobalRdrEnv Source #
pprGlobalRdrEnv :: Bool -> GlobalRdrEnv -> SDoc Source #
globalRdrEnvElts :: GlobalRdrEnv -> [GlobalRdrElt] Source #
lookupGRE_RdrName :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt] Source #
Look for this RdrName
in the global environment. Omits record fields
without selector functions (see Note [NoFieldSelectors] in GHC.Rename.Env).
lookupGRE_RdrName' :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt] Source #
Look for this RdrName
in the global environment. Includes record fields
without selector functions (see Note [NoFieldSelectors] in GHC.Rename.Env).
lookupGRE_Name :: GlobalRdrEnv -> Name -> Maybe GlobalRdrElt Source #
lookupGRE_GreName :: GlobalRdrEnv -> GreName -> Maybe GlobalRdrElt Source #
lookupGRE_FieldLabel :: GlobalRdrEnv -> FieldLabel -> Maybe GlobalRdrElt Source #
Look for a particular record field selector in the environment, where the selector name and field label may be different: the GlobalRdrEnv is keyed on the label. See Note [GreNames] for why this happens.
lookupGRE_Name_OccName :: GlobalRdrEnv -> Name -> OccName -> Maybe GlobalRdrElt Source #
Look for precisely this Name
in the environment, but with an OccName
that might differ from that of the Name
. See lookupGRE_FieldLabel
and
Note [GreNames].
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
pickGREs :: RdrName -> [GlobalRdrElt] -> [GlobalRdrElt] Source #
Takes a list of GREs which have the right OccName x
Pick those GREs that are in scope
* Qualified, as x
if want_qual is Qual M _
* Unqualified, as x
if want_unqual is Unqual _
Return each such GRE, with its ImportSpecs filtered, to reflect how it is in scope qualified or unqualified respectively. See Note [GRE filtering]
pickGREsModExp :: ModuleName -> [GlobalRdrElt] -> [(GlobalRdrElt, GlobalRdrElt)] Source #
Pick GREs that are in scope *both* qualified *and* unqualified Return each GRE that is, as a pair (qual_gre, unqual_gre) These two GREs are the original GRE with imports filtered to express how it is in scope qualified an unqualified respectively
Used only for the 'module M' item in export list;
see exports_from_avail
GlobalRdrElts
gresFromAvails :: Maybe ImportSpec -> [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 -> Maybe ImportSpec) -> AvailInfo -> [GlobalRdrElt] Source #
localGREsFromAvail :: AvailInfo -> [GlobalRdrElt] Source #
availFromGRE :: GlobalRdrElt -> AvailInfo Source #
greRdrNames :: GlobalRdrElt -> [RdrName] Source #
greSrcSpan :: GlobalRdrElt -> SrcSpan Source #
gresToAvailInfo :: [GlobalRdrElt] -> [AvailInfo] Source #
Takes a list of distinct GREs and folds them
into AvailInfos. This is more efficient than mapping each individual
GRE to an AvailInfo and the folding using plusAvail
but needs the
uniqueness assumption.
greDefinitionModule :: GlobalRdrElt -> Maybe Module Source #
The module in which the name pointed to by the GRE is defined.
greDefinitionSrcSpan :: GlobalRdrElt -> SrcSpan Source #
The SrcSpan of the name pointed to by the GRE.
greMangledName :: GlobalRdrElt -> Name Source #
A Name
for the GRE for internal use. Careful: the OccName
of this
Name
is not necessarily the same as the greOccName
(see Note [GreNames]).
grePrintableName :: GlobalRdrElt -> Name Source #
A Name
for the GRE suitable for output to the user. Its OccName
will
be the greOccName
(see Note [GreNames]).
greFieldLabel :: GlobalRdrElt -> Maybe FieldLabel Source #
Returns the field label of this GRE, if it has one
Global RdrName
mapping elements: GlobalRdrElt
, Provenance
, ImportSpec
data GlobalRdrElt Source #
Global Reader Element
An element of the GlobalRdrEnv
Instances
Data GlobalRdrElt Source # | |
Defined in GHC.Types.Name.Reader gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GlobalRdrElt -> c GlobalRdrElt Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GlobalRdrElt Source # toConstr :: GlobalRdrElt -> Constr Source # dataTypeOf :: GlobalRdrElt -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GlobalRdrElt) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GlobalRdrElt) Source # gmapT :: (forall b. Data b => b -> b) -> GlobalRdrElt -> GlobalRdrElt Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GlobalRdrElt -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GlobalRdrElt -> r Source # gmapQ :: (forall d. Data d => d -> u) -> GlobalRdrElt -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> GlobalRdrElt -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt Source # | |
HasOccName GlobalRdrElt Source # | |
Defined in GHC.Types.Name.Reader occName :: GlobalRdrElt -> OccName Source # | |
Outputable GlobalRdrElt Source # | |
Defined in GHC.Types.Name.Reader ppr :: GlobalRdrElt -> SDoc Source # |
isLocalGRE :: GlobalRdrElt -> Bool Source #
isRecFldGRE :: GlobalRdrElt -> Bool Source #
isDuplicateRecFldGRE :: GlobalRdrElt -> Bool Source #
Is this a record field defined with DuplicateRecordFields? (See Note [GreNames])
isNoFieldSelectorGRE :: GlobalRdrElt -> Bool Source #
Is this a record field defined with NoFieldSelectors? (See Note [NoFieldSelectors] in GHC.Rename.Env)
isFieldSelectorGRE :: GlobalRdrElt -> Bool Source #
Is this a record field defined with FieldSelectors? (See Note [NoFieldSelectors] in GHC.Rename.Env)
unQualOK :: GlobalRdrElt -> Bool Source #
Test if an unqualified 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?
pprNameProvenance :: GlobalRdrElt -> SDoc Source #
Print out one place where the name was define/imported (With -dppr-debug, print them all)
Used where we may have an ordinary name or a record field label. See Note [GreNames] in GHC.Types.Name.Reader.
Instances
Data GreName Source # | |
Defined in GHC.Types.Avail gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GreName -> c GreName Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GreName Source # toConstr :: GreName -> Constr Source # dataTypeOf :: GreName -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GreName) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GreName) Source # gmapT :: (forall b. Data b => b -> b) -> GreName -> GreName Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GreName -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GreName -> r Source # gmapQ :: (forall d. Data d => d -> u) -> GreName -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> GreName -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GreName -> m GreName Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GreName -> m GreName Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GreName -> m GreName Source # | |
NFData GreName Source # | |
Defined in GHC.Types.Avail | |
HasOccName GreName Source # | |
Binary GreName Source # | |
Outputable GreName Source # | |
Eq GreName Source # | |
Ord GreName Source # | |
greNameSrcSpan :: GreName -> SrcSpan Source #
See Note [Parents]
Instances
Data Parent Source # | |
Defined in GHC.Types.Name.Reader gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Parent -> c Parent Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Parent Source # toConstr :: Parent -> Constr Source # dataTypeOf :: Parent -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Parent) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Parent) Source # gmapT :: (forall b. Data b => b -> b) -> Parent -> Parent Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Parent -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Parent -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Parent -> m Parent Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Parent -> m Parent Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Parent -> m Parent Source # | |
Outputable Parent Source # | |
Eq Parent Source # | |
greParent_maybe :: GlobalRdrElt -> Maybe Name Source #
data ImportSpec Source #
Import Specification
The ImportSpec
of something says how it came to be imported
It's quite elaborate so that we can give accurate unused-name warnings.
Instances
Data ImportSpec Source # | |
Defined in GHC.Types.Name.Reader gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportSpec -> c ImportSpec Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImportSpec Source # toConstr :: ImportSpec -> Constr Source # dataTypeOf :: ImportSpec -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ImportSpec) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportSpec) Source # gmapT :: (forall b. Data b => b -> b) -> ImportSpec -> ImportSpec Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportSpec -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportSpec -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ImportSpec -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportSpec -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec Source # | |
Outputable ImportSpec Source # | |
Defined in GHC.Types.Name.Reader ppr :: ImportSpec -> SDoc Source # | |
Eq ImportSpec Source # | |
Defined in GHC.Types.Name.Reader (==) :: ImportSpec -> ImportSpec -> Bool # (/=) :: ImportSpec -> ImportSpec -> Bool # |
data ImpDeclSpec Source #
Import Declaration Specification
Describes a particular import declaration and is
shared among all the Provenance
s for that decl
ImpDeclSpec | |
|
Instances
Data ImpDeclSpec Source # | |
Defined in GHC.Types.Name.Reader gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImpDeclSpec -> c ImpDeclSpec Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImpDeclSpec Source # toConstr :: ImpDeclSpec -> Constr Source # dataTypeOf :: ImpDeclSpec -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ImpDeclSpec) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImpDeclSpec) Source # gmapT :: (forall b. Data b => b -> b) -> ImpDeclSpec -> ImpDeclSpec Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ImpDeclSpec -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImpDeclSpec -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec Source # | |
Eq ImpDeclSpec Source # | |
Defined in GHC.Types.Name.Reader (==) :: ImpDeclSpec -> ImpDeclSpec -> Bool # (/=) :: ImpDeclSpec -> ImpDeclSpec -> Bool # |
data ImpItemSpec Source #
Import Item Specification
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 |
|
Instances
Data ImpItemSpec Source # | |
Defined in GHC.Types.Name.Reader gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImpItemSpec -> c ImpItemSpec Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImpItemSpec Source # toConstr :: ImpItemSpec -> Constr Source # dataTypeOf :: ImpItemSpec -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ImpItemSpec) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImpItemSpec) Source # gmapT :: (forall b. Data b => b -> b) -> ImpItemSpec -> ImpItemSpec Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ImpItemSpec -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImpItemSpec -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec Source # | |
Eq ImpItemSpec Source # | |
Defined in GHC.Types.Name.Reader (==) :: ImpItemSpec -> ImpItemSpec -> Bool # (/=) :: ImpItemSpec -> ImpItemSpec -> Bool # |
importSpecLoc :: ImportSpec -> SrcSpan Source #
isExplicitItem :: ImpItemSpec -> Bool Source #
bestImport :: [ImportSpec] -> ImportSpec Source #