witherable-0.4.2: filterable traversable
Copyright(c) Fumiaki Kinoshita 2020
LicenseBSD3
MaintainerFumiaki Kinoshita <fumiexcel@gmail.com>
Stabilityprovisional
Portabilitynon-portable
Safe HaskellTrustworthy
LanguageHaskell2010

Witherable

Description

 
Synopsis

Documentation

class Functor f => Filterable f where Source #

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

Like mapMaybe.

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

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

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

Instances

Instances details
Filterable [] Source # 
Instance details

Defined in Witherable

Methods

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

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

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

Filterable Maybe Source # 
Instance details

Defined in Witherable

Methods

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

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

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

Filterable Option Source # 
Instance details

Defined in Witherable

Methods

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

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

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

Filterable ZipList Source # 
Instance details

Defined in Witherable

Methods

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

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

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

Filterable IntMap Source # 
Instance details

Defined in Witherable

Methods

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

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

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

Filterable Seq Source # 
Instance details

Defined in Witherable

Methods

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

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

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

Filterable Vector Source # 
Instance details

Defined in Witherable

Methods

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

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

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

Monoid e => Filterable (Either e) Source # 
Instance details

Defined in Witherable

Methods

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

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

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

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

Defined in Witherable

Methods

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

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

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

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

Defined in Witherable

Methods

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

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

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

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

Defined in Witherable

Methods

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

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

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

Filterable (Map k) Source # 
Instance details

Defined in Witherable

Methods

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

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

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

Functor f => Filterable (MaybeT f) Source # 
Instance details

Defined in Witherable

Methods

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

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

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

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

Defined in Witherable

Methods

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

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

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

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

Defined in Witherable

Filterable f => Filterable (Rec1 f) Source # 
Instance details

Defined in Witherable

Methods

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

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

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

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

Defined in Witherable

Methods

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

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

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

Filterable t => Filterable (Reverse t) Source # 
Instance details

Defined in Witherable

Methods

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

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

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

Filterable f => Filterable (IdentityT f) Source # 
Instance details

Defined in Witherable

Methods

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

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

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

Filterable t => Filterable (Backwards t) Source # 
Instance details

Defined in Witherable

Methods

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

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

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

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

Defined in Witherable

Methods

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

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

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

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

Defined in Witherable

Methods

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

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

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

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

Defined in Witherable

Methods

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

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

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

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

Defined in Witherable

Methods

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

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

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

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

Defined in Witherable

Methods

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

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

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

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

Defined in Witherable

Methods

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

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

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

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

Defined in Witherable

Methods

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

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

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

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

Defined in Witherable

Methods

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

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

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

(<$?>) :: Filterable f => (a -> Maybe b) -> f a -> f b infixl 4 Source #

An infix alias for mapMaybe. The name of the operator alludes to <$>, and has the same fixity.

Since: 0.3.1

(<&?>) :: Filterable f => f a -> (a -> Maybe b) -> f b infixl 1 Source #

Flipped version of <$?>, the Filterable version of <&>. It has the same fixity as <&>.

(<&?>) = flip mapMaybe

Since: 0.3.1

class (Traversable t, Filterable t) => Witherable t where Source #

An enhancement of Traversable with Filterable

A definition of wither must satisfy the following laws:

identity
wither (Identity . Just) ≡ Identity
composition
Compose . fmap (wither f) . wither g ≡ wither (Compose . fmap (wither f) . g)

Parametricity implies the naturality law:

naturality
t . wither f ≡ wither (t . f)

Where t is an /applicative transformation/ in the sense described in the Traversable documentation.

In the relation to superclasses, these should satisfy too:

conservation
wither (fmap Just . f) = traverse f
pure filter
wither (Identity . f) = Identity . mapMaybe f

See the Properties.md and Laws.md files in the git distribution for more in-depth explanation about properties of Witherable containers.

The laws and restrictions are enough to constrain wither to be uniquely determined as the following default implementation.

wither f = fmap catMaybes . traverse f

If not to provide better-performing implementation, it's not necessary to implement any one method of Witherable. For example, if a type constructor T already has instances of Traversable and Filterable, the next one line is sufficient to provide the Witherable T instance.

instance Witherable T

Minimal complete definition

Nothing

Methods

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

Effectful mapMaybe.

wither (pure . f) ≡ pure . mapMaybe f

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

Monadic variant of wither. This may have more efficient implementation.

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

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

Instances

Instances details
Witherable [] Source #

Methods are good consumers for fusion.

Instance details

Defined in Witherable

Methods

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

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

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

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

Witherable Maybe Source # 
Instance details

Defined in Witherable

