cl3-posit-1.0.0.0: Clifford Algebra of three dimensional space, implemented with Posit numbers.
Copyright(C) 2017-2024 Nathan Waivio
LicenseBSD3
MaintainerNathan Waivio <nathan.waivio@gmail.com>
StabilityStable
Portabilityunportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Posit.Cl3

Description

Library implementing standard functions for the Algebra of Physical Space Cl(3,0)

Synopsis

The type for the Algebra of Physical Space

data Cl3 es where Source #

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-0
  • V3 is the Three Dimensional Real Vector constructor Grade-1
  • BV is the Bivector constructor Grade-2 an Imaginary Three Dimensional Vector
  • I is the Imaginary constructor Grade-3 and is the Pseudo-Scalar for APS
  • PV 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

Instances details
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.

Instance details

Defined in Posit.Cl3

Methods

sizeOf :: Cl3 es -> Int #

alignment :: Cl3 es -> Int #

peekElemOff :: Ptr (Cl3 es) -> Int -> IO (Cl3 es) #

pokeElemOff :: Ptr (Cl3 es) -> Int -> Cl3 es -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Cl3 es) #

pokeByteOff :: Ptr b -> Int -> Cl3 es -> IO () #

peek :: Ptr (Cl3 es) -> IO (Cl3 es) #

poke :: Ptr (Cl3 es) -> Cl3 es -> IO () #

PositF es => Floating (Cl3 es) Source #

Cl(3,0) has a Floating instance.

Instance details

Defined in Posit.Cl3

Methods

pi :: Cl3 es #

exp :: Cl3 es -> Cl3 es #

log :: Cl3 es -> Cl3 es #

sqrt :: Cl3 es -> Cl3 es #

(**) :: Cl3 es -> Cl3 es -> Cl3 es #

logBase :: Cl3 es -> Cl3 es -> Cl3 es #

sin :: Cl3 es -> Cl3 es #

cos :: Cl3 es -> Cl3 es #

tan :: Cl3 es -> Cl3 es #

asin :: Cl3 es -> Cl3 es #

acos :: Cl3 es -> Cl3 es #

atan :: Cl3 es -> Cl3 es #

sinh :: Cl3 es -> Cl3 es #

cosh :: Cl3 es -> Cl3 es #

tanh :: Cl3 es -> Cl3 es #

asinh :: Cl3 es -> Cl3 es #

acosh :: Cl3 es -> Cl3 es #

atanh :: Cl3 es -> Cl3 es #

log1p :: Cl3 es -> Cl3 es #

expm1 :: Cl3 es -> Cl3 es #

log1pexp :: Cl3 es -> Cl3 es #

log1mexp :: Cl3 es -> Cl3 es #

PositF es => Num (Cl3 es) Source #

Cl3 has a Num instance. Num is addition, geometric product, negation, abs the largest singular value, and signum.

Instance details

Defined in Posit.Cl3

Methods

(+) :: Cl3 es -> Cl3 es -> Cl3 es #

(-) :: Cl3 es -> Cl3 es -> Cl3 es #

(*) :: Cl3 es -> Cl3 es -> Cl3 es #

negate :: Cl3 es -> Cl3 es #

abs :: Cl3 es -> Cl3 es #

signum :: Cl3 es -> Cl3 es #

fromInteger :: Integer -> Cl3 es #

(Read (Posit es), PositC es) => Read (Cl3 es) Source # 
Instance details

Defined in Posit.Cl3

Methods

readsPrec :: Int -> ReadS (Cl3 es) #

readList :: ReadS [Cl3 es] #

readPrec :: ReadPrec (Cl3 es) #

readListPrec :: ReadPrec [Cl3 es] #

PositF es => Fractional (Cl3 es) Source #

Cl(3,0) has a Fractional instance

Instance details

Defined in Posit.Cl3

Methods

(/) :: Cl3 es -> Cl3 es -> Cl3 es #

recip :: Cl3 es -> Cl3 es #

fromRational :: Rational -> Cl3 es #

PositC es => Show (Cl3 es) Source #

In case we don't derive Show, provide showOctave as the Show instance

Instance details

Defined in Posit.Cl3

Methods

showsPrec :: Int -> Cl3 es -> ShowS #

show :: Cl3 es -> String #

showList :: [Cl3 es] -> ShowS #

PositC es => NFData (Cl3 es) Source #

Cl3 can be reduced to a normal form.

Instance details

Defined in Posit.Cl3

Methods

rnf :: Cl3 es -> () #

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.

Instance details

Defined in Posit.Cl3

Methods

(==) :: Cl3 es -> Cl3 es -> Bool #

