#if __GLASGOW_HASKELL__ >= 702
#endif
#if __GLASGOW_HASKELL__ >= 706
#endif
module Data.Bifunctor.Join
  ( Join(..)
  ) 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 Join p a = Join { runJoin :: p a a }
  deriving
    (
#if __GLASGOW_HASKELL__ >= 702
      Generic
#endif
#if __GLASGOW_HASKELL__ >= 708
    , Typeable
#endif
    )
deriving instance Eq   (p a a) => Eq   (Join p a)
deriving instance Ord  (p a a) => Ord  (Join p a)
deriving instance Show (p a a) => Show (Join p a)
deriving instance Read (p a a) => Read (Join p a)
instance Bifunctor p => Functor (Join p) where
  fmap f (Join a) = Join (bimap f f a)
  
instance Biapplicative p => Applicative (Join p) where
  pure a = Join (bipure a a)
  
  Join f <*> Join a = Join (f <<*>> a)
  
  Join a *> Join b = Join (a *>> b)
  
  Join a <* Join b = Join (a <<* b)
  
instance Bifoldable p => Foldable (Join p) where
  foldMap f (Join a) = bifoldMap f f a
  
instance Bitraversable p => Traversable (Join p) where
  traverse f (Join a) = fmap Join (bitraverse f f a)
  
  sequenceA (Join a) = fmap Join (bisequenceA a)