ghc-9.8.2: The GHC API
Safe HaskellNone
LanguageHaskell2010

GHC.Types.Name.Reader

Description

GHC uses several kinds of name internally:

Synopsis

The main type

data RdrName Source #

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`
( ~ )

Constructors

Unqual OccName

Unqualified name

Used for ordinary, unqualified occurrences, e.g. x, y or Foo. Create such a RdrName with mkRdrUnqual

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 Bar.x, Bar.y or Bar.Foo. Create such a RdrName with mkRdrQual

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 mkOrig

Exact Name

Exact name

We know exactly the Name. This is used:

  1. When the parser parses built-in syntax like [] and (,), but wants a RdrName from it
  2. By Template Haskell, when TH has generated a unique name

Such a RdrName can be created by using getRdrName on a Name

Instances

Instances details
Data RdrName Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

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 # 
Instance details

Defined in GHC.Parser.PostProcess

HasOccName RdrName Source # 
Instance details

Defined in GHC.Types.Name.Reader

Outputable RdrName Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: RdrName -> SDoc Source #

OutputableBndr RdrName Source # 
Instance details

Defined in GHC.Types.Name.Reader

Eq RdrName Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

(==) :: RdrName -> RdrName -> Bool #

(/=) :: RdrName -> RdrName -> Bool #

Ord RdrName Source # 
Instance details

Defined in GHC.Types.Name.Reader

type Anno RdrName Source # 
Instance details

Defined in GHC.Hs.Extension

type Anno (LocatedN RdrName) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN RdrName] Source # 
Instance details

Defined in GHC.Hs.Binds

Construction

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

getRdrName :: NamedThing thing => thing -> RdrName Source #

Destruction

Local mapping of RdrName to Name

data LocalRdrEnv Source #

Local Reader Environment See Note [LocalRdrEnv]

Instances

Instances details
Outputable LocalRdrEnv Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: LocalRdrEnv -> SDoc Source #

Global mapping of RdrName to GlobalRdrElts

type GlobalRdrEnvX info = OccEnv [GlobalRdrEltX info] Source #

Parametrises GlobalRdrEnv over the presence or absence of GREInfo.

See Note [IfGlobalRdrEnv].

type GlobalRdrEnv = GlobalRdrEnvX GREInfo 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

type IfGlobalRdrEnv = GlobalRdrEnvX () Source #

A GlobalRdrEnv in which the GlobalRdrElts don't have any GREInfo attached to them. This is useful to avoid space leaks, see Note [IfGlobalRdrEnv].

Looking up GlobalRdrElts

data FieldsOrSelectors Source #

When looking up GREs, we may or may not want to include fields that were defined in modules with NoFieldSelectors enabled. See Note [NoFieldSelectors].

Constructors

WantNormal

Include normal names, and fields with selectors, but ignore fields without selectors.

WantBoth

Include normal names and all fields (regardless of whether they have selectors).

WantField

Include only fields, with or without selectors, ignoring any non-fields in scope.

data LookupGRE info where Source #

What should we look up in a GlobalRdrEnv? Should we only look up names with the exact same OccName, or do we allow different NameSpaces?

Depending on the answer, we might need more or less information from the GlobalRdrEnv, e.g. if we want to include matching record fields we need to know if the corresponding record fields define field selectors, for which we need to consult the GREInfo. This is why this datatype is a GADT.

See Note [IfGlobalRdrEnv].

Constructors

LookupOccName

Look for this specific OccName, with the exact same NameSpace, in the GlobalRdrEnv.

Fields

LookupRdrName

Look up the OccName of this RdrName in the GlobalRdrEnv, filtering out those whose qualification matches that of the RdrName.

Lookup returns an empty result for Exact or Orig RdrNames.

Fields

LookupExactName

Look for GREs with the same unique as the given Name in the GlobalRdrEnv.

Fields

LookupChildren

Look up children GlobalRdrElts with a given Parent.

Fields

lookupGRE :: GlobalRdrEnvX info -> LookupGRE info -> [GlobalRdrEltX info] Source #

Look something up in the Global Reader Environment.

The LookupGRE argument specifies what to look up, and in particular whether there should there be any lee-way if the NameSpaces don't exactly match.

data WhichGREs info where Source #

How should we look up in a GlobalRdrEnv? Which NameSpaces are considered relevant for a given lookup?

Constructors

SameNameSpace :: forall info. WhichGREs info

Only consider GlobalRdrElts with the exact NameSpace we look up.

RelevantGREs

Allow GlobalRdrElts with different NameSpaces, e.g. allow looking up record fields from the variable NameSpace, or looking up a TyCon from the data constructor NameSpace.

Fields

Bundled Patterns

pattern AllRelevantGREs :: WhichGREs GREInfo

Look up as many possibly relevant GlobalRdrElts as possible.

pattern RelevantGREsFOS :: FieldsOrSelectors -> WhichGREs GREInfo

Look up relevant GREs, taking into account the interaction between the variable and field NameSpaces as determined by the FieldsOrSelector argument.

Instances

Instances details
Outputable (WhichGREs info) Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: WhichGREs info -> SDoc Source #

greIsRelevant Source #

Arguments

:: WhichGREs GREInfo

specification of which GlobalRdrElts to consider relevant

-> NameSpace

the NameSpace of the thing we are looking up

-> GlobalRdrElt

the GlobalRdrElt we have looked up, in a potentially different NameSpace than we wanted

-> Bool 

After looking up something with the given NameSpace, is the resulting GlobalRdrElt we have obtained relevant, according to the RelevantGREs specification of which NameSpaces are relevant?

data LookupChild Source #

Constructors

LookupChild 

Fields

Instances

Instances details
Outputable LookupChild Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: LookupChild -> SDoc Source #

lookupGRE_Name :: Outputable info => GlobalRdrEnvX info -> Name -> Maybe (GlobalRdrEltX info) Source #

Look for precisely this Name in the environment, in the same NameSpace as the Name.

This tests whether it is in scope, ignoring anything else that might be in scope which doesn't have the same Unique.

lookupGRE_FieldLabel :: GlobalRdrEnv -> FieldLabel -> Maybe FieldGlobalRdrElt Source #

Look for a particular record field selector in the environment.

transformGREs :: (GlobalRdrElt -> GlobalRdrElt) -> [OccName] -> GlobalRdrEnv -> GlobalRdrEnv Source #

Apply a transformation function to the GREs for these OccNames

pickGREs :: RdrName -> [GlobalRdrEltX info] -> [GlobalRdrEltX info] 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 -> [GlobalRdrEltX info] -> [(GlobalRdrEltX info, GlobalRdrEltX info)] 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

gresToAvailInfo :: [GlobalRdrEltX info] -> [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 then folding using plusAvail, but needs the uniqueness assumption.

greDefinitionModule :: GlobalRdrEltX info -> Maybe Module Source #

The module in which the name pointed to by the GRE is defined.

greDefinitionSrcSpan :: GlobalRdrEltX info -> SrcSpan Source #

The SrcSpan of the name pointed to by the GRE.

greFieldLabel_maybe :: GlobalRdrElt -> Maybe FieldLabel Source #

Returns the field label of this GRE, if it has one

Global RdrName mapping elements: GlobalRdrElt, Provenance, ImportSpec

data GlobalRdrEltX info Source #

Global Reader Element

Something in scope in the renamer; usually a member of the GlobalRdrEnv. See Note [GlobalRdrElt provenance].

Why do we parametrise over the gre_info field? See Note [IfGlobalRdrEnv].

Constructors

GRE 

Fields

  • gre_name :: !Name
     
  • gre_par :: !Parent

    See Note [Parents]

  • gre_lcl :: !Bool

    True = the thing was defined locally

  • gre_imp :: !(Bag ImportSpec)

    In scope through these imports See Note [GlobalRdrElt provenance] for the relation between gre_lcl and gre_imp.

  • gre_info :: info

    Information the renamer knows about this particular Name.

    Careful about forcing this field! Forcing it can trigger the loading of interface files.

    Note [Retrieving the GREInfo from interfaces] in GHC.Types.GREInfo.

Instances

Instances details
Data info => Data (GlobalRdrEltX info) Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GlobalRdrEltX info -> c (GlobalRdrEltX info) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GlobalRdrEltX info) Source #

toConstr :: GlobalRdrEltX info -> Constr Source #

dataTypeOf :: GlobalRdrEltX info -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GlobalRdrEltX info)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GlobalRdrEltX info)) Source #

gmapT :: (forall b. Data b => b -> b) -> GlobalRdrEltX info -> GlobalRdrEltX info Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GlobalRdrEltX info -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GlobalRdrEltX info -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GlobalRdrEltX info -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GlobalRdrEltX info -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GlobalRdrEltX info -> m (GlobalRdrEltX info) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalRdrEltX info -> m (GlobalRdrEltX info) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalRdrEltX info -> m (GlobalRdrEltX info) Source #

NFData a => NFData (GlobalRdrEltX a) Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

rnf :: GlobalRdrEltX a -> () Source #

HasOccName (GlobalRdrEltX info) Source # 
Instance details

Defined in GHC.Types.Name.Reader

Outputable info => Outputable (GlobalRdrEltX info) Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: GlobalRdrEltX info -> SDoc Source #

type GlobalRdrElt = GlobalRdrEltX GREInfo Source #

Global Reader Element

Something in scope in the renamer; usually a member of the GlobalRdrEnv. See Note [GlobalRdrElt provenance].

type IfGlobalRdrElt = GlobalRdrEltX () Source #

A GlobalRdrElt in which we stripped out the GREInfo field, in order to avoid space leaks.

See Note [IfGlobalRdrEnv].

forceGlobalRdrEnv :: GlobalRdrEnvX info -> IfGlobalRdrEnv Source #

Drop all GREInfo fields in a GlobalRdrEnv in order to avoid space leaks. See Note [Forcing GREInfo] in GHC.Types.GREInfo.

hydrateGlobalRdrEnv :: (Name -> IO info) -> GlobalRdrEnvX noInfo -> GlobalRdrEnvX info Source #

Hydrate a previously dehydrated GlobalRdrEnv, by (lazily!) looking up the GREInfo using the provided function.

See Note [Forcing GREInfo] in GHC.Types.GREInfo.

isLocalGRE :: GlobalRdrEltX info -> Bool Source #

Is this GlobalRdrElt defined locally?

isImportedGRE :: GlobalRdrEltX info -> Bool Source #

Is this GlobalRdrElt imported?

Not just the negation of isLocalGRE, because it might be an Exact or Orig name reference. See Note [GlobalRdrElt provenance].

isRecFldGRE :: GlobalRdrEltX info -> Bool Source #

Is this a record field GRE?

Important: does not consult the GreInfo field.

isDuplicateRecFldGRE :: GlobalRdrElt -> Bool Source #

Is this a record field defined with DuplicateRecordFields?

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 :: GlobalRdrEltX info -> 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 :: GlobalRdrEltX info -> SDoc Source #

Print out one place where the name was define/imported (With -dppr-debug, print them all)

Shadowing

greClashesWith :: GlobalRdrElt -> GlobalRdrElt -> Bool Source #

greClashesWith new_gre old_gre computes whether new_gre clashes with old_gre (assuming they both have the same underlying occNameFS).

shadowNames Source #

Arguments

:: Bool

discard names that are only available qualified?

-> GlobalRdrEnv 
-> GlobalRdrEnv 
-> GlobalRdrEnv 

Information attached to a GlobalRdrElt

data ConLikeName Source #

The Name of a ConLike.

Useful when we are in the renamer and don't yet have a full DataCon or PatSyn to hand.

Constructors

DataConName 
PatSynName 

Instances

Instances details
Data ConLikeName Source # 
Instance details

Defined in GHC.Types.GREInfo

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConLikeName -> c ConLikeName Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConLikeName Source #

toConstr :: ConLikeName -> Constr Source #

dataTypeOf :: ConLikeName -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConLikeName) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConLikeName) Source #

gmapT :: (forall b. Data b => b -> b) -> ConLikeName -> ConLikeName Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConLikeName -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConLikeName -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ConLikeName -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConLikeName -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConLikeName -> m ConLikeName Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConLikeName -> m ConLikeName Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConLikeName -> m ConLikeName Source #

NFData ConLikeName Source # 
Instance details

Defined in GHC.Types.GREInfo

Methods

rnf :: ConLikeName -> () Source #

Uniquable ConLikeName Source # 
Instance details

Defined in GHC.Types.GREInfo

Outputable ConLikeName Source # 
Instance details

Defined in GHC.Types.GREInfo

Methods

ppr :: ConLikeName -> SDoc Source #

Eq ConLikeName Source # 
Instance details

Defined in GHC.Types.GREInfo

data GREInfo Source #

Information about a Name that is pertinent to the renamer.

See Note [GREInfo]

Constructors

Vanilla

No particular information... e.g. a function

UnboundGRE

An unbound GRE... could be anything

IAmTyCon !(TyConFlavour Name)

TyCon

IAmConLike

ConLike

Fields

  • !ConInfo

    The constructor fields. See Note [Local constructor info in the renamer]. | Record field

IAmRecField !RecFieldInfo 

Instances

Instances details
Data GREInfo Source # 
Instance details

Defined in GHC.Types.GREInfo

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GREInfo -> c GREInfo Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GREInfo Source #

toConstr :: GREInfo -> Constr Source #

dataTypeOf :: GREInfo -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GREInfo) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GREInfo) Source #

gmapT :: (forall b. Data b => b -> b) -> GREInfo -> GREInfo Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GREInfo -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GREInfo -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GREInfo -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GREInfo -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GREInfo -> m GREInfo Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GREInfo -> m GREInfo Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GREInfo -> m GREInfo Source #

NFData GREInfo Source # 
Instance details

Defined in GHC.Types.GREInfo

Methods

rnf :: GREInfo -> () Source #

Outputable GREInfo Source # 
Instance details

Defined in GHC.Types.GREInfo

Methods

ppr :: GREInfo -> SDoc Source #

data RecFieldInfo Source #

Constructors

RecFieldInfo 

Fields

  • recFieldLabel :: !FieldLabel
     
  • recFieldCons :: !(UniqSet ConLikeName)

    The constructors which have this field label. Always non-empty.

    NB: these constructors will always share a single parent, as the field label disambiguates between parents in the presence of duplicate record fields.

Instances

Instances details
Data RecFieldInfo Source # 
Instance details

Defined in GHC.Types.GREInfo

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RecFieldInfo -> c RecFieldInfo Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RecFieldInfo Source #

toConstr :: RecFieldInfo -> Constr Source #

dataTypeOf :: RecFieldInfo -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RecFieldInfo) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecFieldInfo) Source #

gmapT :: (forall b. Data b => b -> b) -> RecFieldInfo -> RecFieldInfo Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecFieldInfo -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecFieldInfo -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RecFieldInfo -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RecFieldInfo -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecFieldInfo -> m RecFieldInfo Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecFieldInfo -> m RecFieldInfo Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecFieldInfo -> m RecFieldInfo Source #

NFData RecFieldInfo Source # 
Instance details

Defined in GHC.Types.GREInfo

Methods

rnf :: RecFieldInfo -> () Source #

Outputable RecFieldInfo Source # 
Instance details

Defined in GHC.Types.GREInfo

Eq RecFieldInfo Source # 
Instance details

Defined in GHC.Types.GREInfo

Parent information

data Parent Source #

See Note [Parents]

Constructors

NoParent 
ParentIs 

Fields

Instances

Instances details
Data Parent Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

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 #

NFData Parent Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

rnf :: Parent -> () Source #

Outputable Parent Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: Parent -> SDoc Source #

Eq Parent Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

(==) :: Parent -> Parent -> Bool #

(/=) :: Parent -> Parent -> Bool #

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.

Constructors

ImpSpec 

Instances

Instances details
Data ImportSpec Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

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 #

NFData ImportSpec Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

rnf :: ImportSpec -> () Source #

Outputable ImportSpec Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: ImportSpec -> SDoc Source #

Eq ImportSpec Source # 
Instance details

Defined in GHC.Types.Name.Reader

data ImpDeclSpec Source #

Import Declaration Specification

Describes a particular import declaration and is shared among all the Provenances for that decl

Constructors

ImpDeclSpec 

Fields

  • is_mod :: !Module

    Module imported, e.g. import Muggle Note the Muggle may well not be the defining module for this thing!

  • is_as :: !ModuleName

    Import alias, e.g. from as M (or Muggle if there is no as clause)

  • is_qual :: !Bool

    Was this import qualified?

  • is_dloc :: !SrcSpan

    The location of the entire import declaration

Instances

Instances details
Data ImpDeclSpec Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

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 # 
Instance details

Defined in GHC.Types.Name.Reader

data ImpItemSpec Source #

Import Item Specification

Describes import info a particular Name

Constructors

ImpAll

The import had no import list, or had a hiding list

ImpSome

The import had an import list. The is_explicit field is True iff the thing was named explicitly in the import specs rather than being imported as part of a "..." group. Consider:

import C( T(..) )

Here the constructors of T are not named explicitly; only T is named explicitly.

Fields

Instances

Instances details
Data ImpItemSpec Source # 
Instance details

Defined in GHC.Types.Name.Reader

Methods

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 # 
Instance details

Defined in GHC.Types.Name.Reader

Utils

opIsAt :: RdrName -> Bool Source #

Indicate if the given name is the "@" operator