-- | A semigroup is a binary associative operation. module Data.Semigroup( Semigroup((.++.)), (<++>) ) where import Data.Monoid import Data.Sequence import qualified Data.Set as S import qualified Data.Map as M import qualified Data.IntSet as IS import qualified Data.IntMap as IM import qualified Data.ByteString as B import Control.Monad.Identity import Control.Applicative -- | A binary operation that must satisfy associativity. Unlike a @Monoid@, an identity in not essential. class Semigroup a where (.++.) :: a -> a -> a -- | A binary associative operation lifted into an applicative functor. (<++>) :: (Applicative f, Semigroup a) => f a -> f a -> f a (<++>) = liftA2 (.++.) instance Monoid a => Semigroup (Identity a) where (.++.) = liftM2 mappend instance Semigroup () where _ .++. _ = () instance Semigroup b => Semigroup (a -> b) where (.++.) = (<++>) instance Semigroup a => Semigroup (IO a) where (.++.) = (<++>) instance (Semigroup a, Semigroup b) => Semigroup (a, b) where (a1, b1) .++. (a2, b2) = (a1 .++. a2, b1 .++. b2) instance (Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c) where (a1, b1, c1) .++. (a2, b2, c2) = (a1 .++. a2, b1 .++. b2, c1 .++. c2) instance (Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d) where (a1, b1, c1, d1) .++. (a2, b2, c2, d2) = (a1 .++. a2, b1 .++. b2, c1 .++. c2, d1 .++. d2) instance (Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e) where (a1, b1, c1, d1, e1) .++. (a2, b2, c2, d2, e2) = (a1 .++. a2, b1 .++. b2, c1 .++. c2, d1 .++. d2, e1 .++. e2) instance Semigroup Ordering where a .++. b = runIdentity (Identity a .++. Identity b) instance Semigroup All where a .++. b = runIdentity (Identity a .++. Identity b) instance Semigroup Any where a .++. b = runIdentity (Identity a .++. Identity b) instance Semigroup a => Semigroup (Dual a) where Dual a .++. Dual b = Dual (b .++. a) instance Semigroup (Endo a) where a .++. b = runIdentity (Identity a .++. Identity b) instance Num a => Semigroup (Product a) where a .++. b = runIdentity (Identity a .++. Identity b) instance Num a => Semigroup (Sum a) where a .++. b = runIdentity (Identity a .++. Identity b) instance Semigroup a => Semigroup (Maybe a) where Nothing .++. b = b a .++. Nothing = a Just a .++. Just b = Just (a .++. b) instance Semigroup (First a) where a .++. b = runIdentity (Identity a .++. Identity b) instance Semigroup (Last a) where a .++. b = runIdentity (Identity a .++. Identity b) instance Semigroup [a] where (.++.) = (++) instance Semigroup (Seq a) where (.++.) = mappend instance Ord a => Semigroup (S.Set a) where (.++.) = mappend instance Ord k => Semigroup (M.Map k v) where (.++.) = mappend instance Semigroup IS.IntSet where (.++.) = mappend instance Semigroup (IM.IntMap v) where (.++.) = mappend instance Semigroup B.ByteString where (.++.) = mappend