| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Avail
Synopsis
- type Avails = [AvailInfo]
- data AvailInfo
- avail :: Name -> AvailInfo
- availsToNameSet :: [AvailInfo] -> NameSet
- availsToNameSetWithSelectors :: [AvailInfo] -> NameSet
- availsToNameEnv :: [AvailInfo] -> NameEnv AvailInfo
- availName :: AvailInfo -> Name
- availNames :: AvailInfo -> [Name]
- availNonFldNames :: AvailInfo -> [Name]
- availNamesWithSelectors :: AvailInfo -> [Name]
- availFlds :: AvailInfo -> [FieldLabel]
- availsNamesWithOccs :: [AvailInfo] -> [(Name, OccName)]
- availNamesWithOccs :: AvailInfo -> [(Name, OccName)]
- 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]
Documentation
Records what things are "available", i.e. in scope
Constructors
| Avail Name | An ordinary identifier in scope | 
| AvailTC Name [Name] [FieldLabel] | A type or class in scope. Parameters: 1) The name of the type or class 2) The available pieces of type or class, excluding field selectors. 3) The record fields of the type (see Note [Representing fields in AvailInfo]). The AvailTC Invariant:
   * If the type or class is itself
     to be in scope, it must be
     *first* in this list.  Thus,
     typically:  | 
Instances
| Eq AvailInfo Source # | |
| Data AvailInfo Source # | |
| Defined in 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 :: (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 # | |
| Outputable AvailInfo Source # | |
| Binary AvailInfo Source # | |
availsToNameSet :: [AvailInfo] -> NameSet Source #
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 GenAvailInfo
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
availNamesWithOccs :: AvailInfo -> [(Name, OccName)] Source #
Names made available by the availability information, paired with
 the OccName used to refer to each one.
When DuplicateRecordFields is in use, the Name may be the
 mangled name of a record selector (e.g. $sel:foo:MkT) while the
 OccName will be the label of the field (e.g. foo).
See Note [Representing fields in AvailInfo].
filterAvail :: (Name -> Bool) -> AvailInfo -> [AvailInfo] -> [AvailInfo] Source #
filters an AvailInfo by the given predicate