{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-} module Clean.Monoid where import qualified Prelude as P import Clean.Core class Nil z where zero :: z instance Nil () where zero = () instance Nil Int where zero = 0 instance Nil [a] where zero = [] instance (Nil a,Nil b) => Nil (a:*:b) where zero = (zero,zero) instance Nil a => Nil (a:+:b) where zero = Left zero class Nil m => Monoid m where (+) :: m -> m -> m instance Monoid () where _+_ = () instance Monoid Int where (+) = (P.+) instance Monoid [a] where []+l = l ; (x:t)+l = x:(t+l) instance (Monoid a,Monoid b) => Monoid (a:*:b) where (a,b)+(c,d) = (a+c,b+d) instance Submonoid b a => Monoid (a:+:b) where Left a+Left b = Left (a+b) a+b = Right (from a+from b) where from = to <|> id class (Monoid a,Monoid b) => Submonoid a b where to :: b -> a instance Monoid a => Submonoid a () where to _ = zero newtype Endo k a = Endo { runEndo :: k a a } instance Category k => Nil (Endo k a) where zero = Endo id instance Category k => Monoid (Endo k a) where Endo f+Endo g = Endo (f . g)