module Data.Bifunctor.Joker
( Joker(..)
) where
import Control.Applicative
import Data.Biapplicative
import Data.Bifoldable
import Data.Bitraversable
import Data.Foldable
import Data.Traversable
newtype Joker g a b = Joker { runJoker :: g b }
deriving (Eq,Ord,Show,Read)
instance Functor g => Bifunctor (Joker g) where
first _ = Joker . runJoker
second g = Joker . fmap g . runJoker
bimap _ g = Joker . fmap g . runJoker
instance Functor g => Functor (Joker g a) where
fmap g = Joker . fmap g . runJoker
instance Applicative g => Biapplicative (Joker g) where
bipure _ b = Joker (pure b)
Joker mf <<*>> Joker mx = Joker (mf <*> mx)
instance Foldable g => Bifoldable (Joker g) where
bifoldMap _ g = foldMap g . runJoker
instance Foldable g => Foldable (Joker g a) where
foldMap g = foldMap g . runJoker
instance Traversable g => Bitraversable (Joker g) where
bitraverse _ g = fmap Joker . traverse g . runJoker
instance Traversable g => Traversable (Joker g a) where
traverse g = fmap Joker . traverse g . runJoker