module Data.Bifunctor.Tannen
( Tannen(..)
) 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 Tannen f p a b = Tannen { runTannen :: f (p a b) }
deriving (Eq,Ord,Show,Read)
instance (Functor f, Bifunctor p) => Bifunctor (Tannen f p) where
first f = Tannen . fmap (first f) . runTannen
second f = Tannen . fmap (second f) . runTannen
bimap f g = Tannen . fmap (bimap f g) . runTannen
instance (Functor f, Bifunctor p) => Functor (Tannen f p a) where
fmap f = Tannen . fmap (second f) . runTannen
instance (Apply f, Biapply p) => Biapply (Tannen f p) where
Tannen fg <<.>> Tannen xy = Tannen ((<<.>>) <$> fg <.> xy)
instance (Applicative f, Biapplicative p) => Biapplicative (Tannen f p) where
bipure a b = Tannen (pure (bipure a b))
Tannen fg <<*>> Tannen xy = Tannen ((<<*>>) <$> fg <*> xy)
instance (Foldable f, Bifoldable p) => Foldable (Tannen f p a) where
foldMap f = foldMap (bifoldMap (const mempty) f) . runTannen
instance (Foldable f, Bifoldable p) => Bifoldable (Tannen f p) where
bifoldMap f g = foldMap (bifoldMap f g) . runTannen
instance (Traversable f, Bitraversable p) => Traversable (Tannen f p a) where
traverse f = fmap Tannen . traverse (bitraverse pure f) . runTannen
instance (Traversable f, Bitraversable p) => Bitraversable (Tannen f p) where
bitraverse f g = fmap Tannen . traverse (bitraverse f g) . runTannen
instance (Foldable1 f, Bifoldable1 p) => Bifoldable1 (Tannen f p) where
bifoldMap1 f g = foldMap1 (bifoldMap1 f g) . runTannen
instance (Traversable1 f, Bitraversable1 p) => Bitraversable1 (Tannen f p) where
bitraverse1 f g = fmap Tannen . traverse1 (bitraverse1 f g) . runTannen