filtrable-0.1.4.0: Class of filtrable containers
Safe HaskellSafe
LanguageHaskell2010

Data.Filtrable

Synopsis

Documentation

class Functor f => Filtrable f where Source #

Class of filtrable containers, i.e. containers we can map over while selectively dropping elements.

Laws:

Laws if Foldable f:

Minimal complete definition

mapMaybe | catMaybes

Methods

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

Map the container with the given function, dropping the elements for which it returns Nothing.

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

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

Drop the elements for which the given predicate is False.

mapMaybeA :: (Traversable f, Applicative p) => (a -> p (Maybe b)) -> f a -> p (f b) Source #

Traverse the container with the given function, dropping the elements for which it returns Nothing.

filterA :: (Traversable f, Applicative p) => (a -> p Bool) -> f a -> p (f a) Source #

Drop the elements for which the given predicate is False.

mapEither :: (a -> Either b c) -> f a -> (f b, f c) Source #

Map the container with the given function, collecting the Lefts and the Rights separately.

mapEitherA :: (Traversable f, Applicative p) => (a -> p (Either b c)) -> f a -> p (f b, f c) Source #

Traverse the container with the given function, collecting the Lefts and the Rights separately.

partitionEithers :: f (Either a b) -> (f a, f b) Source #

Instances

Instances details
Filtrable [] Source # 
Instance details

Defined in Data.Filtrable

Methods

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

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

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

mapMaybeA :: (Traversable [], Applicative p) => (a -> p (Maybe b)) -> [a] -> p [b] Source #

filterA :: (Traversable [], Applicative p) => (a -> p Bool) -> [a] -> p [a] Source #

mapEither :: (a -> Either b c) -> [a] -> ([b], [c]) Source #

mapEitherA :: (Traversable [], Applicative p) => (a -> p (Either b c)) -> [a] -> p ([b], [c]) Source #

partitionEithers :: [Either a b] -> ([a], [b]) Source #

Filtrable Maybe Source # 
Instance details

Defined in Data.Filtrable

Methods

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

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

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

mapMaybeA :: (Traversable Maybe, Applicative p) => (a -> p (Maybe b)) -> Maybe a -> p (Maybe b) Source #

filterA :: (Traversable Maybe, Applicative p) => (a -> p Bool) -> Maybe a -> p (Maybe a) Source #

mapEither :: (a -> Either b c) -> Maybe a -> (Maybe b, Maybe c) Source #

mapEitherA :: (Traversable Maybe, Applicative p) => (a -> p (Either b c)) -> Maybe a -> p (Maybe b, Maybe c) Source #

partitionEithers :: Maybe (Either a b) -> (Maybe a, Maybe b) Source #

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

Defined in Data.Filtrable

Methods

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

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

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

mapMaybeA :: (Traversable Proxy, Applicative p) => (a -> p (Maybe b)) -> Proxy a -> p (Proxy b) Source #

filterA :: (Traversable Proxy, Applicative p) => (a -> p Bool) -> Proxy a -> p (Proxy a) Source #

mapEither :: (a -> Either b c) -> Proxy a -> (Proxy b, Proxy c) Source #

mapEitherA :: (Traversable Proxy, Applicative p) => (a -> p (Either b c)) -> Proxy a -> p (Proxy b, Proxy c) Source #

partitionEithers :: Proxy (Either a b) -> (Proxy a, Proxy b) Source #

Filtrable (Const a :: Type -> Type) Source # 
Instance details

Defined in Data.Filtrable

Methods

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

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

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

mapMaybeA :: (Traversable (Const a), Applicative p) => (a0 -> p (Maybe b)) -> Const a a0 -> p (Const a b) Source #

filterA :: (Traversable (Const a), Applicative p) => (a0 -> p Bool) -> Const a a0 -> p (Const a a0) Source #

mapEither :: (a0 -> Either b c) -> Const a a0 -> (Const a b, Const a c) Source #

mapEitherA :: (Traversable (Const a), Applicative p) => (a0 -> p (Either b c)) -> Const a a0 -> p (Const a b, Const a c) Source #

partitionEithers :: Const a (Either a0 b) -> (Const a a0, Const a b) Source #

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

Defined in Data.Filtrable

Methods

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

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

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

mapMaybeA :: (Traversable (Product f g), Applicative p) => (a -> p (Maybe b)) -> Product f g a -> p (Product f g b) Source #

filterA :: (Traversable (Product f g), Applicative p) => (a -> p Bool) -> Product f g a -> p (Product f g a) Source #

mapEither :: (a -> Either b c) -> Product f g a -> (Product f g b, Product f g c) Source #

mapEitherA :: (Traversable (Product f g), Applicative p) => (a -> p (Either b c)) -> Product f g a -> p (Product f g b, Product f g c) Source #

partitionEithers :: Product f g (Either a b) -> (Product f g a, Product f g b) Source #

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

Defined in Data.Filtrable

Methods

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

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

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

mapMaybeA :: (Traversable (Sum f g), Applicative p) => (a -> p (Maybe b)) -> Sum f g a -> p (Sum f g b) Source #

filterA :: (Traversable (Sum f g), Applicative p) => (a -> p Bool) -> Sum f g a -> p (Sum f g a) Source #

mapEither :: (a -> Either b c) -> Sum f g a -> (Sum f g b, Sum f g c) Source #

mapEitherA :: (Traversable (Sum f g), Applicative p) => (a -> p (Either b c)) -> Sum f g a -> p (Sum f g b, Sum f g c) Source #

partitionEithers :: Sum f g (Either a b) -> (Sum f g a, Sum f g b) Source #

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

Defined in Data.Filtrable

Methods

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

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

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

mapMaybeA :: (Traversable (Compose f g), Applicative p) => (a -> p (Maybe b)) -> Compose f g a -> p (Compose f g b) Source #

filterA :: (Traversable (Compose f g), Applicative p) => (a -> p Bool) -> Compose f g a -> p (Compose f g a) Source #

mapEither :: (a -> Either b c) -> Compose f g a -> (Compose f g b, Compose f g c) Source #

mapEitherA :: (Traversable (Compose f g), Applicative p) => (a -> p (Either b c)) -> Compose f g a -> p (Compose f g b, Compose f g c) Source #

partitionEithers :: Compose f g (Either a b) -> (Compose f g a, Compose f g b) Source #

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

(<*?>) :: (Applicative p, Filtrable p) => p (a -> Maybe b) -> p a -> p b infixl 4 Source #

nub :: (Filtrable f, Traversable f, Eq a) => f a -> f a Source #

\(\mathcal{O}(n^2)\) Delete all but the first copy of each element, special case of nubBy.

nubBy :: (Filtrable f, Traversable f) => (a -> a -> Bool) -> f a -> f a Source #

\(\mathcal{O}(n^2)\) Delete all but the first copy of each element, with the given relation.

nubOrd :: (Filtrable f, Traversable f, Ord a) => f a -> f a Source #

\(\mathcal{O}(n^2)\) Delete all but the first copy of each element, special case of nubOrdBy.

nubOrdBy :: (Filtrable f, Traversable f) => (a -> a -> Ordering) -> f a -> f a Source #

\(\mathcal{O}(n^2)\) Delete all but the first copy of each element, with the given relation.