witherable-class-0.0.1: Witherable = Traversable + Filterable
Safe HaskellNone
LanguageHaskell2010

Data.Witherable.Class

Description

Deprecated: Import Witherable instead

Synopsis

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:

conservation
mapMaybe (Just . f) ≡ fmap f
composition
mapMaybe f . mapMaybe g ≡ mapMaybe (f <=< g)

Minimal complete definition

mapMaybe | catMaybes

Methods

mapMaybe :: (a -> Maybe b) -> f a -> f b #

Like mapMaybe.

catMaybes :: f (Maybe a) -> f a #

filter :: (a -> Bool) -> f a -> f a #

filter f . filter g ≡ filter (liftA2 (&&) g f)

Instances

Instances details
Filterable [] 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> [a] -> [b] #

catMaybes :: [Maybe a] -> [a] #

filter :: (a -> Bool) -> [a] -> [a] #

Filterable Maybe 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> Maybe a -> Maybe b #

catMaybes :: Maybe (Maybe a) -> Maybe a #

filter :: (a -> Bool) -> Maybe a -> Maybe a #

Filterable Option 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> Option a -> Option b #

catMaybes :: Option (Maybe a) -> Option a #

filter :: (a -> Bool) -> Option a -> Option a #

Filterable ZipList 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> ZipList a -> ZipList b #

catMaybes :: ZipList (Maybe a) -> ZipList a #

filter :: (a -> Bool) -> ZipList a -> ZipList a #

Filterable IntMap 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> IntMap a -> IntMap b #

catMaybes :: IntMap (Maybe a) -> IntMap a #

filter :: (a -> Bool) -> IntMap a -> IntMap a #

Filterable Seq 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> Seq a -> Seq b #

catMaybes :: Seq (Maybe a) -> Seq a #

filter :: (a -> Bool) -> Seq a -> Seq a #

Filterable Vector 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> Vector a -> Vector b #

catMaybes :: Vector (Maybe a) -> Vector a #

filter :: (a -> Bool) -> Vector a -> Vector a #

Monoid e => Filterable (Either e) 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> Either e a -> Either e b #

catMaybes :: Either e (Maybe a) -> Either e a #

filter :: (a -> Bool) -> Either e a -> Either e a #

Filterable (V1 :: Type -> Type) 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> V1 a -> V1 b #

catMaybes :: V1 (Maybe a) -> V1 a #

filter :: (a -> Bool) -> V1 a -> V1 a #

Filterable (U1 :: Type -> Type) 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> U1 a -> U1 b #

catMaybes :: U1 (Maybe a) -> U1 a #

filter :: (a -> Bool) -> U1 a -> U1 a #

Filterable (Proxy :: Type -> Type) 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> Proxy a -> Proxy b #

catMaybes :: Proxy (Maybe a) -> Proxy a #

filter :: (a -> Bool) -> Proxy a -> Proxy a #

Filterable (Map k) 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> Map k a -> Map k b #

catMaybes :: Map k (Maybe a) -> Map k a #

filter :: (a -> Bool) -> Map k a -> Map k a #

Functor f => Filterable (MaybeT f) 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> MaybeT f a -> MaybeT f b #

catMaybes :: MaybeT f (Maybe a) -> MaybeT f a #

filter :: (a -> Bool) -> MaybeT f a -> MaybeT f a #

(Eq k, Hashable k) => Filterable (HashMap k) 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> HashMap k a -> HashMap k b #

catMaybes :: HashMap k (Maybe a) -> HashMap k a #

filter :: (a -> Bool) -> HashMap k a -> HashMap k a #

(Foldable f, Alternative f) => Filterable (WrappedFoldable f) 
Instance details

Defined in Witherable

Filterable f => Filterable (Rec1 f) 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> Rec1 f a -> Rec1 f b #

catMaybes :: Rec1 f (Maybe a) -> Rec1 f a #

filter :: (a -> Bool) -> Rec1 f a -> Rec1 f a #

Filterable (Const r :: Type -> Type) 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> Const r a -> Const r b #

catMaybes :: Const r (Maybe a) -> Const r a #

filter :: (a -> Bool) -> Const r a -> Const r a #

Filterable t => Filterable (Reverse t) 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> Reverse t a -> Reverse t b #

catMaybes :: Reverse t (Maybe a) -> Reverse t a #

filter :: (a -> Bool) -> Reverse t a -> Reverse t a #

