{-#LANGUAGE MultiParamTypeClasses #-} {-#LANGUAGE FlexibleInstances #-} -- | Typeclasses for Group and Tensor, extending 'Monoid'. module Data.Tensor ( module Data.Monoid , Group (..) , Tensor (..) ) where import Data.Monoid -- | A group is a monoid with an invert operation. -- Intuition: '><' is to '<>' what subtraction is to addition; 'invert' turns a -- value into its complement (see Laws below), and corresponds with unary minus -- in addition. -- -- Laws: -- -- > a >< b == a <> (invert b) -- > a >< mempty == a -- > a >< a == mempty -- > a <> (invert a) == mempty -- > invert mempty == mempty -- class Monoid a => Group a where -- | Dual to '<>'. (><) :: a -> a -> a a >< b = a <> invert b -- | \"Negation\": convert an operand into its dual. invert :: a -> a invert x = mempty >< x infixl 6 >< instance Num a => Group (Sum a) where invert = Sum . negate . getSum -- | Tensor allows us to define a relationship between two types, the second -- one forming a Group. -- The intuition is that the first type models something like a -- "location", and the second (the group) models the relative distance between -- two locations. Examples of Tensors include date/time values (point in time) -- and timespans; positions in a vector space and displacement vectors; -- pitches and intervals in music. -- -- Tensor provides three operations: '?<>' (\"tensor addition\"), adding a -- \"distance\" to a \"location\"; '?><' (\"tensor subtraction\"), undoing the effect -- of adding a \"distance\" to a \"location\", and '>?<', getting the \"distance\" -- between two \"locations\". -- -- Laws: -- -- > a ?<> (b >?< a) == b -- > a ?<> (x <> y) == a ?<> x ?<> y -- > a ?>< b == a ?<> (invert b) -- > a ?<> (x >< y) == a ?<> x ?>< y class Group b => Tensor a b where (?<>) :: a -> b -> a (?><) :: a -> b -> a (>?<) :: a -> a -> b a ?>< b = a ?<> invert b infixl 6 ?<> infixl 6 ?>< infixl 6 >?< -- | All groups trivially form tensors with themselves instance Group a => Tensor a a where (?<>) = (<>) (?><) = (><) (>?<) = (><)