ghc-9.13: The GHC API
Safe HaskellNone
LanguageGHC2021

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 Name

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

  • [Name]

    The available pieces of type or class

Instances

Instances details
NFData AvailInfo Source # 
Instance details

Defined in GHC.Types.Avail

Methods

rnf :: 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 #

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 #

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

toConstr :: AvailInfo -> Constr #

dataTypeOf :: AvailInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

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 #

Names and fields made available by the availability information.

availSubordinateNames :: AvailInfo -> [Name] 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; plusAvail does that

newtype DetOrdAvails Source #

Occurrences of Avails in interface files must be deterministically ordered to guarantee interface file determinism.

We guarantee a deterministic order by either using the order explicitly given by the user (e.g. in an explicit constructor export list) or instead by sorting the avails with sortAvails.

Bundled Patterns

pattern DetOrdAvails :: Avails -> DetOrdAvails

It's always safe to match on DetOrdAvails

Instances

Instances details
NFData DetOrdAvails Source # 
Instance details

Defined in GHC.Types.Avail

Methods

rnf :: DetOrdAvails -> () Source #

Binary DetOrdAvails Source # 
Instance details

Defined in GHC.Types.Avail

Outputable DetOrdAvails Source # 
Instance details

Defined in GHC.Types.Avail