Filterable f => Filterable (IdentityT f) 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> IdentityT f a -> IdentityT f b #

catMaybes :: IdentityT f (Maybe a) -> IdentityT f a #

filter :: (a -> Bool) -> IdentityT f a -> IdentityT f a #

Filterable t => Filterable (Backwards t) 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> Backwards t a -> Backwards t b #

catMaybes :: Backwards t (Maybe a) -> Backwards t a #

filter :: (a -> Bool) -> Backwards t a -> Backwards t a #

Filterable (K1 i c :: Type -> Type) 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> K1 i c a -> K1 i c b #

catMaybes :: K1 i c (Maybe a) -> K1 i c a #

filter :: (a -> Bool) -> K1 i c a -> K1 i c a #

(Filterable f, Filterable g) => Filterable (f :+: g) 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> (f :+: g) a -> (f :+: g) b #

catMaybes :: (f :+: g) (Maybe a) -> (f :+: g) a #

filter :: (a -> Bool) -> (f :+: g) a -> (f :+: g) a #

(Filterable f, Filterable g) => Filterable (f :*: g) 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> (f :*: g) a -> (f :*: g) b #

catMaybes :: (f :*: g) (Maybe a) -> (f :*: g) a #

filter :: (a -> Bool) -> (f :*: g) a -> (f :*: g) a #

(Filterable f, Filterable g) => Filterable (Product f g) 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> Product f g a -> Product f g b #

catMaybes :: Product f g (Maybe a) -> Product f g a #

filter :: (a -> Bool) -> Product f g a -> Product f g a #

(Filterable f, Filterable g) => Filterable (Sum f g) 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> Sum f g a -> Sum f g b #

catMaybes :: Sum f g (Maybe a) -> Sum f g a #

filter :: (a -> Bool) -> Sum f g a -> Sum f g a #

Filterable f => Filterable (M1 i c f) 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> M1 i c f a -> M1 i c f b #

catMaybes :: M1 i c f (Maybe a) -> M1 i c f a #

filter :: (a -> Bool) -> M1 i c f a -> M1 i c f a #

(Functor f, Filterable g) => Filterable (f :.: g) 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> (f :.: g) a -> (f :.: g) b #

catMaybes :: (f :.: g) (Maybe a) -> (f :.: g) a #

filter :: (a -> Bool) -> (f :.: g) a -> (f :.: g) a #

(Functor f, Filterable g) => Filterable (Compose f g) 
Instance details

Defined in Witherable

Methods

mapMaybe :: (a -> Maybe b) -> Compose f g a -> Compose f g b #

catMaybes :: Compose f g (Maybe a) -> Compose f g a #

filter :: (a -> Bool) -> Compose f g a -> Compose f g a #

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 (fmap Just . f) ≡ traverse f
composition
Compose . fmap (wither f) . wither g ≡ wither (Compose . fmap (wither f) . g)

Parametricity implies the naturality law:

Whenever t is an /applicative transformation/ in the sense described in the Traversable documentation,

t . wither f ≡ 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) #

Effectful mapMaybe.

wither (pure . f) ≡ pure . mapMaybe f

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

Instances details
Witherable []

Methods are good consumers for fusion.

Instance details

Defined in Witherable

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> [a] -> f [b] #

witherM :: Monad m => (a -> m (Maybe b)) -> [a] -> m [b] #

filterA :: Applicative f => (a -> f Bool) -> [a] -> f [a] #

witherMap :: Applicative m => ([b] -> r) -> (a -> m (Maybe b)) -> [a] -> m r #

Witherable Maybe 
Instance details

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 
Instance details

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 
Instance details

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 
Instance details

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 
Instance details

Defined in Witherable

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> Seq a -> f (Seq b) #

witherM :: Monad m => (a -> m (Maybe b)) -> Seq a -> m (Seq b) #

filterA :: Applicative f => (a -> f Bool) -> Seq a -> f (Seq a) #

witherMap :: Applicative m => (Seq b -> r) -> (a -> m (Maybe b)) -> Seq a -> m r #

Witherable Vector 
Instance details

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) 
Instance details

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) 
Instance details

Defined in Witherable

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> V1 a -> f (V1 b) #

witherM :: Monad m => (a -> m (Maybe b)) -> V1 a -> m (V1 b) #

filterA :: Applicative f => (a -> f Bool) -> V1 a -> f (V1 a) #

