ghc-9.4.2: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Types.Avail

Synopsis

Documentation

type Avails = [AvailInfo] Source #

A collection of AvailInfo - several things that are "available"

data AvailInfo Source #

Records what things are "available", i.e. in scope

Constructors

Avail GreName

An ordinary identifier in scope, or a field label without a parent type (see Note [Representing pattern synonym fields in AvailInfo]).

AvailTC

A type or class in scope

The AvailTC Invariant: If the type or class is itself to be in scope, it must be first in this list. Thus, typically:

AvailTC Eq [Eq, ==, \/=]

Fields

  • Name

    The name of the type or class

  • [GreName]

    The available pieces of type or class (see Note [Representing fields in AvailInfo]).

Instances

Instances details
Data AvailInfo Source # 
Instance details

Defined in GHC.Types.Avail

Methods

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

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

toConstr :: AvailInfo -> Constr Source #

dataTypeOf :: AvailInfo -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Binary AvailInfo Source # 
Instance details

Defined in GHC.Types.Avail

Outputable AvailInfo Source # 
Instance details

Defined in GHC.Types.Avail

Methods

ppr :: AvailInfo -> SDoc Source #

Eq AvailInfo Source #

Used when deciding if the interface has changed

Instance details

Defined in GHC.Types.Avail

availExportsDecl :: AvailInfo -> Bool Source #

Does this AvailInfo export the parent decl? This depends on the invariant that the parent is first if it appears at all.

availName :: AvailInfo -> Name Source #

Just the main name made available, i.e. not the available pieces of type or class brought into scope by the AvailInfo

availNames :: AvailInfo -> [Name] Source #

All names made available by the availability information (excluding overloaded selectors)

availNonFldNames :: AvailInfo -> [Name] Source #

Names for non-fields made available by the availability information

availNamesWithSelectors :: AvailInfo -> [Name] Source #

All names made available by the availability information (including overloaded selectors)

availFlds :: AvailInfo -> [FieldLabel] Source #

Fields made available by the availability information

availGreNames :: AvailInfo -> [GreName] Source #

Names and fields made available by the availability information.

availSubordinateGreNames :: AvailInfo -> [GreName] Source #

Names and fields made available by the availability information, other than the main decl itself.

stableAvailCmp :: AvailInfo -> AvailInfo -> Ordering Source #

Compare lexicographically

trimAvail :: AvailInfo -> Name -> AvailInfo Source #

trims an AvailInfo to keep only a single name

filterAvail :: (Name -> Bool) -> AvailInfo -> [AvailInfo] -> [AvailInfo] Source #

filters an AvailInfo by the given predicate

filterAvails :: (Name -> Bool) -> [AvailInfo] -> [AvailInfo] Source #

filters AvailInfos by the given predicate

nubAvails :: [AvailInfo] -> [AvailInfo] Source #

Combines AvailInfos from the same family avails may have several items with the same availName E.g import Ix( Ix(..), index ) will give Ix(Ix,index,range) and Ix(index) We want to combine these; addAvail does that

data GreName Source #

Used where we may have an ordinary name or a record field label. See Note [GreNames] in GHC.Types.Name.Reader.

Instances

Instances details
Data GreName Source # 
Instance details

Defined in GHC.Types.Avail

Methods

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 #

HasOccName GreName Source # 
Instance details

Defined in GHC.Types.Avail

Binary GreName Source # 
Instance details

Defined in GHC.Types.Avail

Outputable GreName Source # 
Instance details

Defined in GHC.Types.Avail

Methods

ppr :: GreName -> SDoc Source #

Eq GreName Source # 
Instance details

Defined in GHC.Types.Avail

Methods

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

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

greNameMangledName :: GreName -> Name Source #

A Name for internal use, but not for output to the user. For fields, the OccName will be the selector. See Note [GreNames] in GHC.Types.Name.Reader.

greNamePrintableName :: GreName -> Name Source #

A Name suitable for output to the user. For fields, the OccName will be the field label. See Note [GreNames] in GHC.Types.Name.Reader.