rings-0.0.3: Ring-like objects.

Safe HaskellSafe
LanguageHaskell2010

Data.Algebra

Synopsis

Documentation

(><) :: (Representable f, Algebra r (Rep f)) => f r -> f r -> f r infixl 7 Source #

Multiplication operator on a free algebra.

In particular this is cross product on the I3 basis in R^3:

>>> V3 1 0 0 >< V3 0 1 0 >< V3 0 1 0 :: V3 Int
V3 (-1) 0 0
>>> V3 1 0 0 >< (V3 0 1 0 >< V3 0 1 0) :: V3 Int
V3 0 0 0

Caution in general (><) needn't be commutative, nor even associative.

The cross product in particular satisfies the following properties:

a >< a = mempty
a >< b = negate ( b >< a ) , 
a >< ( b <> c ) = ( a >< b ) <> ( a >< c ) , 
( r a ) >< b = a >< ( r b ) = r ( a >< b ) . 
a >< ( b >< c ) <> b >< ( c >< a ) <> c >< ( a >< b ) = mempty . 

See Jacobi identity.

For associative algebras, use (*) instead for clarity:

>>> (1 :+ 2) >< (3 :+ 4) :: Complex Int
(-5) :+ 10
>>> (1 :+ 2) * (3 :+ 4) :: Complex Int
(-5) :+ 10
>>> qi >< qj :: QuatM
Quaternion 0.000000 (V3 0.000000 0.000000 1.000000)
>>> qi * qj :: QuatM
Quaternion 0.000000 (V3 0.000000 0.000000 1.000000)

(//) :: Representable f => Division r (Rep f) => f r -> f r -> f r infixl 7 Source #

Division operator on a free division algebra.

>>> (1 :+ 0) // (0 :+ 1)
0.0 :+ (-1.0)

(.@.) :: Representable f => Composition a (Rep f) => Semigroup (f a) => Field a => f a -> f a -> a infix 6 Source #

Bilinear form on a free composition algebra.

>>> V2 1 2 .@. V2 1 2
5.0
>>> V2 1 2 .@. V2 2 (-1)
0.0
>>> V3 1 1 1 .@. V3 1 1 (-2)
0.0
>>> (1 :+ 2) .@. (2 :+ (-1)) :: Double
0.0
>>> qi .@. qj :: Double
0.0
>>> qj .@. qk :: Double
0.0
>>> qk .@. qi :: Double
0.0
>>> qk .@. qk :: Double
1.0

unit :: Representable f => Unital r (Rep f) => f r Source #

Unit of a unital algebra.

>>> unit :: Complex Int
1 :+ 0
>>> unit :: QuatD
Quaternion 1.0 (V3 0.0 0.0 0.0)

norm :: (Representable f, Composition r (Rep f)) => f r -> r Source #

Norm of a composition algebra.

norm x * norm y = norm (x >< y)
norm . norm' $ x = norm x * norm x

conj :: Representable f => Composition r (Rep f) => f r -> f r Source #

triple :: Free f => Foldable f => Algebra a (Rep f) => f a -> f a -> f a -> a Source #

Scalar triple product.

triple x y z = triple z x y = triple y z x
triple x y z = negate $ triple x z y = negate $ triple y x z
triple x x y = triple x y y = triple x y x = zero
(triple x y z) *. x = (x >< y) >< (x >< z)
>>> triple (V3 0 0 1) (V3 1 0 0) (V3 0 1 0) :: Double
1.0

reciprocal :: Representable f => Division a (Rep f) => f a -> f a Source #

class Semiring r => Algebra r a where Source #

Algebra over a semiring.

Needn't be associative or unital.

Methods

multiplyWith :: (a -> a -> r) -> a -> r Source #

Instances
Semiring r => Algebra r () Source # 
Instance details

Defined in Data.Algebra

Methods

multiplyWith :: (() -> () -> r) -> () -> r Source #

Ring r => Algebra r QuaternionBasis Source # 
Instance details

Defined in Data.Semimodule.Vector

Ring r => Algebra r I3 Source # 
Instance details

Defined in Data.Semimodule.Vector

Methods

multiplyWith :: (I3 -> I3 -> r) -> I3 -> r Source #

Semiring r => Algebra r I2 Source # 
Instance details

Defined in Data.Semimodule.Vector

Methods

multiplyWith :: (I2 -> I2 -> r) -> I2 -> r Source #

Semiring r => Algebra r [a] Source #

Tensor algebra

>>> multiplyWith (<>) [1..3 :: Int]
[1,2,3,1,2,3,1,2,3,1,2,3]
>>> multiplyWith (\f g -> fold (f ++ g)) [1..3] :: Int
24
Instance details

Defined in Data.Algebra

Methods

multiplyWith :: ([a] -> [a] -> r) -> [a] -> r Source #

(Algebra r a, Algebra r b) => Algebra r (a, b) Source # 
Instance details

Defined in Data.Algebra

Methods

multiplyWith :: ((a, b) -> (a, b) -> r) -> (a, b) -> r Source #

(Algebra r a, Algebra r b, Algebra r c) => Algebra r (a, b, c) Source # 
Instance details

Defined in Data.Algebra

Methods

multiplyWith :: ((a, b, c) -> (a, b, c) -> r) -> (a, b, c) -> r Source #

class Algebra r a => Composition r a where Source #

Composition algebra over a free semimodule.

Methods

conjugateWith :: (a -> r) -> a -> r Source #

normWith :: (a -> r) -> r Source #

Instances
Ring r => Composition r QuaternionBasis Source # 
Instance details

Defined in Data.Semimodule.Vector

Ring r => Composition r I3 Source # 
Instance details

Defined in Data.Semimodule.Vector

Methods

conjugateWith :: (I3 -> r) -> I3 -> r Source #

normWith :: (I3 -> r) -> r Source #

Semiring r => Composition r I2 Source # 
Instance details

Defined in Data.Semimodule.Vector

Methods

conjugateWith :: (I2 -> r) -> I2 -> r Source #

normWith :: (I2 -> r) -> r Source #

class (Semiring r, Algebra r a) => Unital r a where Source #

Methods

unitWith :: r -> a -> r Source #

Instances
Semiring r => Unital r () Source # 
Instance details

Defined in Data.Algebra

Methods

unitWith :: r -> () -> r Source #

Ring r => Unital r QuaternionBasis Source # 
Instance details

Defined in Data.Semimodule.Vector

Methods

unitWith :: r -> QuaternionBasis -> r Source #

Semiring r => Unital r [a] Source # 
Instance details

Defined in Data.Algebra

Methods

unitWith :: r -> [a] -> r Source #

(Unital r a, Unital r b) => Unital r (a, b) Source # 
Instance details

Defined in Data.Algebra

Methods

unitWith :: r -> (a, b) -> r Source #

(Unital r a, Unital r b, Unital r c) => Unital r (a, b, c) Source # 
Instance details

Defined in Data.Algebra

Methods

unitWith :: r -> (a, b, c) -> r Source #

class (Semifield r, Unital r a) => Division r a where Source #

A (not necessarily associative) division algebra.

Methods

reciprocalWith :: (a -> r) -> a -> r Source #

Instances
Field r => Division r QuaternionBasis Source # 
Instance details

Defined in Data.Semimodule.Vector