| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Witherable.Class
Description
Deprecated: Import Witherable instead
Synopsis
- class Functor f => Filterable (f :: Type -> Type) where
- class (Traversable t, Filterable t) => Witherable (t :: Type -> Type) where
- wither :: Applicative f => (a -> f (Maybe b)) -> t a -> f (t b)
- witherM :: Monad m => (a -> m (Maybe b)) -> t a -> m (t b)
- filterA :: Applicative f => (a -> f Bool) -> t a -> f (t a)
- witherMap :: Applicative m => (t b -> r) -> (a -> m (Maybe b)) -> t a -> m r
- class (FunctorWithIndex i t, Filterable t) => FilterableWithIndex i (t :: Type -> Type) | t -> i where
- class (TraversableWithIndex i t, Witherable t) => WitherableWithIndex i (t :: Type -> Type) | t -> i where
- iwither :: Applicative f => (i -> a -> f (Maybe b)) -> t a -> f (t b)
- iwitherM :: Monad m => (i -> a -> m (Maybe b)) -> t a -> m (t b)
- ifilterA :: Applicative f => (i -> a -> f Bool) -> t a -> f (t a)
Documentation
class Functor f => Filterable (f :: Type -> Type) where #
Like Functor, but you can remove elements instead of updating them.
Formally, the class Filterable represents a functor from Kleisli Maybe to Hask.
A definition of mapMaybe must satisfy the following laws:
Instances
class (Traversable t, Filterable t) => Witherable (t :: Type -> Type) where #
An enhancement of Traversable with Filterable
A definition of wither must satisfy the following laws:
- conservation
wither(fmapJust. f) ≡traversef- composition
Compose.fmap(witherf) .witherg ≡wither(Compose.fmap(witherf) . g)
Parametricity implies the naturality law:
Whenever t is an /applicative transformation/ in the sense described in the
Traversable documentation,
t .witherf ≡wither(t . f)
See the Properties.md file in the git distribution for some special properties of
empty containers.
Minimal complete definition
Nothing
Methods
wither :: Applicative f => (a -> f (Maybe b)) -> t a -> f (t b) #
witherM :: Monad m => (a -> m (Maybe b)) -> t a -> m (t b) #
Monadic variant of wither. This may have more efficient implementation.filterA :: Applicative f => (a -> f Bool) -> t a -> f (t a) #
witherMap :: Applicative m => (t b -> r) -> (a -> m (Maybe b)) -> t a -> m r #
Instances
| Witherable [] | Methods are good consumers for fusion. |
Defined in Witherable | |
| Witherable Maybe | |
Defined in Witherable Methods wither :: Applicative f => (a -> f (Maybe b)) -> Maybe a -> f (Maybe b) # witherM :: Monad m => (a -> m (Maybe b)) -> Maybe a -> m (Maybe b) # filterA :: Applicative f => (a -> f Bool) -> Maybe a -> f (Maybe a) # witherMap :: Applicative m => (Maybe b -> r) -> (a -> m (Maybe b)) -> Maybe a -> m r # | |
| Witherable Option | |
Defined in Witherable Methods wither :: Applicative f => (a -> f (Maybe b)) -> Option a -> f (Option b) # witherM :: Monad m => (a -> m (Maybe b)) -> Option a -> m (Option b) # filterA :: Applicative f => (a -> f Bool) -> Option a -> f (Option a) # witherMap :: Applicative m => (Option b -> r) -> (a -> m (Maybe b)) -> Option a -> m r # | |
| Witherable ZipList | |
Defined in Witherable Methods wither :: Applicative f => (a -> f (Maybe b)) -> ZipList a -> f (ZipList b) # witherM :: Monad m => (a -> m (Maybe b)) -> ZipList a -> m (ZipList b) # filterA :: Applicative f => (a -> f Bool) -> ZipList a -> f (ZipList a) # witherMap :: Applicative m => (ZipList b -> r) -> (a -> m (Maybe b)) -> ZipList a -> m r # | |
| Witherable IntMap | |
Defined in Witherable Methods wither :: Applicative f => (a -> f (Maybe b)) -> IntMap a -> f (IntMap b) # witherM :: Monad m => (a -> m (Maybe b)) -> IntMap a -> m (IntMap b) # filterA :: Applicative f => (a -> f Bool) -> IntMap a -> f (IntMap a) # witherMap :: Applicative m => (IntMap b -> r) -> (a -> m (Maybe b)) -> IntMap a -> m r # | |
| Witherable Seq | |
Defined in Witherable | |
| Witherable Vector | |
Defined in Witherable Methods wither :: Applicative f => (a -> f (Maybe b)) -> Vector a -> f (Vector b) # witherM :: Monad m => (a -> m (Maybe b)) -> Vector a -> m (Vector b) # filterA :: Applicative f => (a -> f Bool) -> Vector a -> f (Vector a) # witherMap :: Applicative m => (Vector b -> r) -> (a -> m (Maybe b)) -> Vector a -> m r # | |
| Monoid e => Witherable (Either e) | |
Defined in Witherable Methods wither :: Applicative f => (a -> f (Maybe b)) -> Either e a -> f (Either e b) # witherM :: Monad m => (a -> m (Maybe b)) -> Either e a -> m (Either e b) # filterA :: Applicative f => (a -> f Bool) -> Either e a -> f (Either e a) # witherMap :: Applicative m => (Either e b -> r) -> (a -> m (Maybe b)) -> Either e a -> m r # | |
| Witherable (V1 :: Type -> Type) | |
Defined in Witherable | |
| Witherable (U1 :: Type -> Type) | |
Defined in Witherable | |
| Witherable (Proxy :: Type -> Type) | |
Defined in Witherable Methods wither :: Applicative f => (a -> f (Maybe b)) -> Proxy a -> f (Proxy b) # witherM :: Monad m => (a -> m (Maybe b)) -> Proxy a -> m (Proxy b) # filterA :: Applicative f => (a -> f Bool) -> Proxy a -> f (Proxy a) # witherMap :: Applicative m => (Proxy b -> r) -> (a -> m (Maybe b)) -> Proxy a -> m r # | |
| Witherable (Map k) | |
Defined in Witherable Methods wither :: Applicative f => (a -> f (Maybe b)) -> Map k a -> f (Map k b) # witherM :: Monad m => (a -> m (Maybe b)) -> Map k a -> m (Map k b) # filterA :: Applicative f => (a -> f Bool) -> Map k a -> f (Map k a) # witherMap :: Applicative m => (Map k b -> r) -> (a -> m (Maybe b)) -> Map k a -> m r # | |
| Traversable t => Witherable (MaybeT t) | |
Defined in Witherable Methods wither :: Applicative f => (a -> f (Maybe b)) -> MaybeT t a -> f (MaybeT t b) # witherM :: Monad m => (a -> m (Maybe b)) -> MaybeT t a -> m (MaybeT t b) # filterA :: Applicative f => (a -> f Bool) -> MaybeT t a -> f (MaybeT t a) # witherMap :: Applicative m => (MaybeT t b -> r) -> (a -> m (Maybe b)) -> MaybeT t a -> m r # | |
| (Eq k, Hashable k) => Witherable (HashMap k) | |
Defined in Witherable Methods wither :: Applicative f => (a -> f (Maybe b)) -> HashMap k a -> f (HashMap k b) # witherM :: Monad m => (a -> m (Maybe b)) -> HashMap k a -> m (HashMap k b) # filterA :: Applicative f => (a -> f Bool) -> HashMap k a -> f (HashMap k a) # witherMap :: Applicative m => (HashMap k b -> r) -> (a -> m (Maybe b)) -> HashMap k a -> m r # | |
| (Alternative f, Traversable f) => Witherable (WrappedFoldable f) | |
Defined in Witherable Methods wither :: Applicative f0 => (a -> f0 (Maybe b)) -> WrappedFoldable f a -> f0 (WrappedFoldable f b) # witherM :: Monad m => (a -> m (Maybe b)) -> WrappedFoldable f a -> m (WrappedFoldable f b) # filterA :: Applicative f0 => (a -> f0 Bool) -> WrappedFoldable f a -> f0 (WrappedFoldable f a) # witherMap :: Applicative m => (WrappedFoldable f b -> r) -> (a -> m (Maybe b)) -> WrappedFoldable f a -> m r # | |
| Witherable f => Witherable (Rec1 f) | |
Defined in Witherable Methods wither :: Applicative f0 => (a -> f0 (Maybe b)) -> Rec1 f a -> f0 (Rec1 f b) # witherM :: Monad m => (a -> m (Maybe b)) -> Rec1 f a -> m (Rec1 f b) # filterA :: Applicative f0 => (a -> f0 Bool) -> Rec1 f a -> f0 (Rec1 f a) # witherMap :: Applicative m => (Rec1 f b -> r) -> (a -> m (Maybe b)) -> Rec1 f a -> m r # | |
| Witherable (Const r :: Type -> Type) | |
Defined in Witherable Methods wither :: Applicative f => (a -> f (Maybe b)) -> Const r a -> f (Const r b) # witherM :: Monad m => (a -> m (Maybe b)) -> Const r a -> m (Const r b) # filterA :: Applicative f => (a -> f Bool) -> Const r a -> f (Const r a) # witherMap :: Applicative m => (Const r b -> r0) -> (a -> m (Maybe b)) -> Const r a -> m r0 # | |
| Witherable t => Witherable (Reverse t) | Wither from right to left. |
Defined in Witherable Methods wither :: Applicative f => (a -> f (Maybe b)) -> Reverse t a -> f (Reverse t b) # witherM :: Monad m => (a -> m (Maybe b)) -> Reverse t a -> m (Reverse t b) # filterA :: Applicative f => (a -> f Bool) -> Reverse t a -> f (Reverse t a) # witherMap :: Applicative m => (Reverse t b -> r) -> (a -> m (Maybe b)) -> Reverse t a -> m r # | |
| Witherable f => Witherable (IdentityT f) | |
Defined in Witherable Methods wither :: Applicative f0 => (a -> f0 (Maybe b)) -> IdentityT f a -> f0 (IdentityT f b) # witherM :: Monad m => (a -> m (Maybe b)) -> IdentityT f a -> m (IdentityT f b) # filterA :: Applicative f0 => (a -> f0 Bool) -> IdentityT f a -> f0 (IdentityT f a) # witherMap :: Applicative m => (IdentityT f b -> r) -> (a -> m (Maybe b)) -> IdentityT f a -> m r # | |
| Witherable t => Witherable (Backwards t) | |
Defined in Witherable Methods wither :: Applicative f => (a -> f (Maybe b)) -> Backwards t a -> f (Backwards t b) # witherM :: Monad m => (a -> m (Maybe b)) -> Backwards t a -> m (Backwards t b) # filterA :: Applicative f => (a -> f Bool) -> Backwards t a -> f (Backwards t a) # witherMap :: Applicative m => (Backwards t b -> r) -> (a -> m (Maybe b)) -> Backwards t a -> m r # | |
| Witherable (K1 i c :: Type -> Type) | |
Defined in Witherable Methods wither :: Applicative f => (a -> f (Maybe b)) -> K1 i c a -> f (K1 i c b) # witherM :: Monad m => (a -> m (Maybe b)) -> K1 i c a -> m (K1 i c b) # filterA :: Applicative f => (a -> f Bool) -> K1 i c a -> f (K1 i c a) # witherMap :: Applicative m => (K1 i c b -> r) -> (a -> m (Maybe b)) -> K1 i c a -> m r # | |
| (Witherable f, Witherable g) => Witherable (f :+: g) | |
Defined in Witherable Methods wither :: Applicative f0 => (a -> f0 (Maybe b)) -> (f :+: g) a -> f0 ((f :+: g) b) # witherM :: Monad m => (a -> m (Maybe b)) -> (f :+: g) a -> m ((f :+: g) b) # filterA :: Applicative f0 => (a -> f0 Bool) -> (f :+: g) a -> f0 ((f :+: g) a) # witherMap :: Applicative m => ((f :+: g) b -> r) -> (a -> m (Maybe b)) -> (f :+: g) a -> m r # | |
| (Witherable f, Witherable g) => Witherable (f :*: g) | |
Defined in Witherable Methods wither :: Applicative f0 => (a -> f0 (Maybe b)) -> (f :*: g) a -> f0 ((f :*: g) b) # witherM :: Monad m => (a -> m (Maybe b)) -> (f :*: g) a -> m ((f :*: g) b) # filterA :: Applicative f0 => (a -> f0 Bool) -> (f :*: g) a -> f0 ((f :*: g) a) # witherMap :: Applicative m => ((f :*: g) b -> r) -> (a -> m (Maybe b)) -> (f :*: g) a -> m r # | |
| (Witherable f, Witherable g) => Witherable (Product f g) | |
Defined in Witherable Methods wither :: Applicative f0 => (a -> f0 (Maybe b)) -> Product f g a -> f0 (Product f g b) # witherM :: Monad m => (a -> m (Maybe b)) -> Product f g a -> m (Product f g b) # filterA :: Applicative f0 => (a -> f0 Bool) -> Product f g a -> f0 (Product f g a) # witherMap :: Applicative m => (Product f g b -> r) -> (a -> m (Maybe b)) -> Product f g a -> m r # | |
| (Witherable f, Witherable g) => Witherable (Sum f g) | |
Defined in Witherable Methods wither :: Applicative f0 => (a -> f0 (Maybe b)) -> Sum f g a -> f0 (Sum f g b) # witherM :: Monad m => (a -> m (Maybe b)) -> Sum f g a -> m (Sum f g b) # filterA :: Applicative f0 => (a -> f0 Bool) -> Sum f g a -> f0 (Sum f g a) # witherMap :: Applicative m => (Sum f g b -> r) -> (a -> m (Maybe b)) -> Sum f g a -> m r # | |
| Witherable f => Witherable (M1 i c f) | |
Defined in Witherable Methods wither :: Applicative f0 => (a -> f0 (Maybe b)) -> M1 i c f a -> f0 (M1 i c f b) # witherM :: Monad m => (a -> m (Maybe b)) -> M1 i c f a -> m (M1 i c f b) # filterA :: Applicative f0 => (a -> f0 Bool) -> M1 i c f a -> f0 (M1 i c f a) # witherMap :: Applicative m => (M1 i c f b -> r) -> (a -> m (Maybe b)) -> M1 i c f a -> m r # | |
| (Traversable f, Witherable g) => Witherable (f :.: g) | |
Defined in Witherable Methods wither :: Applicative f0 => (a -> f0 (Maybe b)) -> (f :.: g) a -> f0 ((f :.: g) b) # witherM :: Monad m => (a -> m (Maybe b)) -> (f :.: g) a -> m ((f :.: g) b) # filterA :: Applicative f0 => (a -> f0 Bool) -> (f :.: g) a -> f0 ((f :.: g) a) # witherMap :: Applicative m => ((f :.: g) b -> r) -> (a -> m (Maybe b)) -> (f :.: g) a -> m r # | |
| (Traversable f, Witherable g) => Witherable (Compose f g) | |
Defined in Witherable Methods wither :: Applicative f0 => (a -> f0 (Maybe b)) -> Compose f g a -> f0 (Compose f g b) # witherM :: Monad m => (a -> m (Maybe b)) -> Compose f g a -> m (Compose f g b) # filterA :: Applicative f0 => (a -> f0 Bool) -> Compose f g a -> f0 (Compose f g a) # witherMap :: Applicative m => (Compose f g b -> r) -> (a -> m (Maybe b)) -> Compose f g a -> m r # | |
class (FunctorWithIndex i t, Filterable t) => FilterableWithIndex i (t :: Type -> Type) | t -> i where #
Indexed variant of Filterable.
Minimal complete definition
Nothing
Instances
class (TraversableWithIndex i t, Witherable t) => WitherableWithIndex i (t :: Type -> Type) | t -> i where #
Indexed variant of Witherable.
Minimal complete definition
Nothing
Methods
iwither :: Applicative f => (i -> a -> f (Maybe b)) -> t a -> f (t b) #
iwitherM :: Monad m => (i -> a -> m (Maybe b)) -> t a -> m (t b) #
Monadic variant of wither. This may have more efficient implementation.ifilterA :: Applicative f => (i -> a -> f Bool) -> t a -> f (t a) #