{-# LANGUAGE CPP                        #-}
{-# LANGUAGE DeriveGeneric              #-}
#if !MIN_VERSION_base(4,12,0)
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE Trustworthy                #-}
#else
{-# LANGUAGE Safe                       #-}
#endif
module Relude.Monoid
    ( 
      module Data.Monoid
    , module Data.Semigroup
    , Ap (..)
      
    , maybeToMonoid
    , memptyIfFalse
    , memptyIfTrue
    ) where
#if MIN_VERSION_base(4,12,0)
import Data.Monoid (Ap (..))
#endif
import Data.Monoid (All (..), Alt (..), Any (..), Dual (..), Endo (..), First (..), Last (..),
                    Monoid (..), Product (..), Sum (..))
import Data.Semigroup (Semigroup (sconcat, stimes, (<>)), WrappedMonoid, cycle1, mtimesDefault,
                       stimesIdempotent, stimesIdempotentMonoid, stimesMonoid)
import Relude.Bool.Reexport (Bool (..))
import Relude.Monad.Reexport (Maybe, fromMaybe)
#if !MIN_VERSION_base(4,12,0)
import GHC.Generics (Generic1)
import Relude.Applicative (Alternative, Applicative (..), liftA2)
import Relude.Base (Eq, Generic, Ord, Show)
import Relude.Enum (Bounded (..), Enum)
import Relude.Function (($), (.))
import Relude.Functor.Reexport (Functor (..))
import Relude.Monad.Reexport (Monad, MonadFail, MonadPlus)
import Relude.Numeric (Num (..))
import Relude.String.Reexport (Read)
#endif
maybeToMonoid :: Monoid m => Maybe m -> m
maybeToMonoid :: forall m. Monoid m => Maybe m -> m
maybeToMonoid = m -> Maybe m -> m
forall a. a -> Maybe a -> a
fromMaybe m
forall a. Monoid a => a
mempty
{-# INLINE maybeToMonoid #-}
memptyIfFalse :: Monoid m => Bool -> m -> m
memptyIfFalse :: forall m. Monoid m => Bool -> m -> m
memptyIfFalse Bool
p m
val = if Bool
p then m
val else m
forall a. Monoid a => a
mempty
{-# INLINE memptyIfFalse #-}
memptyIfTrue :: Monoid m => Bool -> m -> m
memptyIfTrue :: forall m. Monoid m => Bool -> m -> m
memptyIfTrue Bool
p m
val = if Bool
p then m
forall a. Monoid a => a
mempty else m
val
{-# INLINE memptyIfTrue #-}
#if !MIN_VERSION_base(4,12,0)
newtype Ap f a = Ap { getAp :: f a }
    deriving ( Alternative
             , Applicative
             , Enum
             , Eq
             , Functor
             , Generic
             , Generic1
             , Monad
             , MonadFail
             , MonadPlus
             , Ord
             , Read
             , Show
             )
instance (Applicative f, Semigroup a) => Semigroup (Ap f a) where
        (Ap x) <> (Ap y) = Ap $ liftA2 (<>) x y
instance (Applicative f, Semigroup a, Monoid a) => Monoid (Ap f a) where
        mempty = Ap $ pure mempty
        mappend = (<>)
instance (Applicative f, Bounded a) => Bounded (Ap f a) where
  minBound = pure minBound
  maxBound = pure maxBound
instance (Applicative f, Num a) => Num (Ap f a) where
  (+)         = liftA2 (+)
  (*)         = liftA2 (*)
  negate      = fmap negate
  fromInteger = pure . fromInteger
  abs         = fmap abs
  signum      = fmap signum
#endif