{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE CPP, DeriveFunctor, DeriveFoldable, DeriveTraversable, StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances, FlexibleContexts, GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE EmptyCase #-}
{-# LANGUAGE Trustworthy #-}
module Witherable
( Filterable(..)
, (<$?>)
, (<&?>)
, Witherable(..)
, ordNub
, ordNubOn
, hashNub
, hashNubOn
, forMaybe
, FilterableWithIndex(..)
, WitherableWithIndex(..)
, WrappedFoldable(..)
)
where
import Control.Applicative
import Control.Applicative.Backwards (Backwards (..))
import Control.Monad.Trans.Identity
import Control.Monad.Trans.Maybe
import Control.Monad.Trans.State.Lazy (evalState, state)
import Data.Bool (bool)
import Data.Coerce (coerce)
import Data.Foldable.WithIndex
import Data.Functor.Compose
import Data.Functor.Product as P
import Data.Functor.Reverse (Reverse (..))
import Data.Functor.Sum as Sum
import Data.Functor.WithIndex
import Data.Functor.WithIndex.Instances ()
import Data.Hashable
import Data.Monoid
import Data.Orphans ()
import Data.Proxy
#if !MIN_VERSION_base(4,16,0)
import Data.Semigroup (Option (..))
#endif
import Data.Traversable.WithIndex
import Data.Void
import Prelude hiding (filter)
import qualified Data.Foldable as F
import qualified Data.HashMap.Lazy as HM
import qualified Data.HashSet as HSet
import qualified Data.IntMap.Lazy as IM
import qualified Data.Map.Lazy as M
import qualified Data.Maybe as Maybe
import qualified Data.Sequence as S
import qualified Data.Set as Set
import qualified Data.Traversable as T
import qualified Data.Vector as V
import qualified GHC.Generics as Generics
import qualified Prelude
class Functor f => Filterable f where
mapMaybe :: (a -> Maybe b) -> f a -> f b
mapMaybe a -> Maybe b
f = f (Maybe b) -> f b
forall a. f (Maybe a) -> f a
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes (f (Maybe b) -> f b) -> (f a -> f (Maybe b)) -> f a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Maybe b) -> f a -> f (Maybe b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Maybe b
f
{-# INLINE mapMaybe #-}
catMaybes :: f (Maybe a) -> f a
catMaybes = (Maybe a -> Maybe a) -> f (Maybe a) -> f a
forall a b. (a -> Maybe b) -> f a -> f b
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe Maybe a -> Maybe a
forall a. a -> a
id
{-# INLINE catMaybes #-}
filter :: (a -> Bool) -> f a -> f a
filter a -> Bool
f = (a -> Maybe a) -> f a -> f a
forall a b. (a -> Maybe b) -> f a -> f b
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe ((a -> Maybe a) -> f a -> f a) -> (a -> Maybe a) -> f a -> f a
forall a b. (a -> b) -> a -> b
$ \a
a -> if a -> Bool
f a
a then a -> Maybe a
forall a. a -> Maybe a
Just a
a else Maybe a
forall a. Maybe a
Nothing
{-# INLINE filter #-}
drain :: f a -> f b
drain = (a -> Maybe b) -> f a -> f b
forall a b. (a -> Maybe b) -> f a -> f b
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe (Maybe b -> a -> Maybe b
forall a b. a -> b -> a
const Maybe b
forall a. Maybe a
Nothing)
{-# INLINE drain #-}
{-# MINIMAL mapMaybe | catMaybes #-}
class (T.Traversable t, Filterable t) => Witherable t where
wither :: Applicative f => (a -> f (Maybe b)) -> t a -> f (t b)
wither a -> f (Maybe b)
f = (t (Maybe b) -> t b) -> f (t (Maybe b)) -> f (t b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap t (Maybe b) -> t b
forall a. t (Maybe a) -> t a
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes (f (t (Maybe b)) -> f (t b))
-> (t a -> f (t (Maybe b))) -> t a -> f (t b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> f (Maybe b)) -> t a -> f (t (Maybe b))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b)
T.traverse a -> f (Maybe b)
f
{-# INLINE wither #-}
witherM :: Monad m => (a -> m (Maybe b)) -> t a -> m (t b)
witherM = (a -> m (Maybe b)) -> t a -> m (t b)
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> t a -> f (t b)
wither
filterA :: Applicative f => (a -> f Bool) -> t a -> f (t a)
filterA a -> f Bool
f = (a -> f (Maybe a)) -> t a -> f (t a)
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> t a -> f (t b)
wither ((a -> f (Maybe a)) -> t a -> f (t a))
-> (a -> f (Maybe a)) -> t a -> f (t a)
forall a b. (a -> b) -> a -> b
$ \a
a -> (\Bool
b -> if Bool
b then a -> Maybe a
forall a. a -> Maybe a
Just a
a else Maybe a
forall a. Maybe a
Nothing) (Bool -> Maybe a) -> f Bool -> f (Maybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f Bool
f a
a
witherMap :: (Applicative m) => (t b -> r) -> (a -> m (Maybe b)) -> t a -> m r
witherMap t b -> r
p a -> m (Maybe b)
f = (t b -> r) -> m (t b) -> m r
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap t b -> r
p (m (t b) -> m r) -> (t a -> m (t b)) -> t a -> m r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> m (Maybe b)) -> t a -> m (t b)
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> t a -> f (t b)
wither a -> m (Maybe b)
f
{-# INLINE witherMap #-}
{-# MINIMAL #-}
instance Filterable Maybe where
mapMaybe :: forall a b. (a -> Maybe b) -> Maybe a -> Maybe b
mapMaybe a -> Maybe b
f = (Maybe a -> (a -> Maybe b) -> Maybe b
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= a -> Maybe b
f)
drain :: forall a b. Maybe a -> Maybe b
drain Maybe a
_ = Maybe b
forall a. Maybe a
Nothing
{-# INLINE mapMaybe #-}
instance Witherable Maybe where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> Maybe a -> f (Maybe b)
wither a -> f (Maybe b)
_ Maybe a
Nothing = Maybe b -> f (Maybe b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe b
forall a. Maybe a
Nothing
wither a -> f (Maybe b)
f (Just a
a) = a -> f (Maybe b)
f a
a
{-# INLINABLE wither #-}
#if !MIN_VERSION_base(4,16,0)
instance Filterable Option where
mapMaybe f = (>>= Option . f)
drain _ = Option Nothing
{-# INLINE mapMaybe #-}
instance Witherable Option where
wither f (Option x) = Option <$> wither f x
{-# INLINE wither #-}
#endif
instance Monoid e => Filterable (Either e) where
mapMaybe :: forall a b. (a -> Maybe b) -> Either e a -> Either e b
mapMaybe a -> Maybe b
_ (Left e
e) = e -> Either e b
forall a b. a -> Either a b
Left e
e
mapMaybe a -> Maybe b
f (Right a
a) = Either e b -> (b -> Either e b) -> Maybe b -> Either e b
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (e -> Either e b
forall a b. a -> Either a b
Left e
forall a. Monoid a => a
mempty) b -> Either e b
forall a b. b -> Either a b
Right (Maybe b -> Either e b) -> Maybe b -> Either e b
forall a b. (a -> b) -> a -> b
$ a -> Maybe b
f a
a
{-# INLINABLE mapMaybe #-}
drain :: forall a b. Either e a -> Either e b
drain (Left e
e) = e -> Either e b
forall a b. a -> Either a b
Left e
e
drain (Right a
_) = e -> Either e b
forall a b. a -> Either a b
Left e
forall a. Monoid a => a
mempty
instance Monoid e => Witherable (Either e) where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> Either e a -> f (Either e b)
wither a -> f (Maybe b)
_ (Left e
e) = Either e b -> f (Either e b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (e -> Either e b
forall a b. a -> Either a b
Left e
e)
wither a -> f (Maybe b)
f (Right a
a) = (Maybe b -> Either e b) -> f (Maybe b) -> f (Either e b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Either e b -> (b -> Either e b) -> Maybe b -> Either e b
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (e -> Either e b
forall a b. a -> Either a b
Left e
forall a. Monoid a => a
mempty) b -> Either e b
forall a b. b -> Either a b
Right) (a -> f (Maybe b)
f a
a)
{-# INLINABLE wither #-}
instance Filterable [] where
mapMaybe :: forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe = (a -> Maybe b) -> [a] -> [b]
forall a b. (a -> Maybe b) -> [a] -> [b]
Maybe.mapMaybe
catMaybes :: forall a. [Maybe a] -> [a]
catMaybes = [Maybe a] -> [a]
forall a. [Maybe a] -> [a]
Maybe.catMaybes
filter :: forall a. (a -> Bool) -> [a] -> [a]
filter = (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
Prelude.filter
drain :: forall a b. [a] -> [b]
drain [a]
_ = []
instance Filterable ZipList where
mapMaybe :: forall a b. (a -> Maybe b) -> ZipList a -> ZipList b
mapMaybe a -> Maybe b
f = [b] -> ZipList b
forall a. [a] -> ZipList a
ZipList ([b] -> ZipList b) -> (ZipList a -> [b]) -> ZipList a -> ZipList b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Maybe b) -> [a] -> [b]
forall a b. (a -> Maybe b) -> [a] -> [b]
Maybe.mapMaybe a -> Maybe b
f ([a] -> [b]) -> (ZipList a -> [a]) -> ZipList a -> [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ZipList a -> [a]
forall a. ZipList a -> [a]
getZipList
catMaybes :: forall a. ZipList (Maybe a) -> ZipList a
catMaybes = [a] -> ZipList a
forall a. [a] -> ZipList a
ZipList ([a] -> ZipList a)
-> (ZipList (Maybe a) -> [a]) -> ZipList (Maybe a) -> ZipList a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe a] -> [a]
forall a. [Maybe a] -> [a]
Maybe.catMaybes ([Maybe a] -> [a])
-> (ZipList (Maybe a) -> [Maybe a]) -> ZipList (Maybe a) -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ZipList (Maybe a) -> [Maybe a]
forall a. ZipList a -> [a]
getZipList
filter :: forall a. (a -> Bool) -> ZipList a -> ZipList a
filter a -> Bool
f = [a] -> ZipList a
forall a. [a] -> ZipList a
ZipList ([a] -> ZipList a) -> (ZipList a -> [a]) -> ZipList a -> ZipList a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
Prelude.filter a -> Bool
f ([a] -> [a]) -> (ZipList a -> [a]) -> ZipList a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ZipList a -> [a]
forall a. ZipList a -> [a]
getZipList
drain :: forall a b. ZipList a -> ZipList b
drain ZipList a
_ = [b] -> ZipList b
forall a. [a] -> ZipList a
ZipList []
instance Witherable [] where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> [a] -> f [b]
wither a -> f (Maybe b)
f = (a -> f [b] -> f [b]) -> f [b] -> [a] -> f [b]
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr a -> f [b] -> f [b]
go ([b] -> f [b]
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []) where
go :: a -> f [b] -> f [b]
go a
x f [b]
r = (Maybe b -> [b] -> [b]) -> f (Maybe b) -> f [b] -> f [b]
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (([b] -> [b]) -> (b -> [b] -> [b]) -> Maybe b -> [b] -> [b]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [b] -> [b]
forall a. a -> a
id (:)) (a -> f (Maybe b)
f a
x) f [b]
r
{-# INLINE wither #-}
witherM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> [a] -> m [b]
witherM a -> m (Maybe b)
f = (a -> m [b] -> m [b]) -> m [b] -> [a] -> m [b]
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr a -> m [b] -> m [b]
go ([b] -> m [b]
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []) where
go :: a -> m [b] -> m [b]
go a
x m [b]
r = a -> m (Maybe b)
f a
x m (Maybe b) -> (Maybe b -> m [b]) -> m [b]
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
(\Maybe b
z -> case Maybe b
z of
Maybe b
Nothing -> m [b]
r
Just b
y -> ((:) b
y) ([b] -> [b]) -> m [b] -> m [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m [b]
r
)
{-# INLINE witherM #-}
filterA :: forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> [a] -> f [a]
filterA a -> f Bool
p = [a] -> f [a]
go where
go :: [a] -> f [a]
go (a
x:[a]
xs) = (Bool -> [a] -> [a]) -> f Bool -> f [a] -> f [a]
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (([a] -> [a]) -> ([a] -> [a]) -> Bool -> [a] -> [a]
forall a. a -> a -> Bool -> a
bool [a] -> [a]
forall a. a -> a
id (a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
:)) (a -> f Bool
p a
x) ([a] -> f [a]
go [a]
xs)
go [] = [a] -> f [a]
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
instance Witherable ZipList where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> ZipList a -> f (ZipList b)
wither a -> f (Maybe b)
f = ([b] -> ZipList b) -> f [b] -> f (ZipList b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [b] -> ZipList b
forall a. [a] -> ZipList a
ZipList (f [b] -> f (ZipList b))
-> (ZipList a -> f [b]) -> ZipList a -> f (ZipList b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> f (Maybe b)) -> [a] -> f [b]
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> [a] -> f [b]
wither a -> f (Maybe b)
f ([a] -> f [b]) -> (ZipList a -> [a]) -> ZipList a -> f [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ZipList a -> [a]
forall a. ZipList a -> [a]
getZipList
instance Filterable IM.IntMap where
mapMaybe :: forall a b. (a -> Maybe b) -> IntMap a -> IntMap b
mapMaybe = (a -> Maybe b) -> IntMap a -> IntMap b
forall a b. (a -> Maybe b) -> IntMap a -> IntMap b
IM.mapMaybe
filter :: forall a. (a -> Bool) -> IntMap a -> IntMap a
filter = (a -> Bool) -> IntMap a -> IntMap a
forall a. (a -> Bool) -> IntMap a -> IntMap a
IM.filter
drain :: forall a b. IntMap a -> IntMap b
drain IntMap a
_ = IntMap b
forall a. IntMap a
IM.empty
instance Witherable IM.IntMap where
instance Filterable (M.Map k) where
mapMaybe :: forall a b. (a -> Maybe b) -> Map k a -> Map k b
mapMaybe = (a -> Maybe b) -> Map k a -> Map k b
forall a b k. (a -> Maybe b) -> Map k a -> Map k b
M.mapMaybe
filter :: forall a. (a -> Bool) -> Map k a -> Map k a
filter = (a -> Bool) -> Map k a -> Map k a
forall a k. (a -> Bool) -> Map k a -> Map k a
M.filter
drain :: forall a b. Map k a -> Map k b
drain Map k a
_ = Map k b
forall k a. Map k a
M.empty
instance Witherable (M.Map k) where
#if MIN_VERSION_containers(0,5,8)
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> Map k a -> f (Map k b)
wither a -> f (Maybe b)
f = (k -> a -> f (Maybe b)) -> Map k a -> f (Map k b)
forall (f :: * -> *) k a b.
Applicative f =>
(k -> a -> f (Maybe b)) -> Map k a -> f (Map k b)
M.traverseMaybeWithKey ((a -> f (Maybe b)) -> k -> a -> f (Maybe b)
forall a b. a -> b -> a
const a -> f (Maybe b)
f)
#endif
instance (Eq k, Hashable k) => Filterable (HM.HashMap k) where
mapMaybe :: forall a b. (a -> Maybe b) -> HashMap k a -> HashMap k b
mapMaybe = (a -> Maybe b) -> HashMap k a -> HashMap k b
forall v1 v2 k. (v1 -> Maybe v2) -> HashMap k v1 -> HashMap k v2
HM.mapMaybe
filter :: forall a. (a -> Bool) -> HashMap k a -> HashMap k a
filter = (a -> Bool) -> HashMap k a -> HashMap k a
forall v k. (v -> Bool) -> HashMap k v -> HashMap k v
HM.filter
drain :: forall a b. HashMap k a -> HashMap k b
drain HashMap k a
_ = HashMap k b
forall k v. HashMap k v
HM.empty
instance (Eq k, Hashable k) => Witherable (HM.HashMap k) where
instance Filterable Proxy where
mapMaybe :: forall a b. (a -> Maybe b) -> Proxy a -> Proxy b
mapMaybe a -> Maybe b
_ Proxy a
Proxy = Proxy b
forall {k} (t :: k). Proxy t
Proxy
instance Witherable Proxy where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> Proxy a -> f (Proxy b)
wither a -> f (Maybe b)
_ Proxy a
Proxy = Proxy b -> f (Proxy b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Proxy b
forall {k} (t :: k). Proxy t
Proxy
instance Filterable (Const r) where
mapMaybe :: forall a b. (a -> Maybe b) -> Const r a -> Const r b
mapMaybe a -> Maybe b
_ (Const r
r) = r -> Const r b
forall {k} a (b :: k). a -> Const a b
Const r
r
{-# INLINABLE mapMaybe #-}
instance Witherable (Const r) where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> Const r a -> f (Const r b)
wither a -> f (Maybe b)
_ (Const r
r) = Const r b -> f (Const r b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (r -> Const r b
forall {k} a (b :: k). a -> Const a b
Const r
r)
{-# INLINABLE wither #-}
instance Filterable V.Vector where
filter :: forall a. (a -> Bool) -> Vector a -> Vector a
filter = (a -> Bool) -> Vector a -> Vector a
forall a. (a -> Bool) -> Vector a -> Vector a
V.filter
mapMaybe :: forall a b. (a -> Maybe b) -> Vector a -> Vector b
mapMaybe = (a -> Maybe b) -> Vector a -> Vector b
forall a b. (a -> Maybe b) -> Vector a -> Vector b
V.mapMaybe
drain :: forall a b. Vector a -> Vector b
drain Vector a
_ = Vector b
forall a. Vector a
V.empty
instance Witherable V.Vector where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> Vector a -> f (Vector b)
wither a -> f (Maybe b)
f = ([b] -> Vector b) -> f [b] -> f (Vector b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [b] -> Vector b
forall a. [a] -> Vector a
V.fromList (f [b] -> f (Vector b))
-> (Vector a -> f [b]) -> Vector a -> f (Vector b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> f (Maybe b)) -> [a] -> f [b]
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> [a] -> f [b]
wither a -> f (Maybe b)
f ([a] -> f [b]) -> (Vector a -> [a]) -> Vector a -> f [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector a -> [a]
forall a. Vector a -> [a]
V.toList
{-# INLINABLE wither #-}
witherM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> Vector a -> m (Vector b)
witherM = (a -> m (Maybe b)) -> Vector a -> m (Vector b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> Vector a -> m (Vector b)
V.mapMaybeM
{-# INLINE witherM #-}
instance Filterable S.Seq where
mapMaybe :: forall a b. (a -> Maybe b) -> Seq a -> Seq b
mapMaybe a -> Maybe b
f = [b] -> Seq b
forall a. [a] -> Seq a
S.fromList ([b] -> Seq b) -> (Seq a -> [b]) -> Seq a -> Seq b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Maybe b) -> [a] -> [b]
forall a b. (a -> Maybe b) -> [a] -> [b]
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe a -> Maybe b
f ([a] -> [b]) -> (Seq a -> [a]) -> Seq a -> [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Seq a -> [a]
forall a. Seq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList
{-# INLINABLE mapMaybe #-}
filter :: forall a. (a -> Bool) -> Seq a -> Seq a
filter = (a -> Bool) -> Seq a -> Seq a
forall a. (a -> Bool) -> Seq a -> Seq a
S.filter
drain :: forall a b. Seq a -> Seq b
drain Seq a
_ = Seq b
forall a. Seq a
S.empty
instance Witherable S.Seq where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> Seq a -> f (Seq b)
wither a -> f (Maybe b)
f = ([b] -> Seq b) -> f [b] -> f (Seq b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [b] -> Seq b
forall a. [a] -> Seq a
S.fromList (f [b] -> f (Seq b)) -> (Seq a -> f [b]) -> Seq a -> f (Seq b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> f (Maybe b)) -> [a] -> f [b]
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> [a] -> f [b]
wither a -> f (Maybe b)
f ([a] -> f [b]) -> (Seq a -> [a]) -> Seq a -> f [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Seq a -> [a]
forall a. Seq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList
{-# INLINABLE wither #-}
instance (Functor f, Filterable g) => Filterable (Compose f g) where
mapMaybe :: forall a b. (a -> Maybe b) -> Compose f g a -> Compose f g b
mapMaybe a -> Maybe b
f = f (g b) -> Compose f g b
forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (f (g b) -> Compose f g b)
-> (Compose f g a -> f (g b)) -> Compose f g a -> Compose f g b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (g a -> g b) -> f (g a) -> f (g b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> Maybe b) -> g a -> g b
forall a b. (a -> Maybe b) -> g a -> g b
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe a -> Maybe b
f) (f (g a) -> f (g b))
-> (Compose f g a -> f (g a)) -> Compose f g a -> f (g b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose f g a -> f (g a)
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
filter :: forall a. (a -> Bool) -> Compose f g a -> Compose f g a
filter a -> Bool
p = f (g a) -> Compose f g a
forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (f (g a) -> Compose f g a)
-> (Compose f g a -> f (g a)) -> Compose f g a -> Compose f g a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (g a -> g a) -> f (g a) -> f (g a)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> Bool) -> g a -> g a
forall a. (a -> Bool) -> g a -> g a
forall (f :: * -> *) a. Filterable f => (a -> Bool) -> f a -> f a
filter a -> Bool
p) (f (g a) -> f (g a))
-> (Compose f g a -> f (g a)) -> Compose f g a -> f (g a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose f g a -> f (g a)
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
catMaybes :: forall a. Compose f g (Maybe a) -> Compose f g a
catMaybes = f (g a) -> Compose f g a
forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (f (g a) -> Compose f g a)
-> (Compose f g (Maybe a) -> f (g a))
-> Compose f g (Maybe a)
-> Compose f g a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (g (Maybe a) -> g a) -> f (g (Maybe a)) -> f (g a)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap g (Maybe a) -> g a
forall a. g (Maybe a) -> g a
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes (f (g (Maybe a)) -> f (g a))
-> (Compose f g (Maybe a) -> f (g (Maybe a)))
-> Compose f g (Maybe a)
-> f (g a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose f g (Maybe a) -> f (g (Maybe a))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
drain :: forall a b. Compose f g a -> Compose f g b
drain = f (g b) -> Compose f g b
forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (f (g b) -> Compose f g b)
-> (Compose f g a -> f (g b)) -> Compose f g a -> Compose f g b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (g a -> g b) -> f (g a) -> f (g b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap g a -> g b
forall a b. g a -> g b
forall (f :: * -> *) a b. Filterable f => f a -> f b
drain (f (g a) -> f (g b))
-> (Compose f g a -> f (g a)) -> Compose f g a -> f (g b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose f g a -> f (g a)
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
instance (T.Traversable f, Witherable g) => Witherable (Compose f g) where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> Compose f g a -> f (Compose f g b)
wither a -> f (Maybe b)
f = (f (g b) -> Compose f g b) -> f (f (g b)) -> f (Compose f g b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f (g b) -> Compose f g b
forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (f (f (g b)) -> f (Compose f g b))
-> (Compose f g a -> f (f (g b)))
-> Compose f g a
-> f (Compose f g b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (g a -> f (g b)) -> f (g a) -> f (f (g b))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> f a -> f (f b)
T.traverse ((a -> f (Maybe b)) -> g a -> f (g b)
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> g a -> f (g b)
wither a -> f (Maybe b)
f) (f (g a) -> f (f (g b)))
-> (Compose f g a -> f (g a)) -> Compose f g a -> f (f (g b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose f g a -> f (g a)
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
witherM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> Compose f g a -> m (Compose f g b)
witherM a -> m (Maybe b)
f = (f (g b) -> Compose f g b) -> m (f (g b)) -> m (Compose f g b)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f (g b) -> Compose f g b
forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (m (f (g b)) -> m (Compose f g b))
-> (Compose f g a -> m (f (g b)))
-> Compose f g a
-> m (Compose f g b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (g a -> m (g b)) -> f (g a) -> m (f (g b))
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> f a -> m (f b)
T.mapM ((a -> m (Maybe b)) -> g a -> m (g b)
forall (t :: * -> *) (m :: * -> *) a b.
(Witherable t, Monad m) =>
(a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> g a -> m (g b)
witherM a -> m (Maybe b)
f) (f (g a) -> m (f (g b)))
-> (Compose f g a -> f (g a)) -> Compose f g a -> m (f (g b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose f g a -> f (g a)
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
filterA :: forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> Compose f g a -> f (Compose f g a)
filterA a -> f Bool
p = (f (g a) -> Compose f g a) -> f (f (g a)) -> f (Compose f g a)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f (g a) -> Compose f g a
forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (f (f (g a)) -> f (Compose f g a))
-> (Compose f g a -> f (f (g a)))
-> Compose f g a
-> f (Compose f g a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (g a -> f (g a)) -> f (g a) -> f (f (g a))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> f a -> f (f b)
T.traverse ((a -> f Bool) -> g a -> f (g a)
forall (t :: * -> *) (f :: * -> *) a.
(Witherable t, Applicative f) =>
(a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> g a -> f (g a)
filterA a -> f Bool
p) (f (g a) -> f (f (g a)))
-> (Compose f g a -> f (g a)) -> Compose f g a -> f (f (g a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose f g a -> f (g a)
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
instance (Filterable f, Filterable g) => Filterable (P.Product f g) where
mapMaybe :: forall a b. (a -> Maybe b) -> Product f g a -> Product f g b
mapMaybe a -> Maybe b
f (P.Pair f a
x g a
y) = f b -> g b -> Product f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
P.Pair ((a -> Maybe b) -> f a -> f b
forall a b. (a -> Maybe b) -> f a -> f b
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe a -> Maybe b
f f a
x) ((a -> Maybe b) -> g a -> g b
forall a b. (a -> Maybe b) -> g a -> g b
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe a -> Maybe b
f g a
y)
filter :: forall a. (a -> Bool) -> Product f g a -> Product f g a
filter a -> Bool
p (P.Pair f a
x g a
y) = f a -> g a -> Product f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
P.Pair ((a -> Bool) -> f a -> f a
forall a. (a -> Bool) -> f a -> f a
forall (f :: * -> *) a. Filterable f => (a -> Bool) -> f a -> f a
filter a -> Bool
p f a
x) ((a -> Bool) -> g a -> g a
forall a. (a -> Bool) -> g a -> g a
forall (f :: * -> *) a. Filterable f => (a -> Bool) -> f a -> f a
filter a -> Bool
p g a
y)
catMaybes :: forall a. Product f g (Maybe a) -> Product f g a
catMaybes (P.Pair f (Maybe a)
x g (Maybe a)
y) = f a -> g a -> Product f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
P.Pair (f (Maybe a) -> f a
forall a. f (Maybe a) -> f a
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes f (Maybe a)
x) (g (Maybe a) -> g a
forall a. g (Maybe a) -> g a
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes g (Maybe a)
y)
drain :: forall a b. Product f g a -> Product f g b
drain (P.Pair f a
x g a
y) = f b -> g b -> Product f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
P.Pair (f a -> f b
forall a b. f a -> f b
forall (f :: * -> *) a b. Filterable f => f a -> f b
drain f a
x) (g a -> g b
forall a b. g a -> g b
forall (f :: * -> *) a b. Filterable f => f a -> f b
drain g a
y)
instance (Witherable f, Witherable g) => Witherable (P.Product f g) where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> Product f g a -> f (Product f g b)
wither a -> f (Maybe b)
f (P.Pair f a
x g a
y) = (f b -> g b -> Product f g b)
-> f (f b) -> f (g b) -> f (Product f g b)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 f b -> g b -> Product f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
P.Pair ((a -> f (Maybe b)) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> f a -> f (f b)
wither a -> f (Maybe b)
f f a
x) ((a -> f (Maybe b)) -> g a -> f (g b)
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> g a -> f (g b)
wither a -> f (Maybe b)
f g a
y)
witherM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> Product f g a -> m (Product f g b)
witherM a -> m (Maybe b)
f (P.Pair f a
x g a
y) = (f b -> g b -> Product f g b)
-> m (f b) -> m (g b) -> m (Product f g b)
forall a b c. (a -> b -> c) -> m a -> m b -> m c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 f b -> g b -> Product f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
P.Pair ((a -> m (Maybe b)) -> f a -> m (f b)
forall (t :: * -> *) (m :: * -> *) a b.
(Witherable t, Monad m) =>
(a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> f a -> m (f b)
witherM a -> m (Maybe b)
f f a
x) ((a -> m (Maybe b)) -> g a -> m (g b)
forall (t :: * -> *) (m :: * -> *) a b.
(Witherable t, Monad m) =>
(a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> g a -> m (g b)
witherM a -> m (Maybe b)
f g a
y)
filterA :: forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> Product f g a -> f (Product f g a)
filterA a -> f Bool
p (P.Pair f a
x g a
y) = (f a -> g a -> Product f g a)
-> f (f a) -> f (g a) -> f (Product f g a)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 f a -> g a -> Product f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
P.Pair ((a -> f Bool) -> f a -> f (f a)
forall (t :: * -> *) (f :: * -> *) a.
(Witherable t, Applicative f) =>
(a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> f a -> f (f a)
filterA a -> f Bool
p f a
x) ((a -> f Bool) -> g a -> f (g a)
forall (t :: * -> *) (f :: * -> *) a.
(Witherable t, Applicative f) =>
(a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> g a -> f (g a)
filterA a -> f Bool
p g a
y)
instance (Filterable f, Filterable g) => Filterable (Sum.Sum f g) where
mapMaybe :: forall a b. (a -> Maybe b) -> Sum f g a -> Sum f g b
mapMaybe a -> Maybe b
f (Sum.InL f a
x) = f b -> Sum f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
Sum.InL ((a -> Maybe b) -> f a -> f b
forall a b. (a -> Maybe b) -> f a -> f b
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe a -> Maybe b
f f a
x)
mapMaybe a -> Maybe b
f (Sum.InR g a
y) = g b -> Sum f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
Sum.InR ((a -> Maybe b) -> g a -> g b
forall a b. (a -> Maybe b) -> g a -> g b
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe a -> Maybe b
f g a
y)
catMaybes :: forall a. Sum f g (Maybe a) -> Sum f g a
catMaybes (Sum.InL f (Maybe a)
x) = f a -> Sum f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
Sum.InL (f (Maybe a) -> f a
forall a. f (Maybe a) -> f a
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes f (Maybe a)
x)
catMaybes (Sum.InR g (Maybe a)
y) = g a -> Sum f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
Sum.InR (g (Maybe a) -> g a
forall a. g (Maybe a) -> g a
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes g (Maybe a)
y)
filter :: forall a. (a -> Bool) -> Sum f g a -> Sum f g a
filter a -> Bool
p (Sum.InL f a
x) = f a -> Sum f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
Sum.InL ((a -> Bool) -> f a -> f a
forall a. (a -> Bool) -> f a -> f a
forall (f :: * -> *) a. Filterable f => (a -> Bool) -> f a -> f a
filter a -> Bool
p f a
x)
filter a -> Bool
p (Sum.InR g a
y) = g a -> Sum f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
Sum.InR ((a -> Bool) -> g a -> g a
forall a. (a -> Bool) -> g a -> g a
forall (f :: * -> *) a. Filterable f => (a -> Bool) -> f a -> f a
filter a -> Bool
p g a
y)
drain :: forall a b. Sum f g a -> Sum f g b
drain (Sum.InL f a
x) = f b -> Sum f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
Sum.InL (f a -> f b
forall a b. f a -> f b
forall (f :: * -> *) a b. Filterable f => f a -> f b
drain f a
x)
drain (Sum.InR g a
y) = g b -> Sum f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
Sum.InR (g a -> g b
forall a b. g a -> g b
forall (f :: * -> *) a b. Filterable f => f a -> f b
drain g a
y)
instance (Witherable f, Witherable g) => Witherable (Sum.Sum f g) where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> Sum f g a -> f (Sum f g b)
wither a -> f (Maybe b)
f (Sum.InL f a
x) = f b -> Sum f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
Sum.InL (f b -> Sum f g b) -> f (f b) -> f (Sum f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f (Maybe b)) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> f a -> f (f b)
wither a -> f (Maybe b)
f f a
x
wither a -> f (Maybe b)
f (Sum.InR g a
y) = g b -> Sum f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
Sum.InR (g b -> Sum f g b) -> f (g b) -> f (Sum f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f (Maybe b)) -> g a -> f (g b)
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> g a -> f (g b)
wither a -> f (Maybe b)
f g a
y
witherM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> Sum f g a -> m (Sum f g b)
witherM a -> m (Maybe b)
f (Sum.InL f a
x) = f b -> Sum f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
Sum.InL (f b -> Sum f g b) -> m (f b) -> m (Sum f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> m (Maybe b)) -> f a -> m (f b)
forall (t :: * -> *) (m :: * -> *) a b.
(Witherable t, Monad m) =>
(a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> f a -> m (f b)
witherM a -> m (Maybe b)
f f a
x
witherM a -> m (Maybe b)
f (Sum.InR g a
y) = g b -> Sum f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
Sum.InR (g b -> Sum f g b) -> m (g b) -> m (Sum f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> m (Maybe b)) -> g a -> m (g b)
forall (t :: * -> *) (m :: * -> *) a b.
(Witherable t, Monad m) =>
(a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> g a -> m (g b)
witherM a -> m (Maybe b)
f g a
y
filterA :: forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> Sum f g a -> f (Sum f g a)
filterA a -> f Bool
f (Sum.InL f a
x) = f a -> Sum f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
Sum.InL (f a -> Sum f g a) -> f (f a) -> f (Sum f g a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f Bool) -> f a -> f (f a)
forall (t :: * -> *) (f :: * -> *) a.
(Witherable t, Applicative f) =>
(a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> f a -> f (f a)
filterA a -> f Bool
f f a
x
filterA a -> f Bool
f (Sum.InR g a
y) = g a -> Sum f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
Sum.InR (g a -> Sum f g a) -> f (g a) -> f (Sum f g a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f Bool) -> g a -> f (g a)
forall (t :: * -> *) (f :: * -> *) a.
(Witherable t, Applicative f) =>
(a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> g a -> f (g a)
filterA a -> f Bool
f g a
y
deriving instance Filterable f => Filterable (IdentityT f)
instance Witherable f => Witherable (IdentityT f) where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> IdentityT f a -> f (IdentityT f b)
wither a -> f (Maybe b)
f (IdentityT f a
m) = f b -> IdentityT f b
forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT (f b -> IdentityT f b) -> f (f b) -> f (IdentityT f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f (Maybe b)) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> f a -> f (f b)
wither a -> f (Maybe b)
f f a
m
witherM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> IdentityT f a -> m (IdentityT f b)
witherM a -> m (Maybe b)
f (IdentityT f a
m) = f b -> IdentityT f b
forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT (f b -> IdentityT f b) -> m (f b) -> m (IdentityT f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> m (Maybe b)) -> f a -> m (f b)
forall (t :: * -> *) (m :: * -> *) a b.
(Witherable t, Monad m) =>
(a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> f a -> m (f b)
witherM a -> m (Maybe b)
f f a
m
filterA :: forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> IdentityT f a -> f (IdentityT f a)
filterA a -> f Bool
p (IdentityT f a
m) = f a -> IdentityT f a
forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT (f a -> IdentityT f a) -> f (f a) -> f (IdentityT f a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f Bool) -> f a -> f (f a)
forall (t :: * -> *) (f :: * -> *) a.
(Witherable t, Applicative f) =>
(a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> f a -> f (f a)
filterA a -> f Bool
p f a
m
instance Functor f => Filterable (MaybeT f) where
mapMaybe :: forall a b. (a -> Maybe b) -> MaybeT f a -> MaybeT f b
mapMaybe a -> Maybe b
f = f (Maybe b) -> MaybeT f b
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (f (Maybe b) -> MaybeT f b)
-> (MaybeT f a -> f (Maybe b)) -> MaybeT f a -> MaybeT f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe a -> Maybe b) -> f (Maybe a) -> f (Maybe b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> Maybe b) -> Maybe a -> Maybe b
forall a b. (a -> Maybe b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe a -> Maybe b
f) (f (Maybe a) -> f (Maybe b))
-> (MaybeT f a -> f (Maybe a)) -> MaybeT f a -> f (Maybe b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MaybeT f a -> f (Maybe a)
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT
instance (T.Traversable t) => Witherable (MaybeT t) where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> MaybeT t a -> f (MaybeT t b)
wither a -> f (Maybe b)
f = (t (Maybe b) -> MaybeT t b) -> f (t (Maybe b)) -> f (MaybeT t b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap t (Maybe b) -> MaybeT t b
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (f (t (Maybe b)) -> f (MaybeT t b))
-> (MaybeT t a -> f (t (Maybe b))) -> MaybeT t a -> f (MaybeT t b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe a -> f (Maybe b)) -> t (Maybe a) -> f (t (Maybe b))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b)
T.traverse ((a -> f (Maybe b)) -> Maybe a -> f (Maybe b)
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> Maybe a -> f (Maybe b)
wither a -> f (Maybe b)
f) (t (Maybe a) -> f (t (Maybe b)))
-> (MaybeT t a -> t (Maybe a)) -> MaybeT t a -> f (t (Maybe b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MaybeT t a -> t (Maybe a)
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT
witherM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> MaybeT t a -> m (MaybeT t b)
witherM a -> m (Maybe b)
f = (t (Maybe b) -> MaybeT t b) -> m (t (Maybe b)) -> m (MaybeT t b)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap t (Maybe b) -> MaybeT t b
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (t (Maybe b)) -> m (MaybeT t b))
-> (MaybeT t a -> m (t (Maybe b))) -> MaybeT t a -> m (MaybeT t b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe a -> m (Maybe b)) -> t (Maybe a) -> m (t (Maybe b))
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> t a -> m (t b)
T.mapM ((a -> m (Maybe b)) -> Maybe a -> m (Maybe b)
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> Maybe a -> f (Maybe b)
wither a -> m (Maybe b)
f) (t (Maybe a) -> m (t (Maybe b)))
-> (MaybeT t a -> t (Maybe a)) -> MaybeT t a -> m (t (Maybe b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MaybeT t a -> t (Maybe a)
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT
deriving instance Filterable t => Filterable (Reverse t)
instance Witherable t => Witherable (Reverse t) where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> Reverse t a -> f (Reverse t b)
wither a -> f (Maybe b)
f (Reverse t a
t) =
(t b -> Reverse t b) -> f (t b) -> f (Reverse t b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap t b -> Reverse t b
forall {k} (f :: k -> *) (a :: k). f a -> Reverse f a
Reverse (f (t b) -> f (Reverse t b))
-> (Backwards f (t b) -> f (t b))
-> Backwards f (t b)
-> f (Reverse t b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Backwards f (t b) -> f (t b)
forall {k} (f :: k -> *) (a :: k). Backwards f a -> f a
forwards (Backwards f (t b) -> f (Reverse t b))
-> Backwards f (t b) -> f (Reverse t b)
forall a b. (a -> b) -> a -> b
$ (a -> Backwards f (Maybe b)) -> t a -> Backwards f (t b)
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> t a -> f (t b)
wither ((a -> f (Maybe b)) -> a -> Backwards f (Maybe b)
forall a b. Coercible a b => a -> b
coerce a -> f (Maybe b)
f) t a
t
filterA :: forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> Reverse t a -> f (Reverse t a)
filterA a -> f Bool
f (Reverse t a
t) =
(t a -> Reverse t a) -> f (t a) -> f (Reverse t a)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap t a -> Reverse t a
forall {k} (f :: k -> *) (a :: k). f a -> Reverse f a
Reverse (f (t a) -> f (Reverse t a))
-> (Backwards f (t a) -> f (t a))
-> Backwards f (t a)
-> f (Reverse t a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Backwards f (t a) -> f (t a)
forall {k} (f :: k -> *) (a :: k). Backwards f a -> f a
forwards (Backwards f (t a) -> f (Reverse t a))
-> Backwards f (t a) -> f (Reverse t a)
forall a b. (a -> b) -> a -> b
$ (a -> Backwards f Bool) -> t a -> Backwards f (t a)
forall (t :: * -> *) (f :: * -> *) a.
(Witherable t, Applicative f) =>
(a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> t a -> f (t a)
filterA ((a -> f Bool) -> a -> Backwards f Bool
forall a b. Coercible a b => a -> b
coerce a -> f Bool
f) t a
t
deriving instance Filterable t => Filterable (Backwards t)
instance Witherable t => Witherable (Backwards t) where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> Backwards t a -> f (Backwards t b)
wither a -> f (Maybe b)
f (Backwards t a
xs) = t b -> Backwards t b
forall {k} (f :: k -> *) (a :: k). f a -> Backwards f a
Backwards (t b -> Backwards t b) -> f (t b) -> f (Backwards t b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f (Maybe b)) -> t a -> f (t b)
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> t a -> f (t b)
wither a -> f (Maybe b)
f t a
xs
witherM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> Backwards t a -> m (Backwards t b)
witherM a -> m (Maybe b)
f (Backwards t a
xs) = t b -> Backwards t b
forall {k} (f :: k -> *) (a :: k). f a -> Backwards f a
Backwards (t b -> Backwards t b) -> m (t b) -> m (Backwards t b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> m (Maybe b)) -> t a -> m (t b)
forall (t :: * -> *) (m :: * -> *) a b.
(Witherable t, Monad m) =>
(a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> t a -> m (t b)
witherM a -> m (Maybe b)
f t a
xs
filterA :: forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> Backwards t a -> f (Backwards t a)
filterA a -> f Bool
f (Backwards t a
xs) = t a -> Backwards t a
forall {k} (f :: k -> *) (a :: k). f a -> Backwards f a
Backwards (t a -> Backwards t a) -> f (t a) -> f (Backwards t a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f Bool) -> t a -> f (t a)
forall (t :: * -> *) (f :: * -> *) a.
(Witherable t, Applicative f) =>
(a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> t a -> f (t a)
filterA a -> f Bool
f t a
xs
instance Filterable Generics.V1 where
mapMaybe :: forall a b. (a -> Maybe b) -> V1 a -> V1 b
mapMaybe a -> Maybe b
_ V1 a
v = case V1 a
v of {}
catMaybes :: forall a. V1 (Maybe a) -> V1 a
catMaybes V1 (Maybe a)
v = case V1 (Maybe a)
v of {}
filter :: forall a. (a -> Bool) -> V1 a -> V1 a
filter a -> Bool
_ V1 a
v = case V1 a
v of {}
instance Witherable Generics.V1 where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> V1 a -> f (V1 b)
wither a -> f (Maybe b)
_ V1 a
v = V1 b -> f (V1 b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (V1 b -> f (V1 b)) -> V1 b -> f (V1 b)
forall a b. (a -> b) -> a -> b
$ case V1 a
v of {}
filterA :: forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> V1 a -> f (V1 a)
filterA a -> f Bool
_ V1 a
v = V1 a -> f (V1 a)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (V1 a -> f (V1 a)) -> V1 a -> f (V1 a)
forall a b. (a -> b) -> a -> b
$ case V1 a
v of {}
instance Filterable Generics.U1 where
mapMaybe :: forall a b. (a -> Maybe b) -> U1 a -> U1 b
mapMaybe a -> Maybe b
_ U1 a
_ = U1 b
forall k (p :: k). U1 p
Generics.U1
catMaybes :: forall a. U1 (Maybe a) -> U1 a
catMaybes U1 (Maybe a)
_ = U1 a
forall k (p :: k). U1 p
Generics.U1
filter :: forall a. (a -> Bool) -> U1 a -> U1 a
filter a -> Bool
_ U1 a
_ = U1 a
forall k (p :: k). U1 p
Generics.U1
instance Witherable Generics.U1 where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> U1 a -> f (U1 b)
wither a -> f (Maybe b)
_ U1 a
_ = U1 b -> f (U1 b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure U1 b
forall k (p :: k). U1 p
Generics.U1
filterA :: forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> U1 a -> f (U1 a)
filterA a -> f Bool
_ U1 a
_ = U1 a -> f (U1 a)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure U1 a
forall k (p :: k). U1 p
Generics.U1
instance Filterable (Generics.K1 i c) where
mapMaybe :: forall a b. (a -> Maybe b) -> K1 i c a -> K1 i c b
mapMaybe a -> Maybe b
_ (Generics.K1 c
a) = c -> K1 i c b
forall k i c (p :: k). c -> K1 i c p
Generics.K1 c
a
catMaybes :: forall a. K1 i c (Maybe a) -> K1 i c a
catMaybes (Generics.K1 c
a) = c -> K1 i c a
forall k i c (p :: k). c -> K1 i c p
Generics.K1 c
a
filter :: forall a. (a -> Bool) -> K1 i c a -> K1 i c a
filter a -> Bool
_ (Generics.K1 c
a) = c -> K1 i c a
forall k i c (p :: k). c -> K1 i c p
Generics.K1 c
a
instance Witherable (Generics.K1 i c) where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> K1 i c a -> f (K1 i c b)
wither a -> f (Maybe b)
_ (Generics.K1 c
a) = K1 i c b -> f (K1 i c b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (c -> K1 i c b
forall k i c (p :: k). c -> K1 i c p
Generics.K1 c
a)
filterA :: forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> K1 i c a -> f (K1 i c a)
filterA a -> f Bool
_ (Generics.K1 c
a) = K1 i c a -> f (K1 i c a)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (c -> K1 i c a
forall k i c (p :: k). c -> K1 i c p
Generics.K1 c
a)
instance Filterable f => Filterable (Generics.Rec1 f) where
mapMaybe :: forall a b. (a -> Maybe b) -> Rec1 f a -> Rec1 f b
mapMaybe a -> Maybe b
f (Generics.Rec1 f a
a) = f b -> Rec1 f b
forall k (f :: k -> *) (p :: k). f p -> Rec1 f p
Generics.Rec1 ((a -> Maybe b) -> f a -> f b
forall a b. (a -> Maybe b) -> f a -> f b
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe a -> Maybe b
f f a
a)
catMaybes :: forall a. Rec1 f (Maybe a) -> Rec1 f a
catMaybes (Generics.Rec1 f (Maybe a)
a) = f a -> Rec1 f a
forall k (f :: k -> *) (p :: k). f p -> Rec1 f p
Generics.Rec1 (f (Maybe a) -> f a
forall a. f (Maybe a) -> f a
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes f (Maybe a)
a)
filter :: forall a. (a -> Bool) -> Rec1 f a -> Rec1 f a
filter a -> Bool
f (Generics.Rec1 f a
a) = f a -> Rec1 f a
forall k (f :: k -> *) (p :: k). f p -> Rec1 f p
Generics.Rec1 ((a -> Bool) -> f a -> f a
forall a. (a -> Bool) -> f a -> f a
forall (f :: * -> *) a. Filterable f => (a -> Bool) -> f a -> f a
filter a -> Bool
f f a
a)
instance Witherable f => Witherable (Generics.Rec1 f) where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> Rec1 f a -> f (Rec1 f b)
wither a -> f (Maybe b)
f (Generics.Rec1 f a
a) = (f b -> Rec1 f b) -> f (f b) -> f (Rec1 f b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f b -> Rec1 f b
forall k (f :: k -> *) (p :: k). f p -> Rec1 f p
Generics.Rec1 ((a -> f (Maybe b)) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> f a -> f (f b)
wither a -> f (Maybe b)
f f a
a)
witherM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> Rec1 f a -> m (Rec1 f b)
witherM a -> m (Maybe b)
f (Generics.Rec1 f a
a) = (f b -> Rec1 f b) -> m (f b) -> m (Rec1 f b)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f b -> Rec1 f b
forall k (f :: k -> *) (p :: k). f p -> Rec1 f p
Generics.Rec1 ((a -> m (Maybe b)) -> f a -> m (f b)
forall (t :: * -> *) (m :: * -> *) a b.
(Witherable t, Monad m) =>
(a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> f a -> m (f b)
witherM a -> m (Maybe b)
f f a
a)
filterA :: forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> Rec1 f a -> f (Rec1 f a)
filterA a -> f Bool
f (Generics.Rec1 f a
a) = (f a -> Rec1 f a) -> f (f a) -> f (Rec1 f a)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f a -> Rec1 f a
forall k (f :: k -> *) (p :: k). f p -> Rec1 f p
Generics.Rec1 ((a -> f Bool) -> f a -> f (f a)
forall (t :: * -> *) (f :: * -> *) a.
(Witherable t, Applicative f) =>
(a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> f a -> f (f a)
filterA a -> f Bool
f f a
a)
instance Filterable f => Filterable (Generics.M1 i c f) where
mapMaybe :: forall a b. (a -> Maybe b) -> M1 i c f a -> M1 i c f b
mapMaybe a -> Maybe b
f (Generics.M1 f a
a) = f b -> M1 i c f b
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
Generics.M1 ((a -> Maybe b) -> f a -> f b
forall a b. (a -> Maybe b) -> f a -> f b
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe a -> Maybe b
f f a
a)
catMaybes :: forall a. M1 i c f (Maybe a) -> M1 i c f a
catMaybes (Generics.M1 f (Maybe a)
a) = f a -> M1 i c f a
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
Generics.M1 (f (Maybe a) -> f a
forall a. f (Maybe a) -> f a
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes f (Maybe a)
a)
filter :: forall a. (a -> Bool) -> M1 i c f a -> M1 i c f a
filter a -> Bool
f (Generics.M1 f a
a) = f a -> M1 i c f a
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
Generics.M1 ((a -> Bool) -> f a -> f a
forall a. (a -> Bool) -> f a -> f a
forall (f :: * -> *) a. Filterable f => (a -> Bool) -> f a -> f a
filter a -> Bool
f f a
a)
instance Witherable f => Witherable (Generics.M1 i c f) where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> M1 i c f a -> f (M1 i c f b)
wither a -> f (Maybe b)
f (Generics.M1 f a
a) = (f b -> M1 i c f b) -> f (f b) -> f (M1 i c f b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f b -> M1 i c f b
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
Generics.M1 ((a -> f (Maybe b)) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> f a -> f (f b)
wither a -> f (Maybe b)
f f a
a)
witherM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> M1 i c f a -> m (M1 i c f b)
witherM a -> m (Maybe b)
f (Generics.M1 f a
a) = (f b -> M1 i c f b) -> m (f b) -> m (M1 i c f b)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f b -> M1 i c f b
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
Generics.M1 ((a -> m (Maybe b)) -> f a -> m (f b)
forall (t :: * -> *) (m :: * -> *) a b.
(Witherable t, Monad m) =>
(a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> f a -> m (f b)
witherM a -> m (Maybe b)
f f a
a)
filterA :: forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> M1 i c f a -> f (M1 i c f a)
filterA a -> f Bool
f (Generics.M1 f a
a) = (f a -> M1 i c f a) -> f (f a) -> f (M1 i c f a)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f a -> M1 i c f a
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
Generics.M1 ((a -> f Bool) -> f a -> f (f a)
forall (t :: * -> *) (f :: * -> *) a.
(Witherable t, Applicative f) =>
(a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> f a -> f (f a)
filterA a -> f Bool
f f a
a)
instance (Filterable f, Filterable g) => Filterable ((Generics.:*:) f g) where
mapMaybe :: forall a b. (a -> Maybe b) -> (:*:) f g a -> (:*:) f g b
mapMaybe a -> Maybe b
f (f a
a Generics.:*: g a
b) = (a -> Maybe b) -> f a -> f b
forall a b. (a -> Maybe b) -> f a -> f b
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe a -> Maybe b
f f a
a f b -> g b -> (:*:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
Generics.:*: (a -> Maybe b) -> g a -> g b
forall a b. (a -> Maybe b) -> g a -> g b
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe a -> Maybe b
f g a
b
catMaybes :: forall a. (:*:) f g (Maybe a) -> (:*:) f g a
catMaybes (f (Maybe a)
a Generics.:*: g (Maybe a)
b) = f (Maybe a) -> f a
forall a. f (Maybe a) -> f a
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes f (Maybe a)
a f a -> g a -> (:*:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
Generics.:*: g (Maybe a) -> g a
forall a. g (Maybe a) -> g a
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes g (Maybe a)
b
filter :: forall a. (a -> Bool) -> (:*:) f g a -> (:*:) f g a
filter a -> Bool
f (f a
a Generics.:*: g a
b) = (a -> Bool) -> f a -> f a
forall a. (a -> Bool) -> f a -> f a
forall (f :: * -> *) a. Filterable f => (a -> Bool) -> f a -> f a
filter a -> Bool
f f a
a f a -> g a -> (:*:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
Generics.:*: (a -> Bool) -> g a -> g a
forall a. (a -> Bool) -> g a -> g a
forall (f :: * -> *) a. Filterable f => (a -> Bool) -> f a -> f a
filter a -> Bool
f g a
b
instance (Witherable f, Witherable g) => Witherable ((Generics.:*:) f g) where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> (:*:) f g a -> f ((:*:) f g b)
wither a -> f (Maybe b)
f (f a
a Generics.:*: g a
b) = (f b -> g b -> (:*:) f g b)
-> f (f b) -> f (g b) -> f ((:*:) f g b)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 f b -> g b -> (:*:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
(Generics.:*:) ((a -> f (Maybe b)) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> f a -> f (f b)
wither a -> f (Maybe b)
f f a
a) ((a -> f (Maybe b)) -> g a -> f (g b)
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> g a -> f (g b)
wither a -> f (Maybe b)
f g a
b)
witherM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> (:*:) f g a -> m ((:*:) f g b)
witherM a -> m (Maybe b)
f (f a
a Generics.:*: g a
b) = (f b -> g b -> (:*:) f g b)
-> m (f b) -> m (g b) -> m ((:*:) f g b)
forall a b c. (a -> b -> c) -> m a -> m b -> m c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 f b -> g b -> (:*:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
(Generics.:*:) ((a -> m (Maybe b)) -> f a -> m (f b)
forall (t :: * -> *) (m :: * -> *) a b.
(Witherable t, Monad m) =>
(a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> f a -> m (f b)
witherM a -> m (Maybe b)
f f a
a) ((a -> m (Maybe b)) -> g a -> m (g b)
forall (t :: * -> *) (m :: * -> *) a b.
(Witherable t, Monad m) =>
(a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> g a -> m (g b)
witherM a -> m (Maybe b)
f g a
b)
filterA :: forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> (:*:) f g a -> f ((:*:) f g a)
filterA a -> f Bool
f (f a
a Generics.:*: g a
b) = (f a -> g a -> (:*:) f g a)
-> f (f a) -> f (g a) -> f ((:*:) f g a)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 f a -> g a -> (:*:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
(Generics.:*:) ((a -> f Bool) -> f a -> f (f a)
forall (t :: * -> *) (f :: * -> *) a.
(Witherable t, Applicative f) =>
(a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> f a -> f (f a)
filterA a -> f Bool
f f a
a) ((a -> f Bool) -> g a -> f (g a)
forall (t :: * -> *) (f :: * -> *) a.
(Witherable t, Applicative f) =>
(a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> g a -> f (g a)
filterA a -> f Bool
f g a
b)
instance (Filterable f, Filterable g) => Filterable ((Generics.:+:) f g) where
mapMaybe :: forall a b. (a -> Maybe b) -> (:+:) f g a -> (:+:) f g b
mapMaybe a -> Maybe b
f (Generics.L1 f a
a) = f b -> (:+:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
Generics.L1 ((a -> Maybe b) -> f a -> f b
forall a b. (a -> Maybe b) -> f a -> f b
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe a -> Maybe b
f f a
a)
mapMaybe a -> Maybe b
f (Generics.R1 g a
a) = g b -> (:+:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
Generics.R1 ((a -> Maybe b) -> g a -> g b
forall a b. (a -> Maybe b) -> g a -> g b
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe a -> Maybe b
f g a
a)
catMaybes :: forall a. (:+:) f g (Maybe a) -> (:+:) f g a
catMaybes (Generics.L1 f (Maybe a)
a) = f a -> (:+:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
Generics.L1 (f (Maybe a) -> f a
forall a. f (Maybe a) -> f a
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes f (Maybe a)
a)
catMaybes (Generics.R1 g (Maybe a)
a) = g a -> (:+:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
Generics.R1 (g (Maybe a) -> g a
forall a. g (Maybe a) -> g a
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes g (Maybe a)
a)
filter :: forall a. (a -> Bool) -> (:+:) f g a -> (:+:) f g a
filter a -> Bool
f (Generics.L1 f a
a) = f a -> (:+:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
Generics.L1 ((a -> Bool) -> f a -> f a
forall a. (a -> Bool) -> f a -> f a
forall (f :: * -> *) a. Filterable f => (a -> Bool) -> f a -> f a
filter a -> Bool
f f a
a)
filter a -> Bool
f (Generics.R1 g a
a) = g a -> (:+:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
Generics.R1 ((a -> Bool) -> g a -> g a
forall a. (a -> Bool) -> g a -> g a
forall (f :: * -> *) a. Filterable f => (a -> Bool) -> f a -> f a
filter a -> Bool
f g a
a)
instance (Witherable f, Witherable g) => Witherable ((Generics.:+:) f g) where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> (:+:) f g a -> f ((:+:) f g b)
wither a -> f (Maybe b)
f (Generics.L1 f a
a) = (f b -> (:+:) f g b) -> f (f b) -> f ((:+:) f g b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f b -> (:+:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
Generics.L1 ((a -> f (Maybe b)) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> f a -> f (f b)
wither a -> f (Maybe b)
f f a
a)
wither a -> f (Maybe b)
f (Generics.R1 g a
a) = (g b -> (:+:) f g b) -> f (g b) -> f ((:+:) f g b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap g b -> (:+:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
Generics.R1 ((a -> f (Maybe b)) -> g a -> f (g b)
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> g a -> f (g b)
wither a -> f (Maybe b)
f g a
a)
witherM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> (:+:) f g a -> m ((:+:) f g b)
witherM a -> m (Maybe b)
f (Generics.L1 f a
a) = (f b -> (:+:) f g b) -> m (f b) -> m ((:+:) f g b)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f b -> (:+:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
Generics.L1 ((a -> m (Maybe b)) -> f a -> m (f b)
forall (t :: * -> *) (m :: * -> *) a b.
(Witherable t, Monad m) =>
(a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> f a -> m (f b)
witherM a -> m (Maybe b)
f f a
a)
witherM a -> m (Maybe b)
f (Generics.R1 g a
a) = (g b -> (:+:) f g b) -> m (g b) -> m ((:+:) f g b)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap g b -> (:+:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
Generics.R1 ((a -> m (Maybe b)) -> g a -> m (g b)
forall (t :: * -> *) (m :: * -> *) a b.
(Witherable t, Monad m) =>
(a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> g a -> m (g b)
witherM a -> m (Maybe b)
f g a
a)
filterA :: forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> (:+:) f g a -> f ((:+:) f g a)
filterA a -> f Bool
f (Generics.L1 f a
a) = (f a -> (:+:) f g a) -> f (f a) -> f ((:+:) f g a)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f a -> (:+:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
Generics.L1 ((a -> f Bool) -> f a -> f (f a)
forall (t :: * -> *) (f :: * -> *) a.
(Witherable t, Applicative f) =>
(a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> f a -> f (f a)
filterA a -> f Bool
f f a
a)
filterA a -> f Bool
f (Generics.R1 g a
a) = (g a -> (:+:) f g a) -> f (g a) -> f ((:+:) f g a)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap g a -> (:+:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
Generics.R1 ((a -> f Bool) -> g a -> f (g a)
forall (t :: * -> *) (f :: * -> *) a.
(Witherable t, Applicative f) =>
(a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> g a -> f (g a)
filterA a -> f Bool
f g a
a)
instance (Functor f, Filterable g) => Filterable ((Generics.:.:) f g) where
mapMaybe :: forall a b. (a -> Maybe b) -> (:.:) f g a -> (:.:) f g b
mapMaybe a -> Maybe b
f = f (g b) -> (:.:) f g b
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
f (g p) -> (:.:) f g p
Generics.Comp1 (f (g b) -> (:.:) f g b)
-> ((:.:) f g a -> f (g b)) -> (:.:) f g a -> (:.:) f g b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (g a -> g b) -> f (g a) -> f (g b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> Maybe b) -> g a -> g b
forall a b. (a -> Maybe b) -> g a -> g b
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe a -> Maybe b
f) (f (g a) -> f (g b))
-> ((:.:) f g a -> f (g a)) -> (:.:) f g a -> f (g b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:.:) f g a -> f (g a)
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
(:.:) f g p -> f (g p)
Generics.unComp1
catMaybes :: forall a. (:.:) f g (Maybe a) -> (:.:) f g a
catMaybes = f (g a) -> (:.:) f g a
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
f (g p) -> (:.:) f g p
Generics.Comp1 (f (g a) -> (:.:) f g a)
-> ((:.:) f g (Maybe a) -> f (g a))
-> (:.:) f g (Maybe a)
-> (:.:) f g a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (g (Maybe a) -> g a) -> f (g (Maybe a)) -> f (g a)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap g (Maybe a) -> g a
forall a. g (Maybe a) -> g a
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes (f (g (Maybe a)) -> f (g a))
-> ((:.:) f g (Maybe a) -> f (g (Maybe a)))
-> (:.:) f g (Maybe a)
-> f (g a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:.:) f g (Maybe a) -> f (g (Maybe a))
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
(:.:) f g p -> f (g p)
Generics.unComp1
filter :: forall a. (a -> Bool) -> (:.:) f g a -> (:.:) f g a
filter a -> Bool
f = f (g a) -> (:.:) f g a
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
f (g p) -> (:.:) f g p
Generics.Comp1 (f (g a) -> (:.:) f g a)
-> ((:.:) f g a -> f (g a)) -> (:.:) f g a -> (:.:) f g a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (g a -> g a) -> f (g a) -> f (g a)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> Bool) -> g a -> g a
forall a. (a -> Bool) -> g a -> g a
forall (f :: * -> *) a. Filterable f => (a -> Bool) -> f a -> f a
filter a -> Bool
f) (f (g a) -> f (g a))
-> ((:.:) f g a -> f (g a)) -> (:.:) f g a -> f (g a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:.:) f g a -> f (g a)
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
(:.:) f g p -> f (g p)
Generics.unComp1
instance (T.Traversable f, Witherable g) => Witherable ((Generics.:.:) f g) where
wither :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> (:.:) f g a -> f ((:.:) f g b)
wither a -> f (Maybe b)
f = (f (g b) -> (:.:) f g b) -> f (f (g b)) -> f ((:.:) f g b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f (g b) -> (:.:) f g b
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
f (g p) -> (:.:) f g p
Generics.Comp1 (f (f (g b)) -> f ((:.:) f g b))
-> ((:.:) f g a -> f (f (g b))) -> (:.:) f g a -> f ((:.:) f g b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (g a -> f (g b)) -> f (g a) -> f (f (g b))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> f a -> f (f b)
T.traverse ((a -> f (Maybe b)) -> g a -> f (g b)
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> g a -> f (g b)
wither a -> f (Maybe b)
f) (f (g a) -> f (f (g b)))
-> ((:.:) f g a -> f (g a)) -> (:.:) f g a -> f (f (g b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:.:) f g a -> f (g a)
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
(:.:) f g p -> f (g p)
Generics.unComp1
witherM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> (:.:) f g a -> m ((:.:) f g b)
witherM a -> m (Maybe b)
f = (f (g b) -> (:.:) f g b) -> m (f (g b)) -> m ((:.:) f g b)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f (g b) -> (:.:) f g b
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
f (g p) -> (:.:) f g p
Generics.Comp1 (m (f (g b)) -> m ((:.:) f g b))
-> ((:.:) f g a -> m (f (g b))) -> (:.:) f g a -> m ((:.:) f g b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (g a -> m (g b)) -> f (g a) -> m (f (g b))
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> f a -> m (f b)
T.mapM ((a -> m (Maybe b)) -> g a -> m (g b)
forall (t :: * -> *) (m :: * -> *) a b.
(Witherable t, Monad m) =>
(a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> g a -> m (g b)
witherM a -> m (Maybe b)
f) (f (g a) -> m (f (g b)))
-> ((:.:) f g a -> f (g a)) -> (:.:) f g a -> m (f (g b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:.:) f g a -> f (g a)
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
(:.:) f g p -> f (g p)
Generics.unComp1
filterA :: forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> (:.:) f g a -> f ((:.:) f g a)
filterA a -> f Bool
f = (f (g a) -> (:.:) f g a) -> f (f (g a)) -> f ((:.:) f g a)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f (g a) -> (:.:) f g a
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
f (g p) -> (:.:) f g p
Generics.Comp1 (f (f (g a)) -> f ((:.:) f g a))
-> ((:.:) f g a -> f (f (g a))) -> (:.:) f g a -> f ((:.:) f g a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (g a -> f (g a)) -> f (g a) -> f (f (g a))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> f a -> f (f b)
T.traverse ((a -> f Bool) -> g a -> f (g a)
forall (t :: * -> *) (f :: * -> *) a.
(Witherable t, Applicative f) =>
(a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(a -> f Bool) -> g a -> f (g a)
filterA a -> f Bool
f) (f (g a) -> f (f (g a)))
-> ((:.:) f g a -> f (g a)) -> (:.:) f g a -> f (f (g a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:.:) f g a -> f (g a)
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
(:.:) f g p -> f (g p)
Generics.unComp1
class (FunctorWithIndex i t, Filterable t) => FilterableWithIndex i t | t -> i where
imapMaybe :: (i -> a -> Maybe b) -> t a -> t b
imapMaybe i -> a -> Maybe b
f = t (Maybe b) -> t b
forall a. t (Maybe a) -> t a
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes (t (Maybe b) -> t b) -> (t a -> t (Maybe b)) -> t a -> t b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (i -> a -> Maybe b) -> t a -> t (Maybe b)
forall a b. (i -> a -> b) -> t a -> t b
forall i (f :: * -> *) a b.
FunctorWithIndex i f =>
(i -> a -> b) -> f a -> f b
imap i -> a -> Maybe b
f
{-# INLINE imapMaybe #-}
ifilter :: (i -> a -> Bool) -> t a -> t a
ifilter i -> a -> Bool
f = (i -> a -> Maybe a) -> t a -> t a
forall a b. (i -> a -> Maybe b) -> t a -> t b
forall i (t :: * -> *) a b.
FilterableWithIndex i t =>
(i -> a -> Maybe b) -> t a -> t b
imapMaybe ((i -> a -> Maybe a) -> t a -> t a)
-> (i -> a -> Maybe a) -> t a -> t a
forall a b. (a -> b) -> a -> b
$ \i
i a
a -> if i -> a -> Bool
f i
i a
a then a -> Maybe a
forall a. a -> Maybe a
Just a
a else Maybe a
forall a. Maybe a
Nothing
{-# INLINE ifilter #-}
class (TraversableWithIndex i t, FilterableWithIndex i t, Witherable t) => WitherableWithIndex i t | t -> i where
iwither :: (Applicative f) => (i -> a -> f (Maybe b)) -> t a -> f (t b)
iwither i -> a -> f (Maybe b)
f = (t (Maybe b) -> t b) -> f (t (Maybe b)) -> f (t b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap t (Maybe b) -> t b
forall a. t (Maybe a) -> t a
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes (f (t (Maybe b)) -> f (t b))
-> (t a -> f (t (Maybe b))) -> t a -> f (t b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (i -> a -> f (Maybe b)) -> t a -> f (t (Maybe b))
forall i (t :: * -> *) (f :: * -> *) a b.
(TraversableWithIndex i t, Applicative f) =>
(i -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(i -> a -> f b) -> t a -> f (t b)
itraverse i -> a -> f (Maybe b)
f
iwitherM :: (Monad m) => (i -> a -> m (Maybe b)) -> t a -> m (t b)
iwitherM = (i -> a -> m (Maybe b)) -> t a -> m (t b)
forall i (t :: * -> *) (f :: * -> *) a b.
(WitherableWithIndex i t, Applicative f) =>
(i -> a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(i -> a -> f (Maybe b)) -> t a -> f (t b)
iwither
ifilterA :: (Applicative f) => (i -> a -> f Bool) -> t a -> f (t a)
ifilterA i -> a -> f Bool
f = (i -> a -> f (Maybe a)) -> t a -> f (t a)
forall i (t :: * -> *) (f :: * -> *) a b.
(WitherableWithIndex i t, Applicative f) =>
(i -> a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(i -> a -> f (Maybe b)) -> t a -> f (t b)
iwither (\i
i a
a -> (\Bool
b -> if Bool
b then a -> Maybe a
forall a. a -> Maybe a
Just a
a else Maybe a
forall a. Maybe a
Nothing) (Bool -> Maybe a) -> f Bool -> f (Maybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> i -> a -> f Bool
f i
i a
a)
instance FilterableWithIndex () Maybe
instance WitherableWithIndex () Maybe
instance FilterableWithIndex Int []
instance FilterableWithIndex Int ZipList
instance WitherableWithIndex Int []
instance WitherableWithIndex Int ZipList
instance FilterableWithIndex Int IM.IntMap where
imapMaybe :: forall a b. (Int -> a -> Maybe b) -> IntMap a -> IntMap b
imapMaybe = (Int -> a -> Maybe b) -> IntMap a -> IntMap b
forall a b. (Int -> a -> Maybe b) -> IntMap a -> IntMap b
IM.mapMaybeWithKey
ifilter :: forall a. (Int -> a -> Bool) -> IntMap a -> IntMap a
ifilter = (Int -> a -> Bool) -> IntMap a -> IntMap a
forall a. (Int -> a -> Bool) -> IntMap a -> IntMap a
IM.filterWithKey
instance WitherableWithIndex Int IM.IntMap where
instance FilterableWithIndex k (M.Map k) where
imapMaybe :: forall a b. (k -> a -> Maybe b) -> Map k a -> Map k b
imapMaybe = (k -> a -> Maybe b) -> Map k a -> Map k b
forall k a b. (k -> a -> Maybe b) -> Map k a -> Map k b
M.mapMaybeWithKey
ifilter :: forall a. (k -> a -> Bool) -> Map k a -> Map k a
ifilter = (k -> a -> Bool) -> Map k a -> Map k a
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
M.filterWithKey
instance WitherableWithIndex k (M.Map k) where
#if MIN_VERSION_containers(0,5,8)
iwither :: forall (f :: * -> *) a b.
Applicative f =>
(k -> a -> f (Maybe b)) -> Map k a -> f (Map k b)
iwither = (k -> a -> f (Maybe b)) -> Map k a -> f (Map k b)
forall (f :: * -> *) k a b.
Applicative f =>
(k -> a -> f (Maybe b)) -> Map k a -> f (Map k b)
M.traverseMaybeWithKey
#endif
instance (Eq k, Hashable k) => FilterableWithIndex k (HM.HashMap k) where
imapMaybe :: forall a b. (k -> a -> Maybe b) -> HashMap k a -> HashMap k b
imapMaybe = (k -> a -> Maybe b) -> HashMap k a -> HashMap k b
forall k v1 v2.
(k -> v1 -> Maybe v2) -> HashMap k v1 -> HashMap k v2
HM.mapMaybeWithKey
ifilter :: forall a. (k -> a -> Bool) -> HashMap k a -> HashMap k a
ifilter = (k -> a -> Bool) -> HashMap k a -> HashMap k a
forall k v. (k -> v -> Bool) -> HashMap k v -> HashMap k v
HM.filterWithKey
instance (Eq k, Hashable k) => WitherableWithIndex k (HM.HashMap k) where
instance FilterableWithIndex Void Proxy
instance WitherableWithIndex Void Proxy
instance FilterableWithIndex Int V.Vector where
imapMaybe :: forall a b. (Int -> a -> Maybe b) -> Vector a -> Vector b
imapMaybe = (Int -> a -> Maybe b) -> Vector a -> Vector b
forall a b. (Int -> a -> Maybe b) -> Vector a -> Vector b
V.imapMaybe
ifilter :: forall a. (Int -> a -> Bool) -> Vector a -> Vector a
ifilter = (Int -> a -> Bool) -> Vector a -> Vector a
forall a. (Int -> a -> Bool) -> Vector a -> Vector a
V.ifilter
instance WitherableWithIndex Int V.Vector
instance FilterableWithIndex Int S.Seq
instance WitherableWithIndex Int S.Seq
instance (FunctorWithIndex i f, FilterableWithIndex j g) => FilterableWithIndex (i, j) (Compose f g) where
imapMaybe :: forall a b.
((i, j) -> a -> Maybe b) -> Compose f g a -> Compose f g b
imapMaybe (i, j) -> a -> Maybe b
f = f (g b) -> Compose f g b
forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (f (g b) -> Compose f g b)
-> (Compose f g a -> f (g b)) -> Compose f g a -> Compose f g b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (i -> g a -> g b) -> f (g a) -> f (g b)
forall a b. (i -> a -> b) -> f a -> f b
forall i (f :: * -> *) a b.
FunctorWithIndex i f =>
(i -> a -> b) -> f a -> f b
imap (\i
i -> (j -> a -> Maybe b) -> g a -> g b
forall a b. (j -> a -> Maybe b) -> g a -> g b
forall i (t :: * -> *) a b.
FilterableWithIndex i t =>
(i -> a -> Maybe b) -> t a -> t b
imapMaybe (\j
j -> (i, j) -> a -> Maybe b
f (i
i, j
j))) (f (g a) -> f (g b))
-> (Compose f g a -> f (g a)) -> Compose f g a -> f (g b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose f g a -> f (g a)
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
ifilter :: forall a. ((i, j) -> a -> Bool) -> Compose f g a -> Compose f g a
ifilter (i, j) -> a -> Bool
p = f (g a) -> Compose f g a
forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (f (g a) -> Compose f g a)
-> (Compose f g a -> f (g a)) -> Compose f g a -> Compose f g a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (i -> g a -> g a) -> f (g a) -> f (g a)
forall a b. (i -> a -> b) -> f a -> f b
forall i (f :: * -> *) a b.
FunctorWithIndex i f =>
(i -> a -> b) -> f a -> f b
imap (\i
i -> (j -> a -> Bool) -> g a -> g a
forall a. (j -> a -> Bool) -> g a -> g a
forall i (t :: * -> *) a.
FilterableWithIndex i t =>
(i -> a -> Bool) -> t a -> t a
ifilter (\j
j -> (i, j) -> a -> Bool
p (i
i, j
j))) (f (g a) -> f (g a))
-> (Compose f g a -> f (g a)) -> Compose f g a -> f (g a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose f g a -> f (g a)
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
instance (TraversableWithIndex i f, WitherableWithIndex j g) => WitherableWithIndex (i, j) (Compose f g) where
iwither :: forall (f :: * -> *) a b.
Applicative f =>
((i, j) -> a -> f (Maybe b)) -> Compose f g a -> f (Compose f g b)
iwither (i, j) -> a -> f (Maybe b)
f = (f (g b) -> Compose f g b) -> f (f (g b)) -> f (Compose f g b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f (g b) -> Compose f g b
forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (f (f (g b)) -> f (Compose f g b))
-> (Compose f g a -> f (f (g b)))
-> Compose f g a
-> f (Compose f g b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (i -> g a -> f (g b)) -> f (g a) -> f (f (g b))
forall i (t :: * -> *) (f :: * -> *) a b.
(TraversableWithIndex i t, Applicative f) =>
(i -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(i -> a -> f b) -> f a -> f (f b)
itraverse (\i
i -> (j -> a -> f (Maybe b)) -> g a -> f (g b)
forall i (t :: * -> *) (f :: * -> *) a b.
(WitherableWithIndex i t, Applicative f) =>
(i -> a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(j -> a -> f (Maybe b)) -> g a -> f (g b)
iwither (\j
j -> (i, j) -> a -> f (Maybe b)
f (i
i, j
j))) (f (g a) -> f (f (g b)))
-> (Compose f g a -> f (g a)) -> Compose f g a -> f (f (g b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose f g a -> f (g a)
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
iwitherM :: forall (m :: * -> *) a b.
Monad m =>
((i, j) -> a -> m (Maybe b)) -> Compose f g a -> m (Compose f g b)
iwitherM (i, j) -> a -> m (Maybe b)
f = (f (g b) -> Compose f g b) -> m (f (g b)) -> m (Compose f g b)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f (g b) -> Compose f g b
forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (m (f (g b)) -> m (Compose f g b))
-> (Compose f g a -> m (f (g b)))
-> Compose f g a
-> m (Compose f g b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (i -> g a -> m (g b)) -> f (g a) -> m (f (g b))
forall i (t :: * -> *) (m :: * -> *) a b.
(TraversableWithIndex i t, Monad m) =>
(i -> a -> m b) -> t a -> m (t b)
imapM (\i
i -> (j -> a -> m (Maybe b)) -> g a -> m (g b)
forall i (t :: * -> *) (m :: * -> *) a b.
(WitherableWithIndex i t, Monad m) =>
(i -> a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(j -> a -> m (Maybe b)) -> g a -> m (g b)
iwitherM (\j
j -> (i, j) -> a -> m (Maybe b)
f (i
i, j
j))) (f (g a) -> m (f (g b)))
-> (Compose f g a -> f (g a)) -> Compose f g a -> m (f (g b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose f g a -> f (g a)
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
ifilterA :: forall (f :: * -> *) a.
Applicative f =>
((i, j) -> a -> f Bool) -> Compose f g a -> f (Compose f g a)
ifilterA (i, j) -> a -> f Bool
p = (f (g a) -> Compose f g a) -> f (f (g a)) -> f (Compose f g a)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f (g a) -> Compose f g a
forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (f (f (g a)) -> f (Compose f g a))
-> (Compose f g a -> f (f (g a)))
-> Compose f g a
-> f (Compose f g a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (i -> g a -> f (g a)) -> f (g a) -> f (f (g a))
forall i (t :: * -> *) (f :: * -> *) a b.
(TraversableWithIndex i t, Applicative f) =>
(i -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(i -> a -> f b) -> f a -> f (f b)
itraverse (\i
i -> (j -> a -> f Bool) -> g a -> f (g a)
forall i (t :: * -> *) (f :: * -> *) a.
(WitherableWithIndex i t, Applicative f) =>
(i -> a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(j -> a -> f Bool) -> g a -> f (g a)
ifilterA (\j
j -> (i, j) -> a -> f Bool
p (i
i, j
j))) (f (g a) -> f (f (g a)))
-> (Compose f g a -> f (g a)) -> Compose f g a -> f (f (g a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose f g a -> f (g a)
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
instance (FilterableWithIndex i f, FilterableWithIndex j g) => FilterableWithIndex (Either i j) (P.Product f g) where
imapMaybe :: forall a b.
(Either i j -> a -> Maybe b) -> Product f g a -> Product f g b
imapMaybe Either i j -> a -> Maybe b
f (P.Pair f a
x g a
y) = f b -> g b -> Product f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
P.Pair ((i -> a -> Maybe b) -> f a -> f b
forall a b. (i -> a -> Maybe b) -> f a -> f b
forall i (t :: * -> *) a b.
FilterableWithIndex i t =>
(i -> a -> Maybe b) -> t a -> t b
imapMaybe (Either i j -> a -> Maybe b
f (Either i j -> a -> Maybe b)
-> (i -> Either i j) -> i -> a -> Maybe b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> Either i j
forall a b. a -> Either a b
Left) f a
x) ((j -> a -> Maybe b) -> g a -> g b
forall a b. (j -> a -> Maybe b) -> g a -> g b
forall i (t :: * -> *) a b.
FilterableWithIndex i t =>
(i -> a -> Maybe b) -> t a -> t b
imapMaybe (Either i j -> a -> Maybe b
f (Either i j -> a -> Maybe b)
-> (j -> Either i j) -> j -> a -> Maybe b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. j -> Either i j
forall a b. b -> Either a b
Right) g a
y)
ifilter :: forall a.
(Either i j -> a -> Bool) -> Product f g a -> Product f g a
ifilter Either i j -> a -> Bool
p (P.Pair f a
x g a
y) = f a -> g a -> Product f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
P.Pair ((i -> a -> Bool) -> f a -> f a
forall a. (i -> a -> Bool) -> f a -> f a
forall i (t :: * -> *) a.
FilterableWithIndex i t =>
(i -> a -> Bool) -> t a -> t a
ifilter (Either i j -> a -> Bool
p (Either i j -> a -> Bool) -> (i -> Either i j) -> i -> a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> Either i j
forall a b. a -> Either a b
Left) f a
x) ((j -> a -> Bool) -> g a -> g a
forall a. (j -> a -> Bool) -> g a -> g a
forall i (t :: * -> *) a.
FilterableWithIndex i t =>
(i -> a -> Bool) -> t a -> t a
ifilter (Either i j -> a -> Bool
p (Either i j -> a -> Bool) -> (j -> Either i j) -> j -> a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. j -> Either i j
forall a b. b -> Either a b
Right) g a
y)
instance (WitherableWithIndex i f, WitherableWithIndex j g) => WitherableWithIndex (Either i j) (P.Product f g) where
iwither :: forall (f :: * -> *) a b.
Applicative f =>
(Either i j -> a -> f (Maybe b))
-> Product f g a -> f (Product f g b)
iwither Either i j -> a -> f (Maybe b)
f (P.Pair f a
x g a
y) = (f b -> g b -> Product f g b)
-> f (f b) -> f (g b) -> f (Product f g b)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 f b -> g b -> Product f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
P.Pair ((i -> a -> f (Maybe b)) -> f a -> f (f b)
forall i (t :: * -> *) (f :: * -> *) a b.
(WitherableWithIndex i t, Applicative f) =>
(i -> a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(i -> a -> f (Maybe b)) -> f a -> f (f b)
iwither (Either i j -> a -> f (Maybe b)
f (Either i j -> a -> f (Maybe b))
-> (i -> Either i j) -> i -> a -> f (Maybe b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> Either i j
forall a b. a -> Either a b
Left) f a
x) ((j -> a -> f (Maybe b)) -> g a -> f (g b)
forall i (t :: * -> *) (f :: * -> *) a b.
(WitherableWithIndex i t, Applicative f) =>
(i -> a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(j -> a -> f (Maybe b)) -> g a -> f (g b)
iwither (Either i j -> a -> f (Maybe b)
f (Either i j -> a -> f (Maybe b))
-> (j -> Either i j) -> j -> a -> f (Maybe b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. j -> Either i j
forall a b. b -> Either a b
Right) g a
y)
iwitherM :: forall (m :: * -> *) a b.
Monad m =>
(Either i j -> a -> m (Maybe b))
-> Product f g a -> m (Product f g b)
iwitherM Either i j -> a -> m (Maybe b)
f (P.Pair f a
x g a
y) = (f b -> g b -> Product f g b)
-> m (f b) -> m (g b) -> m (Product f g b)
forall a b c. (a -> b -> c) -> m a -> m b -> m c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 f b -> g b -> Product f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
P.Pair ((i -> a -> m (Maybe b)) -> f a -> m (f b)
forall i (t :: * -> *) (m :: * -> *) a b.
(WitherableWithIndex i t, Monad m) =>
(i -> a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(i -> a -> m (Maybe b)) -> f a -> m (f b)
iwitherM (Either i j -> a -> m (Maybe b)
f (Either i j -> a -> m (Maybe b))
-> (i -> Either i j) -> i -> a -> m (Maybe b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> Either i j
forall a b. a -> Either a b
Left) f a
x) ((j -> a -> m (Maybe b)) -> g a -> m (g b)
forall i (t :: * -> *) (m :: * -> *) a b.
(WitherableWithIndex i t, Monad m) =>
(i -> a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(j -> a -> m (Maybe b)) -> g a -> m (g b)
iwitherM (Either i j -> a -> m (Maybe b)
f (Either i j -> a -> m (Maybe b))
-> (j -> Either i j) -> j -> a -> m (Maybe b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. j -> Either i j
forall a b. b -> Either a b
Right) g a
y)
ifilterA :: forall (f :: * -> *) a.
Applicative f =>
(Either i j -> a -> f Bool) -> Product f g a -> f (Product f g a)
ifilterA Either i j -> a -> f Bool
p (P.Pair f a
x g a
y) = (f a -> g a -> Product f g a)
-> f (f a) -> f (g a) -> f (Product f g a)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 f a -> g a -> Product f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
P.Pair ((i -> a -> f Bool) -> f a -> f (f a)
forall i (t :: * -> *) (f :: * -> *) a.
(WitherableWithIndex i t, Applicative f) =>
(i -> a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(i -> a -> f Bool) -> f a -> f (f a)
ifilterA (Either i j -> a -> f Bool
p (Either i j -> a -> f Bool)
-> (i -> Either i j) -> i -> a -> f Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> Either i j
forall a b. a -> Either a b
Left) f a
x) ((j -> a -> f Bool) -> g a -> f (g a)
forall i (t :: * -> *) (f :: * -> *) a.
(WitherableWithIndex i t, Applicative f) =>
(i -> a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(j -> a -> f Bool) -> g a -> f (g a)
ifilterA (Either i j -> a -> f Bool
p (Either i j -> a -> f Bool)
-> (j -> Either i j) -> j -> a -> f Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. j -> Either i j
forall a b. b -> Either a b
Right) g a
y)
instance (FilterableWithIndex i f, FilterableWithIndex j g) => FilterableWithIndex (Either i j) (Sum.Sum f g) where
imapMaybe :: forall a b. (Either i j -> a -> Maybe b) -> Sum f g a -> Sum f g b
imapMaybe Either i j -> a -> Maybe b
f (Sum.InL f a
x) = f b -> Sum f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
Sum.InL ((i -> a -> Maybe b) -> f a -> f b
forall a b. (i -> a -> Maybe b) -> f a -> f b
forall i (t :: * -> *) a b.
FilterableWithIndex i t =>
(i -> a -> Maybe b) -> t a -> t b
imapMaybe (Either i j -> a -> Maybe b
f (Either i j -> a -> Maybe b)
-> (i -> Either i j) -> i -> a -> Maybe b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> Either i j
forall a b. a -> Either a b
Left) f a
x)
imapMaybe Either i j -> a -> Maybe b
f (Sum.InR g a
y) = g b -> Sum f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
Sum.InR ((j -> a -> Maybe b) -> g a -> g b
forall a b. (j -> a -> Maybe b) -> g a -> g b
forall i (t :: * -> *) a b.
FilterableWithIndex i t =>
(i -> a -> Maybe b) -> t a -> t b
imapMaybe (Either i j -> a -> Maybe b
f (Either i j -> a -> Maybe b)
-> (j -> Either i j) -> j -> a -> Maybe b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. j -> Either i j
forall a b. b -> Either a b
Right) g a
y)
ifilter :: forall a. (Either i j -> a -> Bool) -> Sum f g a -> Sum f g a
ifilter Either i j -> a -> Bool
f (Sum.InL f a
x) = f a -> Sum f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
Sum.InL ((i -> a -> Bool) -> f a -> f a
forall a. (i -> a -> Bool) -> f a -> f a
forall i (t :: * -> *) a.
FilterableWithIndex i t =>
(i -> a -> Bool) -> t a -> t a
ifilter (Either i j -> a -> Bool
f (Either i j -> a -> Bool) -> (i -> Either i j) -> i -> a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> Either i j
forall a b. a -> Either a b
Left) f a
x)
ifilter Either i j -> a -> Bool
f (Sum.InR g a
y) = g a -> Sum f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
Sum.InR ((j -> a -> Bool) -> g a -> g a
forall a. (j -> a -> Bool) -> g a -> g a
forall i (t :: * -> *) a.
FilterableWithIndex i t =>
(i -> a -> Bool) -> t a -> t a
ifilter (Either i j -> a -> Bool
f (Either i j -> a -> Bool) -> (j -> Either i j) -> j -> a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. j -> Either i j
forall a b. b -> Either a b
Right) g a
y)
instance (WitherableWithIndex i f, WitherableWithIndex j g) => WitherableWithIndex (Either i j) (Sum.Sum f g) where
iwither :: forall (f :: * -> *) a b.
Applicative f =>
(Either i j -> a -> f (Maybe b)) -> Sum f g a -> f (Sum f g b)
iwither Either i j -> a -> f (Maybe b)
f (Sum.InL f a
x) = f b -> Sum f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
Sum.InL (f b -> Sum f g b) -> f (f b) -> f (Sum f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (i -> a -> f (Maybe b)) -> f a -> f (f b)
forall i (t :: * -> *) (f :: * -> *) a b.
(WitherableWithIndex i t, Applicative f) =>
(i -> a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(i -> a -> f (Maybe b)) -> f a -> f (f b)
iwither (Either i j -> a -> f (Maybe b)
f (Either i j -> a -> f (Maybe b))
-> (i -> Either i j) -> i -> a -> f (Maybe b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> Either i j
forall a b. a -> Either a b
Left) f a
x
iwither Either i j -> a -> f (Maybe b)
f (Sum.InR g a
y) = g b -> Sum f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
Sum.InR (g b -> Sum f g b) -> f (g b) -> f (Sum f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (j -> a -> f (Maybe b)) -> g a -> f (g b)
forall i (t :: * -> *) (f :: * -> *) a b.
(WitherableWithIndex i t, Applicative f) =>
(i -> a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(j -> a -> f (Maybe b)) -> g a -> f (g b)
iwither (Either i j -> a -> f (Maybe b)
f (Either i j -> a -> f (Maybe b))
-> (j -> Either i j) -> j -> a -> f (Maybe b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. j -> Either i j
forall a b. b -> Either a b
Right) g a
y
iwitherM :: forall (m :: * -> *) a b.
Monad m =>
(Either i j -> a -> m (Maybe b)) -> Sum f g a -> m (Sum f g b)
iwitherM Either i j -> a -> m (Maybe b)
f (Sum.InL f a
x) = f b -> Sum f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
Sum.InL (f b -> Sum f g b) -> m (f b) -> m (Sum f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (i -> a -> m (Maybe b)) -> f a -> m (f b)
forall i (t :: * -> *) (m :: * -> *) a b.
(WitherableWithIndex i t, Monad m) =>
(i -> a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(i -> a -> m (Maybe b)) -> f a -> m (f b)
iwitherM (Either i j -> a -> m (Maybe b)
f (Either i j -> a -> m (Maybe b))
-> (i -> Either i j) -> i -> a -> m (Maybe b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> Either i j
forall a b. a -> Either a b
Left) f a
x
iwitherM Either i j -> a -> m (Maybe b)
f (Sum.InR g a
y) = g b -> Sum f g b
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
Sum.InR (g b -> Sum f g b) -> m (g b) -> m (Sum f g b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (j -> a -> m (Maybe b)) -> g a -> m (g b)
forall i (t :: * -> *) (m :: * -> *) a b.
(WitherableWithIndex i t, Monad m) =>
(i -> a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(j -> a -> m (Maybe b)) -> g a -> m (g b)
iwitherM (Either i j -> a -> m (Maybe b)
f (Either i j -> a -> m (Maybe b))
-> (j -> Either i j) -> j -> a -> m (Maybe b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. j -> Either i j
forall a b. b -> Either a b
Right) g a
y
ifilterA :: forall (f :: * -> *) a.
Applicative f =>
(Either i j -> a -> f Bool) -> Sum f g a -> f (Sum f g a)
ifilterA Either i j -> a -> f Bool
f (Sum.InL f a
x) = f a -> Sum f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
Sum.InL (f a -> Sum f g a) -> f (f a) -> f (Sum f g a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (i -> a -> f Bool) -> f a -> f (f a)
forall i (t :: * -> *) (f :: * -> *) a.
(WitherableWithIndex i t, Applicative f) =>
(i -> a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(i -> a -> f Bool) -> f a -> f (f a)
ifilterA (Either i j -> a -> f Bool
f (Either i j -> a -> f Bool)
-> (i -> Either i j) -> i -> a -> f Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> Either i j
forall a b. a -> Either a b
Left) f a
x
ifilterA Either i j -> a -> f Bool
f (Sum.InR g a
y) = g a -> Sum f g a
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
Sum.InR (g a -> Sum f g a) -> f (g a) -> f (Sum f g a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (j -> a -> f Bool) -> g a -> f (g a)
forall i (t :: * -> *) (f :: * -> *) a.
(WitherableWithIndex i t, Applicative f) =>
(i -> a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(j -> a -> f Bool) -> g a -> f (g a)
ifilterA (Either i j -> a -> f Bool
f (Either i j -> a -> f Bool)
-> (j -> Either i j) -> j -> a -> f Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. j -> Either i j
forall a b. b -> Either a b
Right) g a
y
deriving instance (FilterableWithIndex i f) => FilterableWithIndex i (IdentityT f)
instance (WitherableWithIndex i f) => WitherableWithIndex i (IdentityT f) where
iwither :: forall (f :: * -> *) a b.
Applicative f =>
(i -> a -> f (Maybe b)) -> IdentityT f a -> f (IdentityT f b)
iwither i -> a -> f (Maybe b)
f (IdentityT f a
m) = f b -> IdentityT f b
forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT (f b -> IdentityT f b) -> f (f b) -> f (IdentityT f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (i -> a -> f (Maybe b)) -> f a -> f (f b)
forall i (t :: * -> *) (f :: * -> *) a b.
(WitherableWithIndex i t, Applicative f) =>
(i -> a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(i -> a -> f (Maybe b)) -> f a -> f (f b)
iwither i -> a -> f (Maybe b)
f f a
m
iwitherM :: forall (m :: * -> *) a b.
Monad m =>
(i -> a -> m (Maybe b)) -> IdentityT f a -> m (IdentityT f b)
iwitherM i -> a -> m (Maybe b)
f (IdentityT f a
m) = f b -> IdentityT f b
forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT (f b -> IdentityT f b) -> m (f b) -> m (IdentityT f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (i -> a -> m (Maybe b)) -> f a -> m (f b)
forall i (t :: * -> *) (m :: * -> *) a b.
(WitherableWithIndex i t, Monad m) =>
(i -> a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(i -> a -> m (Maybe b)) -> f a -> m (f b)
iwitherM i -> a -> m (Maybe b)
f f a
m
ifilterA :: forall (f :: * -> *) a.
Applicative f =>
(i -> a -> f Bool) -> IdentityT f a -> f (IdentityT f a)
ifilterA i -> a -> f Bool
p (IdentityT f a
m) = f a -> IdentityT f a
forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT (f a -> IdentityT f a) -> f (f a) -> f (IdentityT f a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (i -> a -> f Bool) -> f a -> f (f a)
forall i (t :: * -> *) (f :: * -> *) a.
(WitherableWithIndex i t, Applicative f) =>
(i -> a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(i -> a -> f Bool) -> f a -> f (f a)
ifilterA i -> a -> f Bool
p f a
m
deriving instance FilterableWithIndex i t => FilterableWithIndex i (Reverse t)
instance WitherableWithIndex i t => WitherableWithIndex i (Reverse t) where
iwither :: forall (f :: * -> *) a b.
Applicative f =>
(i -> a -> f (Maybe b)) -> Reverse t a -> f (Reverse t b)
iwither i -> a -> f (Maybe b)
f (Reverse t a
t) = (t b -> Reverse t b) -> f (t b) -> f (Reverse t b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap t b -> Reverse t b
forall {k} (f :: k -> *) (a :: k). f a -> Reverse f a
Reverse (f (t b) -> f (Reverse t b))
-> (Backwards f (t b) -> f (t b))
-> Backwards f (t b)
-> f (Reverse t b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Backwards f (t b) -> f (t b)
forall {k} (f :: k -> *) (a :: k). Backwards f a -> f a
forwards (Backwards f (t b) -> f (Reverse t b))
-> Backwards f (t b) -> f (Reverse t b)
forall a b. (a -> b) -> a -> b
$ (i -> a -> Backwards f (Maybe b)) -> t a -> Backwards f (t b)
forall i (t :: * -> *) (f :: * -> *) a b.
(WitherableWithIndex i t, Applicative f) =>
(i -> a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(i -> a -> f (Maybe b)) -> t a -> f (t b)
iwither (\i
i -> f (Maybe b) -> Backwards f (Maybe b)
forall {k} (f :: k -> *) (a :: k). f a -> Backwards f a
Backwards (f (Maybe b) -> Backwards f (Maybe b))
-> (a -> f (Maybe b)) -> a -> Backwards f (Maybe b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> a -> f (Maybe b)
f i
i) t a
t
ifilterA :: forall (f :: * -> *) a.
Applicative f =>
(i -> a -> f Bool) -> Reverse t a -> f (Reverse t a)
ifilterA i -> a -> f Bool
p (Reverse t a
t) = (t a -> Reverse t a) -> f (t a) -> f (Reverse t a)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap t a -> Reverse t a
forall {k} (f :: k -> *) (a :: k). f a -> Reverse f a
Reverse (f (t a) -> f (Reverse t a))
-> (Backwards f (t a) -> f (t a))
-> Backwards f (t a)
-> f (Reverse t a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Backwards f (t a) -> f (t a)
forall {k} (f :: k -> *) (a :: k). Backwards f a -> f a
forwards (Backwards f (t a) -> f (Reverse t a))
-> Backwards f (t a) -> f (Reverse t a)
forall a b. (a -> b) -> a -> b
$ (i -> a -> Backwards f Bool) -> t a -> Backwards f (t a)
forall i (t :: * -> *) (f :: * -> *) a.
(WitherableWithIndex i t, Applicative f) =>
(i -> a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(i -> a -> f Bool) -> t a -> f (t a)
ifilterA (\i
i -> f Bool -> Backwards f Bool
forall {k} (f :: k -> *) (a :: k). f a -> Backwards f a
Backwards (f Bool -> Backwards f Bool)
-> (a -> f Bool) -> a -> Backwards f Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> a -> f Bool
p i
i) t a
t
deriving instance FilterableWithIndex i t => FilterableWithIndex i (Backwards t)
instance WitherableWithIndex i t => WitherableWithIndex i (Backwards t) where
iwither :: forall (f :: * -> *) a b.
Applicative f =>
(i -> a -> f (Maybe b)) -> Backwards t a -> f (Backwards t b)
iwither i -> a -> f (Maybe b)
f (Backwards t a
xs) = t b -> Backwards t b
forall {k} (f :: k -> *) (a :: k). f a -> Backwards f a
Backwards (t b -> Backwards t b) -> f (t b) -> f (Backwards t b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (i -> a -> f (Maybe b)) -> t a -> f (t b)
forall i (t :: * -> *) (f :: * -> *) a b.
(WitherableWithIndex i t, Applicative f) =>
(i -> a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(i -> a -> f (Maybe b)) -> t a -> f (t b)
iwither i -> a -> f (Maybe b)
f t a
xs
iwitherM :: forall (m :: * -> *) a b.
Monad m =>
(i -> a -> m (Maybe b)) -> Backwards t a -> m (Backwards t b)
iwitherM i -> a -> m (Maybe b)
f (Backwards t a
xs) = t b -> Backwards t b
forall {k} (f :: k -> *) (a :: k). f a -> Backwards f a
Backwards (t b -> Backwards t b) -> m (t b) -> m (Backwards t b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (i -> a -> m (Maybe b)) -> t a -> m (t b)
forall i (t :: * -> *) (m :: * -> *) a b.
(WitherableWithIndex i t, Monad m) =>
(i -> a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(i -> a -> m (Maybe b)) -> t a -> m (t b)
iwitherM i -> a -> m (Maybe b)
f t a
xs
ifilterA :: forall (f :: * -> *) a.
Applicative f =>
(i -> a -> f Bool) -> Backwards t a -> f (Backwards t a)
ifilterA i -> a -> f Bool
f (Backwards t a
xs) = t a -> Backwards t a
forall {k} (f :: k -> *) (a :: k). f a -> Backwards f a
Backwards (t a -> Backwards t a) -> f (t a) -> f (Backwards t a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (i -> a -> f Bool) -> t a -> f (t a)
forall i (t :: * -> *) (f :: * -> *) a.
(WitherableWithIndex i t, Applicative f) =>
(i -> a -> f Bool) -> t a -> f (t a)
forall (f :: * -> *) a.
Applicative f =>
(i -> a -> f Bool) -> t a -> f (t a)
ifilterA i -> a -> f Bool
f t a
xs
(<$?>) :: Filterable f => (a -> Maybe b) -> f a -> f b
<$?> :: forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
(<$?>) = (a -> Maybe b) -> f a -> f b
forall a b. (a -> Maybe b) -> f a -> f b
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe
infixl 4 <$?>
(<&?>) :: Filterable f => f a -> (a -> Maybe b) -> f b
f a
as <&?> :: forall (f :: * -> *) a b.
Filterable f =>
f a -> (a -> Maybe b) -> f b
<&?> a -> Maybe b
f = (a -> Maybe b) -> f a -> f b
forall a b. (a -> Maybe b) -> f a -> f b
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe a -> Maybe b
f f a
as
infixl 1 <&?>
forMaybe :: (Witherable t, Applicative f) => t a -> (a -> f (Maybe b)) -> f (t b)
forMaybe :: forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
t a -> (a -> f (Maybe b)) -> f (t b)
forMaybe = ((a -> f (Maybe b)) -> t a -> f (t b))
-> t a -> (a -> f (Maybe b)) -> f (t b)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (a -> f (Maybe b)) -> t a -> f (t b)
forall (t :: * -> *) (f :: * -> *) a b.
(Witherable t, Applicative f) =>
(a -> f (Maybe b)) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f (Maybe b)) -> t a -> f (t b)
wither
{-# INLINE forMaybe #-}
ordNub :: (Witherable t, Ord a) => t a -> t a
ordNub :: forall (t :: * -> *) a. (Witherable t, Ord a) => t a -> t a
ordNub = (a -> a) -> t a -> t a
forall (t :: * -> *) b a.
(Witherable t, Ord b) =>
(a -> b) -> t a -> t a
ordNubOn a -> a
forall a. a -> a
id
{-# INLINE ordNub #-}
ordNubOn :: (Witherable t, Ord b) => (a -> b) -> t a -> t a
ordNubOn :: forall (t :: * -> *) b a.
(Witherable t, Ord b) =>
(a -> b) -> t a -> t a
ordNubOn a -> b
p t a
t = State (Set b) (t a) -> Set b -> t a
forall s a. State s a -> s -> a
evalState ((a -> StateT (Set b) Identity (Maybe a))
-> t a -> State (Set b) (t a)
forall (t :: * -> *) (m :: * -> *) a b.
(Witherable t, Monad m) =>
(a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> t a -> m (t b)
witherM a -> StateT (Set b) Identity (Maybe a)
forall {m :: * -> *}. Monad m => a -> StateT (Set b) m (Maybe a)
f t a
t) Set b
forall a. Set a
Set.empty where
f :: a -> StateT (Set b) m (Maybe a)
f a
a = (Set b -> (Maybe a, Set b)) -> StateT (Set b) m (Maybe a)
forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
state ((Set b -> (Maybe a, Set b)) -> StateT (Set b) m (Maybe a))
-> (Set b -> (Maybe a, Set b)) -> StateT (Set b) m (Maybe a)
forall a b. (a -> b) -> a -> b
$ \Set b
s ->
#if MIN_VERSION_containers(0,6,3)
case (Bool -> BoolPair Bool) -> b -> Set b -> BoolPair (Set b)
forall a (f :: * -> *).
(Ord a, Functor f) =>
(Bool -> f Bool) -> a -> Set a -> f (Set a)
Set.alterF (\Bool
x -> Bool -> Bool -> BoolPair Bool
forall a. Bool -> a -> BoolPair a
BoolPair Bool
x Bool
True) (a -> b
p a
a) Set b
s of
BoolPair Bool
True Set b
s' -> (Maybe a
forall a. Maybe a
Nothing, Set b
s')
BoolPair Bool
False Set b
s' -> (a -> Maybe a
forall a. a -> Maybe a
Just a
a, Set b
s')
#else
if Set.member (p a) s
then (Nothing, s)
else (Just a, Set.insert (p a) s)
#endif
{-# INLINE ordNubOn #-}
hashNub :: (Witherable t, Eq a, Hashable a) => t a -> t a
hashNub :: forall (t :: * -> *) a.
(Witherable t, Eq a, Hashable a) =>
t a -> t a
hashNub = (a -> a) -> t a -> t a
forall (t :: * -> *) b a.
(Witherable t, Eq b, Hashable b) =>
(a -> b) -> t a -> t a
hashNubOn a -> a
forall a. a -> a
id
{-# INLINE hashNub #-}
hashNubOn :: (Witherable t, Eq b, Hashable b) => (a -> b) -> t a -> t a
hashNubOn :: forall (t :: * -> *) b a.
(Witherable t, Eq b, Hashable b) =>
(a -> b) -> t a -> t a
hashNubOn a -> b
p t a
t = State (HashSet b) (t a) -> HashSet b -> t a
forall s a. State s a -> s -> a
evalState ((a -> StateT (HashSet b) Identity (Maybe a))
-> t a -> State (HashSet b) (t a)
forall (t :: * -> *) (m :: * -> *) a b.
(Witherable t, Monad m) =>
(a -> m (Maybe b)) -> t a -> m (t b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> t a -> m (t b)
witherM a -> StateT (HashSet b) Identity (Maybe a)
forall {m :: * -> *}.
Monad m =>
a -> StateT (HashSet b) m (Maybe a)
f t a
t) HashSet b
forall a. HashSet a
HSet.empty
where
f :: a -> StateT (HashSet b) m (Maybe a)
f a
a = (HashSet b -> (Maybe a, HashSet b))
-> StateT (HashSet b) m (Maybe a)
forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
state ((HashSet b -> (Maybe a, HashSet b))
-> StateT (HashSet b) m (Maybe a))
-> (HashSet b -> (Maybe a, HashSet b))
-> StateT (HashSet b) m (Maybe a)
forall a b. (a -> b) -> a -> b
$ \HashSet b
s ->
let g :: Maybe a -> BoolPair (Maybe ())
g Maybe a
Nothing = Bool -> Maybe () -> BoolPair (Maybe ())
forall a. Bool -> a -> BoolPair a
BoolPair Bool
False (() -> Maybe ()
forall a. a -> Maybe a
Just ())
g (Just a
_) = Bool -> Maybe () -> BoolPair (Maybe ())
forall a. Bool -> a -> BoolPair a
BoolPair Bool
True (() -> Maybe ()
forall a. a -> Maybe a
Just ())
in case (Maybe () -> BoolPair (Maybe ()))
-> b -> HashMap b () -> BoolPair (HashMap b ())
forall (f :: * -> *) k v.
(Functor f, Eq k, Hashable k) =>
(Maybe v -> f (Maybe v)) -> k -> HashMap k v -> f (HashMap k v)
HM.alterF Maybe () -> BoolPair (Maybe ())
forall {a}. Maybe a -> BoolPair (Maybe ())
g (a -> b
p a
a) (HashSet b -> HashMap b ()
forall a. HashSet a -> HashMap a ()
HSet.toMap HashSet b
s) of
BoolPair Bool
True HashMap b ()
s' -> (Maybe a
forall a. Maybe a
Nothing, HashMap b () -> HashSet b
forall a. HashMap a () -> HashSet a
HSet.fromMap HashMap b ()
s')
BoolPair Bool
False HashMap b ()
s' -> (a -> Maybe a
forall a. a -> Maybe a
Just a
a, HashMap b () -> HashSet b
forall a. HashMap a () -> HashSet a
HSet.fromMap HashMap b ()
s')
{-# INLINE hashNubOn #-}
data BoolPair a = BoolPair !Bool a deriving (forall a b. (a -> b) -> BoolPair a -> BoolPair b)
-> (forall a b. a -> BoolPair b -> BoolPair a) -> Functor BoolPair
forall a b. a -> BoolPair b -> BoolPair a
forall a b. (a -> b) -> BoolPair a -> BoolPair b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> BoolPair a -> BoolPair b
fmap :: forall a b. (a -> b) -> BoolPair a -> BoolPair b
$c<$ :: forall a b. a -> BoolPair b -> BoolPair a
<$ :: forall a b. a -> BoolPair b -> BoolPair a
Functor
mapMaybeDefault :: (F.Foldable f, Alternative f) => (a -> Maybe b) -> f a -> f b
mapMaybeDefault :: forall (f :: * -> *) a b.
(Foldable f, Alternative f) =>
(a -> Maybe b) -> f a -> f b
mapMaybeDefault a -> Maybe b
p = (a -> f b -> f b) -> f b -> f a -> f b
forall a b. (a -> b -> b) -> b -> f a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr (\a
x f b
xs -> case a -> Maybe b
p a
x of
Just b
a -> b -> f b
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure b
a f b -> f b -> f b
forall a. f a -> f a -> f a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> f b
xs
Maybe b
_ -> f b
xs) f b
forall a. f a
forall (f :: * -> *) a. Alternative f => f a
empty
{-# INLINABLE mapMaybeDefault #-}
imapMaybeDefault :: (FoldableWithIndex i f, Alternative f) => (i -> a -> Maybe b) -> f a -> f b
imapMaybeDefault :: forall i (f :: * -> *) a b.
(FoldableWithIndex i f, Alternative f) =>
(i -> a -> Maybe b) -> f a -> f b
imapMaybeDefault i -> a -> Maybe b
p = (i -> a -> f b -> f b) -> f b -> f a -> f b
forall a b. (i -> a -> b -> b) -> b -> f a -> b
forall i (f :: * -> *) a b.
FoldableWithIndex i f =>
(i -> a -> b -> b) -> b -> f a -> b
ifoldr (\i
i a
x f b
xs -> case i -> a -> Maybe b
p i
i a
x of
Just b
a -> b -> f b
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure b
a f b -> f b -> f b
forall a. f a -> f a -> f a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> f b
xs
Maybe b
_ -> f b
xs) f b
forall a. f a
forall (f :: * -> *) a. Alternative f => f a
empty
{-# INLINABLE imapMaybeDefault #-}
newtype WrappedFoldable f a = WrapFilterable {forall (f :: * -> *) a. WrappedFoldable f a -> f a
unwrapFoldable :: f a}
deriving ((forall a b.
(a -> b) -> WrappedFoldable f a -> WrappedFoldable f b)
-> (forall a b. a -> WrappedFoldable f b -> WrappedFoldable f a)
-> Functor (WrappedFoldable f)
forall a b. a -> WrappedFoldable f b -> WrappedFoldable f a
forall a b. (a -> b) -> WrappedFoldable f a -> WrappedFoldable f b
forall (f :: * -> *) a b.
Functor f =>
a -> WrappedFoldable f b -> WrappedFoldable f a
forall (f :: * -> *) a b.
Functor f =>
(a -> b) -> WrappedFoldable f a -> WrappedFoldable f b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall (f :: * -> *) a b.
Functor f =>
(a -> b) -> WrappedFoldable f a -> WrappedFoldable f b
fmap :: forall a b. (a -> b) -> WrappedFoldable f a -> WrappedFoldable f b
$c<$ :: forall (f :: * -> *) a b.
Functor f =>
a -> WrappedFoldable f b -> WrappedFoldable f a
<$ :: forall a b. a -> WrappedFoldable f b -> WrappedFoldable f a
Functor, (forall m. Monoid m => WrappedFoldable f m -> m)
-> (forall m a. Monoid m => (a -> m) -> WrappedFoldable f a -> m)
-> (forall m a. Monoid m => (a -> m) -> WrappedFoldable f a -> m)
-> (forall a b. (a -> b -> b) -> b -> WrappedFoldable f a -> b)
-> (forall a b. (a -> b -> b) -> b -> WrappedFoldable f a -> b)
-> (forall b a. (b -> a -> b) -> b -> WrappedFoldable f a -> b)
-> (forall b a. (b -> a -> b) -> b -> WrappedFoldable f a -> b)
-> (forall a. (a -> a -> a) -> WrappedFoldable f a -> a)
-> (forall a. (a -> a -> a) -> WrappedFoldable f a -> a)
-> (forall a. WrappedFoldable f a -> [a])
-> (forall a. WrappedFoldable f a -> Bool)
-> (forall a. WrappedFoldable f a -> Int)
-> (forall a. Eq a => a -> WrappedFoldable f a -> Bool)
-> (forall a. Ord a => WrappedFoldable f a -> a)
-> (forall a. Ord a => WrappedFoldable f a -> a)
-> (forall a. Num a => WrappedFoldable f a -> a)
-> (forall a. Num a => WrappedFoldable f a -> a)
-> Foldable (WrappedFoldable f)
forall a. Eq a => a -> WrappedFoldable f a -> Bool
forall a. Num a => WrappedFoldable f a -> a
forall a. Ord a => WrappedFoldable f a -> a
forall m. Monoid m => WrappedFoldable f m -> m
forall a. WrappedFoldable f a -> Bool
forall a. WrappedFoldable f a -> Int
forall a. WrappedFoldable f a -> [a]
forall a. (a -> a -> a) -> WrappedFoldable f a -> a
forall m a. Monoid m => (a -> m) -> WrappedFoldable f a -> m
forall b a. (b -> a -> b) -> b -> WrappedFoldable f a -> b
forall a b. (a -> b -> b) -> b -> WrappedFoldable f a -> b
forall (f :: * -> *) a.
(Foldable f, Eq a) =>
a -> WrappedFoldable f a -> Bool
forall (f :: * -> *) a.
(Foldable f, Num a) =>
WrappedFoldable f a -> a
forall (f :: * -> *) a.
(Foldable f, Ord a) =>
WrappedFoldable f a -> a
forall (f :: * -> *) m.
(Foldable f, Monoid m) =>
WrappedFoldable f m -> m
forall (f :: * -> *) a. Foldable f => WrappedFoldable f a -> Bool
forall (f :: * -> *) a. Foldable f => WrappedFoldable f a -> Int
forall (f :: * -> *) a. Foldable f => WrappedFoldable f a -> [a]
forall (f :: * -> *) a.
Foldable f =>
(a -> a -> a) -> WrappedFoldable f a -> a
forall (f :: * -> *) m a.
(Foldable f, Monoid m) =>
(a -> m) -> WrappedFoldable f a -> m
forall (f :: * -> *) b a.
Foldable f =>
(b -> a -> b) -> b -> WrappedFoldable f a -> b
forall (f :: * -> *) a b.
Foldable f =>
(a -> b -> b) -> b -> WrappedFoldable f a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall (f :: * -> *) m.
(Foldable f, Monoid m) =>
WrappedFoldable f m -> m
fold :: forall m. Monoid m => WrappedFoldable f m -> m
$cfoldMap :: forall (f :: * -> *) m a.
(Foldable f, Monoid m) =>
(a -> m) -> WrappedFoldable f a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> WrappedFoldable f a -> m
$cfoldMap' :: forall (f :: * -> *) m a.
(Foldable f, Monoid m) =>
(a -> m) -> WrappedFoldable f a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> WrappedFoldable f a -> m
$cfoldr :: forall (f :: * -> *) a b.
Foldable f =>
(a -> b -> b) -> b -> WrappedFoldable f a -> b
foldr :: forall a b. (a -> b -> b) -> b -> WrappedFoldable f a -> b
$cfoldr' :: forall (f :: * -> *) a b.
Foldable f =>
(a -> b -> b) -> b -> WrappedFoldable f a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> WrappedFoldable f a -> b
$cfoldl :: forall (f :: * -> *) b a.
Foldable f =>
(b -> a -> b) -> b -> WrappedFoldable f a -> b
foldl :: forall b a. (b -> a -> b) -> b -> WrappedFoldable f a -> b
$cfoldl' :: forall (f :: * -> *) b a.
Foldable f =>
(b -> a -> b) -> b -> WrappedFoldable f a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> WrappedFoldable f a -> b
$cfoldr1 :: forall (f :: * -> *) a.
Foldable f =>
(a -> a -> a) -> WrappedFoldable f a -> a
foldr1 :: forall a. (a -> a -> a) -> WrappedFoldable f a -> a
$cfoldl1 :: forall (f :: * -> *) a.
Foldable f =>
(a -> a -> a) -> WrappedFoldable f a -> a
foldl1 :: forall a. (a -> a -> a) -> WrappedFoldable f a -> a
$ctoList :: forall (f :: * -> *) a. Foldable f => WrappedFoldable f a -> [a]
toList :: forall a. WrappedFoldable f a -> [a]
$cnull :: forall (f :: * -> *) a. Foldable f => WrappedFoldable f a -> Bool
null :: forall a. WrappedFoldable f a -> Bool
$clength :: forall (f :: * -> *) a. Foldable f => WrappedFoldable f a -> Int
length :: forall a. WrappedFoldable f a -> Int
$celem :: forall (f :: * -> *) a.
(Foldable f, Eq a) =>
a -> WrappedFoldable f a -> Bool
elem :: forall a. Eq a => a -> WrappedFoldable f a -> Bool
$cmaximum :: forall (f :: * -> *) a.
(Foldable f, Ord a) =>
WrappedFoldable f a -> a
maximum :: forall a. Ord a => WrappedFoldable f a -> a
$cminimum :: forall (f :: * -> *) a.
(Foldable f, Ord a) =>
WrappedFoldable f a -> a
minimum :: forall a. Ord a => WrappedFoldable f a -> a
$csum :: forall (f :: * -> *) a.
(Foldable f, Num a) =>
WrappedFoldable f a -> a
sum :: forall a. Num a => WrappedFoldable f a -> a
$cproduct :: forall (f :: * -> *) a.
(Foldable f, Num a) =>
WrappedFoldable f a -> a
product :: forall a. Num a => WrappedFoldable f a -> a
F.Foldable, Functor (WrappedFoldable f)
Foldable (WrappedFoldable f)
(Functor (WrappedFoldable f), Foldable (WrappedFoldable f)) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> WrappedFoldable f a -> f (WrappedFoldable f b))
-> (forall (f :: * -> *) a.
Applicative f =>
WrappedFoldable f (f a) -> f (WrappedFoldable f a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> WrappedFoldable f a -> m (WrappedFoldable f b))
-> (forall (m :: * -> *) a.
Monad m =>
WrappedFoldable f (m a) -> m (WrappedFoldable f a))
-> Traversable (WrappedFoldable f)
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (f :: * -> *). Traversable f => Functor (WrappedFoldable f)
forall (f :: * -> *). Traversable f => Foldable (WrappedFoldable f)
forall (f :: * -> *) (m :: * -> *) a.
(Traversable f, Monad m) =>
WrappedFoldable f (m a) -> m (WrappedFoldable f a)
forall (f :: * -> *) (f :: * -> *) a.
(Traversable f, Applicative f) =>
WrappedFoldable f (f a) -> f (WrappedFoldable f a)
forall (f :: * -> *) (m :: * -> *) a b.
(Traversable f, Monad m) =>
(a -> m b) -> WrappedFoldable f a -> m (WrappedFoldable f b)
forall (f :: * -> *) (f :: * -> *) a b.
(Traversable f, Applicative f) =>
(a -> f b) -> WrappedFoldable f a -> f (WrappedFoldable f b)
forall (m :: * -> *) a.
Monad m =>
WrappedFoldable f (m a) -> m (WrappedFoldable f a)
forall (f :: * -> *) a.
Applicative f =>
WrappedFoldable f (f a) -> f (WrappedFoldable f a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> WrappedFoldable f a -> m (WrappedFoldable f b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> WrappedFoldable f a -> f (WrappedFoldable f b)
$ctraverse :: forall (f :: * -> *) (f :: * -> *) a b.
(Traversable f, Applicative f) =>
(a -> f b) -> WrappedFoldable f a -> f (WrappedFoldable f b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> WrappedFoldable f a -> f (WrappedFoldable f b)
$csequenceA :: forall (f :: * -> *) (f :: * -> *) a.
(Traversable f, Applicative f) =>
WrappedFoldable f (f a) -> f (WrappedFoldable f a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
WrappedFoldable f (f a) -> f (WrappedFoldable f a)
$cmapM :: forall (f :: * -> *) (m :: * -> *) a b.
(Traversable f, Monad m) =>
(a -> m b) -> WrappedFoldable f a -> m (WrappedFoldable f b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> WrappedFoldable f a -> m (WrappedFoldable f b)
$csequence :: forall (f :: * -> *) (m :: * -> *) a.
(Traversable f, Monad m) =>
WrappedFoldable f (m a) -> m (WrappedFoldable f a)
sequence :: forall (m :: * -> *) a.
Monad m =>
WrappedFoldable f (m a) -> m (WrappedFoldable f a)
T.Traversable, Functor (WrappedFoldable f)
Functor (WrappedFoldable f) =>
(forall a. a -> WrappedFoldable f a)
-> (forall a b.
WrappedFoldable f (a -> b)
-> WrappedFoldable f a -> WrappedFoldable f b)
-> (forall a b c.
(a -> b -> c)
-> WrappedFoldable f a
-> WrappedFoldable f b
-> WrappedFoldable f c)
-> (forall a b.
WrappedFoldable f a -> WrappedFoldable f b -> WrappedFoldable f b)
-> (forall a b.
WrappedFoldable f a -> WrappedFoldable f b -> WrappedFoldable f a)
-> Applicative (WrappedFoldable f)
forall a. a -> WrappedFoldable f a
forall a b.
WrappedFoldable f a -> WrappedFoldable f b -> WrappedFoldable f a
forall a b.
WrappedFoldable f a -> WrappedFoldable f b -> WrappedFoldable f b
forall a b.
WrappedFoldable f (a -> b)
-> WrappedFoldable f a -> WrappedFoldable f b
forall a b c.
(a -> b -> c)
-> WrappedFoldable f a
-> WrappedFoldable f b
-> WrappedFoldable f c
forall (f :: * -> *).
Functor f =>
(forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
forall (f :: * -> *). Applicative f => Functor (WrappedFoldable f)
forall (f :: * -> *) a. Applicative f => a -> WrappedFoldable f a
forall (f :: * -> *) a b.
Applicative f =>
WrappedFoldable f a -> WrappedFoldable f b -> WrappedFoldable f a
forall (f :: * -> *) a b.
Applicative f =>
WrappedFoldable f a -> WrappedFoldable f b -> WrappedFoldable f b
forall (f :: * -> *) a b.
Applicative f =>
WrappedFoldable f (a -> b)
-> WrappedFoldable f a -> WrappedFoldable f b
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c)
-> WrappedFoldable f a
-> WrappedFoldable f b
-> WrappedFoldable f c
$cpure :: forall (f :: * -> *) a. Applicative f => a -> WrappedFoldable f a
pure :: forall a. a -> WrappedFoldable f a
$c<*> :: forall (f :: * -> *) a b.
Applicative f =>
WrappedFoldable f (a -> b)
-> WrappedFoldable f a -> WrappedFoldable f b
<*> :: forall a b.
WrappedFoldable f (a -> b)
-> WrappedFoldable f a -> WrappedFoldable f b
$cliftA2 :: forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c)
-> WrappedFoldable f a
-> WrappedFoldable f b
-> WrappedFoldable f c
liftA2 :: forall a b c.
(a -> b -> c)
-> WrappedFoldable f a
-> WrappedFoldable f b
-> WrappedFoldable f c
$c*> :: forall (f :: * -> *) a b.
Applicative f =>
WrappedFoldable f a -> WrappedFoldable f b -> WrappedFoldable f b
*> :: forall a b.
WrappedFoldable f a -> WrappedFoldable f b -> WrappedFoldable f b
$c<* :: forall (f :: * -> *) a b.
Applicative f =>
WrappedFoldable f a -> WrappedFoldable f b -> WrappedFoldable f a
<* :: forall a b.
WrappedFoldable f a -> WrappedFoldable f b -> WrappedFoldable f a
Applicative, Applicative (WrappedFoldable f)
Applicative (WrappedFoldable f) =>
(forall a. WrappedFoldable f a)
-> (forall a.
WrappedFoldable f a -> WrappedFoldable f a -> WrappedFoldable f a)
-> (forall a. WrappedFoldable f a -> WrappedFoldable f [a])
-> (forall a. WrappedFoldable f a -> WrappedFoldable f [a])
-> Alternative (WrappedFoldable f)
forall a. WrappedFoldable f a
forall a. WrappedFoldable f a -> WrappedFoldable f [a]
forall a.
WrappedFoldable f a -> WrappedFoldable f a -> WrappedFoldable f a
forall (f :: * -> *).
Applicative f =>
(forall a. f a)
-> (forall a. f a -> f a -> f a)
-> (forall a. f a -> f [a])
-> (forall a. f a -> f [a])
-> Alternative f
forall (f :: * -> *).
Alternative f =>
Applicative (WrappedFoldable f)
forall (f :: * -> *) a. Alternative f => WrappedFoldable f a
forall (f :: * -> *) a.
Alternative f =>
WrappedFoldable f a -> WrappedFoldable f [a]
forall (f :: * -> *) a.
Alternative f =>
WrappedFoldable f a -> WrappedFoldable f a -> WrappedFoldable f a
$cempty :: forall (f :: * -> *) a. Alternative f => WrappedFoldable f a
empty :: forall a. WrappedFoldable f a
$c<|> :: forall (f :: * -> *) a.
Alternative f =>
WrappedFoldable f a -> WrappedFoldable f a -> WrappedFoldable f a
<|> :: forall a.
WrappedFoldable f a -> WrappedFoldable f a -> WrappedFoldable f a
$csome :: forall (f :: * -> *) a.
Alternative f =>
WrappedFoldable f a -> WrappedFoldable f [a]
some :: forall a. WrappedFoldable f a -> WrappedFoldable f [a]
$cmany :: forall (f :: * -> *) a.
Alternative f =>
WrappedFoldable f a -> WrappedFoldable f [a]
many :: forall a. WrappedFoldable f a -> WrappedFoldable f [a]
Alternative)
instance (FunctorWithIndex i f) => FunctorWithIndex i (WrappedFoldable f) where
imap :: forall a b.
(i -> a -> b) -> WrappedFoldable f a -> WrappedFoldable f b
imap i -> a -> b
f = f b -> WrappedFoldable f b
forall (f :: * -> *) a. f a -> WrappedFoldable f a
WrapFilterable (f b -> WrappedFoldable f b)
-> (WrappedFoldable f a -> f b)
-> WrappedFoldable f a
-> WrappedFoldable f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (i -> a -> b) -> f a -> f b
forall a b. (i -> a -> b) -> f a -> f b
forall i (f :: * -> *) a b.
FunctorWithIndex i f =>
(i -> a -> b) -> f a -> f b
imap i -> a -> b
f (f a -> f b)
-> (WrappedFoldable f a -> f a) -> WrappedFoldable f a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrappedFoldable f a -> f a
forall (f :: * -> *) a. WrappedFoldable f a -> f a
unwrapFoldable
instance (FoldableWithIndex i f) => FoldableWithIndex i (WrappedFoldable f) where
ifoldMap :: forall m a. Monoid m => (i -> a -> m) -> WrappedFoldable f a -> m
ifoldMap i -> a -> m
f = (i -> a -> m) -> f a -> m
forall m a. Monoid m => (i -> a -> m) -> f a -> m
forall i (f :: * -> *) m a.
(FoldableWithIndex i f, Monoid m) =>
(i -> a -> m) -> f a -> m
ifoldMap i -> a -> m
f (f a -> m)
-> (WrappedFoldable f a -> f a) -> WrappedFoldable f a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrappedFoldable f a -> f a
forall (f :: * -> *) a. WrappedFoldable f a -> f a
unwrapFoldable
instance (TraversableWithIndex i f) => TraversableWithIndex i (WrappedFoldable f) where
itraverse :: forall (f :: * -> *) a b.
Applicative f =>
(i -> a -> f b) -> WrappedFoldable f a -> f (WrappedFoldable f b)
itraverse i -> a -> f b
f = (f b -> WrappedFoldable f b) -> f (f b) -> f (WrappedFoldable f b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f b -> WrappedFoldable f b
forall (f :: * -> *) a. f a -> WrappedFoldable f a
WrapFilterable (f (f b) -> f (WrappedFoldable f b))
-> (WrappedFoldable f a -> f (f b))
-> WrappedFoldable f a
-> f (WrappedFoldable f b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (i -> a -> f b) -> f a -> f (f b)
forall i (t :: * -> *) (f :: * -> *) a b.
(TraversableWithIndex i t, Applicative f) =>
(i -> a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(i -> a -> f b) -> f a -> f (f b)
itraverse i -> a -> f b
f (f a -> f (f b))
-> (WrappedFoldable f a -> f a) -> WrappedFoldable f a -> f (f b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrappedFoldable f a -> f a
forall (f :: * -> *) a. WrappedFoldable f a -> f a
unwrapFoldable
instance (F.Foldable f, Alternative f) => Filterable (WrappedFoldable f) where
{-#INLINE mapMaybe#-}
mapMaybe :: forall a b.
(a -> Maybe b) -> WrappedFoldable f a -> WrappedFoldable f b
mapMaybe = (a -> Maybe b) -> WrappedFoldable f a -> WrappedFoldable f b
forall (f :: * -> *) a b.
(Foldable f, Alternative f) =>
(a -> Maybe b) -> f a -> f b
mapMaybeDefault
instance (FunctorWithIndex i f, FoldableWithIndex i f, Alternative f) => FilterableWithIndex i (WrappedFoldable f) where
{-# INLINE imapMaybe #-}
imapMaybe :: forall a b.
(i -> a -> Maybe b) -> WrappedFoldable f a -> WrappedFoldable f b
imapMaybe = (i -> a -> Maybe b) -> WrappedFoldable f a -> WrappedFoldable f b
forall i (f :: * -> *) a b.
(FoldableWithIndex i f, Alternative f) =>
(i -> a -> Maybe b) -> f a -> f b
imapMaybeDefault
instance (Alternative f, T.Traversable f) => Witherable (WrappedFoldable f)