witherMap :: Applicative m => (V1 b -> r) -> (a -> m (Maybe b)) -> V1 a -> m r #

Witherable (U1 :: Type -> Type) 
Instance details

Defined in Witherable

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> U1 a -> f (U1 b) #

witherM :: Monad m => (a -> m (Maybe b)) -> U1 a -> m (U1 b) #

filterA :: Applicative f => (a -> f Bool) -> U1 a -> f (U1 a) #

witherMap :: Applicative m => (U1 b -> r) -> (a -> m (Maybe b)) -> U1 a -> m r #

Witherable (Proxy :: Type -> Type) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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.

Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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

Methods

imapMaybe :: (i -> a -> Maybe b) -> t a -> t b #

ifilter :: (i -> a -> Bool) -> t a -> t a #

ifilter f . ifilter g ≡ ifilter (i -> liftA2 (&&) (f i) (g i))

Instances

Instances details
FilterableWithIndex Int [] 
Instance details

Defined in Witherable

Methods

imapMaybe :: (Int -> a -> Maybe b) -> [a] -> [b] #

ifilter :: (Int -> a -> Bool) -> [a] -> [a] #

FilterableWithIndex Int ZipList 
Instance details

Defined in Witherable

Methods

imapMaybe :: (Int -> a -> Maybe b) -> ZipList a -> ZipList b #

ifilter :: (Int -> a -> Bool) -> ZipList a -> ZipList a #

FilterableWithIndex Int IntMap 
Instance details

Defined in Witherable

Methods

imapMaybe :: (Int -> a -> Maybe b) -> IntMap a -> IntMap b #

ifilter :: (Int -> a -> Bool) -> IntMap a -> IntMap a #

FilterableWithIndex Int Seq 
Instance details

Defined in Witherable

Methods

imapMaybe :: (Int -> a -> Maybe b) -> Seq a -> Seq b #

ifilter :: (Int -> a -> Bool) -> Seq a -> Seq a #

FilterableWithIndex Int Vector 
Instance details

Defined in Witherable

Methods

imapMaybe :: (Int -> a -> Maybe b) -> Vector a -> Vector b #

ifilter :: (Int -> a -> Bool) -> Vector a -> Vector a #

FilterableWithIndex () Maybe 
Instance details

Defined in Witherable

Methods

imapMaybe :: (() -> a -> Maybe b) -> Maybe a -> Maybe b #

ifilter :: (() -> a -> Bool) -> Maybe a -> Maybe a #

FilterableWithIndex k (Map k) 
Instance details

Defined in Witherable

Methods

imapMaybe :: (k -> a -> Maybe b) -> Map k a -> Map k b #

ifilter :: (k -> a -> Bool) -> Map k a -> Map k a #

(Eq k, Hashable k) => FilterableWithIndex k (HashMap k) 
Instance details

Defined in Witherable

Methods

imapMaybe :: (k -> a -> Maybe b) -> HashMap k a -> HashMap k b #

ifilter :: (k -> a -> Bool) -> HashMap k a -> HashMap k a #

(FunctorWithIndex i f, FoldableWithIndex i f, Alternative f) => FilterableWithIndex i (WrappedFoldable f) 
Instance details

Defined in Witherable

Methods

imapMaybe :: (i -> a -> Maybe b) -> WrappedFoldable f a -> WrappedFoldable f b #

ifilter :: (i -> a -> Bool) -> WrappedFoldable f a -> WrappedFoldable f a #

FilterableWithIndex Void (Proxy :: Type -> Type) 
Instance details

Defined in Witherable

Methods

imapMaybe :: (Void -> a -> Maybe b) -> Proxy a -> Proxy b #

ifilter :: (Void -> a -> Bool) -> Proxy a -> Proxy a #

FilterableWithIndex i t => FilterableWithIndex i (Reverse t) 
Instance details

Defined in Witherable

Methods

imapMaybe :: (i -> a -> Maybe b) -> Reverse t a -> Reverse t b #

ifilter :: (i -> a -> Bool) -> Reverse t a -> Reverse t a #

FilterableWithIndex i f => FilterableWithIndex i (IdentityT f) 
Instance details

Defined in Witherable

Methods

imapMaybe :: (i -> a -> Maybe b) -> IdentityT f a -> IdentityT f b #

ifilter :: (i -> a -> Bool) -> IdentityT f a -> IdentityT f a #

