bifunctors-4.1.1.1: Bifunctors

Portabilityportable
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellSafe-Inferred

Data.Bifoldable

Description

 

Synopsis

Documentation

class Bifoldable p whereSource

Minimal definition either bifoldr or bifoldMap

Bifoldable identifies foldable structures with two different varieties of elements. Common examples are Either and '(,)':

 instance Bifoldable Either where
   bifoldMap f _ (Left  a) = f a
   bifoldMap _ g (Right b) = g b

 instance Bifoldable (,) where
   bifoldr f g z (a, b) = f a (g b z)

When defining more than the minimal set of definitions, one should ensure that the following identities hold:

 bifoldbifoldMap id id
 bifoldMap f g ≡ bifoldr (mappend . f) (mappend . g) mempty
 bifoldr f g z t ≡ appEndo (bifoldMap (Endo . f) (Endo . g) t) z

Methods

bifold :: Monoid m => p m m -> mSource

Combines the elements of a structure using a monoid.

bifoldbifoldMap id id

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> p a b -> mSource

Combines the elements of a structure, given ways of mapping them to a common monoid.

bifoldMap f g ≡ bifoldr (mappend . f) (mappend . g) mempty

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> p a b -> cSource

Combines the elements of a structure in a right associative manner. Given a hypothetical function toEitherList :: p a b -> [Either a b] yielding a list of all elements of a structure in order, the following would hold:

bifoldr f g z ≡ foldr (either f g) z . toEitherList

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> p a b -> cSource

Combines the elments of a structure in a left associative manner. Given a hypothetical function toEitherList :: p a b -> [Either a b] yielding a list of all elements of a structure in order, the following would hold:

bifoldl f g z ≡ foldl (acc -> either (f acc) (g acc)) z .  toEitherList

bifoldr' :: Bifoldable t => (a -> c -> c) -> (b -> c -> c) -> c -> t a b -> cSource

As bifoldr, but strict in the result of the reduction functions at each step.

bifoldrM :: (Bifoldable t, Monad m) => (a -> c -> m c) -> (b -> c -> m c) -> c -> t a b -> m cSource

Right associative monadic bifold over a structure.

bifoldl' :: Bifoldable t => (a -> b -> a) -> (a -> c -> a) -> a -> t b c -> aSource

As bifoldl, but strict in the result of the reductionf unctions at each step.

bifoldlM :: (Bifoldable t, Monad m) => (a -> b -> m a) -> (a -> c -> m a) -> a -> t b c -> m aSource

Left associative monadic bifold over a structure.

bitraverse_ :: (Bifoldable t, Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f ()Source

As bitraverse, but ignores the results of the functions, merely performing the actions.

bifor_ :: (Bifoldable t, Applicative f) => t a b -> (a -> f c) -> (b -> f d) -> f ()Source

As bitraverse_, but with the structure as the primary argument.

bimapM_ :: (Bifoldable t, Monad m) => (a -> m c) -> (b -> m d) -> t a b -> m ()Source

As bimapM, but ignores the results of the functions, merely performing the actions.

biforM_ :: (Bifoldable t, Monad m) => t a b -> (a -> m c) -> (b -> m d) -> m ()Source

As bimapM_, but with the structure as the primary argument.

bisequenceA_ :: (Bifoldable t, Applicative f) => t (f a) (f b) -> f ()Source

As bisequenceA, but ignores the results of the actions.

bisequence_ :: (Bifoldable t, Monad m) => t (m a) (m b) -> m ()Source

As bisequence, but ignores the results of the actions.

biList :: Bifoldable t => t a a -> [a]Source

Collects the list of elements of a structure in order.

biconcat :: Bifoldable t => t [a] [a] -> [a]Source

Reduces a structure of lists to the concatenation of those lists.

biconcatMap :: Bifoldable t => (a -> [c]) -> (b -> [c]) -> t a b -> [c]Source

Given a means of mapping the elements of a structure to lists, computes the concatenation of all such lists in order.

biany :: Bifoldable t => (a -> Bool) -> (b -> Bool) -> t a b -> BoolSource

Determines whether any element of the structure satisfies the appropriate predicate.

biall :: Bifoldable t => (a -> Bool) -> (b -> Bool) -> t a b -> BoolSource

Determines whether all elements of the structure satisfy the appropriate predicate.