Methods

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

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

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

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

Witherable Option Source # 
Instance details

Defined in Witherable

Methods

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

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

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

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

Witherable ZipList Source # 
Instance details

Defined in Witherable

Methods

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

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

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

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

Witherable IntMap Source # 
Instance details

Defined in Witherable

Methods

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

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

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

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

Witherable Seq Source # 
Instance details

Defined in Witherable

Methods

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

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

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

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

Witherable Vector Source # 
Instance details

Defined in Witherable

Methods

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

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

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

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

Monoid e => Witherable (Either e) Source # 
Instance details

Defined in Witherable

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> Either e a -> f (Either e b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> Either e a -> m (Either e b) Source #

filterA :: Applicative f => (a -> f Bool) -> Either e a -> f (Either e a) Source #

witherMap :: Applicative m => (Either e b -> r) -> (a -> m (Maybe b)) -> Either e a -> m r Source #

Witherable (V1 :: Type -> Type) Source # 
Instance details

Defined in Witherable

Methods

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

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

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

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

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

Defined in Witherable

Methods

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

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

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

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

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

Defined in Witherable

Methods

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

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

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

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

Witherable (Map k) Source # 
Instance details

Defined in Witherable

Methods

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

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

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

witherMap :: Applicative m => (Map k b -> r) -> (a -> m (Maybe b)) -> Map k a -> m r Source #

Traversable t => Witherable (MaybeT t) Source # 
Instance details

Defined in Witherable

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> MaybeT t a -> f (MaybeT t b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> MaybeT t a -> m (MaybeT t b) Source #

filterA :: Applicative f => (a -> f Bool) -> MaybeT t a -> f (MaybeT t a) Source #

witherMap :: Applicative m => (MaybeT t b -> r) -> (a -> m (Maybe b)) -> MaybeT t a -> m r Source #

(Eq k, Hashable k) => Witherable (HashMap k) Source # 
Instance details

Defined in Witherable

Methods

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

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

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

witherMap :: Applicative m => (HashMap k b -> r) -> (a -> m (Maybe b)) -> HashMap k a -> m r Source #

(Alternative f, Traversable f) => Witherable (WrappedFoldable f) Source # 
Instance details

Defined in Witherable

Methods

wither :: Applicative f0 => (a -> f0 (Maybe b)) -> WrappedFoldable f a -> f0 (WrappedFoldable f b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> WrappedFoldable f a -> m (WrappedFoldable f b) Source #

filterA :: Applicative f0 => (a -> f0 Bool) -> WrappedFoldable f a -> f0 (WrappedFoldable f a) Source #

witherMap :: Applicative m => (WrappedFoldable f b -> r) -> (a -> m (Maybe b)) -> WrappedFoldable f a -> m r Source #

Witherable f => Witherable (Rec1 f) Source # 
Instance details

Defined in Witherable

Methods

wither :: Applicative f0 => (a -> f0 (Maybe b)) -> Rec1 f a -> f0 (Rec1 f b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> Rec1 f a -> m (Rec1 f b) Source #

filterA :: Applicative f0 => (a -> f0 Bool) -> Rec1 f a -> f0 (Rec1 f a) Source #

witherMap :: Applicative m => (Rec1 f b -> r) -> (a -> m (Maybe b)) -> Rec1 f a -> m r Source #

Witherable (Const r :: Type -> Type) Source # 
Instance details

Defined in Witherable

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> Const r a -> f (Const r b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> Const r a -> m (Const r b) Source #

filterA :: Applicative f => (a -> f Bool) -> Const r a -> f (Const r a) Source #

witherMap :: Applicative m => (Const r b -> r0) -> (a -> m (Maybe b)) -> Const r a -> m r0 Source #

Witherable t => Witherable (Reverse t) Source #

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

witherM :: Monad m => (a -> m (Maybe b)) -> Reverse t a -> m (Reverse t b) Source #

filterA :: Applicative f => (a -> f Bool) -> Reverse t a -> f (Reverse t a) Source #

witherMap :: Applicative m => (Reverse t b -> r) -> (a -> m (Maybe b)) -> Reverse t a -> m r Source #

Witherable f => Witherable (IdentityT f) Source # 
Instance details

Defined in Witherable

Methods

wither :: Applicative f0 => (a -> f0 (Maybe b)) -> IdentityT f a -> f0 (IdentityT f b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> IdentityT f a -> m (IdentityT f b) Source #

filterA :: Applicative f0 => (a -> f0 Bool) -> IdentityT f a -> f0 (IdentityT f a) Source #

witherMap :: Applicative m => (IdentityT f b -> r) -> (a -> m (Maybe b)) -> IdentityT f a -> m r Source #

Witherable t => Witherable (Backwards t) Source # 
Instance details

Defined in Witherable

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> Backwards t a -> f (Backwards t b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> Backwards t a -> m (Backwards t b) Source #

filterA :: Applicative f => (a -> f Bool) -> Backwards t a -> f (Backwards t a) Source #

witherMap :: Applicative m => (Backwards t b -> r) -> (a -> m (Maybe b)) -> Backwards t a -> m r Source #

Witherable (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Witherable

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> K1 i c a -> f (K1 i c b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> K1 i c a -> m (K1 i c b) Source #

filterA :: Applicative f => (a -> f Bool) -> K1 i c a -> f (K1 i c a) Source #

witherMap :: Applicative m => (K1 i c b -> r) -> (a -> m (Maybe b)) -> K1 i c a -> m r Source #

(Witherable f, Witherable g) => Witherable (f :+: g) Source # 
Instance details

Defined in Witherable

Methods

wither :: Applicative f0 => (a -> f0 (Maybe b)) -> (f :+: g) a -> f0 ((f :+: g) b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> (f :+: g) a -> m ((f :+: g) b) Source #

filterA :: Applicative f0 => (a -> f0 Bool) -> (f :+: g) a -> f0 ((f :+: g) a) Source #

witherMap :: Applicative m => ((f :+: g) b -> r) -> (a -> m (Maybe b)) -> (f :+: g) a -> m r Source #

(Witherable f, Witherable g) => Witherable (f :*: g) Source # 
Instance details

Defined in Witherable

Methods

wither :: Applicative f0 => (a -> f0 (Maybe b)) -> (f :*: g) a -> f0 ((f :*: g) b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> (f :*: g) a -> m ((f :*: g) b) Source #

filterA :: Applicative f0 => (a -> f0 Bool) -> (f :*: g) a -> f0 ((f :*: g) a) Source #

witherMap :: Applicative m => ((f :*: g) b -> r) -> (a -> m (Maybe b)) -> (f :*: g) a -> m r Source #

(Witherable f, Witherable g) => Witherable (Product f g) Source # 
Instance details

Defined in Witherable

Methods

wither :: Applicative f0 => (a -> f0 (Maybe b)) -> Product f g a -> f0 (Product f g b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> Product f g a -> m (Product f g b) Source #

filterA :: Applicative f0 => (a -> f0 Bool) -> Product f g a -> f0 (Product f g a) Source #

witherMap :: Applicative m => (Product f g b -> r) -> (a -> m (Maybe b)) -> Product f g a -> m r Source #

(Witherable f, Witherable g) => Witherable (Sum f g) Source # 
Instance details

Defined in Witherable

Methods

wither :: Applicative f0 => (a -> f0 (Maybe b)) -> Sum f g a -> f0 (Sum f g b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> Sum f g a -> m (Sum f g b) Source #

filterA :: Applicative f0 => (a -> f0 Bool) -> Sum f g a -> f0 (Sum f g a) Source #

witherMap :: Applicative m => (Sum f g b -> r) -> (a -> m (Maybe b)) -> Sum f g a -> m r Source #

Witherable f => Witherable (M1 i c f) Source # 
Instance details

Defined in Witherable

Methods

wither :: Applicative f0 => (a -> f0 (Maybe b)) -> M1 i c f a -> f0 (M1 i c f b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> M1 i c f a -> m (M1 i c f b) Source #

filterA :: Applicative f0 => (a -> f0 Bool) -> M1 i c f a -> f0 (M1 i c f a) Source #

witherMap :: Applicative m => (M1 i c f b -> r) -> (a -> m (Maybe b)) -> M1 i c f a -> m r Source #

(Traversable f, Witherable g) => Witherable (f :.: g) Source # 
Instance details

Defined in Witherable

Methods

wither :: Applicative f0 => (a -> f0 (Maybe b)) -> (f :.: g) a -> f0 ((f :.: g) b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> (f :.: g) a -> m ((f :.: g) b) Source #

filterA :: Applicative f0 => (a -> f0 Bool) -> (f :.: g) a -> f0 ((f :.: g) a) Source #

witherMap :: Applicative m => ((f :.: g) b -> r) -> (a -> m (Maybe b)) -> (f :.: g) a -> m r Source #

(Traversable f, Witherable g) => Witherable (Compose f g) Source # 
Instance details

Defined in Witherable

Methods

wither :: Applicative f0 => (a -> f0 (Maybe b)) -> Compose f g a -> f0 (Compose f g b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> Compose f g a -> m (Compose f g b) Source #

filterA :: Applicative f0 => (a -> f0 Bool) -> Compose f g a -> f0 (Compose f g a) Source #

witherMap :: Applicative m => (Compose f g b -> r) -> (a -> m (Maybe b)) -> Compose f g a -> m r Source #

ordNub :: (Witherable t, Ord a) => t a -> t a Source #

Removes duplicate elements from a list, keeping only the first occurrence. This is asymptotically faster than using nub from Data.List.

>>> ordNub [3,2,1,3,2,1]
[3,2,1]

ordNubOn :: (Witherable t, Ord b) => (a -> b) -> t a -> t a Source #

The ordNubOn function behaves just like ordNub, except it uses a another type to determine equivalence classes.

>>> ordNubOn fst [(True, 'x'), (False, 'y'), (True, 'z')]
[(True,'x'),(False,'y')]

hashNub :: (Witherable t, Eq a, Hashable a) => t a -> t a Source #

Removes duplicate elements from a list, keeping only the first occurrence. This is usually faster than ordNub, especially for things that have a slow comparison (like String).

>>> hashNub [3,2,1,3,2,1]
[3,2,1]

hashNubOn :: (Witherable t, Eq b, Hashable b) => (a -> b) -> t a -> t a Source #

The hashNubOn function behaves just like ordNub, except it uses a another type to determine equivalence classes.

>>> hashNubOn fst [(True, 'x'), (False, 'y'), (True, 'z')]
[(True,'x'),(False,'y')]

forMaybe :: (Witherable t, Applicative f) => t a -> (a -> f (Maybe b)) -> f (t b) Source #

Indexed variants

class (FunctorWithIndex i t, Filterable t) => FilterableWithIndex i t | t -> i where Source #

Indexed variant of Filterable.

Minimal complete definition

Nothing

Methods

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

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

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

Instances

Instances details
FilterableWithIndex Int [] Source # 
Instance details

Defined in Witherable

Methods

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

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

FilterableWithIndex Int ZipList Source # 
Instance details

Defined in Witherable

Methods

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

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

FilterableWithIndex Int IntMap Source # 
Instance details

Defined in Witherable

Methods

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

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

FilterableWithIndex Int Seq Source # 
Instance details

Defined in Witherable

Methods

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

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

FilterableWithIndex Int Vector Source # 
Instance details

Defined in Witherable

Methods

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

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

FilterableWithIndex () Maybe Source # 
Instance details

Defined in Witherable

Methods

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

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

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

Defined in Witherable

Methods

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

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

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

Defined in Witherable

Methods

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

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

FilterableWithIndex k (Map k) Source # 
Instance details

Defined in Witherable

Methods

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

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

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

Defined in Witherable

Methods

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

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

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

Defined in Witherable

Methods

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

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

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

Defined in Witherable

Methods

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

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

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

Defined in Witherable

Methods

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

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

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

Defined in Witherable

Methods

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

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

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

Defined in Witherable

Methods

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

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

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

Defined in Witherable

Methods

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

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

class (TraversableWithIndex i t, Witherable t) => WitherableWithIndex i t | t -> i where Source #

Indexed variant of Witherable.

Minimal complete definition

Nothing

Methods

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

Effectful imapMaybe.

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

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

Monadic variant of wither. This may have more efficient implementation.

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

Instances

Instances details
WitherableWithIndex Int [] Source # 
Instance details

Defined in Witherable

Methods

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

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

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

WitherableWithIndex Int ZipList Source # 
Instance details

Defined in Witherable

Methods

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

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

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

WitherableWithIndex Int IntMap Source # 
Instance details

Defined in Witherable

Methods

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

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

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

WitherableWithIndex Int Seq Source # 
Instance details

Defined in Witherable

Methods

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

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

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

WitherableWithIndex Int Vector Source # 
Instance details

Defined in Witherable

Methods

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

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

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

WitherableWithIndex () Maybe Source # 
Instance details

Defined in Witherable

Methods

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

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

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

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

Defined in Witherable

Methods

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

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

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

WitherableWithIndex k (Map k) Source # 
Instance details

Defined in Witherable

Methods

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

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

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

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

Defined in Witherable

Methods

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

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

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

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

Defined in Witherable

Methods

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

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

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

WitherableWithIndex i t => WitherableWithIndex i (Reverse t) Source #

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

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

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

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

Defined in Witherable

Methods

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

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

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

(WitherableWithIndex i f, WitherableWithIndex j g) => WitherableWithIndex (Either i j) (Sum f g) Source # 
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) Source #

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

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

(WitherableWithIndex i f, WitherableWithIndex j g) => WitherableWithIndex (Either i j) (Product f g) Source # 
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) Source #

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

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

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

Defined in Witherable

Methods

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

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

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

Wrapper

newtype WrappedFoldable f a Source #

Constructors

WrapFilterable 

Fields

Instances

Instances details
FunctorWithIndex i f => FunctorWithIndex i (WrappedFoldable f) Source # 
Instance details

Defined in Witherable

Methods

imap :: (i -> a -> b) -> WrappedFoldable f a -> WrappedFoldable f b #

FoldableWithIndex i f => FoldableWithIndex i (WrappedFoldable f) Source # 
Instance details

Defined in Witherable

Methods

ifoldMap :: Monoid m => (i -> a -> m) -> WrappedFoldable f a -> m #

ifoldMap' :: Monoid m => (i -> a -> m) -> WrappedFoldable f a -> m #

ifoldr :: (i -> a -> b -> b) -> b -> WrappedFoldable f a -> b #

ifoldl :: (i -> b -> a -> b) -> b -> WrappedFoldable f a -> b #

ifoldr' :: (i -> a -> b -> b) -> b -> WrappedFoldable f a -> b #

ifoldl' :: (i -> b -> a -> b) -> b -> WrappedFoldable f a -> b #

TraversableWithIndex i f => TraversableWithIndex i (WrappedFoldable f) Source # 
Instance details

Defined in Witherable

Methods

itraverse :: Applicative f0 => (i -> a -> f0 b) -> WrappedFoldable f a -> f0 (WrappedFoldable f b) #

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

Defined in Witherable

Methods

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

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

Functor f => Functor (WrappedFoldable f) Source # 
Instance details

Defined in Witherable

Methods

fmap :: (a -> b) -> WrappedFoldable f a -> WrappedFoldable f b #

(<$) :: a -> WrappedFoldable f b -> WrappedFoldable f a #

Applicative f => Applicative (WrappedFoldable f) Source # 
Instance details

Defined in Witherable

Foldable f => Foldable (WrappedFoldable f) Source # 
Instance details

Defined in Witherable

Methods

fold :: Monoid m => WrappedFoldable f m -> m #

foldMap :: Monoid m => (a -> m) -> WrappedFoldable f a -> m #

foldMap' :: Monoid m => (a -> m) -> WrappedFoldable f a -> m #

foldr :: (a -> b -> b) -> b -> WrappedFoldable f a -> b #

foldr' :: (a -> b -> b) -> b -> WrappedFoldable f a -> b #

foldl :: (b -> a -> b) -> b -> WrappedFoldable f a -> b #

foldl' :: (b -> a -> b) -> b -> WrappedFoldable f a -> b #

foldr1 :: (a -> a -> a) -> WrappedFoldable f a -> a #

foldl1 :: (a -> a -> a) -> WrappedFoldable f a -> a #

toList :: WrappedFoldable f a -> [a] #

null :: WrappedFoldable f a -> Bool #

length :: WrappedFoldable f a -> Int #

elem :: Eq a => a -> WrappedFoldable f a -> Bool #

maximum :: Ord a => WrappedFoldable f a -> a #

minimum :: Ord a => WrappedFoldable f a -> a #

sum :: Num a => WrappedFoldable f a -> a #

product :: Num a => WrappedFoldable f a -> a #

Traversable f => Traversable (WrappedFoldable f) Source # 
Instance details

Defined in Witherable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> WrappedFoldable f a -> f0 (WrappedFoldable f b) #

sequenceA :: Applicative f0 => WrappedFoldable f (f0 a) -> f0 (WrappedFoldable f a) #

mapM :: Monad m => (a -> m b) -> WrappedFoldable f a -> m (WrappedFoldable f b) #

sequence :: Monad m => WrappedFoldable f (m a) -> m (WrappedFoldable f a) #

Alternative f => Alternative (WrappedFoldable f) Source # 
Instance details

Defined in Witherable

(Alternative f, Traversable f) => Witherable (WrappedFoldable f) Source # 
Instance details

Defined in Witherable

Methods

wither :: Applicative f0 => (a -> f0 (Maybe b)) -> WrappedFoldable f a -> f0 (WrappedFoldable f b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> WrappedFoldable f a -> m (WrappedFoldable f b) Source #

filterA :: Applicative f0 => (a -> f0 Bool) -> WrappedFoldable f a -> f0 (WrappedFoldable f a) Source #

witherMap :: Applicative m => (WrappedFoldable f b -> r) -> (a -> m (Maybe b)) -> WrappedFoldable f a -> m r Source #

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

Defined in Witherable