witherable-0.3: filterable traversable

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

Data.Witherable

Contents

Description

 
Synopsis

Documentation

class Functor f => Filterable f where Source #

Like Functor, but it include Maybe effects.

Formally, the class Filterable represents a functor from Kleisli Maybe to Hask.

A definition of mapMaybe must satisfy the following laws:

identity
mapMaybe Just ≡ id
conservation
mapMaybe (Just . f) ≡ fmap f
composition
mapMaybe f . mapMaybe g ≡ mapMaybe (f <=< g)

Minimal complete definition

mapMaybe | catMaybes

Methods

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 # 
Instance details

Defined in Data.Witherable

Methods

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

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

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

Filterable Maybe Source # 
Instance details

Defined in Data.Witherable

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 #

Filterable IntMap Source # 
Instance details

Defined in Data.Witherable

Methods

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

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

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

Filterable Seq Source # 
Instance details

Defined in Data.Witherable

Methods

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

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

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

Filterable Vector Source # 
Instance details

Defined in Data.Witherable

Methods

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

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

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

Monoid e => Filterable (Either e) Source # 
Instance details

Defined in Data.Witherable

Methods

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

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

filter :: (a -> Bool) -> Either e a -> Either e a Source #

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

Defined in Data.Witherable

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 #

Filterable (Map k) Source # 
Instance details

Defined in Data.Witherable

Methods

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

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

filter :: (a -> Bool) -> Map k a -> Map k a Source #

Functor f => Filterable (MaybeT f) Source # 
Instance details

Defined in Data.Witherable

Methods

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

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

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

(Eq k, Hashable k) => Filterable (HashMap k) Source # 
Instance details

Defined in Data.Witherable

Methods

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

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

filter :: (a -> Bool) -> HashMap k a -> HashMap k a Source #

Filterable (Const r :: Type -> Type) Source # 
Instance details

Defined in Data.Witherable

Methods

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

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

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

Filterable f => Filterable (IdentityT f) Source # 
Instance details

Defined in Data.Witherable

Methods

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

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

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

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

Defined in Data.Witherable

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 #

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

Defined in Data.Witherable

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 #

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

Defined in Data.Witherable

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 #

class (Traversable t, Filterable t) => Witherable t where Source #

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

A definition of wither must satisfy the following laws:

identity
wither (pure . Just) ≡ pure
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)

Minimal complete definition

Nothing

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> t a -> f (t b) Source #

traverse f ≡ wither (fmap Just . f)

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 #

