Copyright | (c) Fumiaki Kinoshita 2015 |
---|---|
License | BSD3 |
Maintainer | Fumiaki Kinoshita <fumiexcel@gmail.com> |
Stability | provisional |
Portability | non-portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Synopsis
- class Functor f => Filterable f where
- (<$?>) :: Filterable f => (a -> Maybe b) -> f a -> f b
- (<&?>) :: Filterable f => f a -> (a -> Maybe b) -> f b
- class (Traversable t, Filterable t) => Witherable t where
- wither :: Applicative f => (a -> f (Maybe b)) -> t a -> f (t b)
- witherM :: Monad m => (a -> m (Maybe b)) -> t a -> m (t b)
- filterA :: Applicative f => (a -> f Bool) -> t a -> f (t a)
- ordNub :: (Witherable t, Ord a) => t a -> t a
- hashNub :: (Witherable t, Eq a, Hashable a) => t a -> t a
- forMaybe :: (Witherable t, Applicative f) => t a -> (a -> f (Maybe b)) -> f (t b)
- type FilterLike f s t a b = (a -> f (Maybe b)) -> s -> f t
- type Filter s t a b = forall f. Applicative f => FilterLike f s t a b
- type FilterLike' f s a = FilterLike f s s a a
- type Filter' s a = forall f. Applicative f => FilterLike' f s a
- witherOf :: FilterLike f s t a b -> (a -> f (Maybe b)) -> s -> f t
- forMaybeOf :: FilterLike f s t a b -> s -> (a -> f (Maybe b)) -> f t
- mapMaybeOf :: FilterLike Identity s t a b -> (a -> Maybe b) -> s -> t
- catMaybesOf :: FilterLike Identity s t (Maybe a) a -> s -> t
- filterAOf :: Functor f => FilterLike' f s a -> (a -> f Bool) -> s -> f s
- filterOf :: FilterLike' Identity s a -> (a -> Bool) -> s -> s
- ordNubOf :: Ord a => FilterLike' (State (Set a)) s a -> s -> s
- hashNubOf :: (Eq a, Hashable a) => FilterLike' (State (HashSet a)) s a -> s -> s
- cloneFilter :: FilterLike (Peat a b) s t a b -> Filter s t a b
- newtype Peat a b t = Peat {
- runPeat :: forall f. Applicative f => (a -> f (Maybe b)) -> f t
Documentation
class Functor f => Filterable f where Source #
Like Functor
, but you can remove elements instead of updating them.
Formally, the class Filterable
represents a functor from Kleisli Maybe
to Hask
.
A definition of mapMaybe
must satisfy the following laws:
mapMaybe :: (a -> Maybe b) -> f a -> f b Source #
Like mapMaybe
.
catMaybes :: f (Maybe a) -> f a Source #
filter :: (a -> Bool) -> f a -> f a Source #
Filterable
f .Filterable
g ≡ filter (liftA2
(&&
) f g)
Instances
Filterable [] Source # | |
Filterable Maybe Source # | |
Filterable IntMap Source # | |
Filterable Seq Source # | |
Filterable Vector Source # | |
Monoid e => Filterable (Either e) Source # | |
Filterable (Proxy :: Type -> Type) Source # | |
Filterable (Map k) Source # | |
Functor f => Filterable (MaybeT f) Source # | |
(Eq k, Hashable k) => Filterable (HashMap k) Source # | |
Filterable (Const r :: Type -> Type) Source # | |
Filterable f => Filterable (IdentityT f) Source # | |
(Filterable f, Filterable g) => Filterable (Product f g) Source # | |
(Filterable f, Filterable g) => Filterable (Sum f g) Source # | |
(Functor f, Filterable g) => Filterable (Compose f g) Source # | |
(<$?>) :: Filterable f => (a -> Maybe b) -> f a -> f b infixl 4 Source #
(<&?>) :: Filterable f => f a -> (a -> Maybe b) -> f b infixl 1 Source #
class (Traversable t, Filterable t) => Witherable t where Source #
An enhancement of Traversable
with Filterable
A definition of wither
must satisfy the following laws:
- conservation
wither
(fmap
Just
. f) ≡traverse
f- composition
Compose
.fmap
(wither
f) .wither
g ≡wither
(Compose
.fmap
(wither
f) . g)
Parametricity implies the naturality law:
t .wither
f ≡wither
(t . f)
Nothing
wither :: Applicative f => (a -> f (Maybe b)) -> t a -> f (t b) Source #
witherM :: Monad m => (a -> m (Maybe b)) -> t a -> m (t b) Source #
Monadic variant of wither
. This may have more efficient implementation.
filterA :: Applicative f => (a -> f Bool) -> t a -> f (t a) Source #
Instances
Witherable [] Source # | |
Witherable Maybe Source # | |
Witherable IntMap Source # | |
Witherable Seq Source # | |
Witherable Vector Source # | |
Monoid e => Witherable (Either e) Source # | |
Witherable (Proxy :: Type -> Type) Source # | |
Witherable (Map k) Source # | |
Traversable t => Witherable (MaybeT t) Source # | |
(Eq k, Hashable k) => Witherable (HashMap k) Source # | |
Witherable (Const r :: Type -> Type) Source # | |
Witherable f => Witherable (IdentityT f) Source # | |
Defined in Data.Witherable | |
(Witherable f, Witherable g) => Witherable (Product f g) Source # | |
Defined in Data.Witherable | |
(Witherable f, Witherable g) => Witherable (Sum f g) Source # | |
(Traversable f, Witherable g) => Witherable (Compose f g) Source # | |
Defined in Data.Witherable |
ordNub :: (Witherable t, Ord a) => t a -> t a Source #
forMaybe :: (Witherable t, Applicative f) => t a -> (a -> f (Maybe b)) -> f (t b) Source #
Generalization
type FilterLike f s t a b = (a -> f (Maybe b)) -> s -> f t Source #
This type allows combinators to take a Filter
specializing the parameter f
.
type Filter s t a b = forall f. Applicative f => FilterLike f s t a b Source #
type FilterLike' f s a = FilterLike f s s a a Source #
A simple FilterLike
.
type Filter' s a = forall f. Applicative f => FilterLike' f s a Source #
A simple Filter
.
witherOf :: FilterLike f s t a b -> (a -> f (Maybe b)) -> s -> f t Source #
forMaybeOf :: FilterLike f s t a b -> s -> (a -> f (Maybe b)) -> f t Source #
mapMaybeOf :: FilterLike Identity s t a b -> (a -> Maybe b) -> s -> t Source #
mapMaybe
through a filter.
catMaybesOf :: FilterLike Identity s t (Maybe a) a -> s -> t Source #
catMaybes
through a filter.
filterAOf :: Functor f => FilterLike' f s a -> (a -> f Bool) -> s -> f s Source #
filterA
through a filter.
filterOf :: FilterLike' Identity s a -> (a -> Bool) -> s -> s Source #
Filter each element of a structure targeted by a Filter
.
ordNubOf :: Ord a => FilterLike' (State (Set a)) s a -> s -> s Source #
Remove the duplicate elements through a filter.
hashNubOf :: (Eq a, Hashable a) => FilterLike' (State (HashSet a)) s a -> s -> s Source #
Remove the duplicate elements through a filter.
It is often faster than ordNubOf
, especially when the comparison is expensive.
Cloning
cloneFilter :: FilterLike (Peat a b) s t a b -> Filter s t a b Source #
Reconstitute a Filter
from its monomorphic form.