| Copyright | (C) 2017-2022 Nathan Waivio |
|---|---|
| License | BSD3 |
| Maintainer | Nathan Waivio <nathan.waivio@gmail.com> |
| Stability | Stable |
| Portability | unportable |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Algebra.Geometric.Cl3
Contents
- The type for the Algebra of Physical Space
- Clifford Conjugate and Complex Conjugate
- The littlest singular value
- Constructor Selectors - For optimizing and simplifying calculations
- Pretty Printing for use with Octave
- Eliminate grades that are less than
tolto use a simpler Constructor - Compact Storable types for the Cl3 Constructors with smart constructors
- Random Instances
- Helpful Functions
Description
Library implementing standard functions for the Algebra of Physical Space Cl(3,0)
Synopsis
- data Cl3 where
- R :: !Double -> Cl3
- V3 :: !Double -> !Double -> !Double -> Cl3
- BV :: !Double -> !Double -> !Double -> Cl3
- I :: !Double -> Cl3
- PV :: !Double -> !Double -> !Double -> !Double -> Cl3
- H :: !Double -> !Double -> !Double -> !Double -> Cl3
- C :: !Double -> !Double -> Cl3
- BPV :: !Double -> !Double -> !Double -> !Double -> !Double -> !Double -> Cl3
- ODD :: !Double -> !Double -> !Double -> !Double -> Cl3
- TPV :: !Double -> !Double -> !Double -> !Double -> Cl3
- APS :: !Double -> !Double -> !Double -> !Double -> !Double -> !Double -> !Double -> !Double -> Cl3
- bar :: Cl3 -> Cl3
- dag :: Cl3 -> Cl3
- lsv :: Cl3 -> Cl3
- toR :: Cl3 -> Cl3
- toV3 :: Cl3 -> Cl3
- toBV :: Cl3 -> Cl3
- toI :: Cl3 -> Cl3
- toPV :: Cl3 -> Cl3
- toH :: Cl3 -> Cl3
- toC :: Cl3 -> Cl3
- toBPV :: Cl3 -> Cl3
- toODD :: Cl3 -> Cl3
- toTPV :: Cl3 -> Cl3
- toAPS :: Cl3 -> Cl3
- showOctave :: Cl3 -> String
- reduce :: Cl3 -> Cl3
- tol :: Cl3
- data Cl3_R
- toCl3_R :: Cl3 -> Cl3_R
- fromCl3_R :: Cl3_R -> Cl3
- data Cl3_V3
- toCl3_V3 :: Cl3 -> Cl3_V3
- fromCl3_V3 :: Cl3_V3 -> Cl3
- data Cl3_BV
- toCl3_BV :: Cl3 -> Cl3_BV
- fromCl3_BV :: Cl3_BV -> Cl3
- data Cl3_I
- toCl3_I :: Cl3 -> Cl3_I
- fromCl3_I :: Cl3_I -> Cl3
- data Cl3_PV
- toCl3_PV :: Cl3 -> Cl3_PV
- fromCl3_PV :: Cl3_PV -> Cl3
- data Cl3_H
- toCl3_H :: Cl3 -> Cl3_H
- fromCl3_H :: Cl3_H -> Cl3
- data Cl3_C
- toCl3_C :: Cl3 -> Cl3_C
- fromCl3_C :: Cl3_C -> Cl3
- data Cl3_BPV
- toCl3_BPV :: Cl3 -> Cl3_BPV
- fromCl3_BPV :: Cl3_BPV -> Cl3
- data Cl3_ODD
- toCl3_ODD :: Cl3 -> Cl3_ODD
- fromCl3_ODD :: Cl3_ODD -> Cl3
- data Cl3_TPV
- toCl3_TPV :: Cl3 -> Cl3_TPV
- fromCl3_TPV :: Cl3_TPV -> Cl3
- data Cl3_APS
- toCl3_APS :: Cl3 -> Cl3_APS
- fromCl3_APS :: Cl3_APS -> Cl3
- randR :: RandomGen g => g -> (Cl3, g)
- rangeR :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g)
- randV3 :: RandomGen g => g -> (Cl3, g)
- rangeV3 :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g)
- randBV :: RandomGen g => g -> (Cl3, g)
- rangeBV :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g)
- randI :: RandomGen g => g -> (Cl3, g)
- rangeI :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g)
- randPV :: RandomGen g => g -> (Cl3, g)
- rangePV :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g)
- randH :: RandomGen g => g -> (Cl3, g)
- rangeH :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g)
- randC :: RandomGen g => g -> (Cl3, g)
- rangeC :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g)
- randBPV :: RandomGen g => g -> (Cl3, g)
- rangeBPV :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g)
- randODD :: RandomGen g => g -> (Cl3, g)
- rangeODD :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g)
- randTPV :: RandomGen g => g -> (Cl3, g)
- rangeTPV :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g)
- randAPS :: RandomGen g => g -> (Cl3, g)
- rangeAPS :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g)
- randUnitV3 :: RandomGen g => g -> (Cl3, g)
- randProjector :: RandomGen g => g -> (Cl3, g)
- randNilpotent :: RandomGen g => g -> (Cl3, g)
- randUnitary :: RandomGen g => g -> (Cl3, g)
- eigvals :: Cl3 -> (Cl3, Cl3)
- hasNilpotent :: Cl3 -> Bool
- spectraldcmp :: (Cl3 -> Cl3) -> (Cl3 -> Cl3) -> Cl3 -> Cl3
- project :: Cl3 -> Cl3
- mIx :: Cl3 -> Cl3
- timesI :: Cl3 -> Cl3
- abssignum :: Cl3 -> (Cl3, Cl3)
The type for the Algebra of Physical Space
Cl3 provides specialized constructors for sub-algebras and other geometric objects contained in the algebra. Cl(3,0), abbreviated to Cl3, is a Geometric Algebra of 3 dimensional space known as the Algebra of Physical Space (APS). Geometric Algebras are Real Clifford Algebras, double precision floats are used to approximate real numbers in this library. Single and Double grade combinations are specialized using algebraic datatypes and live within the APS.
Ris the constructor for the Real Scalar Sub-algebra Grade-0V3is the Three Dimensional Real Vector constructor Grade-1BVis the Bivector constructor Grade-2 an Imaginary Three Dimensional VectorIis the Imaginary constructor Grade-3 and is the Pseudo-Scalar for APSPVis the Paravector constructor with Grade-0 and Grade-1 elements, a Real Scalar plus Vector, (R + V3)His the Quaternion constructor it is the Even Sub-algebra with Grade-0 and Grade-2 elements, a Real Scalar plus Bivector, (R + BV)Cis the Complex constructor it is the Scalar Sub-algebra with Grade-0 and Grade-3 elements, a Real Scalar plus Imaginar Scalar, (R + I)BPVis the Biparavector constructor with Grade-1 and Grade-2 elements, a Real Vector plus Bivector, (V3 + BV)ODDis the Odd constructor with Grade-1 and Grade-3 elements, a Vector plus Imaginary Scalar, (V3 + I)TPVis the Triparavector constructor with Grade-2 and Grade-3 elements, a Bivector plus Imaginary, (BV + I)APSis the constructor for an element in the Algebra of Physical Space with Grade-0 through Grade-3 elements
Constructors
| R :: !Double -> Cl3 | |
| V3 :: !Double -> !Double -> !Double -> Cl3 | |
| BV :: !Double -> !Double -> !Double -> Cl3 | |
| I :: !Double -> Cl3 | |
| PV :: !Double -> !Double -> !Double -> !Double -> Cl3 | |
| H :: !Double -> !Double -> !Double -> !Double -> Cl3 | |
| C :: !Double -> !Double -> Cl3 | |
| BPV :: !Double -> !Double -> !Double -> !Double -> !Double -> !Double -> Cl3 | |
| ODD :: !Double -> !Double -> !Double -> !Double -> Cl3 | |
| TPV :: !Double -> !Double -> !Double -> !Double -> Cl3 | |
| APS :: !Double -> !Double -> !Double -> !Double -> !Double -> !Double -> !Double -> !Double -> Cl3 |
Instances
Clifford Conjugate and Complex Conjugate
The littlest singular value
Constructor Selectors - For optimizing and simplifying calculations
Pretty Printing for use with Octave
showOctave :: Cl3 -> String Source #
showOctave for useful for debug purposes.
The additional octave definition is needed:
e0 = [1,0;0,1]; e1=[0,1;1,0]; e2=[0,-i;i,0]; e3=[1,0;0,-1];
This allows one to take advantage of the isomorphism between Cl3 and M(2,C)
Eliminate grades that are less than tol to use a simpler Constructor
reduce function reduces the number of grades in a specialized Cliffor if they
are zero-ish
Compact Storable types for the Cl3 Constructors with smart constructors
Cl3_R a compact storable data type for R.
Instances
| Read Cl3_R Source # | |
| Show Cl3_R Source # | |
| Storable Cl3_R Source # | |
toCl3_R :: Cl3 -> Cl3_R Source #
toCl3_R converts a Cl3 value constructed with R to its compact form.
Cl3_V3 a compact storable data type for V3.
Instances
| Read Cl3_V3 Source # | |
| Show Cl3_V3 Source # | |
| Storable Cl3_V3 Source # | |
toCl3_V3 :: Cl3 -> Cl3_V3 Source #
toCl3_V3 converts a Cl3 value constructed with V3 to its compact form.
fromCl3_V3 :: Cl3_V3 -> Cl3 Source #
fromCl3_V3 converts the compact Cl3_V3 type back to a Cl3 type.
Cl3_BV a compact storable data type for BV.
Instances
| Read Cl3_BV Source # | |
| Show Cl3_BV Source # | |
| Storable Cl3_BV Source # | |
toCl3_BV :: Cl3 -> Cl3_BV Source #
toCl3_BV converts a Cl3 value constructed with BV to its compact form.
fromCl3_BV :: Cl3_BV -> Cl3 Source #
fromCl3_BV converts the compact Cl3_BV type back to a Cl3 type.
Cl3_I a compact storable data type for I.
Instances
| Read Cl3_I Source # | |
| Show Cl3_I Source # | |
| Storable Cl3_I Source # | |
toCl3_I :: Cl3 -> Cl3_I Source #
toCl3_I converts a Cl3 value constructed with I to its compact form.
Cl3_PV a compact storable data type for PV.
Instances
| Read Cl3_PV Source # | |
| Show Cl3_PV Source # | |
| Storable Cl3_PV Source # | |
toCl3_PV :: Cl3 -> Cl3_PV Source #
toCl3_PV converts a Cl3 value constructed with PV to its compact form.
fromCl3_PV :: Cl3_PV -> Cl3 Source #
fromCl3_PV converts the compact Cl3_PV type back to a Cl3 type.
Cl3_H a compact storable data type for H.
Instances
| Read Cl3_H Source # | |
| Show Cl3_H Source # | |
| Storable Cl3_H Source # | |
toCl3_H :: Cl3 -> Cl3_H Source #
toCl3_H converts a Cl3 value constructed with H to its compact form.
Cl3_C a compact storable data type for C.
Instances
| Read Cl3_C Source # | |
| Show Cl3_C Source # | |
| Storable Cl3_C Source # | |
toCl3_C :: Cl3 -> Cl3_C Source #
toCl3_C converts a Cl3 value constructed with C to its compact form.
Cl3_BPV a compact storable data type for BPV.
Instances
| Read Cl3_BPV Source # | |
| Show Cl3_BPV Source # | |
| Storable Cl3_BPV Source # | |
toCl3_BPV :: Cl3 -> Cl3_BPV Source #
toCl3_BPV converts a Cl3 value constructed with BPV to its compact form.
fromCl3_BPV :: Cl3_BPV -> Cl3 Source #
fromCl3_BPV converts the compact Cl3_BPV type back to a Cl3 type.
Cl3_ODD a compact storable data type for ODD.
Instances
| Read Cl3_ODD Source # | |
| Show Cl3_ODD Source # | |
| Storable Cl3_ODD Source # | |
toCl3_ODD :: Cl3 -> Cl3_ODD Source #
toCl3_ODD converts a Cl3 value constructed with ODD to its compact form.
fromCl3_ODD :: Cl3_ODD -> Cl3 Source #
fromCl3_ODD converts the compact Cl3_ODD type back to a Cl3 type.
Cl3_TPV a compact storable data type for TPV.
Instances
| Read Cl3_TPV Source # | |
| Show Cl3_TPV Source # | |
| Storable Cl3_TPV Source # | |
toCl3_TPV :: Cl3 -> Cl3_TPV Source #
toCl3_TPV converts a Cl3 value constructed with TPV to its compact form.
fromCl3_TPV :: Cl3_TPV -> Cl3 Source #
fromCl3_TPV converts the compact Cl3_TPV type back to a Cl3 type.
Cl3_APS a compact storable data type for APS.
Instances
| Read Cl3_APS Source # | |
| Show Cl3_APS Source # | |
| Storable Cl3_APS Source # | |
toCl3_APS :: Cl3 -> Cl3_APS Source #
toCl3_APS converts a Cl3 value constructed with APS to its compact form.
fromCl3_APS :: Cl3_APS -> Cl3 Source #
fromCl3_APS converts the compact Cl3_APS type back to a Cl3 type.
Random Instances
randR :: RandomGen g => g -> (Cl3, g) Source #
randR random Real Scalar (Grade 0) with random magnitude and random sign
rangeR :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g) Source #
rangeR random Real Scalar (Grade 0) with random magnitude within a range and a random sign
randV3 :: RandomGen g => g -> (Cl3, g) Source #
randV3 random Vector (Grade 1) with random magnitude and random direction
the direction is using spherical coordinates
rangeV3 :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g) Source #
rangeV3 random Vector (Grade 1) with random magnitude within a range and a random direction
randBV :: RandomGen g => g -> (Cl3, g) Source #
randBV random Bivector (Grade 2) with random magnitude and random direction
the direction is using spherical coordinates
rangeBV :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g) Source #
rangeBV random Bivector (Grade 2) with random magnitude in a range and a random direction
randI :: RandomGen g => g -> (Cl3, g) Source #
randI random Imaginary Scalar (Grade 3) with random magnitude and random sign
rangeI :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g) Source #
rangeI random Imaginary Scalar (Grade 3) with random magnitude within a range and random sign
randPV :: RandomGen g => g -> (Cl3, g) Source #
randPV random Paravector made from random Grade 0 and Grade 1 elements
rangePV :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g) Source #
rangePV random Paravector made from random Grade 0 and Grade 1 elements within a range
randH :: RandomGen g => g -> (Cl3, g) Source #
randH random Quaternion made from random Grade 0 and Grade 2 elements
rangeH :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g) Source #
rangeH random Quaternion made from random Grade 0 and Grade 2 elements within a range
rangeC :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g) Source #
rangeC random combination of Grade 0 and Grade 3 within a range
rangeBPV :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g) Source #
rangeBPV random combination of Grade 1 and Grade 2 within a range
rangeODD :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g) Source #
rangeODD random combination of Grade 1 and Grade 3 within a range
rangeTPV :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g) Source #
rangeTPV random combination of Grade 2 and Grade 3 within a range
rangeAPS :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g) Source #
rangeAPS random combination of all 4 grades within a range
randUnitV3 :: RandomGen g => g -> (Cl3, g) Source #
randUnitV3 a unit vector with a random direction
randProjector :: RandomGen g => g -> (Cl3, g) Source #
randProjector a projector with a random direction
randNilpotent :: RandomGen g => g -> (Cl3, g) Source #
randNilpotent a nilpotent element with a random orientation
randUnitary :: RandomGen g => g -> (Cl3, g) Source #
randUnitary a unitary element with a random orientation
Helpful Functions
eigvals :: Cl3 -> (Cl3, Cl3) Source #
eigvals calculates the eignenvalues of the cliffor.
This is useful for determining if a cliffor is the pole
of a function.
hasNilpotent :: Cl3 -> Bool Source #
hasNilpotent takes a Cliffor and determines if the vector part and the bivector part are
orthoganl and equal in magnitude, i.e. that it is simular to a nilpotent BPV.
spectraldcmp :: (Cl3 -> Cl3) -> (Cl3 -> Cl3) -> Cl3 -> Cl3 Source #
spectraldcmp the spectral decomposition of a function to calculate analytic functions of cliffors in Cl(3,0).
This function requires the desired function's R, I, and C instances to be calculated and the function's derivative.
If multiple functions are being composed, its best to pass the composition of the funcitons
to this function and the derivative to this function. Any function with a Taylor Series
approximation should be able to be used. A real, imaginary, and complex version of the function to be decomposed
must be provided and spectraldcmp will handle the case for an arbitrary Cliffor.
It may be possible to add, in the future, a RULES pragma like:
"spectral decomposition function composition" forall f f' g g' cliff. spectraldcmp f f' (spectraldcmp g g' cliff) = spectraldcmp (f.g) (f'.g') cliff
project :: Cl3 -> Cl3 Source #
project makes a projector based off of the vector content of the Cliffor.
mIx a more effecient 'x -> I (-1) * x' typically useful for converting a
Bivector to a Vector in the same direction. Related to Hodge Dual and/or
Inverse Hodge Star.