Copyright | (c) James M. Lawrence |
---|---|
License | MIT |
Maintainer | James M. Lawrence <llmjjmll@gmail.com> |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
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.
- data Nion n a
- type Complex a = Nion Tag1 a
- type Quaternion a = Nion Tag2 a
- type Octonion a = Nion Tag3 a
- type Sedenion a = Nion Tag4 a
- nion :: (Tag n, Num a) => [a] -> Nion n a
- fromScalar :: a -> Nion n a
- complex :: a -> a -> Complex a
- quaternion :: a -> a -> a -> a -> Quaternion a
- octonion :: a -> a -> a -> a -> a -> a -> a -> a -> Octonion a
- sedenion :: a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> Sedenion a
- dot :: Conjugable a => Nion n a -> Nion n a -> a
- cross :: Conjugable a => Nion n a -> Nion n a -> Nion n a
- sqnorm :: Conjugable a => Nion n a -> a
- norm :: (Conjugable a, Floating a) => Nion n a -> a
- polar :: (Tag n, Conjugable a, RealFloat a) => Nion n a -> (a, a, Nion n a)
- (**.) :: (Tag n, Conjugable a, RealFloat a) => Nion n a -> a -> Nion n a
- (.+) :: Conjugable a => a -> Nion n a -> Nion n a
- (+.) :: Conjugable a => Nion n a -> a -> Nion n a
- (.-) :: Conjugable a => a -> Nion n a -> Nion n a
- (-.) :: Conjugable a => Nion n a -> a -> Nion n a
- (.*) :: Conjugable a => a -> Nion n a -> Nion n a
- (*.) :: Conjugable a => Nion n a -> a -> Nion n a
- (/.) :: (Conjugable a, Fractional a) => Nion n a -> a -> Nion n a
- coord :: (Tag n, Num a, Integral b, Bits b) => Nion n a -> b -> a
- coords :: (Tag n, Num a) => Nion n a -> [a]
- setCoord :: (Tag n, Conjugable a, Integral b, Bits b) => Nion n a -> b -> a -> Nion n a
- scalarPart :: Nion n a -> a
- purePart :: Num a => Nion n a -> Nion n a
- basisElement :: (Tag n, Conjugable a, Bits i, Integral i) => i -> Nion n a
- class Num a => Conjugable a where
- conj :: a -> a
- scalarPart' :: a -> a
- class Tag n where
- data Tag0
- data Tag1
- data Tag2
- data Tag3
- data Tag4
- data Tag5
- data Tag6
- data Tag7
- data Tag8
- data Tag9
- data Tag10
- data Tag11
- data Tag12
- data Tag13
- data Tag14
- data Tag15
- data Tag16
- data Tag17
- data Tag18
- data Tag19
- data Tag20
- data Tag21
- data Tag22
- data Tag23
- data Tag24
- data Tag25
- data Tag26
- data Tag27
- data Tag28
- data Tag29
- data Tag30
Types
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.
(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 Quaternion a = Nion Tag2 a Source
Quaternions, the 2^2-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.
quaternion :: a -> a -> a -> a -> Quaternion a Source
Construct a quaternion.
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. (1 `dot`)
is equivalent to
.scalarPart
cross :: Conjugable a => Nion n a -> Nion n a -> Nion n a Source
Cross product. (1 `cross`)
is equivalent to
. The
cross product of two pures yields an element that is orthogonal to
both operands.purePart
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.
(**.) :: (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
setCoord :: (Tag n, Conjugable a, Integral 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
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 is the identity (id
), which is the default implementation.
Nothing
Tags
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.