Copyright | (c) Fumiaki Kinoshita 2015 |
---|---|
License | BSD3 |
Maintainer | Fumiaki Kinoshita <fumiexcel@gmail.com> |
Stability | provisional |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- class Functor f => Filterable (f :: Type -> Type) 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 :: Type -> Type) 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)
- class (FunctorWithIndex i t, Filterable t) => FilterableWithIndex i t | t -> i where
- class (TraversableWithIndex i t, Witherable t) => WitherableWithIndex i t | t -> i where
- iwither :: Applicative f => (i -> a -> f (Maybe b)) -> t a -> f (t b)
- iwitherM :: Monad m => (i -> a -> m (Maybe b)) -> t a -> m (t b)
- ifilterA :: Applicative f => (i -> a -> f Bool) -> t a -> f (t a)
- type WitherLike f s t a b = (a -> f (Maybe b)) -> s -> f t
- type Wither s t a b = forall f. Applicative f => WitherLike f s t a b
- type WitherLike' f s a = WitherLike f s s a a
- type Wither' s a = forall f. Applicative f => WitherLike' f s a
- type FilterLike f s t a b = WitherLike f s t a b
- type Filter s t a b = Wither s t a b
- type FilterLike' f s a = WitherLike' f s a
- type Filter' s a = Wither' 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
- newtype WrappedFoldable f a = WrapFilterable {
- unwrapFoldable :: f a
Documentation
class Functor f => Filterable (f :: Type -> Type) where #
Like Functor
, but you can remove elements instead of updating them.
Formally, the class Filterable
represents a functor from Kleisli Maybe
to Hask
.
A definition of mapMaybe
must satisfy the following laws:
Instances
(<$?>) :: 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 :: Type -> Type) where #
An enhancement of Traversable
with Filterable
A definition of wither
must satisfy the following laws:
- conservation
wither
(fmap
Just
. f) ≡traverse
f- composition
Compose
.fmap
(wither
f) .wither
g ≡wither
(Compose
.fmap
(wither
f) . g)
Parametricity implies the naturality law:
t .wither
f ≡wither
(t . f)
Nothing
wither :: Applicative f => (a -> f (Maybe b)) -> t a -> f (t b) #
witherM :: Monad m => (a -> m (Maybe b)) -> t a -> m (t b) #
Monadic variant of wither
. This may have more efficient implementation.
filterA :: Applicative f => (a -> f Bool) -> t a -> f (t a) #
Instances
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 #
Indexed variants
class (FunctorWithIndex i t, Filterable t) => FilterableWithIndex i t | t -> i where Source #
Indexed variant of Filterable
.
Nothing
Instances
class (TraversableWithIndex i t, Witherable t) => WitherableWithIndex i t | t -> i where Source #
Indexed variant of Witherable
.
Nothing
iwither :: Applicative f => (i -> a -> f (Maybe b)) -> t a -> f (t b) Source #
iwitherM :: Monad m => (i -> a -> m (Maybe b)) -> t a -> m (t b) Source #
Monadic variant of wither
. This may have more efficient implementation.
ifilterA :: Applicative f => (i -> a -> f Bool) -> t a -> f (t a) Source #
Instances
Generalization
type WitherLike 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 Wither s t a b = forall f. Applicative f => WitherLike f s t a b Source #
type WitherLike' f s a = WitherLike f s s a a Source #
A simple WitherLike
.
type Wither' s a = forall f. Applicative f => WitherLike' f s a Source #
A simple Wither
.
type FilterLike f s t a b = WitherLike f s t a b Source #
Deprecated: Use WitherLike instead
type FilterLike' f s a = WitherLike' f s a Source #
Deprecated: Use WitherLike' instead
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.
This is used to characterize and clone a Filter
.
Since FilterLike (Peat a b) s t a b
is monomorphic, it can be used to store a filter in a container.
Peat | |
|
Wrapper
newtype WrappedFoldable f a Source #
WrapFilterable | |
|
Instances
Orphan instances
Filterable (MonoidalMap k) Source # | |
mapMaybe :: (a -> Maybe b) -> MonoidalMap k a -> MonoidalMap k b # catMaybes :: MonoidalMap k (Maybe a) -> MonoidalMap k a # filter :: (a -> Bool) -> MonoidalMap k a -> MonoidalMap k a # | |
Witherable (MonoidalMap k) Source # | |
wither :: Applicative f => (a -> f (Maybe b)) -> MonoidalMap k a -> f (MonoidalMap k b) # witherM :: Monad m => (a -> m (Maybe b)) -> MonoidalMap k a -> m (MonoidalMap k b) # filterA :: Applicative f => (a -> f Bool) -> MonoidalMap k a -> f (MonoidalMap k a) # |