FilterableWithIndex i t => FilterableWithIndex i (Backwards t) 
Instance details

Defined in Witherable

Methods

imapMaybe :: (i -> a -> Maybe b) -> Backwards t a -> Backwards t b #

ifilter :: (i -> a -> Bool) -> Backwards t a -> Backwards t a #

(FilterableWithIndex i f, FilterableWithIndex j g) => FilterableWithIndex (Either i j) (Sum f g) 
Instance details

Defined in Witherable

Methods

imapMaybe :: (Either i j -> a -> Maybe b) -> Sum f g a -> Sum f g b #

ifilter :: (Either i j -> a -> Bool) -> Sum f g a -> Sum f g a #

(FilterableWithIndex i f, FilterableWithIndex j g) => FilterableWithIndex (Either i j) (Product f g) 
Instance details

Defined in Witherable

Methods

imapMaybe :: (Either i j -> a -> Maybe b) -> Product f g a -> Product f g b #

ifilter :: (Either i j -> a -> Bool) -> Product f g a -> Product f g a #

(FunctorWithIndex i f, FilterableWithIndex j g) => FilterableWithIndex (i, j) (Compose f g) 
Instance details

Defined in Witherable

Methods

imapMaybe :: ((i, j) -> a -> Maybe b) -> Compose f g a -> Compose f g b #

ifilter :: ((i, j) -> a -> Bool) -> Compose f g a -> Compose f g a #

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) #

Effectful imapMaybe.

iwither ( i -> pure . f i) ≡ pure . imapMaybe f

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) #

Instances

Instances details
WitherableWithIndex Int [] 
Instance details

Defined in Witherable

Methods

iwither :: Applicative f => (Int -> a -> f (Maybe b)) -> [a] -> f [b] #

iwitherM :: Monad m => (Int -> a -> m (Maybe b)) -> [a] -> m [b] #

ifilterA :: Applicative f => (Int -> a -> f Bool) -> [a] -> f [a] #

WitherableWithIndex Int ZipList 
Instance details

Defined in Witherable

Methods

iwither :: Applicative f => (Int -> a -> f (Maybe b)) -> ZipList a -> f (ZipList b) #

iwitherM :: Monad m => (Int -> a -> m (Maybe b)) -> ZipList a -> m (ZipList b) #

ifilterA :: Applicative f => (Int -> a -> f Bool) -> ZipList a -> f (ZipList a) #

WitherableWithIndex Int IntMap 
Instance details

Defined in Witherable

Methods

iwither :: Applicative f => (Int -> a -> f (Maybe b)) -> IntMap a -> f (IntMap b) #

iwitherM :: Monad m => (Int -> a -> m (Maybe b)) -> IntMap a -> m (IntMap b) #

ifilterA :: Applicative f => (Int -> a -> f Bool) -> IntMap a -> f (IntMap a) #

WitherableWithIndex Int Seq 
Instance details

Defined in Witherable

Methods

iwither :: Applicative f => (Int -> a -> f (Maybe b)) -> Seq a -> f (Seq b) #

iwitherM :: Monad m => (Int -> a -> m (Maybe b)) -> Seq a -> m (Seq b) #

ifilterA :: Applicative f => (Int -> a -> f Bool) -> Seq a -> f (Seq a) #

WitherableWithIndex Int Vector 
Instance details

Defined in Witherable

Methods

iwither :: Applicative f => (Int -> a -> f (Maybe b)) -> Vector a -> f (Vector b) #

iwitherM :: Monad m => (Int -> a -> m (Maybe b)) -> Vector a -> m (Vector b) #

ifilterA :: Applicative f => (Int -> a -> f Bool) -> Vector a -> f (Vector a) #

WitherableWithIndex () Maybe 
Instance details

Defined in Witherable

Methods

iwither :: Applicative f => (() -> a -> f (Maybe b)) -> Maybe a -> f (Maybe b) #

iwitherM :: Monad m => (() -> a -> m (Maybe b)) -> Maybe a -> m (Maybe b) #

ifilterA :: Applicative f => (() -> a -> f Bool) -> Maybe a -> f (Maybe a) #

WitherableWithIndex k (Map k) 
Instance details

Defined in Witherable

Methods

iwither :: Applicative f => (k -> a -> f (Maybe b)) -> Map k a -> f (Map k b) #

