module Data.Bifunctor.Biff
( Biff(..)
) where
import Control.Applicative
import Data.Biapplicative
import Data.Bifunctor.Apply
import Data.Bifoldable
import Data.Bitraversable
import Data.Foldable
import Data.Functor.Apply
import Data.Monoid
import Data.Semigroup.Bifoldable
import Data.Semigroup.Bitraversable
import Data.Semigroup.Foldable
import Data.Semigroup.Traversable
import Data.Traversable
newtype Biff p f g a b = Biff { runBiff :: p (f a) (g b) }
deriving (Eq,Ord,Show,Read)
instance (Bifunctor p, Functor f, Functor g) => Bifunctor (Biff p f g) where
first f = Biff . first (fmap f) . runBiff
second f = Biff . second (fmap f) . runBiff
bimap f g = Biff . bimap (fmap f) (fmap g) . runBiff
instance (Bifunctor p, Functor g) => Functor (Biff p f g a) where
fmap f = Biff . second (fmap f) . runBiff
instance (Biapply p, Apply f, Apply g) => Biapply (Biff p f g) where
Biff fg <<.>> Biff xy = Biff (bimap (<.>) (<.>) fg <<.>> xy)
instance (Biapplicative p, Applicative f, Applicative g) => Biapplicative (Biff p f g) where
bipure a b = Biff (bipure (pure a) (pure b))
Biff fg <<*>> Biff xy = Biff (bimap (<*>) (<*>) fg <<*>> xy)
instance (Bifoldable p, Foldable g) => Foldable (Biff p f g a) where
foldMap f = bifoldMap (const mempty) (foldMap f) . runBiff
instance (Bifoldable p, Foldable f, Foldable g) => Bifoldable (Biff p f g) where
bifoldMap f g = bifoldMap (foldMap f) (foldMap g) . runBiff
instance (Bitraversable p, Traversable g) => Traversable (Biff p f g a) where
traverse f = fmap Biff . bitraverse pure (traverse f) . runBiff
instance (Bitraversable p, Traversable f, Traversable g) => Bitraversable (Biff p f g) where
bitraverse f g = fmap Biff . bitraverse (traverse f) (traverse g) . runBiff
instance (Bifoldable1 p, Foldable1 f, Foldable1 g) => Bifoldable1 (Biff p f g) where
bifoldMap1 f g = bifoldMap1 (foldMap1 f) (foldMap1 g) . runBiff
instance (Bitraversable1 p, Traversable1 f, Traversable1 g) => Bitraversable1 (Biff p f g) where
bitraverse1 f g = fmap Biff . bitraverse1 (traverse1 f) (traverse1 g) . runBiff