module Data.Group where import Data.Monoid -- |A 'Group' is a 'Monoid' plus a function, 'invert', such that: -- -- @a \<> invert a == mempty@ -- -- @invert a \<> a == mempty@ class Monoid m => Group m where invert :: m -> m instance Group () where invert () = () instance Num a => Group (Sum a) where invert = Sum . negate . getSum {-# INLINE invert #-} instance Fractional a => Group (Product a) where invert = Product . recip . getProduct {-# INLINE invert #-} instance Group a => Group (Dual a) where invert = Dual . invert . getDual {-# INLINE invert #-} instance Group b => Group (a -> b) where invert f = invert . f instance (Group a, Group b) => Group (a, b) where invert (a, b) = (invert a, invert b) instance (Group a, Group b, Group c) => Group (a, b, c) where invert (a, b, c) = (invert a, invert b, invert c) instance (Group a, Group b, Group c, Group d) => Group (a, b, c, d) where invert (a, b, c, d) = (invert a, invert b, invert c, invert d) instance (Group a, Group b, Group c, Group d, Group e) => Group (a, b, c, d, e) where invert (a, b, c, d, e) = (invert a, invert b, invert c, invert d, invert e) -- |An 'Abelian' group is a 'Group' that follows the rule: -- -- @a \<> b == b \<> a@ class Group g => Abelian g instance Abelian () instance Num a => Abelian (Sum a) instance Fractional a => Abelian (Product a) instance Abelian a => Abelian (Dual a) instance Abelian b => Abelian (a -> b) instance (Abelian a, Abelian b) => Abelian (a, b) instance (Abelian a, Abelian b, Abelian c) => Abelian (a, b, c) instance (Abelian a, Abelian b, Abelian c, Abelian d) => Abelian (a, b, c, d) instance (Abelian a, Abelian b, Abelian c, Abelian d, Abelian e) => Abelian (a, b, c, d, e)