iwitherM :: Monad m => (k -> a -> m (Maybe b)) -> Map k a -> m (Map k b) #

ifilterA :: Applicative f => (k -> a -> f Bool) -> Map k a -> f (Map k a) #

(Eq k, Hashable k) => WitherableWithIndex k (HashMap k) 
Instance details

Defined in Witherable

Methods

iwither :: Applicative f => (k -> a -> f (Maybe b)) -> HashMap k a -> f (HashMap k b) #

iwitherM :: Monad m => (k -> a -> m (Maybe b)) -> HashMap k a -> m (HashMap k b) #

ifilterA :: Applicative f => (k -> a -> f Bool) -> HashMap k a -> f (HashMap k a) #

WitherableWithIndex Void (Proxy :: Type -> Type) 
Instance details

Defined in Witherable

Methods

iwither :: Applicative f => (Void -> a -> f (Maybe b)) -> Proxy a -> f (Proxy b) #

iwitherM :: Monad m => (Void -> a -> m (Maybe b)) -> Proxy a -> m (Proxy b) #

ifilterA :: Applicative f => (Void -> a -> f Bool) -> Proxy a -> f (Proxy a) #

WitherableWithIndex i t => WitherableWithIndex i (Reverse t)

Wither from right to left.

Instance details

Defined in Witherable

Methods

iwither :: Applicative f => (i -> a -> f (Maybe b)) -> Reverse t a -> f (Reverse t b) #

iwitherM :: Monad m => (i -> a -> m (Maybe b)) -> Reverse t a -> m (Reverse t b) #

ifilterA :: Applicative f => (i -> a -> f Bool) -> Reverse t a -> f (Reverse t a) #

WitherableWithIndex i f => WitherableWithIndex i (IdentityT f) 
Instance details

Defined in Witherable

Methods

iwither :: Applicative f0 => (i -> a -> f0 (Maybe b)) -> IdentityT f a -> f0 (IdentityT f b) #

iwitherM :: Monad m => (i -> a -> m (Maybe b)) -> IdentityT f a -> m (IdentityT f b) #

ifilterA :: Applicative f0 => (i -> a -> f0 Bool) -> IdentityT f a -> f0 (IdentityT f a) #

WitherableWithIndex i t => WitherableWithIndex i (Backwards t) 
Instance details

Defined in Witherable

Methods

iwither :: Applicative f => (i -> a -> f (Maybe b)) -> Backwards t a -> f (Backwards t b) #

iwitherM :: Monad m => (i -> a -> m (Maybe b)) -> Backwards t a -> m (Backwards t b) #

ifilterA :: Applicative f => (i -> a -> f Bool) -> Backwards t a -> f (Backwards t a) #

(WitherableWithIndex i f, WitherableWithIndex j g) => WitherableWithIndex (Either i j) (Sum f g) 
Instance details

Defined in Witherable

Methods

iwither :: Applicative f0 => (Either i j -> a -> f0 (Maybe b)) -> Sum f g a -> f0 (Sum f g b) #

iwitherM :: Monad m => (Either i j -> a -> m (Maybe b)) -> Sum f g a -> m (Sum f g b) #

ifilterA :: Applicative f0 => (Either i j -> a -> f0 Bool) -> Sum f g a -> f0 (Sum f g a) #

(WitherableWithIndex i f, WitherableWithIndex j g) => WitherableWithIndex (Either i j) (Product f g) 
Instance details

Defined in Witherable

Methods

iwither :: Applicative f0 => (Either i j -> a -> f0 (Maybe b)) -> Product f g a -> f0 (Product f g b) #

iwitherM :: Monad m => (Either i j -> a -> m (Maybe b)) -> Product f g a -> m (Product f g b) #

ifilterA :: Applicative f0 => (Either i j -> a -> f0 Bool) -> Product f g a -> f0 (Product f g a) #

(TraversableWithIndex i f, WitherableWithIndex j g) => WitherableWithIndex (i, j) (Compose f g) 
Instance details

Defined in Witherable

Methods

iwither :: Applicative f0 => ((i, j) -> a -> f0 (Maybe b)) -> Compose f g a -> f0 (Compose f g b) #

iwitherM :: Monad m => ((i, j) -> a -> m (Maybe b)) -> Compose f g a -> m (Compose f g b) #

ifilterA :: Applicative f0 => ((i, j) -> a -> f0 Bool) -> Compose f g a -> f0 (Compose f g a) #