{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE StandaloneDeriving #-}
#ifndef MIN_VERSION_semigroups
#define MIN_VERSION_semigroups(x,y,z) 0
#endif
module Data.Bitraversable
( Bitraversable(..)
, bisequenceA
, bisequence
, bimapM
, bifor
, biforM
, bimapAccumL
, bimapAccumR
, bimapDefault
, bifoldMapDefault
) where
import Control.Applicative
import Data.Bifunctor
import Data.Bifoldable
#if MIN_VERSION_semigroups(0,16,2)
import Data.Semigroup
#else
import Data.Monoid
#endif
#ifdef MIN_VERSION_tagged
import Data.Tagged
#endif
#if __GLASGOW_HASKELL__ >= 708 && __GLASGOW_HASKELL__ < 710
import Data.Typeable
#endif
class (Bifunctor t, Bifoldable t) => Bitraversable t where
bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bitraverse f g = bisequenceA . bimap f g
{-# INLINE bitraverse #-}
bisequenceA :: (Bitraversable t, Applicative f) => t (f a) (f b) -> f (t a b)
bisequenceA = bitraverse id id
{-# INLINE bisequenceA #-}
bimapM :: (Bitraversable t, Monad m) => (a -> m c) -> (b -> m d) -> t a b -> m (t c d)
bimapM f g = unwrapMonad . bitraverse (WrapMonad . f) (WrapMonad . g)
{-# INLINE bimapM #-}
bisequence :: (Bitraversable t, Monad m) => t (m a) (m b) -> m (t a b)
bisequence = bimapM id id
{-# INLINE bisequence #-}
#if __GLASGOW_HASKELL__ >= 708 && __GLASGOW_HASKELL__ < 710
deriving instance Typeable Bitraversable
#endif
#if MIN_VERSION_semigroups(0,16,2)
instance Bitraversable Arg where
bitraverse f g (Arg a b) = Arg <$> f a <*> g b
#endif
instance Bitraversable (,) where
bitraverse f g ~(a, b) = (,) <$> f a <*> g b
{-# INLINE bitraverse #-}
instance Bitraversable ((,,) x) where
bitraverse f g ~(x, a, b) = (,,) x <$> f a <*> g b
{-# INLINE bitraverse #-}
instance Bitraversable ((,,,) x y) where
bitraverse f g ~(x, y, a, b) = (,,,) x y <$> f a <*> g b
{-# INLINE bitraverse #-}
instance Bitraversable ((,,,,) x y z) where
bitraverse f g ~(x, y, z, a, b) = (,,,,) x y z <$> f a <*> g b
{-# INLINE bitraverse #-}
instance Bitraversable ((,,,,,) x y z w) where
bitraverse f g ~(x, y, z, w, a, b) = (,,,,,) x y z w <$> f a <*> g b
{-# INLINE bitraverse #-}
instance Bitraversable ((,,,,,,) x y z w v) where
bitraverse f g ~(x, y, z, w, v, a, b) = (,,,,,,) x y z w v <$> f a <*> g b
{-# INLINE bitraverse #-}
instance Bitraversable Either where
bitraverse f _ (Left a) = Left <$> f a
bitraverse _ g (Right b) = Right <$> g b
{-# INLINE bitraverse #-}
instance Bitraversable Const where
bitraverse f _ (Const a) = Const <$> f a
{-# INLINE bitraverse #-}
#ifdef MIN_VERSION_tagged
instance Bitraversable Tagged where
bitraverse _ g (Tagged b) = Tagged <$> g b
{-# INLINE bitraverse #-}
#endif
bifor :: (Bitraversable t, Applicative f) => t a b -> (a -> f c) -> (b -> f d) -> f (t c d)
bifor t f g = bitraverse f g t
{-# INLINE bifor #-}
biforM :: (Bitraversable t, Monad m) => t a b -> (a -> m c) -> (b -> m d) -> m (t c d)
biforM t f g = bimapM f g t
{-# INLINE biforM #-}
newtype StateL s a = StateL { runStateL :: s -> (s, a) }
instance Functor (StateL s) where
fmap f (StateL k) = StateL $ \ s ->
let (s', v) = k s in (s', f v)
{-# INLINE fmap #-}
instance Applicative (StateL s) where
pure x = StateL (\ s -> (s, x))
{-# INLINE pure #-}
StateL kf <*> StateL kv = StateL $ \ s ->
let (s', f) = kf s
(s'', v) = kv s'
in (s'', f v)
{-# INLINE (<*>) #-}
bimapAccumL :: Bitraversable t => (a -> b -> (a, c)) -> (a -> d -> (a, e)) -> a -> t b d -> (a, t c e)
bimapAccumL f g s t = runStateL (bitraverse (StateL . flip f) (StateL . flip g) t) s
{-# INLINE bimapAccumL #-}
newtype StateR s a = StateR { runStateR :: s -> (s, a) }
instance Functor (StateR s) where
fmap f (StateR k) = StateR $ \ s ->
let (s', v) = k s in (s', f v)
{-# INLINE fmap #-}
instance Applicative (StateR s) where
pure x = StateR (\ s -> (s, x))
{-# INLINE pure #-}
StateR kf <*> StateR kv = StateR $ \ s ->
let (s', v) = kv s
(s'', f) = kf s'
in (s'', f v)
{-# INLINE (<*>) #-}
bimapAccumR :: Bitraversable t => (a -> b -> (a, c)) -> (a -> d -> (a, e)) -> a -> t b d -> (a, t c e)
bimapAccumR f g s t = runStateR (bitraverse (StateR . flip f) (StateR . flip g) t) s
{-# INLINE bimapAccumR #-}
newtype Id a = Id { getId :: a }
instance Functor Id where
fmap f (Id x) = Id (f x)
{-# INLINE fmap #-}
instance Applicative Id where
pure = Id
{-# INLINE pure #-}
Id f <*> Id x = Id (f x)
{-# INLINE (<*>) #-}
bimapDefault :: Bitraversable t => (a -> b) -> (c -> d) -> t a c -> t b d
bimapDefault f g = getId . bitraverse (Id . f) (Id . g)
{-# INLINE bimapDefault #-}
bifoldMapDefault :: (Bitraversable t, Monoid m) => (a -> m) -> (b -> m) -> t a b -> m
bifoldMapDefault f g = getConst . bitraverse (Const . f) (Const . g)
{-# INLINE bifoldMapDefault #-}