module Data.AdditiveGroup
  ( 
    AdditiveGroup(..), (^-^), sumV
  , Sum(..), inSum, inSum2
  ) where
import Prelude hiding (foldr)
import Control.Applicative
import Data.Monoid (Monoid(..))
import Data.Foldable (Foldable,foldr)
import Data.Complex hiding (magnitude)
import Data.Ratio
import Data.MemoTrie
infixl 6 ^+^, ^-^
class AdditiveGroup v where
  
  zeroV :: v
  
  (^+^) :: v -> v -> v
  
  negateV :: v -> v
(^-^) :: AdditiveGroup v => v -> v -> v
v ^-^ v' = v ^+^ negateV v'
sumV :: (Foldable f, AdditiveGroup v) => f v -> v
sumV = foldr (^+^) zeroV
instance AdditiveGroup () where
  zeroV     = ()
  () ^+^ () = ()
  negateV   = id
instance AdditiveGroup Int     where {zeroV=0; (^+^) = (+); negateV = negate}
instance AdditiveGroup Integer where {zeroV=0; (^+^) = (+); negateV = negate}
instance AdditiveGroup Float   where {zeroV=0; (^+^) = (+); negateV = negate}
instance AdditiveGroup Double  where {zeroV=0; (^+^) = (+); negateV = negate}
instance Integral a => AdditiveGroup (Ratio a) where
  {zeroV=0; (^+^) = (+); negateV = negate}
instance (RealFloat v, AdditiveGroup v) => AdditiveGroup (Complex v) where
  zeroV   = zeroV :+ zeroV
  (^+^)   = (+)
  negateV = negate
instance (AdditiveGroup u,AdditiveGroup v) => AdditiveGroup (u,v) where
  zeroV             = (zeroV,zeroV)
  (u,v) ^+^ (u',v') = (u^+^u',v^+^v')
  negateV (u,v)     = (negateV u,negateV v)
instance (AdditiveGroup u,AdditiveGroup v,AdditiveGroup w)
    => AdditiveGroup (u,v,w) where
  zeroV                  = (zeroV,zeroV,zeroV)
  (u,v,w) ^+^ (u',v',w') = (u^+^u',v^+^v',w^+^w')
  negateV (u,v,w)        = (negateV u,negateV v,negateV w)
instance (AdditiveGroup u,AdditiveGroup v,AdditiveGroup w,AdditiveGroup x)
    => AdditiveGroup (u,v,w,x) where
  zeroV                       = (zeroV,zeroV,zeroV,zeroV)
  (u,v,w,x) ^+^ (u',v',w',x') = (u^+^u',v^+^v',w^+^w',x^+^x')
  negateV (u,v,w,x)           = (negateV u,negateV v,negateV w,negateV x)
instance AdditiveGroup v => AdditiveGroup (a -> v) where
  zeroV   = pure   zeroV
  (^+^)   = liftA2 (^+^)
  negateV = fmap   negateV
instance AdditiveGroup a => AdditiveGroup (Maybe a) where
  zeroV = Nothing
  Nothing ^+^ b'      = b'
  a' ^+^ Nothing      = a'
  Just a' ^+^ Just b' = Just (a' ^+^ b')
  negateV = fmap negateV
instance (HasTrie u, AdditiveGroup v) => AdditiveGroup (u :->: v) where
  zeroV   = pure   zeroV
  (^+^)   = liftA2 (^+^)
  negateV = fmap   negateV
newtype Sum a = Sum { getSum :: a }
  deriving (Eq, Ord, Read, Show, Bounded)
instance Functor Sum where
  fmap f (Sum a) = Sum (f a)
instance Applicative Sum where
  pure  = Sum
  (<*>) = inSum2 ($)
instance AdditiveGroup a => Monoid (Sum a) where
  mempty  = Sum zeroV
  mappend = liftA2 (^+^)
inSum :: (a -> b) -> (Sum a -> Sum b)
inSum = getSum ~> Sum
inSum2 :: (a -> b -> c) -> (Sum a -> Sum b -> Sum c)
inSum2 = getSum ~> inSum
instance AdditiveGroup a => AdditiveGroup (Sum a) where
  zeroV   = mempty
  (^+^)   = mappend
  negateV = inSum negateV
(~>) :: (a' -> a) -> (b -> b') -> ((a -> b) -> (a' -> b'))
(i ~> o) f = o . f . i