(/=) :: Cl3 es -> Cl3 es -> Bool #

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 abs and then the littlest singular value lsv. Some arbitrary cliffors may return EQ for Ord but not be exactly == equivalent, but they are related by a right and left multiplication of two unitary elements. For instance for the Cliffors A and B, A == B could be False, but compare A B is EQ, because A * V = U * B, where V and U are unitary.

Instance details

Defined in Posit.Cl3

Methods

compare :: Cl3 es -> Cl3 es -> Ordering #

(<) :: Cl3 es -> Cl3 es -> Bool #

(<=) :: Cl3 es -> Cl3 es -> Bool #

(>) :: Cl3 es -> Cl3 es -> Bool #

(>=) :: Cl3 es -> Cl3 es -> Bool #

max :: Cl3 es -> Cl3 es -> Cl3 es #

min :: Cl3 es -> Cl3 es -> Cl3 es #

PositF es => Random (Cl3 es) Source #

Random instance for the Random library

Instance details

Defined in Posit.Cl3

Methods

randomR :: RandomGen g => (Cl3 es, Cl3 es) -> g -> (Cl3 es, g) #

random :: RandomGen g => g -> (Cl3 es, g) #

randomRs :: RandomGen g => (Cl3 es, Cl3 es) -> g -> [Cl3 es] #

randoms :: RandomGen g => g -> [Cl3 es] #

(PositC es1, PositC es2) => Convertible (Cl3 es1) (Cl3 es2) Source # 
Instance details

Defined in Posit.Cl3

Methods

convert :: Cl3 es1 -> Cl3 es2 #

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

toR :: PositC es => Cl3 es -> Cl3 es Source #

toR takes any Cliffor and returns the R portion

toV3 :: PositC es => Cl3 es -> Cl3 es Source #

toV3 takes any Cliffor and returns the V3 portion

toBV :: PositC es => Cl3 es -> Cl3 es Source #

toBV takes any Cliffor and returns the BV portion

toI :: PositC es => Cl3 es -> Cl3 es Source #

toI takes any Cliffor and returns the I portion

toPV :: PositC es => Cl3 es -> Cl3 es Source #

toPV takes any Cliffor and returns the PV poriton

toH :: PositC es => Cl3 es -> Cl3 es Source #

toH takes any Cliffor and returns the H portion

toC :: PositC es => Cl3 es -> Cl3 es Source #

toC takes any Cliffor and returns the C portion

toBPV :: PositC es => Cl3 es -> Cl3 es Source #

toBPV takes any Cliffor and returns the BPV portion

toODD :: PositC es => Cl3 es -> Cl3 es Source #

toODD takes any Cliffor and returns the ODD portion

toTPV :: PositC es => Cl3 es -> Cl3 es Source #

toTPV takes any Cliffor and returns the TPV portion

toAPS :: PositC es => Cl3 es -> Cl3 es Source #

toAPS takes any Cliffor and returns the APS portion

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

tol :: PositF es => Cl3 es Source #

tol currently 128*eps

Compact Storable types for the Cl3 Constructors with smart constructors

data Cl3_R es Source #

Cl3_R a compact storable data type for R.

Instances

Instances details
PositC es => Storable (Cl3_R es) Source # 
Instance details

Defined in Posit.Cl3

Methods

sizeOf :: Cl3_R es -> Int #

alignment :: Cl3_R es -> Int #

peekElemOff :: Ptr (Cl3_R es) -> Int -> IO (Cl3_R es) #

pokeElemOff :: Ptr (Cl3_R es) -> Int -> Cl3_R es -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Cl3_R es) #

pokeByteOff :: Ptr b -> Int -> Cl3_R es -> IO () #

peek :: Ptr (Cl3_R es) -> IO (Cl3_R es) #

poke :: Ptr (Cl3_R es) -> Cl3_R es -> IO () #

PositC es => Show (Cl3_R es) Source # 
Instance details

Defined in Posit.Cl3

Methods

showsPrec :: Int -> Cl3_R es -> ShowS #

show :: Cl3_R es -> String #

showList :: [Cl3_R es] -> ShowS #

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.

data Cl3_V3 es Source #

Cl3_V3 a compact storable data type for V3.

Instances

Instances details
PositC es => Storable (Cl3_V3 es) Source # 
Instance details

Defined in Posit.Cl3

Methods

sizeOf :: Cl3_V3 es -> Int #

alignment :: Cl3_V3 es -> Int #

peekElemOff :: Ptr (Cl3_V3 es) -> Int -> IO (Cl3_V3 es) #

pokeElemOff :: Ptr (Cl3_V3 es) -> Int -> Cl3_V3 es -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Cl3_V3 es) #

pokeByteOff :: Ptr b -> Int -> Cl3_V3 es -> IO () #

peek :: Ptr (Cl3_V3 es) -> IO (Cl3_V3 es) #

poke :: Ptr (Cl3_V3 es) -> Cl3_V3 es -> IO () #

