{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe, TypeOperators, QuasiQuotes #-}
module Data.Invertible.Monoid
  ( BiEndo(..)
  , dual
  , endo
  , biEndo
  , all
  , any
  , sum
  , product
  , first
  , last
  , alt
  ) where
import Prelude hiding (fmap, (<$>), all, any, sum, product, last)
import qualified Control.Category as C
import Data.Monoid
import Data.Invertible.Bijection
import Data.Invertible.TH
dual :: a <-> Dual a
dual = [biCase|a <-> Dual a|]
endo :: (a -> a) <-> Endo a
endo = [biCase|a <-> Endo a|]
newtype BiEndo a = BiEndo { appBiEndo :: a <-> a }
#if MIN_VERSION_base(4,11,0)
instance Semigroup (BiEndo a) where
  BiEndo f <> BiEndo g = BiEndo (f C.. g)
#endif
instance Monoid (BiEndo a) where
  mempty = BiEndo C.id
  BiEndo f `mappend` BiEndo g = BiEndo (f C.. g)
biEndo :: (a <-> a) <-> BiEndo a
biEndo = [biCase|a <-> BiEndo a|]
all :: Bool <-> All
all = [biCase|a <-> All a|]
any :: Bool <-> Any
any = [biCase|a <-> Any a|]
sum :: a <-> Sum a
sum = [biCase|a <-> Sum a|]
product :: a <-> Product a
product = [biCase|a <-> Product a|]
first :: Maybe a <-> First a
first = [biCase|a <-> First a|]
last :: Maybe a <-> Last a
last = [biCase|a <-> Last a|]
alt :: f a <-> Alt f a
alt = [biCase|a <-> Alt a|]