Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type Avails = [AvailInfo]
- data AvailInfo
- avail :: Name -> AvailInfo
- availField :: FieldLabel -> AvailInfo
- availTC :: Name -> [Name] -> [FieldLabel] -> AvailInfo
- availsToNameSet :: [AvailInfo] -> NameSet
- availsToNameSetWithSelectors :: [AvailInfo] -> NameSet
- availsToNameEnv :: [AvailInfo] -> NameEnv AvailInfo
- availExportsDecl :: AvailInfo -> Bool
- availName :: AvailInfo -> Name
- availGreName :: AvailInfo -> GreName
- availNames :: AvailInfo -> [Name]
- availNonFldNames :: AvailInfo -> [Name]
- availNamesWithSelectors :: AvailInfo -> [Name]
- availFlds :: AvailInfo -> [FieldLabel]
- availGreNames :: AvailInfo -> [GreName]
- availSubordinateGreNames :: AvailInfo -> [GreName]
- stableAvailCmp :: AvailInfo -> AvailInfo -> Ordering
- plusAvail :: AvailInfo -> AvailInfo -> AvailInfo
- trimAvail :: AvailInfo -> Name -> AvailInfo
- filterAvail :: (Name -> Bool) -> AvailInfo -> [AvailInfo] -> [AvailInfo]
- filterAvails :: (Name -> Bool) -> [AvailInfo] -> [AvailInfo]
- nubAvails :: [AvailInfo] -> [AvailInfo]
- data GreName
- greNameMangledName :: GreName -> Name
- greNamePrintableName :: GreName -> Name
- greNameSrcSpan :: GreName -> SrcSpan
- greNameFieldLabel :: GreName -> Maybe FieldLabel
- partitionGreNames :: [GreName] -> ([Name], [FieldLabel])
- stableGreNameCmp :: GreName -> GreName -> Ordering
Documentation
Records what things are "available", i.e. in scope
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, ==, \/=] |
Instances
Data AvailInfo Source # | |
Defined in GHC.Types.Avail 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 # | |
NFData AvailInfo Source # | |
Defined in GHC.Types.Avail | |
Binary AvailInfo Source # | |
Outputable AvailInfo Source # | |
Eq AvailInfo Source # | Used when deciding if the interface has changed |
availField :: FieldLabel -> AvailInfo Source #
availsToNameSet :: [AvailInfo] -> NameSet Source #
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
availGreName :: AvailInfo -> GreName Source #
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.
filterAvail :: (Name -> Bool) -> AvailInfo -> [AvailInfo] -> [AvailInfo] Source #
filters an AvailInfo
by the given predicate
filterAvails :: (Name -> Bool) -> [AvailInfo] -> [AvailInfo] Source #
filters AvailInfo
s by the given predicate
nubAvails :: [AvailInfo] -> [AvailInfo] Source #
Combines AvailInfo
s 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
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 # | |
greNameMangledName :: GreName -> Name Source #
greNamePrintableName :: GreName -> Name Source #
greNameSrcSpan :: GreName -> SrcSpan Source #
partitionGreNames :: [GreName] -> ([Name], [FieldLabel]) Source #