cl3-1.0.0.0: Clifford Algebra of three dimensional space.

Copyright(C) 2018 Nathan Waivio
LicenseBSD3
MaintainerNathan Waivio <nathan.waivio@gmail.com>
StabilityStable
Portabilityunportable
Safe HaskellSafe
LanguageHaskell2010

Algebra.Geometric.Cl3

Contents

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 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, double precision floats are used to approximate real numbers in this library. Single and Double grade combinations are specialized and live within the APS.

  • R is the constructor for the Real Scalar Sub-algebra Grade-0
  • V3 is the Vector constructor Grade-1
  • BV is the Bivector constructor Grade-2
  • 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
  • H is the Quaternion constructor it is the Even Sub-algebra with Grade-0 and Grade-2 elements
  • C is the Complex constructor it is the Scalar Sub-algebra with Grade-0 and Grade-3 elements
  • BPV is the Biparavector constructor with Grade-1 and Grade-2 elements
  • ODD is the Odd constructor with Grade-1 and Grade-3 elements
  • TPV is the Triparavector constructor with Grade-2 and Grade-3 elements
  • APS is 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

Eq Cl3 Source #

Cl(3,0) has the property of equivalence. Eq is True when all of the grade elements are equivalent.

Methods

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

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

Floating Cl3 Source #

Cl(3,0) has a Floating instance.

Methods

pi :: Cl3 #

exp :: Cl3 -> Cl3 #

log :: Cl3 -> Cl3 #

sqrt :: Cl3 -> Cl3 #

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

logBase :: Cl3 -> Cl3 -> Cl3 #

sin :: Cl3 -> Cl3 #

cos :: Cl3 -> Cl3 #

tan :: Cl3 -> Cl3 #

asin :: Cl3 -> Cl3 #

acos :: Cl3 -> Cl3 #

atan :: Cl3 -> Cl3 #

sinh :: Cl3 -> Cl3 #

cosh :: Cl3 -> Cl3 #

tanh :: Cl3 -> Cl3 #

asinh :: Cl3 -> Cl3 #

acosh :: Cl3 -> Cl3 #

atanh :: Cl3 -> Cl3 #

log1p :: Cl3 -> Cl3 #

expm1 :: Cl3 -> Cl3 #

log1pexp :: Cl3 -> Cl3 #

log1mexp :: Cl3 -> Cl3 #

Fractional Cl3 Source #

Cl(3,0) has a Fractional instance

Methods

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

recip :: Cl3 -> Cl3 #

fromRational :: Rational -> Cl3 #

Data Cl3 Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cl3 -> c Cl3 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Cl3 #

toConstr :: Cl3 -> Constr #

dataTypeOf :: Cl3 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Cl3) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cl3) #

gmapT :: (forall b. Data b => b -> b) -> Cl3 -> Cl3 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cl3 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cl3 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Cl3 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Cl3 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Cl3 -> m Cl3 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Cl3 -> m Cl3 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Cl3 -> m Cl3 #

Num Cl3 Source #

Cl3 has a Num instance. Num is addition, geometric product, negation, abs the largest singular value, and signum like a unit vector of sorts.

Methods

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

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

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

negate :: Cl3 -> Cl3 #

abs :: Cl3 -> Cl3 #

signum :: Cl3 -> Cl3 #

fromInteger :: Integer -> Cl3 #

Ord Cl3 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. 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.

Methods

compare :: Cl3 -> Cl3 -> Ordering #

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

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

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

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

max :: Cl3 -> Cl3 -> Cl3 #

min :: Cl3 -> Cl3 -> Cl3 #

Read Cl3 Source # 
Show Cl3 Source # 

Methods

showsPrec :: Int -> Cl3 -> ShowS #

show :: Cl3 -> String #

showList :: [Cl3] -> ShowS #

Generic Cl3 Source # 

Associated Types

type Rep Cl3 :: * -> * #

Methods

from :: Cl3 -> Rep Cl3 x #

to :: Rep Cl3 x -> Cl3 #

Storable Cl3 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.

Methods

sizeOf :: Cl3 -> Int #

alignment :: Cl3 -> Int #

