{-# LANGUAGE Trustworthy #-}{-# LANGUAGE ScopedTypeVariables #-}------------------------------------------------------------------------------- |-- Module : Data.Bitraversable-- Copyright : (C) 2011-2016 Edward Kmett-- License : BSD-style (see the file LICENSE)---- Maintainer : libraries@haskell.org-- Stability : provisional-- Portability : portable---- @since 4.10.0.0----------------------------------------------------------------------------moduleData.Bitraversable(Bitraversable (..),bisequenceA ,bisequence ,bimapM ,bifor ,biforM ,bimapAccumL ,bimapAccumR ,bimapDefault ,bifoldMapDefault )whereimportControl.Applicative importData.Bifunctor importData.Bifoldable importData.Coerce importData.Functor.Identity (Identity (..))importData.Functor.Utils (StateL (..),StateR (..))importGHC.Generics (K1 (..))-- $setup-- >>> import Prelude-- >>> import Data.Maybe-- >>> import Data.List (find)-- | '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.---- As opposed to 'Traversable' data structures, which have one variety of-- element on which an action can be performed, 'Bitraversable' data structures-- have two such varieties of elements.---- A definition of 'bitraverse' must satisfy the following laws:---- [Naturality]-- @'bitraverse' (t . f) (t . g) ≡ t . 'bitraverse' f g@-- for every applicative transformation @t@---- [Identity]-- @'bitraverse' 'Identity' 'Identity' ≡ 'Identity'@---- [Composition]-- @'Data.Functor.Compose.Compose' .-- 'fmap' ('bitraverse' g1 g2) .-- 'bitraverse' f1 f2-- ≡ 'bitraverse' ('Data.Functor.Compose.Compose' . 'fmap' g1 . f1)-- ('Data.Functor.Compose.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-- 'Data.Functor.Compose.Compose' are from "Data.Functor.Identity" and-- "Data.Functor.Compose".---- 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.---- @since 4.10.0.0class(Bifunctor t ,Bifoldable t )=>Bitraversable t where-- | Evaluates the relevant functions at each element in the structure,-- running the action, and builds a new structure with the same shape, using-- the results produced from sequencing the actions.---- @'bitraverse' f g ≡ 'bisequenceA' . 'bimap' f g@---- For a version that ignores the results, see 'bitraverse_'.---- ==== __Examples__---- Basic usage:---- >>> bitraverse listToMaybe (find odd) (Left [])-- Nothing---- >>> bitraverse listToMaybe (find odd) (Left [1, 2, 3])-- Just (Left 1)---- >>> bitraverse listToMaybe (find odd) (Right [4, 5])-- Just (Right 5)---- >>> bitraverse listToMaybe (find odd) ([1, 2, 3], [4, 5])-- Just (1,5)---- >>> bitraverse listToMaybe (find odd) ([], [4, 5])-- Nothing---- @since 4.10.0.0bitraverse ::Applicative f =>(a ->f c )->(b ->f d )->t a b ->f (t c d )bitraverse a -> f c
f b -> f d
g =forall (t :: * -> * -> *) (f :: * -> *) a b.
(Bitraversable t, Applicative f) =>
t (f a) (f b) -> f (t a b)
bisequenceA forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap a -> f c
f b -> f d
g -- | Alias for 'bisequence'.---- @since 4.10.0.0bisequenceA ::(Bitraversable t ,Applicative f )=>t (f a )(f b )->f (t a b )bisequenceA :: forall (t :: * -> * -> *) (f :: * -> *) a b.
(Bitraversable t, Applicative f) =>
t (f a) (f b) -> f (t a b)
bisequenceA =forall (t :: * -> * -> *) (f :: * -> *) a b.
(Bitraversable t, Applicative f) =>
t (f a) (f b) -> f (t a b)
bisequence -- | Alias for 'bitraverse'.---- @since 4.10.0.0bimapM ::(Bitraversable t ,Applicative f )=>(a ->f c )->(b ->f d )->t a b ->f (t c d )bimapM :: forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bimapM =forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bitraverse -- | Sequences all the actions in a structure, building a new structure with-- the same shape using the results of the actions. For a version that ignores-- the results, see 'bisequence_'.---- @'bisequence' ≡ 'bitraverse' 'id' 'id'@---- ==== __Examples__---- Basic usage:---- >>> bisequence (Just 4, Nothing)-- Nothing---- >>> bisequence (Just 4, Just 5)-- Just (4,5)---- >>> bisequence ([1, 2, 3], [4, 5])-- [(1,4),(1,5),(2,4),(2,5),(3,4),(3,5)]---- @since 4.10.0.0bisequence ::(Bitraversable t ,Applicative f )=>t (f a )(f b )->f (t a b )bisequence :: forall (t :: * -> * -> *) (f :: * -> *) a b.
(Bitraversable t, Applicative f) =>
t (f a) (f b) -> f (t a b)
bisequence =forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bitraverse forall a. a -> a
id forall a. a -> a
id -- | @since 4.10.0.0instanceBitraversable (,)wherebitraverse :: forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c) -> (b -> f d) -> (a, b) -> f (c, d)
bitraverse a -> f c
f b -> f d
g ~(a
a ,b
b )=forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (,)(a -> f c
f a
a )(b -> f d
g b
b )-- | @since 4.10.0.0instanceBitraversable ((,,)x )wherebitraverse :: forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c) -> (b -> f d) -> (x, a, b) -> f (x, c, d)
bitraverse a -> f c
f b -> f d
g ~(x
x ,a
a ,b
b )=forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 ((,,)x
x )(a -> f c
f a
a )(b -> f d
g b
b )-- | @since 4.10.0.0instanceBitraversable ((,,,)x y )wherebitraverse :: forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c) -> (b -> f d) -> (x, y, a, b) -> f (x, y, c, d)
bitraverse a -> f c
f b -> f d
g ~(x
x ,y
y ,a
a ,b
b )=forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 ((,,,)x
x y
y )(a -> f c
f a
a )(b -> f d
g b
b )-- | @since 4.10.0.0instanceBitraversable ((,,,,)x y z )wherebitraverse :: forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c) -> (b -> f d) -> (x, y, z, a, b) -> f (x, y, z, c, d)
bitraverse a -> f c
f b -> f d
g ~(x
x ,y
y ,z
z ,a
a ,b
b )=forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 ((,,,,)x
x y
y z
z )(a -> f c
f a
a )(b -> f d
g b
b )-- | @since 4.10.0.0instanceBitraversable ((,,,,,)x y z w )wherebitraverse :: forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c)
-> (b -> f d) -> (x, y, z, w, a, b) -> f (x, y, z, w, c, d)
bitraverse a -> f c
f b -> f d
g ~(x
x ,y
y ,z
z ,w
w ,a
a ,b
b )=forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 ((,,,,,)x
x y
y z
z w
w )(a -> f c
f a
a )(b -> f d
g b
b )-- | @since 4.10.0.0instanceBitraversable ((,,,,,,)x y z w v )wherebitraverse :: forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c)
-> (b -> f d) -> (x, y, z, w, v, a, b) -> f (x, y, z, w, v, c, d)
bitraverse a -> f c
f b -> f d
g ~(x
x ,y
y ,z
z ,w
w ,v
v ,a
a ,b
b )=forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 ((,,,,,,)x
x y
y z
z w
w v
v )(a -> f c
f a
a )(b -> f d
g b
b )-- | @since 4.10.0.0instanceBitraversable Either wherebitraverse :: forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c) -> (b -> f d) -> Either a b -> f (Either c d)
bitraverse a -> f c
f b -> f d
_(Left a
a )=forall a b. a -> Either a b
Left forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f c
f a
a bitraverse a -> f c
_b -> f d
g (Right b
b )=forall a b. b -> Either a b
Right forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> b -> f d
g b
b -- | @since 4.10.0.0instanceBitraversable Const wherebitraverse :: forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c) -> (b -> f d) -> Const a b -> f (Const c d)
bitraverse a -> f c
f b -> f d
_(Const a
a )=forall {k} a (b :: k). a -> Const a b
Const forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f c
f a
a -- | @since 4.10.0.0instanceBitraversable (K1 i )wherebitraverse :: forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c) -> (b -> f d) -> K1 i a b -> f (K1 i c d)
bitraverse a -> f c
f b -> f d
_(K1 a
c )=forall k i c (p :: k). c -> K1 i c p
K1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f c
f a
c -- | 'bifor' is 'bitraverse' with the structure as the first argument. For a-- version that ignores the results, see 'bifor_'.---- ==== __Examples__---- Basic usage:---- >>> bifor (Left []) listToMaybe (find even)-- Nothing---- >>> bifor (Left [1, 2, 3]) listToMaybe (find even)-- Just (Left 1)---- >>> bifor (Right [4, 5]) listToMaybe (find even)-- Just (Right 4)---- >>> bifor ([1, 2, 3], [4, 5]) listToMaybe (find even)-- Just (1,4)---- >>> bifor ([], [4, 5]) listToMaybe (find even)-- Nothing---- @since 4.10.0.0bifor ::(Bitraversable t ,Applicative f )=>t a b ->(a ->f c )->(b ->f d )->f (t c d )bifor :: forall (t :: * -> * -> *) (f :: * -> *) a b c d.
(Bitraversable t, Applicative f) =>
t a b -> (a -> f c) -> (b -> f d) -> f (t c d)
bifor t a b
t a -> f c
f b -> f d
g =forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bitraverse a -> f c
f b -> f d
g t a b
t -- | Alias for 'bifor'.---- @since 4.10.0.0biforM ::(Bitraversable t ,Applicative f )=>t a b ->(a ->f c )->(b ->f d )->f (t c d )biforM :: forall (t :: * -> * -> *) (f :: * -> *) a b c d.
(Bitraversable t, Applicative f) =>
t a b -> (a -> f c) -> (b -> f d) -> f (t c d)
biforM =forall (t :: * -> * -> *) (f :: * -> *) a b c d.
(Bitraversable t, Applicative f) =>
t a b -> (a -> f c) -> (b -> f d) -> f (t c d)
bifor -- | The 'bimapAccumL' function behaves like a combination of 'bimap' and-- 'bifoldl'; it 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.---- ==== __Examples__---- Basic usage:---- >>> bimapAccumL (\acc bool -> (acc + 1, show bool)) (\acc string -> (acc * 2, reverse string)) 3 (True, "foo")-- (8,("True","oof"))---- @since 4.10.0.0bimapAccumL ::Bitraversable t =>(a ->b ->(a ,c ))->(a ->d ->(a ,e ))->a ->t b d ->(a ,t c e )bimapAccumL :: forall (t :: * -> * -> *) a b c d e.
Bitraversable t =>
(a -> b -> (a, c))
-> (a -> d -> (a, e)) -> a -> t b d -> (a, t c e)
bimapAccumL a -> b -> (a, c)
f a -> d -> (a, e)
g a
s t b d
t =forall s a. StateL s a -> s -> (s, a)
runStateL (forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bitraverse (forall s a. (s -> (s, a)) -> StateL s a
StateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> b -> (a, c)
f )(forall s a. (s -> (s, a)) -> StateL s a
StateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> d -> (a, e)
g )t b d
t )a
s -- | The 'bimapAccumR' function behaves like a combination of 'bimap' and-- 'bifoldr'; it 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.---- ==== __Examples__---- Basic usage:---- >>> bimapAccumR (\acc bool -> (acc + 1, show bool)) (\acc string -> (acc * 2, reverse string)) 3 (True, "foo")-- (7,("True","oof"))---- @since 4.10.0.0bimapAccumR ::Bitraversable t =>(a ->b ->(a ,c ))->(a ->d ->(a ,e ))->a ->t b d ->(a ,t c e )bimapAccumR :: forall (t :: * -> * -> *) a b c d e.
Bitraversable t =>
(a -> b -> (a, c))
-> (a -> d -> (a, e)) -> a -> t b d -> (a, t c e)
bimapAccumR a -> b -> (a, c)
f a -> d -> (a, e)
g a
s t b d
t =forall s a. StateR s a -> s -> (s, a)
runStateR (forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bitraverse (forall s a. (s -> (s, a)) -> StateR s a
StateR forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> b -> (a, c)
f )(forall s a. (s -> (s, a)) -> StateR s a
StateR forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> d -> (a, e)
g )t b d
t )a
s -- | A default definition of 'bimap' in terms of the 'Bitraversable'-- operations.---- @'bimapDefault' f g ≡-- 'runIdentity' . 'bitraverse' ('Identity' . f) ('Identity' . g)@---- @since 4.10.0.0bimapDefault ::forallt a b c d .Bitraversable t =>(a ->b )->(c ->d )->t a c ->t b d -- See Note [Function coercion] in Data.Functor.Utils.bimapDefault :: forall (t :: * -> * -> *) a b c d.
Bitraversable t =>
(a -> b) -> (c -> d) -> t a c -> t b d
bimapDefault =coerce :: forall a b. Coercible a b => a -> b
coerce (forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bitraverse ::(a ->Identity b )->(c ->Identity d )->t a c ->Identity (t b d )){-# INLINEbimapDefault #-}-- | A default definition of 'bifoldMap' in terms of the 'Bitraversable'-- operations.---- @'bifoldMapDefault' f g ≡-- 'getConst' . 'bitraverse' ('Const' . f) ('Const' . g)@---- @since 4.10.0.0bifoldMapDefault ::forallt m a b .(Bitraversable t ,Monoid m )=>(a ->m )->(b ->m )->t a b ->m -- See Note [Function coercion] in Data.Functor.Utils.bifoldMapDefault :: forall (t :: * -> * -> *) m a b.
(Bitraversable t, Monoid m) =>
(a -> m) -> (b -> m) -> t a b -> m
bifoldMapDefault =coerce :: forall a b. Coercible a b => a -> b
coerce (forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bitraverse ::(a ->Const m ())->(b ->Const m ())->t a b ->Const m (t ()())){-# INLINEbifoldMapDefault #-}

AltStyle によって変換されたページ (->オリジナル) /