| Copyright | (c) Fumiaki Kinoshita 2015 |
|---|---|
| License | BSD3 |
| Maintainer | Fumiaki Kinoshita <fumiexcel@gmail.com> |
| Stability | provisional |
| Portability | non-portable |
| Safe Haskell | Trustworthy |
| Language | Haskell2010 |
Data.Witherable
Description
- class Traversable t => Witherable t where
- ordNub :: (Witherable t, Ord a) => t a -> t a
- hashNub :: (Witherable t, Eq a, Hashable a) => t a -> t a
- 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
- 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 (Dungeon a b) s t a b -> Filter s t a b
- newtype Dungeon a b t = Dungeon {
- runDungeon :: forall f. Applicative f => (a -> f (Maybe b)) -> f t
- newtype Chipped t a = Chipped {
- getChipped :: t (Maybe a)
Documentation
class Traversable t => Witherable t where Source
Like traverse, but you can remove elements instead of updating them.
traversef ≡wither(fmapJust. f)
A definition of wither must satisfy the following laws:
- identity
wither(pure. Just) ≡pure- composition
Compose . fmap (witherf) .witherg ≡wither(Compose . fmap (witherf) . g)
Parametricity implies the naturality law:
t .witherf =wither(t . f)
Methods
wither :: Applicative f => (a -> f (Maybe b)) -> t a -> f (t b) Source
mapMaybe :: (a -> Maybe b) -> t a -> t b Source
catMaybes :: t (Maybe a) -> t a Source
filterA :: Applicative f => (a -> f Bool) -> t a -> f (t a) Source
Instances
| Witherable [] | |
| Witherable Maybe | |
| Witherable IntMap | |
| Witherable Seq | |
| Witherable Vector | |
| Monoid e => Witherable (Either e) | |
| Witherable (Const r) | |
| Witherable (Proxy *) | |
| Ord k => Witherable (Map k) | |
| (Eq k, Hashable k) => Witherable (HashMap k) | |
| Traversable t => Witherable (Chipped t) |
ordNub :: (Witherable t, Ord a) => t a -> t a Source
hashNub :: (Witherable t, Eq a, Hashable a) => t a -> t a Source
Generalization
type FilterLike f s t a b = (a -> f (Maybe b)) -> s -> f t Source
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
type Filter' s a = forall f. Applicative f => FilterLike' f s a Source
witherOf :: FilterLike f s t a b -> (a -> f (Maybe b)) -> s -> 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
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 (Dungeon a b) s t a b -> Filter s t a b Source
Constructors
| Dungeon | |
Fields
| |
Instances
| Functor (Dungeon a b) | |
| Applicative (Dungeon a b) |
Witherable from Traversable
Traversable containers which hold Maybe are witherable.
Constructors
| Chipped | |
Fields
| |
Instances
| Functor t => Functor (Chipped t) | |
| Applicative t => Applicative (Chipped t) | |
| Foldable t => Foldable (Chipped t) | |
| Traversable t => Traversable (Chipped t) | |
| Traversable t => Witherable (Chipped t) | |
| Eq (t (Maybe a)) => Eq (Chipped t a) | |
| Ord (t (Maybe a)) => Ord (Chipped t a) | |
| Read (t (Maybe a)) => Read (Chipped t a) | |
| Show (t (Maybe a)) => Show (Chipped t a) |