| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Data.Algebra
Synopsis
- (><) :: (Representable f, Algebra r (Rep f)) => f r -> f r -> f r
- (//) :: Representable f => Division r (Rep f) => f r -> f r -> f r
- (.@.) :: Representable f => Composition a (Rep f) => Semigroup (f a) => Field a => f a -> f a -> a
- unit :: Representable f => Unital r (Rep f) => f r
- norm :: (Representable f, Composition r (Rep f)) => f r -> r
- conj :: Representable f => Composition r (Rep f) => f r -> f r
- triple :: Free f => Foldable f => Algebra a (Rep f) => f a -> f a -> f a -> a
- reciprocal :: Representable f => Division a (Rep f) => f a -> f a
- class Semiring r => Algebra r a where
- multiplyWith :: (a -> a -> r) -> a -> r
- class Algebra r a => Composition r a where
- conjugateWith :: (a -> r) -> a -> r
- normWith :: (a -> r) -> r
- class (Semiring r, Algebra r a) => Unital r a where
- unitWith :: r -> a -> r
- class (Semifield r, Unital r a) => Division r a where
- reciprocalWith :: (a -> r) -> a -> r
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 IntV3 (-1) 0 0>>>V3 1 0 0 >< (V3 0 1 0 >< V3 0 1 0) :: V3 IntV3 0 0 0
Caution in general (><) needn't be commutative, nor even associative.
The cross product in particular satisfies the following properties:
a><a =memptya><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 :: QuatMQuaternion 0.000000 (V3 0.000000 0.000000 1.000000)>>>qi * qj :: QuatMQuaternion 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 25.0>>>V2 1 2 .@. V2 2 (-1)0.0>>>V3 1 1 1 .@. V3 1 1 (-2)0.0
>>>(1 :+ 2) .@. (2 :+ (-1)) :: Double0.0
>>>qi .@. qj :: Double0.0>>>qj .@. qk :: Double0.0>>>qk .@. qi :: Double0.0>>>qk .@. qk :: Double1.0
unit :: Representable f => Unital r (Rep f) => f r Source #
Unit of a unital algebra.
>>>unit :: Complex Int1 :+ 0>>>unit :: QuatDQuaternion 1.0 (V3 0.0 0.0 0.0)
norm :: (Representable f, Composition r (Rep f)) => f r -> r Source #
conj :: Representable f => Composition r (Rep f) => f r -> f r Source #
reciprocal :: Representable f => Division a (Rep f) => f a -> f a Source #
reciprocalx = (/quadrancex)<$>conjx
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 # | |
Defined in Data.Algebra Methods multiplyWith :: (() -> () -> r) -> () -> r Source # | |
| Ring r => Algebra r QuaternionBasis Source # | |
Defined in Data.Semimodule.Vector Methods multiplyWith :: (QuaternionBasis -> QuaternionBasis -> r) -> QuaternionBasis -> r Source # | |
| Ring r => Algebra r I3 Source # | |
Defined in Data.Semimodule.Vector | |
| Semiring r => Algebra r I2 Source # | |
Defined in Data.Semimodule.Vector | |
| Semiring r => Algebra r [a] Source # | Tensor algebra
|
Defined in Data.Algebra Methods multiplyWith :: ([a] -> [a] -> r) -> [a] -> r Source # | |
| (Algebra r a, Algebra r b) => Algebra r (a, b) Source # | |
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 # | |
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.
Instances
| Ring r => Composition r QuaternionBasis Source # | |
Defined in Data.Semimodule.Vector Methods conjugateWith :: (QuaternionBasis -> r) -> QuaternionBasis -> r Source # normWith :: (QuaternionBasis -> r) -> r Source # | |
| Ring r => Composition r I3 Source # | |
Defined in Data.Semimodule.Vector | |
| Semiring r => Composition r I2 Source # | |
Defined in Data.Semimodule.Vector | |
class (Semiring r, Algebra r a) => Unital r a where Source #
Instances
| Semiring r => Unital r () Source # | |
Defined in Data.Algebra | |
| Ring r => Unital r QuaternionBasis Source # | |
Defined in Data.Semimodule.Vector Methods unitWith :: r -> QuaternionBasis -> r Source # | |
| Semiring r => Unital r [a] Source # | |
Defined in Data.Algebra | |
| (Unital r a, Unital r b) => Unital r (a, b) Source # | |
Defined in Data.Algebra | |
| (Unital r a, Unital r b, Unital r c) => Unital r (a, b, c) Source # | |
Defined in Data.Algebra | |
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 # | |
Defined in Data.Semimodule.Vector Methods reciprocalWith :: (QuaternionBasis -> r) -> QuaternionBasis -> r Source # | |