bifunctors-5.2: Bifunctors

Copyright(C) 2011-2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Data.Bitraversable

Description

 

Synopsis

Documentation

class (Bifunctor t, Bifoldable t) => Bitraversable t where

Bitraversable identifies bifunctorial data structures whose elements can be traversed in order, performing Applicative or Monad actions at each element, and collecting a result structure with the same shape.

A definition of traverse must satisfy the following laws:

naturality
bitraverse (t . f) (t . g) ≡ t . bitraverse f g for every applicative transformation t
identity
bitraverse Identity IdentityIdentity
composition
Compose . fmap (bitraverse g1 g2) . bitraverse f1 f2 ≡ traverse (Compose . fmap g1 . f1) (Compose . fmap g2 . f2)

where an applicative transformation is a function

t :: (Applicative f, Applicative g) => f a -> g a

preserving the Applicative operations:

t (pure x) = pure x
t (f <*> x) = t f <*> t x

and the identity functor Identity and composition functors Compose are defined as

newtype Identity a = Identity { runIdentity :: a }

instance Functor Identity where
  fmap f (Identity x) = Identity (f x)

instance Applicative Identity where
  pure = Identity
  Identity f <*> Identity x = Identity (f x)

newtype Compose f g a = Compose (f (g a))

instance (Functor f, Functor g) => Functor (Compose f g) where
  fmap f (Compose x) = Compose (fmap (fmap f) x)

instance (Applicative f, Applicative g) => Applicative (Compose f g) where
  pure = Compose . pure . pure
  Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)

Some simple examples are Either and '(,)':

instance Bitraversable Either where
  bitraverse f _ (Left x) = Left <$> f x
  bitraverse _ g (Right y) = Right <$> g y

instance Bitraversable (,) where
  bitraverse f g (x, y) = (,) <$> f x <*> g y

Bitraversable relates to its superclasses in the following ways:

bimap f g ≡ runIdentity . bitraverse (Identity . f) (Identity . g)
bifoldMap f g = getConst . bitraverse (Const . f) (Const . g)

These are available as bimapDefault and bifoldMapDefault respectively.

Minimal complete definition

Nothing

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> t a b -> f (t c d)

Evaluates the relevant functions at each element in the structure, running the action, and builds a new structure with the same shape, using the elements produced from sequencing the actions.

bitraverse f g ≡ bisequenceA . bimap f g

bisequenceA :: (Bitraversable t, Applicative f) => t (f a) (f b) -> f (t a b)

Sequences all the actions in a structure, building a new structure with the same shape using the results of the actions.

bisequenceAbitraverse id id

bisequence :: (Bitraversable t, Monad m) => t (m a) (m b) -> m (t a b)

As bisequenceA, but uses evidence that m is a Monad rather than an Applicative.

bisequencebimapM id id
bisequenceunwrapMonad . bisequenceA . bimap WrapMonad WrapMonad

bimapM :: (Bitraversable t, Monad m) => (a -> m c) -> (b -> m d) -> t a b -> m (t c d)

As bitraverse, but uses evidence that m is a Monad rather than an Applicative.

bimapM f g ≡ bisequence . bimap f g
bimapM f g ≡ unwrapMonad . bitraverse (WrapMonad . f) (WrapMonad . g)

bifor :: (Bitraversable t, Applicative f) => t a b -> (a -> f c) -> (b -> f d) -> f (t c d)

bifor is bitraverse with the structure as the first argument.

biforM :: (Bitraversable t, Monad m) => t a b -> (a -> m c) -> (b -> m d) -> m (t c d)

biforM is bimapM with the structure as the first argument.

bimapAccumL :: Bitraversable t => (a -> b -> (a, c)) -> (a -> d -> (a, e)) -> a -> t b d -> (a, t c e)

Traverses a structure from left to right, threading a state of type a and using the given actions to compute new elements for the structure.

bimapAccumR :: Bitraversable t => (a -> b -> (a, c)) -> (a -> d -> (a, e)) -> a -> t b d -> (a, t c e)

Traverses a structure from right to left, threading a state of type a and using the given actions to compute new elements for the structure.

bimapDefault :: Bitraversable t => (a -> b) -> (c -> d) -> t a c -> t b d

A default definition of bimap in terms of the Bitraversable operations.

bifoldMapDefault :: (Bitraversable t, Monoid m) => (a -> m) -> (b -> m) -> t a b -> m

A default definition of bifoldMap in terms of the Bitraversable operations.