Copyright | (C) 2017-2024 Nathan Waivio |
---|---|
License | BSD3 |
Maintainer | Nathan Waivio <nathan.waivio@gmail.com> |
Stability | Stable |
Portability | unportable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Posit.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
tol
to use a simpler Constructor - Compact Storable types for the Cl3 Constructors with smart constructors
- Random Instances
- Helpful Functions
- Cl3 Types are Convertable between different Posit representations
Description
Library implementing standard functions for the Algebra of Physical Space Cl(3,0)
Synopsis
- data Cl3 es where
- R :: PositC es => !(Posit es) -> Cl3 es
- V3 :: PositC es => !(Posit es) -> !(Posit es) -> !(Posit es) -> Cl3 es
- BV :: PositC es => !(Posit es) -> !(Posit es) -> !(Posit es) -> Cl3 es
- I :: PositC es => !(Posit es) -> Cl3 es
- PV :: PositC es => !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> Cl3 es
- H :: PositC es => !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> Cl3 es
- C :: PositC es => !(Posit es) -> !(Posit es) -> Cl3 es
- BPV :: PositC es => !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> Cl3 es
- ODD :: PositC es => !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> Cl3 es
- TPV :: PositC es => !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> Cl3 es
- APS :: PositC es => !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> Cl3 es
- type Cl3Posit8 = Cl3 Z_3_2
- type Cl3Posit16 = Cl3 I_3_2
- type Cl3Posit32 = Cl3 II_3_2
- type Cl3Posit64 = Cl3 III_3_2
- type Cl3Posit128 = Cl3 IV_3_2
- type Cl3Posit256 = Cl3 V_3_2
- type Cl3P8 = Cl3 Z_2022
- type Cl3P16 = Cl3 I_2022
- type Cl3P32 = Cl3 II_2022
- type Cl3P64 = Cl3 III_2022
- type Cl3P128 = Cl3 IV_2022
- type Cl3P256 = Cl3 V_2022
- bar :: PositC es => Cl3 es -> Cl3 es
- dag :: PositC es => Cl3 es -> Cl3 es
- lsv :: PositF es => Cl3 es -> Cl3 es
- toR :: PositC es => Cl3 es -> Cl3 es
- toV3 :: PositC es => Cl3 es -> Cl3 es
- toBV :: PositC es => Cl3 es -> Cl3 es
- toI :: PositC es => Cl3 es -> Cl3 es
- toPV :: PositC es => Cl3 es -> Cl3 es
- toH :: PositC es => Cl3 es -> Cl3 es
- toC :: PositC es => Cl3 es -> Cl3 es
- toBPV :: PositC es => Cl3 es -> Cl3 es
- toODD :: PositC es => Cl3 es -> Cl3 es
- toTPV :: PositC es => Cl3 es -> Cl3 es
- toAPS :: PositC es => Cl3 es -> Cl3 es
- showOctave :: PositC es => Cl3 es -> String
- reduce :: PositF es => Cl3 es -> Cl3 es
- tol :: PositF es => Cl3 es
- data Cl3_R es
- toCl3_R :: PositC es => Cl3 es -> Cl3_R es
- fromCl3_R :: PositC es => Cl3_R es -> Cl3 es
- data Cl3_V3 es
- toCl3_V3 :: PositC es => Cl3 es -> Cl3_V3 es
- fromCl3_V3 :: PositC es => Cl3_V3 es -> Cl3 es
- data Cl3_BV es
- toCl3_BV :: PositC es => Cl3 es -> Cl3_BV es
- fromCl3_BV :: PositC es => Cl3_BV es -> Cl3 es
- data Cl3_I es
- toCl3_I :: PositC es => Cl3 es -> Cl3_I es
- fromCl3_I :: PositC es => Cl3_I es -> Cl3 es
- data Cl3_PV es
- toCl3_PV :: PositC es => Cl3 es -> Cl3_PV es
- fromCl3_PV :: PositC es => Cl3_PV es -> Cl3 es
- data Cl3_H es
- toCl3_H :: PositC es => Cl3 es -> Cl3_H es
- fromCl3_H :: PositC es => Cl3_H es -> Cl3 es
- data Cl3_C es
- toCl3_C :: PositC es => Cl3 es -> Cl3_C es
- fromCl3_C :: PositC es => Cl3_C es -> Cl3 es
- data Cl3_BPV es
- toCl3_BPV :: PositC es => Cl3 es -> Cl3_BPV es
- fromCl3_BPV :: PositC es => Cl3_BPV es -> Cl3 es
- data Cl3_ODD es
- toCl3_ODD :: PositC es => Cl3 es -> Cl3_ODD es
- fromCl3_ODD :: PositC es => Cl3_ODD es -> Cl3 es
- data Cl3_TPV es
- toCl3_TPV :: PositC es => Cl3 es -> Cl3_TPV es
- fromCl3_TPV :: PositC es => Cl3_TPV es -> Cl3 es
- data Cl3_APS es
- toCl3_APS :: PositC es => Cl3 es -> Cl3_APS es
- fromCl3_APS :: PositC es => Cl3_APS es -> Cl3 es
- randR :: (PositF es, RandomGen g) => g -> (Cl3 es, g)
- rangeR :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g)
- randV3 :: (PositF es, RandomGen g) => g -> (Cl3 es, g)
- rangeV3 :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g)
- randBV :: (PositF es, RandomGen g) => g -> (Cl3 es, g)
- rangeBV :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g)
- randI :: (PositF es, RandomGen g) => g -> (Cl3 es, g)
- rangeI :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g)
- randPV :: (PositF es, RandomGen g) => g -> (Cl3 es, g)
- rangePV :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g)
- randH :: (PositF es, RandomGen g) => g -> (Cl3 es, g)
- rangeH :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g)
- randC :: (PositF es, RandomGen g) => g -> (Cl3 es, g)
- rangeC :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g)
- randBPV :: (PositF es, RandomGen g) => g -> (Cl3 es, g)
- rangeBPV :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g)
- randODD :: (PositF es, RandomGen g) => g -> (Cl3 es, g)
- rangeODD :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g)
- randTPV :: (PositF es, RandomGen g) => g -> (Cl3 es, g)
- rangeTPV :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g)
- randAPS :: (PositF es, RandomGen g) => g -> (Cl3 es, g)
- rangeAPS :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g)
- randUnitV3 :: (PositF es, RandomGen g) => g -> (Cl3 es, g)
- randProjector :: (PositF es, RandomGen g) => g -> (Cl3 es, g)
- randNilpotent :: (PositF es, RandomGen g) => g -> (Cl3 es, g)
- randUnitary :: (PositF es, RandomGen g) => g -> (Cl3 es, g)
- eigvals :: PositF es => Cl3 es -> (Cl3 es, Cl3 es)
- hasNilpotent :: PositF es => Cl3 es -> Bool
- spectraldcmp :: PositF es => (Cl3 es -> Cl3 es) -> (Cl3 es -> Cl3 es) -> Cl3 es -> Cl3 es
- project :: PositF es => Cl3 es -> Cl3 es
- mIx :: PositC es => Cl3 es -> Cl3 es
- timesI :: PositC es => Cl3 es -> Cl3 es
- abssignum :: PositF es => Cl3 es -> (Cl3 es, Cl3 es)
- class Convertible a b where
- convert :: a -> b
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, posit Numbers are used to approximate real numbers in this library. Single and Double grade combinations are specialized using algebraic datatypes and live within the APS.
R
is the constructor for the Real Scalar Sub-algebra Grade-0V3
is the Three Dimensional Real Vector constructor Grade-1BV
is the Bivector constructor Grade-2 an Imaginary Three Dimensional VectorI
is the Imaginary constructor Grade-3 and is the Pseudo-Scalar for APSPV
is the Paravector constructor with Grade-0 and Grade-1 elements, a Real Scalar plus Vector, (R + V3)H
is the Quaternion constructor it is the Even Sub-algebra with Grade-0 and Grade-2 elements, a Real Scalar plus Bivector, (R + BV)C
is the Complex constructor it is the Scalar Sub-algebra with Grade-0 and Grade-3 elements, a Real Scalar plus Imaginar Scalar, (R + I)BPV
is the Biparavector constructor with Grade-1 and Grade-2 elements, a Real Vector plus Bivector, (V3 + BV)ODD
is the Odd constructor with Grade-1 and Grade-3 elements, a Vector plus Imaginary Scalar, (V3 + I)TPV
is the Triparavector constructor with Grade-2 and Grade-3 elements, a Bivector plus Imaginary, (BV + I)APS
is the constructor for an element in the Algebra of Physical Space with Grade-0 through Grade-3 elements
Constructors
R :: PositC es => !(Posit es) -> Cl3 es | |
V3 :: PositC es => !(Posit es) -> !(Posit es) -> !(Posit es) -> Cl3 es | |
BV :: PositC es => !(Posit es) -> !(Posit es) -> !(Posit es) -> Cl3 es | |
I :: PositC es => !(Posit es) -> Cl3 es | |
PV :: PositC es => !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> Cl3 es | |
H :: PositC es => !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> Cl3 es | |
C :: PositC es => !(Posit es) -> !(Posit es) -> Cl3 es | |
BPV :: PositC es => !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> Cl3 es | |
ODD :: PositC es => !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> Cl3 es | |
TPV :: PositC es => !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> Cl3 es | |
APS :: PositC es => !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> !(Posit es) -> Cl3 es |
Instances
PositC es => Storable (Cl3 es) Source # | Cl3 instance of Storable uses the APS constructor as its standard interface. "peek" returns a cliffor constructed with APS. "poke" converts a cliffor to APS. For a more compact storing of constructors other than APS use the storable subtypes Cl3_R, Cl3_V3, Cl3_BV, Cl3_I, Cl3_PV, Cl3_H, Cl3_C, Cl3_BPV, Cl3_ODD, Cl3_TPV. |
PositF es => Floating (Cl3 es) Source # | Cl(3,0) has a Floating instance. |
PositF es => Num (Cl3 es) Source # | Cl3 has a Num instance. Num is addition, geometric product, negation, |
(Read (Posit es), PositC es) => Read (Cl3 es) Source # | |
PositF es => Fractional (Cl3 es) Source # | Cl(3,0) has a Fractional instance |
PositC es => Show (Cl3 es) Source # | In case we don't derive Show, provide |
PositC es => NFData (Cl3 es) Source # | Cl3 can be reduced to a normal form. |
PositC es => Eq (Cl3 es) Source # | Cl(3,0) has the property of equivalence. Eq is True when all of the grade elements are equivalent. |
PositF es => Ord (Cl3 es) Source # | Cl3 has a total preorder ordering in which all pairs are comparable by two real valued functions.
Comparison of two reals is just the typical real compare function. Comparison of to imaginary numbers
is just the typical comparison function. When reals are compared to anything else it will compare the
absolute value of the reals to the magnitude of the other cliffor. Compare of two complex values
compares the polar magnitude of the complex numbers. Compare of two vectors compares the vector
magnitudes. The Ord instance for the general case is based on the singular values of each cliffor and
this Ordering compares the largest singular value |
PositF es => Random (Cl3 es) Source # | |
(PositC es1, PositC es2) => Convertible (Cl3 es1) (Cl3 es2) Source # | |
type Cl3Posit16 = Cl3 I_3_2 Source #
type Cl3Posit32 = Cl3 II_3_2 Source #
type Cl3Posit64 = Cl3 III_3_2 Source #
type Cl3Posit128 = Cl3 IV_3_2 Source #
type Cl3Posit256 = Cl3 V_3_2 Source #
Clifford Conjugate and Complex Conjugate
bar :: PositC es => Cl3 es -> Cl3 es Source #
bar
is a Clifford Conjugate, the vector grades are negated
dag :: PositC es => Cl3 es -> Cl3 es Source #
dag
is the Complex Conjugate, the imaginary grades are negated
The littlest singular value
lsv :: PositF es => Cl3 es -> Cl3 es Source #
lsv
the littlest singular value. Useful for testing for invertability.
Constructor Selectors - For optimizing and simplifying calculations
Pretty Printing for use with Octave
showOctave :: PositC es => Cl3 es -> 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 :: PositF es => Cl3 es -> Cl3 es Source #
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
PositC es => Storable (Cl3_R es) Source # | |
Defined in Posit.Cl3 | |
PositC es => Show (Cl3_R es) Source # | |
toCl3_R :: PositC es => Cl3 es -> Cl3_R es Source #
toCl3_R
converts a Cl3 value constructed with R to its compact form.
fromCl3_R :: PositC es => Cl3_R es -> Cl3 es Source #
fromCl3_R
converts the compact Cl3_R type back to a Cl3 type.
Cl3_V3
a compact storable data type for V3.
Instances
PositC es => Storable (Cl3_V3 es) Source # | |
Defined in Posit.Cl3 | |
PositC es => Show (Cl3_V3 es) Source # | |
toCl3_V3 :: PositC es => Cl3 es -> Cl3_V3 es Source #
toCl3_V3
converts a Cl3 value constructed with V3 to its compact form.
fromCl3_V3 :: PositC es => Cl3_V3 es -> Cl3 es Source #
fromCl3_V3
converts the compact Cl3_V3 type back to a Cl3 type.
Cl3_BV
a compact storable data type for BV.
Instances
PositC es => Storable (Cl3_BV es) Source # | |
Defined in Posit.Cl3 | |
PositC es => Show (Cl3_BV es) Source # | |
toCl3_BV :: PositC es => Cl3 es -> Cl3_BV es Source #
toCl3_BV
converts a Cl3 value constructed with BV to its compact form.
fromCl3_BV :: PositC es => Cl3_BV es -> Cl3 es Source #
fromCl3_BV
converts the compact Cl3_BV type back to a Cl3 type.
Cl3_I
a compact storable data type for I.
Instances
PositC es => Storable (Cl3_I es) Source # | |
Defined in Posit.Cl3 | |
PositC es => Show (Cl3_I es) Source # | |
toCl3_I :: PositC es => Cl3 es -> Cl3_I es Source #
toCl3_I
converts a Cl3 value constructed with I to its compact form.
fromCl3_I :: PositC es => Cl3_I es -> Cl3 es Source #
fromCl3_I
converts the compact Cl3_I type back to a Cl3 type.
Cl3_PV
a compact storable data type for PV.
Instances
PositC es => Storable (Cl3_PV es) Source # | |
Defined in Posit.Cl3 | |
PositC es => Show (Cl3_PV es) Source # | |
toCl3_PV :: PositC es => Cl3 es -> Cl3_PV es Source #
toCl3_PV
converts a Cl3 value constructed with PV to its compact form.
fromCl3_PV :: PositC es => Cl3_PV es -> Cl3 es Source #
fromCl3_PV
converts the compact Cl3_PV type back to a Cl3 type.
Cl3_H
a compact storable data type for H.
Instances
PositC es => Storable (Cl3_H es) Source # | |
Defined in Posit.Cl3 | |
PositC es => Show (Cl3_H es) Source # | |
toCl3_H :: PositC es => Cl3 es -> Cl3_H es Source #
toCl3_H
converts a Cl3 value constructed with H to its compact form.
fromCl3_H :: PositC es => Cl3_H es -> Cl3 es Source #
fromCl3_H
converts the compact Cl3_H type back to a Cl3 type.
Cl3_C
a compact storable data type for C.
Instances
PositC es => Storable (Cl3_C es) Source # | |
Defined in Posit.Cl3 | |
PositC es => Show (Cl3_C es) Source # | |
toCl3_C :: PositC es => Cl3 es -> Cl3_C es Source #
toCl3_C
converts a Cl3 value constructed with C to its compact form.
fromCl3_C :: PositC es => Cl3_C es -> Cl3 es Source #
fromCl3_C
converts the compact Cl3_C type back to a Cl3 type.
Cl3_BPV
a compact storable data type for BPV.
Instances
PositC es => Storable (Cl3_BPV es) Source # | |
Defined in Posit.Cl3 Methods alignment :: Cl3_BPV es -> Int # peekElemOff :: Ptr (Cl3_BPV es) -> Int -> IO (Cl3_BPV es) # pokeElemOff :: Ptr (Cl3_BPV es) -> Int -> Cl3_BPV es -> IO () # peekByteOff :: Ptr b -> Int -> IO (Cl3_BPV es) # pokeByteOff :: Ptr b -> Int -> Cl3_BPV es -> IO () # | |
PositC es => Show (Cl3_BPV es) Source # | |
toCl3_BPV :: PositC es => Cl3 es -> Cl3_BPV es Source #
toCl3_BPV
converts a Cl3 value constructed with BPV to its compact form.
fromCl3_BPV :: PositC es => Cl3_BPV es -> Cl3 es Source #
fromCl3_BPV
converts the compact Cl3_BPV type back to a Cl3 type.
Cl3_ODD
a compact storable data type for ODD.
Instances
PositC es => Storable (Cl3_ODD es) Source # | |
Defined in Posit.Cl3 Methods alignment :: Cl3_ODD es -> Int # peekElemOff :: Ptr (Cl3_ODD es) -> Int -> IO (Cl3_ODD es) # pokeElemOff :: Ptr (Cl3_ODD es) -> Int -> Cl3_ODD es -> IO () # peekByteOff :: Ptr b -> Int -> IO (Cl3_ODD es) # pokeByteOff :: Ptr b -> Int -> Cl3_ODD es -> IO () # | |
PositC es => Show (Cl3_ODD es) Source # | |
toCl3_ODD :: PositC es => Cl3 es -> Cl3_ODD es Source #
toCl3_ODD
converts a Cl3 value constructed with ODD to its compact form.
fromCl3_ODD :: PositC es => Cl3_ODD es -> Cl3 es Source #
fromCl3_ODD
converts the compact Cl3_ODD type back to a Cl3 type.
Cl3_TPV
a compact storable data type for TPV.
Instances
PositC es => Storable (Cl3_TPV es) Source # | |
Defined in Posit.Cl3 Methods alignment :: Cl3_TPV es -> Int # peekElemOff :: Ptr (Cl3_TPV es) -> Int -> IO (Cl3_TPV es) # pokeElemOff :: Ptr (Cl3_TPV es) -> Int -> Cl3_TPV es -> IO () # peekByteOff :: Ptr b -> Int -> IO (Cl3_TPV es) # pokeByteOff :: Ptr b -> Int -> Cl3_TPV es -> IO () # | |
PositC es => Show (Cl3_TPV es) Source # | |
toCl3_TPV :: PositC es => Cl3 es -> Cl3_TPV es Source #
toCl3_TPV
converts a Cl3 value constructed with TPV to its compact form.
fromCl3_TPV :: PositC es => Cl3_TPV es -> Cl3 es Source #
fromCl3_TPV
converts the compact Cl3_TPV type back to a Cl3 type.
Cl3_APS
a compact storable data type for APS.
Instances
PositC es => Storable (Cl3_APS es) Source # | |
Defined in Posit.Cl3 Methods alignment :: Cl3_APS es -> Int # peekElemOff :: Ptr (Cl3_APS es) -> Int -> IO (Cl3_APS es) # pokeElemOff :: Ptr (Cl3_APS es) -> Int -> Cl3_APS es -> IO () # peekByteOff :: Ptr b -> Int -> IO (Cl3_APS es) # pokeByteOff :: Ptr b -> Int -> Cl3_APS es -> IO () # | |
PositC es => Show (Cl3_APS es) Source # | |
toCl3_APS :: PositC es => Cl3 es -> Cl3_APS es Source #
toCl3_APS
converts a Cl3 value constructed with APS to its compact form.
fromCl3_APS :: PositC es => Cl3_APS es -> Cl3 es Source #
fromCl3_APS
converts the compact Cl3_APS type back to a Cl3 type.
Random Instances
randR :: (PositF es, RandomGen g) => g -> (Cl3 es, g) Source #
randR
random Real Scalar (Grade 0) with random magnitude and random sign
rangeR :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g) Source #
rangeR
random Real Scalar (Grade 0) with random magnitude within a range and a random sign
randV3 :: (PositF es, RandomGen g) => g -> (Cl3 es, g) Source #
randV3
random Vector (Grade 1) with random magnitude and random direction
the direction is using spherical coordinates
rangeV3 :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g) Source #
rangeV3
random Vector (Grade 1) with random magnitude within a range and a random direction
randBV :: (PositF es, RandomGen g) => g -> (Cl3 es, g) Source #
randBV
random Bivector (Grade 2) with random magnitude and random direction
the direction is using spherical coordinates
rangeBV :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g) Source #
rangeBV
random Bivector (Grade 2) with random magnitude in a range and a random direction
randI :: (PositF es, RandomGen g) => g -> (Cl3 es, g) Source #
randI
random Imaginary Scalar (Grade 3) with random magnitude and random sign
rangeI :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g) Source #
rangeI
random Imaginary Scalar (Grade 3) with random magnitude within a range and random sign
randPV :: (PositF es, RandomGen g) => g -> (Cl3 es, g) Source #
randPV
random Paravector made from random Grade 0 and Grade 1 elements
rangePV :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g) Source #
rangePV
random Paravector made from random Grade 0 and Grade 1 elements within a range
randH :: (PositF es, RandomGen g) => g -> (Cl3 es, g) Source #
randH
random Quaternion made from random Grade 0 and Grade 2 elements
rangeH :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g) Source #
rangeH
random Quaternion made from random Grade 0 and Grade 2 elements within a range
randC :: (PositF es, RandomGen g) => g -> (Cl3 es, g) Source #
randC
random combination of Grade 0 and Grade 3
rangeC :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g) Source #
rangeC
random combination of Grade 0 and Grade 3 within a range
randBPV :: (PositF es, RandomGen g) => g -> (Cl3 es, g) Source #
randBPV
random combination of Grade 1 and Grade 2
rangeBPV :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g) Source #
rangeBPV
random combination of Grade 1 and Grade 2 within a range
randODD :: (PositF es, RandomGen g) => g -> (Cl3 es, g) Source #
randODD
random combination of Grade 1 and Grade 3
rangeODD :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g) Source #
rangeODD
random combination of Grade 1 and Grade 3 within a range
randTPV :: (PositF es, RandomGen g) => g -> (Cl3 es, g) Source #
randTPV
random combination of Grade 2 and Grade 3
rangeTPV :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g) Source #
rangeTPV
random combination of Grade 2 and Grade 3 within a range
randAPS :: (PositF es, RandomGen g) => g -> (Cl3 es, g) Source #
randAPS
random combination of all 4 grades
rangeAPS :: (PositF es, RandomGen g) => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g) Source #
rangeAPS
random combination of all 4 grades within a range
randUnitV3 :: (PositF es, RandomGen g) => g -> (Cl3 es, g) Source #
randUnitV3
a unit vector with a random direction
randProjector :: (PositF es, RandomGen g) => g -> (Cl3 es, g) Source #
randProjector
a projector with a random direction
randNilpotent :: (PositF es, RandomGen g) => g -> (Cl3 es, g) Source #
randNilpotent
a nilpotent element with a random orientation
randUnitary :: (PositF es, RandomGen g) => g -> (Cl3 es, g) Source #
randUnitary
a unitary element with a random orientation
Helpful Functions
eigvals :: PositF es => Cl3 es -> (Cl3 es, Cl3 es) Source #
eigvals
calculates the eignenvalues of the cliffor.
This is useful for determining if a cliffor is the pole
of a function.
hasNilpotent :: PositF es => Cl3 es -> 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 :: PositF es => (Cl3 es -> Cl3 es) -> (Cl3 es -> Cl3 es) -> Cl3 es -> Cl3 es 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 :: PositF es => Cl3 es -> Cl3 es Source #
project
makes a projector based off of the vector content of the Cliffor.
mIx :: PositC es => Cl3 es -> Cl3 es Source #
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.
Cl3 Types are Convertable between different Posit representations
class Convertible a b where #
A Convertible class that will cast or convert
between two different Posit es types