PositC es => Show (Cl3_V3 es) Source # 
Instance details

Defined in Posit.Cl3

Methods

showsPrec :: Int -> Cl3_V3 es -> ShowS #

show :: Cl3_V3 es -> String #

showList :: [Cl3_V3 es] -> ShowS #

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.

data Cl3_BV es Source #

Cl3_BV a compact storable data type for BV.

Instances

Instances details
PositC es => Storable (Cl3_BV es) Source # 
Instance details

Defined in Posit.Cl3

Methods

sizeOf :: Cl3_BV es -> Int #

alignment :: Cl3_BV es -> Int #

peekElemOff :: Ptr (Cl3_BV es) -> Int -> IO (Cl3_BV es) #

pokeElemOff :: Ptr (Cl3_BV es) -> Int -> Cl3_BV es -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Cl3_BV es) #

pokeByteOff :: Ptr b -> Int -> Cl3_BV es -> IO () #

peek :: Ptr (Cl3_BV es) -> IO (Cl3_BV es) #

poke :: Ptr (Cl3_BV es) -> Cl3_BV es -> IO () #

PositC es => Show (Cl3_BV es) Source # 
Instance details

Defined in Posit.Cl3

Methods

showsPrec :: Int -> Cl3_BV es -> ShowS #

show :: Cl3_BV es -> String #

showList :: [Cl3_BV es] -> ShowS #

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.

data Cl3_I es Source #

Cl3_I a compact storable data type for I.

Instances

Instances details
PositC es => Storable (Cl3_I es) Source # 
Instance details

Defined in Posit.Cl3

Methods

sizeOf :: Cl3_I es -> Int #

alignment :: Cl3_I es -> Int #

peekElemOff :: Ptr (Cl3_I es) -> Int -> IO (Cl3_I es) #

pokeElemOff :: Ptr (Cl3_I es) -> Int -> Cl3_I es -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Cl3_I es) #

pokeByteOff :: Ptr b -> Int -> Cl3_I es -> IO () #

peek :: Ptr (Cl3_I es) -> IO (Cl3_I es) #

poke :: Ptr (Cl3_I es) -> Cl3_I es -> IO () #

PositC es => Show (Cl3_I es) Source # 
Instance details

Defined in Posit.Cl3

Methods

showsPrec :: Int -> Cl3_I es -> ShowS #

show :: Cl3_I es -> String #

showList :: [Cl3_I es] -> ShowS #

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.

data Cl3_PV es Source #

Cl3_PV a compact storable data type for PV.

Instances

Instances details
PositC es => Storable (Cl3_PV es) Source # 
Instance details

Defined in Posit.Cl3

Methods

sizeOf :: Cl3_PV es -> Int #

alignment :: Cl3_PV es -> Int #

peekElemOff :: Ptr (Cl3_PV es) -> Int -> IO (Cl3_PV es) #

pokeElemOff :: Ptr (Cl3_PV es) -> Int -> Cl3_PV es -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Cl3_PV es) #

pokeByteOff :: Ptr b -> Int -> Cl3_PV es -> IO () #

peek :: Ptr (Cl3_PV es) -> IO (Cl3_PV es) #

poke :: Ptr (Cl3_PV es) -> Cl3_PV es -> IO () #

PositC es => Show (Cl3_PV es) Source # 
Instance details

Defined in Posit.Cl3

Methods

showsPrec :: Int -> Cl3_PV es -> ShowS #

show :: Cl3_PV es -> String #

showList :: [Cl3_PV es] -> ShowS #

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.

data Cl3_H es Source #

Cl3_H a compact storable data type for H.

Instances

Instances details
PositC es => Storable (Cl3_H es) Source # 
Instance details

Defined in Posit.Cl3

Methods

sizeOf :: Cl3_H es -> Int #

alignment :: Cl3_H es -> Int #

peekElemOff :: Ptr (Cl3_H es) -> Int -> IO (Cl3_H es) #

pokeElemOff :: Ptr (Cl3_H es) -> Int -> Cl3_H es -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Cl3_H es) #

pokeByteOff :: Ptr b -> Int -> Cl3_H es -> IO () #

peek :: Ptr (Cl3_H es) -> IO (Cl3_H es) #

poke :: Ptr (Cl3_H es) -> Cl3_H es -> IO () #

PositC es => Show (Cl3_H es) Source # 
Instance details

Defined in Posit.Cl3

Methods

showsPrec :: Int -> Cl3_H es -> ShowS #

show :: Cl3_H es -> String #

showList :: [Cl3_H es] -> ShowS #

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.

data Cl3_C es Source #

Cl3_C a compact storable data type for C.

Instances

Instances details
PositC es => Storable (Cl3_C es) Source # 
Instance details