Compose . fmap (filterA f) . filterA g ≡ filterA (x -> Compose $ fmap (b -> (b&&) $ f x) (g x)
Instances
Witherable [] Source # 
Instance details

Defined in Data.Witherable

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> [a] -> f [b] Source #

witherM :: Monad m => (a -> m (Maybe b)) -> [a] -> m [b] Source #

filterA :: Applicative f => (a -> f Bool) -> [a] -> f [a] Source #

Witherable Maybe Source # 
Instance details

Defined in Data.Witherable

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> Maybe a -> f (Maybe b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> Maybe a -> m (Maybe b) Source #

filterA :: Applicative f => (a -> f Bool) -> Maybe a -> f (Maybe a) Source #

Witherable IntMap Source # 
Instance details

Defined in Data.Witherable

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> IntMap a -> f (IntMap b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> IntMap a -> m (IntMap b) Source #

filterA :: Applicative f => (a -> f Bool) -> IntMap a -> f (IntMap a) Source #

Witherable Seq Source # 
Instance details

Defined in Data.Witherable

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> Seq a -> f (Seq b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> Seq a -> m (Seq b) Source #

filterA :: Applicative f => (a -> f Bool) -> Seq a -> f (Seq a) Source #

Witherable Vector Source # 
Instance details

Defined in Data.Witherable

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> Vector a -> f (Vector b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> Vector a -> m (Vector b) Source #

filterA :: Applicative f => (a -> f Bool) -> Vector a -> f (Vector a) Source #

Monoid e => Witherable (Either e) Source # 
Instance details

Defined in Data.Witherable

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> Either e a -> f (Either e b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> Either e a -> m (Either e b) Source #

filterA :: Applicative f => (a -> f Bool) -> Either e a -> f (Either e a) Source #

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

Defined in Data.Witherable

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> Proxy a -> f (Proxy b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> Proxy a -> m (Proxy b) Source #

filterA :: Applicative f => (a -> f Bool) -> Proxy a -> f (Proxy a) Source #

Witherable (Map k) Source # 
Instance details

Defined in Data.Witherable

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> Map k a -> f (Map k b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> Map k a -> m (Map k b) Source #

filterA :: Applicative f => (a -> f Bool) -> Map k a -> f (Map k a) Source #

Traversable t => Witherable (MaybeT t) Source # 
Instance details

Defined in Data.Witherable

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> MaybeT t a -> f (MaybeT t b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> MaybeT t a -> m (MaybeT t b) Source #

filterA :: Applicative f => (a -> f Bool) -> MaybeT t a -> f (MaybeT t a) Source #

(Eq k, Hashable k) => Witherable (HashMap k) Source # 
Instance details

Defined in Data.Witherable

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> HashMap k a -> f (HashMap k b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> HashMap k a -> m (HashMap k b) Source #

filterA :: Applicative f => (a -> f Bool) -> HashMap k a -> f (HashMap k a) Source #

Witherable (Const r :: Type -> Type) Source # 
Instance details

Defined in Data.Witherable

Methods

wither :: Applicative f => (a -> f (Maybe b)) -> Const r a -> f (Const r b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> Const r a -> m (Const r b) Source #

filterA :: Applicative f => (a -> f Bool) -> Const r a -> f (Const r a) Source #

Witherable f => Witherable (IdentityT f) Source # 
Instance details

Defined in Data.Witherable

Methods

wither :: Applicative f0 => (a -> f0 (Maybe b)) -> IdentityT f a -> f0 (IdentityT f b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> IdentityT f a -> m (IdentityT f b) Source #

filterA :: Applicative f0 => (a -> f0 Bool) -> IdentityT f a -> f0 (IdentityT f a) Source #

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

Defined in Data.Witherable

Methods

wither :: Applicative f0 => (a -> f0 (Maybe b)) -> Product f g a -> f0 (Product f g b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> Product f g a -> m (Product f g b) Source #

filterA :: Applicative f0 => (a -> f0 Bool) -> Product f g a -> f0 (Product f g a) Source #

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

Defined in Data.Witherable

Methods

wither :: Applicative f0 => (a -> f0 (Maybe b)) -> Sum f g a -> f0 (Sum f g b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> Sum f g a -> m (Sum f g b) Source #

filterA :: Applicative f0 => (a -> f0 Bool) -> Sum f g a -> f0 (Sum f g a) Source #

(Traversable f, Witherable g) => Witherable (Compose f g) Source # 
Instance details

Defined in Data.Witherable

Methods

wither :: Applicative f0 => (a -> f0 (Maybe b)) -> Compose f g a -> f0 (Compose f g b) Source #

witherM :: Monad m => (a -> m (Maybe b)) -> Compose f g a -> m (Compose f g b) Source #

filterA :: Applicative f0 => (a -> f0 Bool) -> Compose f g a -> f0 (Compose f g a) Source #

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

Removes duplicate elements from a list, keeping only the first occurrence. This is asymptotically faster 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 comparison (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 #

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 #

A Filter is like a Traversal, but you can also remove targets.

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 #

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 #

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.

newtype Peat a b t Source #

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.

Constructors

Peat 

Fields

Instances
Functor (Peat a b) Source # 
Instance details

Defined in Data.Witherable

Methods

fmap :: (a0 -> b0) -> Peat a b a0 -> Peat a b b0 #

(<$) :: a0 -> Peat a b b0 -> Peat a b a0 #

Applicative (Peat a b) Source # 
Instance details

Defined in Data.Witherable

Methods

pure :: a0 -> Peat a b a0 #

(<*>) :: Peat a b (a0 -> b0) -> Peat a b a0 -> Peat a b b0 #

liftA2 :: (a0 -> b0 -> c) -> Peat a b a0 -> Peat a b b0 -> Peat a b c #

(*>) :: Peat a b a0 -> Peat a b b0 -> Peat a b b0 #

(<*) :: Peat a b a0 -> Peat a b b0 -> Peat a b a0 #