#if __GLASGOW_HASKELL__ >= 702
#endif
#if __GLASGOW_HASKELL__ >= 706
#endif
module Data.Bifunctor.Joker
( Joker(..)
) where
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative
#endif
import Data.Biapplicative
import Data.Bifoldable
import Data.Bitraversable
#if __GLASGOW_HASKELL__ < 710
import Data.Foldable
import Data.Traversable
#endif
#if __GLASGOW_HASKELL__ >= 708
import Data.Typeable
#endif
#if __GLASGOW_HASKELL__ >= 702
import GHC.Generics
#endif
newtype Joker g a b = Joker { runJoker :: g b }
deriving ( Eq, Ord, Show, Read
#if __GLASGOW_HASKELL__ >= 702
, Generic
#endif
#if __GLASGOW_HASKELL__ >= 708
, Generic1
, Typeable
#endif
)
#if __GLASGOW_HASKELL__ >= 702 && __GLASGOW_HASKELL__ < 708
data JokerMetaData
data JokerMetaCons
data JokerMetaSel
instance Datatype JokerMetaData where
datatypeName _ = "Joker"
moduleName _ = "Data.Bifunctor.Joker"
instance Constructor JokerMetaCons where
conName _ = "Joker"
conIsRecord _ = True
instance Selector JokerMetaSel where
selName _ = "runJoker"
instance Generic1 (Joker g a) where
type Rep1 (Joker g a) = D1 JokerMetaData (C1 JokerMetaCons
(S1 JokerMetaSel (Rec1 g)))
from1 = M1 . M1 . M1 . Rec1 . runJoker
to1 = Joker . unRec1 . unM1 . unM1 . unM1
#endif
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