Defined in Posit.Cl3

Methods

sizeOf :: Cl3_C es -> Int #

alignment :: Cl3_C es -> Int #

peekElemOff :: Ptr (Cl3_C es) -> Int -> IO (Cl3_C es) #

pokeElemOff :: Ptr (Cl3_C es) -> Int -> Cl3_C es -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Cl3_C es) #

pokeByteOff :: Ptr b -> Int -> Cl3_C es -> IO () #

peek :: Ptr (Cl3_C es) -> IO (Cl3_C es) #

poke :: Ptr (Cl3_C es) -> Cl3_C es -> IO () #

PositC es => Show (Cl3_C es) Source # 
Instance details

Defined in Posit.Cl3

Methods

showsPrec :: Int -> Cl3_C es -> ShowS #

show :: Cl3_C es -> String #

showList :: [Cl3_C es] -> ShowS #

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.

data Cl3_BPV es Source #

Cl3_BPV a compact storable data type for BPV.

Instances

Instances details
PositC es => Storable (Cl3_BPV es) Source # 
Instance details

Defined in Posit.Cl3

Methods

sizeOf :: Cl3_BPV es -> Int #

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 () #

peek :: Ptr (Cl3_BPV es) -> IO (Cl3_BPV es) #

poke :: Ptr (Cl3_BPV es) -> Cl3_BPV es -> IO () #

PositC es => Show (Cl3_BPV es) Source # 
Instance details

Defined in Posit.Cl3

Methods

showsPrec :: Int -> Cl3_BPV es -> ShowS #

show :: Cl3_BPV es -> String #

showList :: [Cl3_BPV es] -> ShowS #

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.

data Cl3_ODD es Source #

Cl3_ODD a compact storable data type for ODD.

Instances

Instances details
PositC es => Storable (Cl3_ODD es) Source # 
Instance details

Defined in Posit.Cl3

Methods

sizeOf :: Cl3_ODD es -> Int #

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 () #

peek :: Ptr (Cl3_ODD es) -> IO (Cl3_ODD es) #

poke :: Ptr (Cl3_ODD es) -> Cl3_ODD es -> IO () #

PositC es => Show (Cl3_ODD es) Source # 
Instance details

Defined in Posit.Cl3

Methods

showsPrec :: Int -> Cl3_ODD es -> ShowS #

show :: Cl3_ODD es -> String #

showList :: [Cl3_ODD es] -> ShowS #

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.

data Cl3_TPV es Source #

Cl3_TPV a compact storable data type for TPV.

Instances

Instances details
PositC es => Storable (Cl3_TPV es) Source # 
Instance details

Defined in Posit.Cl3

Methods

sizeOf :: Cl3_TPV es -> Int #

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 () #

peek :: Ptr (Cl3_TPV es) -> IO (Cl3_TPV es) #

poke :: Ptr (Cl3_TPV es) -> Cl3_TPV es -> IO () #

PositC es => Show (Cl3_TPV es) Source # 
Instance details

Defined in Posit.Cl3

Methods

showsPrec :: Int -> Cl3_TPV es -> ShowS #

show :: Cl3_TPV es -> String #

showList :: [Cl3_TPV es] -> ShowS #

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.

data Cl3_APS es Source #

Cl3_APS a compact storable data type for APS.

Instances

Instances details
PositC es => Storable (Cl3_APS es) Source # 
Instance details

Defined in Posit.Cl3

Methods

sizeOf :: Cl3_APS es -> Int #

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 () #

peek :: Ptr (Cl3_APS es) -> IO (Cl3_APS es) #

poke :: Ptr (Cl3_APS es) -> Cl3_APS es -> IO () #

PositC es => Show (Cl3_APS es) Source # 
Instance details

Defined in Posit.Cl3

Methods

showsPrec :: Int -> Cl3_APS es -> ShowS #

show :: Cl3_APS es -> String #

showList :: [Cl3_APS es] -> ShowS #

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.

timesI :: PositC es => Cl3 es -> Cl3 es Source #

timesI is a more effecient 'x -> I 1 * x'

abssignum :: PositF es => Cl3 es -> (Cl3 es, Cl3 es) Source #

abssignum is a more effecient 'cl3 -> (abs cl3, signum cl3)' So abs is always R and signum is the same type of constructor as the input signum is the element divided by its largest singular value abs

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

Methods

convert :: a -> b #

Instances

Instances details
(PositC es1, PositC es2) => Convertible (Cl3 es1) (Cl3 es2) Source # 
Instance details

Defined in Posit.Cl3

Methods

convert :: Cl3 es1 -> Cl3 es2 #

(PositC es1, PositC es2) => Convertible (Posit es1) (Posit es2) 
Instance details

Defined in Posit

Methods

convert :: Posit es1 -> Posit es2 #