#if __GLASGOW_HASKELL__ >= 702
#endif
#if __GLASGOW_HASKELL__ >= 706
#endif
module Data.Bifunctor.Clown
( Clown(..)
) 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.Monoid
import Data.Traversable
#endif
#if __GLASGOW_HASKELL__ >= 708
import Data.Typeable
#endif
#if __GLASGOW_HASKELL__ >= 702
import GHC.Generics
#endif
newtype Clown f a b = Clown { runClown :: f a }
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 ClownMetaData
data ClownMetaCons
data ClownMetaSel
instance Datatype ClownMetaData where
datatypeName _ = "Clown"
moduleName _ = "Data.Bifunctor.Clown"
instance Constructor ClownMetaCons where
conName _ = "Clown"
conIsRecord _ = True
instance Selector ClownMetaSel where
selName _ = "runClown"
instance Generic1 (Clown f a) where
type Rep1 (Clown f a) = D1 ClownMetaData (C1 ClownMetaCons
(S1 ClownMetaSel (Rec0 (f a))))
from1 = M1 . M1 . M1 . K1 . runClown
to1 = Clown . unK1 . unM1 . unM1 . unM1
#endif
instance Functor f => Bifunctor (Clown f) where
first f = Clown . fmap f . runClown
second _ = Clown . runClown
bimap f _ = Clown . fmap f . runClown
instance Functor (Clown f a) where
fmap _ = Clown . runClown
instance Applicative f => Biapplicative (Clown f) where
bipure a _ = Clown (pure a)
Clown mf <<*>> Clown mx = Clown (mf <*> mx)
instance Foldable f => Bifoldable (Clown f) where
bifoldMap f _ = foldMap f . runClown
instance Foldable (Clown f a) where
foldMap _ = mempty
instance Traversable f => Bitraversable (Clown f) where
bitraverse f _ = fmap Clown . traverse f . runClown
instance Traversable (Clown f a) where
traverse _ = pure . Clown . runClown