witherable-0.1.3.3: Generalization of filter and catMaybes

Copyright(c) Fumiaki Kinoshita 2015
LicenseBSD3
MaintainerFumiaki Kinoshita <fumiexcel@gmail.com>
Stabilityprovisional
Portabilitynon-portable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Witherable

Contents

Description

 

Synopsis

Documentation

class Traversable t => Witherable t where Source

Like traverse, but you can remove elements instead of updating them.

traverse f ≡ wither (fmap Just . f)

A definition of wither must satisfy the following laws:

identity
wither (pure . Just) ≡ pure
composition
Compose . fmap (wither f) . wither g ≡ wither (Compose . fmap (wither f) . g)

Parametricity implies the naturality law:

t . wither f = wither (t . f)

Minimal complete definition

wither | mapMaybe | catMaybes

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

filter :: (a -> Bool) -> t a -> t a Source

witherM :: (Witherable t, Monad m) => (a -> MaybeT m b) -> t a -> m (t b) Source

blightM :: (Monad m, Witherable t) => t a -> (a -> MaybeT m b) -> m (t b) Source

blightM is witherM with its arguments flipped.

ordNub :: (Witherable t, Ord a) => t a -> t a Source

Removes duplicate elements from a list, keeping only the first occurrence. This is exponentially quicker than using nub from Data.List.

hashNub :: (Witherable t, Eq a, Hashable a) => t a -> t a Source

Removes duplicate elements from a list, keeping only the first occurrence. This is usually faster than ordNub, especially for things that have a slow comparion (like String).

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

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

witherOf is actually id, but left for consistency.

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

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

newtype Peat a b t Source

Constructors

Peat 

Fields

runPeat :: forall f. Applicative f => (a -> f (Maybe b)) -> f t
 

Instances

Witherable from Traversable

newtype Chipped t a Source

Traversable containers which hold Maybe are witherable.

Constructors

Chipped 

Fields

getChipped :: t (Maybe a)