{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TupleSections #-}
module Data.Monoid.SemiDirectProduct
( Semi, unSemi, tag, inject, untag, embed, quotient
) where
#if !MIN_VERSION_base(4,8,0)
import Data.Monoid (Monoid(..))
#endif
import Data.Semigroup (Semigroup(..))
import Data.Monoid.Action
newtype Semi s m = Semi { forall s m. Semi s m -> (s, m)
unSemi :: (s,m) }
instance (Semigroup m, Semigroup s, Action m s) => Semigroup (Semi s m) where
Semi s m
x <> :: Semi s m -> Semi s m -> Semi s m
<> Semi s m
y = forall s m. (s, m) -> Semi s m
Semi (s
xs forall a. Semigroup a => a -> a -> a
<> (m
xm forall m s. Action m s => m -> s -> s
`act` s
ys), m
xm forall a. Semigroup a => a -> a -> a
<> m
ym)
where (s
xs, m
xm) = forall s m. Semi s m -> (s, m)
unSemi Semi s m
x
(s
ys, m
ym) = forall s m. Semi s m -> (s, m)
unSemi Semi s m
y
{-# INLINE (<>) #-}
#if MIN_VERSION_base(4,8,0)
sconcat :: NonEmpty (Semi s m) -> Semi s m
sconcat = forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldr1 forall a. Semigroup a => a -> a -> a
(<>)
{-# INLINE sconcat #-}
#endif
instance (Monoid m, Monoid s, Action m s) => Monoid (Semi s m) where
mempty :: Semi s m
mempty = forall s m. (s, m) -> Semi s m
Semi (forall a. Monoid a => a
mempty, forall a. Monoid a => a
mempty)
{-# INLINE mempty #-}
#if !MIN_VERSION_base(4,11,0)
mappend x y = Semi (xs `mappend` (xm `act` ys), xm `mappend` ym)
where (xs, xm) = unSemi x
(ys, ym) = unSemi y
{-# INLINE mappend #-}
#endif
mconcat :: [Semi s m] -> Semi s m
mconcat = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall a. Monoid a => a -> a -> a
mappend forall a. Monoid a => a
mempty
{-# INLINE mconcat #-}
tag :: s -> m -> Semi s m
tag :: forall s m. s -> m -> Semi s m
tag s
s m
m = forall s m. (s, m) -> Semi s m
Semi (s
s,m
m)
inject :: Monoid m => s -> Semi s m
inject :: forall m s. Monoid m => s -> Semi s m
inject = forall s m. (s, m) -> Semi s m
Semi forall b c a. (b -> c) -> (a -> b) -> a -> c
. (,forall a. Monoid a => a
mempty)
untag :: Semi s m -> s
untag :: forall s m. Semi s m -> s
untag = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s m. Semi s m -> (s, m)
unSemi
embed :: Monoid s => m -> Semi s m
embed :: forall s m. Monoid s => m -> Semi s m
embed = forall s m. (s, m) -> Semi s m
Semi forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. Monoid a => a
mempty,)
quotient :: Semi s m -> m
quotient :: forall s m. Semi s m -> m
quotient = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s m. Semi s m -> (s, m)
unSemi