{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, GeneralizedNewtypeDeriving, FlexibleContexts, TypeOperators #-}
{-# LANGUAGE CPP #-}
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
module Data.Semigroup.Alternative
    ( Alternate(..)
    ) where
import Control.Applicative
#if __GLASGOW_HASKELL__ < 710
import Data.Monoid (Monoid(..))
#endif
import Data.Semigroup (Semigroup(..))
import Data.Semigroup.Reducer (Reducer(..))
newtype Alternate f a = Alternate { getAlternate :: f a }
  deriving (Functor,Applicative,Alternative)
instance Alternative f => Semigroup (Alternate f a) where
  Alternate a <> Alternate b = Alternate (a <|> b)
instance Alternative f => Monoid (Alternate f a) where
  mempty = empty
  Alternate a `mappend` Alternate b = Alternate (a <|> b)
instance Alternative f => Reducer (f a) (Alternate f a) where
  unit = Alternate