cayley-dickson-0.1.3.0: Complex numbers, quaternions, octonions, sedenions, etc.

Copyright(c) James M. Lawrence
LicenseMIT
MaintainerJames M. Lawrence <llmjjmll@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Math.CayleyDickson

Contents

Description

Cayley-Dickson constructions (complex numbers, quaternions, octonions, sedenions, etc.) over general scalars without limit to the number of dimensions.

An element of this structure is composed of an m-dimensional scalar part and an m*(2^n - 1)-dimensional pure part (unrelated to Haskell's uses of "pure"). An element whose scalar part is zero is called a pure. Construction with real scalars yields the Cayley-Dickson algebras, in which case the scalar part is also called the real part. Other structures may be obtained by considering general scalars, for instance the quaternions over complex scalars.

Synopsis

Types

data Nion n a Source

General Cayley-Dickson construction producing "N-ions". The first parameter is a Tag instance that determines the dimension, which is 2 raised to tagVal. The second parameter is the scalar type.

Instances

Functor (Nion n) Source 
Tag n => Applicative (Nion n) Source 
Foldable (Nion n) Source 
Traversable (Nion n) Source 
(Conjugable a, Eq a) => Eq (Nion n a) Source 
(Tag n, Conjugable a, RealFloat a) => Floating (Nion n a) Source

The first pure basis element is arbitrarily chosen as sqrt (-1).

(Conjugable a, Fractional a) => Fractional (Nion n a) Source 
Conjugable a => Num (Nion n a) Source 
(Tag n, Show a, Num a) => Show (Nion n a) Source 
Conjugable a => Conjugable (Nion n a) Source 

type Complex a = Nion Tag1 a Source

Complex numbers, the 2^1-dimensional construction.

type Quaternion a = Nion Tag2 a Source

Quaternions, the 2^2-dimensional construction.

type Octonion a = Nion Tag3 a Source

Octonions, the 2^3-dimensional construction.

type Sedenion a = Nion Tag4 a Source

Sedenions, the 2^4-dimensional construction.

Construction

nion :: (Tag n, Num a) => [a] -> Nion n a Source

Construct an element from a list of coordinates. If the list is too small then the remaining coordinates are padded with zeros. If the list is too large then the extra values are ignored.

fromScalar :: a -> Nion n a Source

Promote a scalar, returning an element whose scalar part is the argument and whose pure part is zero. The element behaves as if it were padded with zeros, but no actual padding is done.

complex :: a -> a -> Complex a Source

Construct a complex number.

quaternion :: a -> a -> a -> a -> Quaternion a Source

Construct a quaternion.

octonion :: a -> a -> a -> a -> a -> a -> a -> a -> Octonion a Source

Construct an octonion.

sedenion :: a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> Sedenion a Source

Construct a sedenion.

Operations

dot :: Conjugable a => Nion n a -> Nion n a -> a Source

Dot product (actually the Hermitian inner product, a generalization of the dot product).

cross :: Conjugable a => Nion n a -> Nion n a -> Nion n a Source

Cross product.

sqnorm :: Conjugable a => Nion n a -> a Source

Squared norm: the dot product of an element with itself.

norm :: (Conjugable a, Floating a) => Nion n a -> a Source

Square root of sqnorm.

polar :: (Tag n, Conjugable a, RealFloat a) => Nion n a -> (a, a, Nion n a) Source

Return (s, t, u) such that (approximately)

x == s .* exp (t .* u)

where s and t are scalars, s >= 0, and u is a unit pure.

If x has no pure part then u is arbitrarily chosen to be the first pure basis element.

Operations with scalars

The mnemonic is that the period (".") is on the side of the scalar.

(^.) :: (Conjugable a, Integral b) => Nion n a -> b -> Nion n a infixr 8 Source

Raise to a non-negative integral power.

(^^.) :: (Conjugable a, Fractional a, Integral b) => Nion n a -> b -> Nion n a infixr 8 Source

Raise to an integral power.

(**.) :: (Tag n, Conjugable a, RealFloat a) => Nion n a -> a -> Nion n a infixr 8 Source

Raise to a scalar power.

(.+) :: Conjugable a => a -> Nion n a -> Nion n a infix 6 Source

Equivalent to fromScalar x + y.

(+.) :: Conjugable a => Nion n a -> a -> Nion n a infix 6 Source

Equivalent to x + fromScalar y.

(.-) :: Conjugable a => a -> Nion n a -> Nion n a infix 6 Source

Equivalent to fromScalar x - y.

(-.) :: Conjugable a => Nion n a -> a -> Nion n a infix 6 Source

Equivalent to x - fromScalar y.

(.*) :: Conjugable a => a -> Nion n a -> Nion n a infix 7 Source

Equivalent to fromScalar x * y.

(*.) :: Conjugable a => Nion n a -> a -> Nion n a infix 7 Source

Equivalent to x * fromScalar y.

(/.) :: (Conjugable a, Fractional a) => Nion n a -> a -> Nion n a infix 7 Source

Equivalent to x / fromScalar y.

Accessors

coord :: (Tag n, Num a, Integral b, Bits b) => Nion n a -> b -> a Source

Get the nth coordinate.

coords :: (Tag n, Num a) => Nion n a -> [a] Source

List of coordinates for this element.

setCoord :: (Tag n, Conjugable a, Num b, Bits b) => Nion n a -> b -> a -> Nion n a Source

Set the nth coordinate, returning a new element.

scalarPart :: Nion n a -> a Source

Equivalent to coord x 0.

purePart :: Num a => Nion n a -> Nion n a Source

Equivalent to setCoord x 0 0.

Constants

basisElement :: (Tag n, Conjugable a, Bits i, Integral i) => i -> Nion n a Source

The nth basis element.

Classes

class Num a => Conjugable a where Source

The conjugate of an element is obtained by negating the pure part and conjugating the scalar part. The conjugate of a real number (which has no pure part) is the identity (id).

Methods

conj :: a -> a Source

Tags

class Tag n where Source

Tags serve to determine a type's dimension, which is 2 raised to tagVal. Tag instances are included for convenience only, as you may create your own tag.

Methods

tagVal :: Proxy n -> Integer Source

data Tag0 Source

Instances

data Tag1 Source

Instances

data Tag2 Source

Instances

data Tag3 Source

Instances

data Tag4 Source

Instances

data Tag5 Source

Instances

data Tag6 Source

Instances

data Tag7 Source

Instances

data Tag8 Source

Instances

data Tag9 Source

Instances

data Tag10 Source

Instances

data Tag11 Source

Instances

data Tag12 Source

Instances

data Tag13 Source

Instances

data Tag14 Source

Instances

data Tag15 Source

Instances

data Tag16 Source

Instances

data Tag17 Source

Instances

data Tag18 Source

Instances

data Tag19 Source

Instances

data Tag20 Source

Instances

data Tag21 Source

Instances

data Tag22 Source

Instances

data Tag23 Source

Instances

data Tag24 Source

Instances

data Tag25 Source

Instances

data Tag26 Source

Instances

data Tag27 Source

Instances

data Tag28 Source

Instances

data Tag29 Source

Instances

data Tag30 Source

Instances