peekElemOff :: Ptr Cl3 -> Int -> IO Cl3 #

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

peekByteOff :: Ptr b -> Int -> IO Cl3 #

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

peek :: Ptr Cl3 -> IO Cl3 #

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

Random Cl3 Source #

Random instance for the Random library

Methods

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

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

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

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

randomRIO :: (Cl3, Cl3) -> IO Cl3 #

randomIO :: IO Cl3 #

type Rep Cl3 Source # 
type Rep Cl3 = D1 * (MetaData "Cl3" "Algebra.Geometric.Cl3" "cl3-1.0.0.0-8ml8zruHBXs8BLm1WT8dPi" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "R" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double))) (C1 * (MetaCons "V3" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)))))) ((:+:) * (C1 * (MetaCons "BV" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double))))) ((:+:) * (C1 * (MetaCons "I" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double))) (C1 * (MetaCons "PV" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "H" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double))))) ((:+:) * (C1 * (MetaCons "C" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)))) (C1 * (MetaCons "BPV" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)))))))) ((:+:) * (C1 * (MetaCons "ODD" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double))))) ((:+:) * (C1 * (MetaCons "TPV" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double))))) (C1 * (MetaCons "APS" PrefixI False) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double))))))))))

Clifford Conjugate and Complex Conjugate

bar :: Cl3 -> Cl3 Source #

bar is a Clifford Conjugate, the vector grades are negated

dag :: Cl3 -> Cl3 Source #

dag is the Complex Conjugate, the imaginary grades are negated

The littlest singular value

lsv :: Cl3 -> Cl3 Source #

lsv the littlest singular value. Useful for testing for invertability.

Constructor Selectors - For optimizing and simplifying calculations

toR :: Cl3 -> Cl3 Source #

toR takes any Cliffor and returns the R portion

toV3 :: Cl3 -> Cl3 Source #

toV3 takes any Cliffor and returns the V3 portion

toBV :: Cl3 -> Cl3 Source #

toBV takes any Cliffor and returns the BV portion

toI :: Cl3 -> Cl3 Source #

toI takes any Cliffor and returns the I portion

toPV :: Cl3 -> Cl3 Source #

toPV takes any Cliffor and returns the PV poriton

toH :: Cl3 -> Cl3 Source #

toH takes any Cliffor and returns the H portion

toC :: Cl3 -> Cl3 Source #

toC takes any Cliffor and returns the C portion

toBPV :: Cl3 -> Cl3 Source #

toBPV takes any Cliffor and returns the BPV portion

toODD :: Cl3 -> Cl3 Source #

toODD takes any Cliffor and returns the ODD portion

toTPV :: Cl3 -> Cl3 Source #

toTPV takes any Cliffor and returns the TPV portion

toAPS :: Cl3 -> Cl3 Source #

toAPS takes any Cliffor and returns the APS portion

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 :: Cl3 -> Cl3 Source #

reduce function reduces the number of grades in a specialized Cliffor if some are zero

tol :: Cl3 Source #

tol currently 128*eps

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

randC :: RandomGen g => g -> (Cl3, g) Source #

randC random combination of Grade 0 and Grade 3

rangeC :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g) Source #

rangeC random combination of Grade 0 and Grade 3 within a range

randBPV :: RandomGen g => g -> (Cl3, g) Source #

randBPV random combination of Grade 1 and Grade 2

rangeBPV :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g) Source #

rangeBPV random combination of Grade 1 and Grade 2 within a range

randODD :: RandomGen g => g -> (Cl3, g) Source #

randODD random combination of Grade 1 and Grade 3

rangeODD :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g) Source #

rangeODD random combination of Grade 1 and Grade 3 within a range

randTPV :: RandomGen g => g -> (Cl3, g) Source #

randTPV random combination of Grade 2 and Grade 3

rangeTPV :: RandomGen g => (Cl3, Cl3) -> g -> (Cl3, g) Source #

rangeTPV random combination of Grade 2 and Grade 3 within a range

randAPS :: RandomGen g => g -> (Cl3, g) Source #

randAPS random combination of all 4 grades

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

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 to be calculated and it'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. 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. We have safty problem with unreduced values, so it calls reduce first, as a view pattern.