clif-0.1.0.0: A Clifford algebra number type for Haskell

Copyright(c) Matti A. Eskelinen 2016
LicenseMIT
Maintainermatti.a.eskelinen@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Clif.Internal

Contents

Description

This module implements the various Clif operations on the underlying type. Currently Clif is implemented on top of Data.Map, with blades as keys and scalar multipliers as values.

Warning

This module is not intended to be imported by end users and may change drastically in the future. It is currently exposed (and documented) only to help development.

As development continues, some of the definitions here may be exported from the other modules. Comments and suggestions are welcomed.

Synopsis

Type Clif

newtype Clif b a Source #

A data type representing a Clif (multivector) composed of direct sum of scaled blades

Constructors

Clif 

Fields

Instances

Functor (Clif b) Source # 

Methods

fmap :: (a -> b) -> Clif b a -> Clif b b #

(<$) :: a -> Clif b b -> Clif b a #

(Eq b, Eq a, Basis b a) => Eq (Clif b a) Source #

The Eq instance calculates the canonical forms of the compared Clifs before comparison.

Methods

(==) :: Clif b a -> Clif b a -> Bool #

(/=) :: Clif b a -> Clif b a -> Bool #

(Eq a, Basis b a, Fractional a) => Fractional (Clif b a) Source #

Inverse elements only exist for Clifs c for which c times c is scalar. For others, recip does not terminate.

Methods

(/) :: Clif b a -> Clif b a -> Clif b a #

recip :: Clif b a -> Clif b a #

fromRational :: Rational -> Clif b a #

(Eq a, Basis b a) => Num (Clif b a) Source #

Note that abs and signum are only well-defined on the scalar component of each Clif, and zero otherwise.

Methods

(+) :: Clif b a -> Clif b a -> Clif b a #

(-) :: Clif b a -> Clif b a -> Clif b a #

(*) :: Clif b a -> Clif b a -> Clif b a #

negate :: Clif b a -> Clif b a #

abs :: Clif b a -> Clif b a #

signum :: Clif b a -> Clif b a #

fromInteger :: Integer -> Clif b a #

(Show b, Show a) => Show (Clif b a) Source #

Show instance just shows the underlying Map for now

Methods

showsPrec :: Int -> Clif b a -> ShowS #

show :: Clif b a -> String #

showList :: [Clif b a] -> ShowS #

Constructors

fromList :: (Eq a, Basis b a) => [([b], a)] -> Clif b a Source #

Constructs a Clif from a list of blades and their multipliers in canonical form.

>>> fromList [([], 42), ([E 1, E 2], 1)]
42 *: [] + 1 *: [E 1,E 2]

blade :: (Eq a, Basis b a) => [b] -> a -> Clif b a Source #

Constructor for a blade

(*:) :: (Eq a, Basis b a) => a -> [b] -> Clif b a infix 9 Source #

Infix synonym for flip blade

vec :: (Eq a, Basis b a) => b -> a -> Clif b a Source #

Constructor for basis vector values. Note that vec a s is equivalent to blade [a] s.

Operations

gMul :: (Eq a, Basis b a) => Clif b a -> Clif b a -> Clif b a Source #

The Clifford (geometric) product on Clifs.

gMul' :: (Eq a, Basis b a) => Map [b] a -> Map [b] a -> Map [b] a Source #

The Clifford product on Maps of blades and multipliers. Filter out zero values

gPlus :: (Eq a, Basis b a) => Clif b a -> Clif b a -> Clif b a Source #

Addition of Clif values (direct sum).

gPlus' :: (Eq a, Basis b a) => Map [b] a -> Map [b] a -> Map [b] a Source #

Direct sum of matching keys from two Maps. Filter out zero values.

rev :: Ord b => Clif b a -> Clif b a Source #

Reverse of a Clif, i.e. the reverse of all its component blades.

rev' :: Ord b => Map [b] a -> Map [b] a Source #

Reverses each blade (key)

canon :: (Eq a, Basis b a) => Clif b a -> Clif b a Source #

Returns the canonical form of a Clif

canon' :: (Eq a, Basis b a) => Map [b] a -> Map [b] a Source #

Returns the canonical representation of a Clif (blades simplified and in canonical order)

grade :: (Eq a, Basis b a) => Int -> Clif b a -> Clif b a Source #

Grade projection on the given grade. For negative values, returns zero.

Note that this always calculates the canonical form of a Clif before projecting it.

grade' :: (Eq a, Basis b a) => Int -> Map [b] a -> Map [b] a Source #

Filter blades (keys) by their length.

contractWith :: (Eq a, Basis b a) => (Int -> Int -> Int) -> Clif b a -> Clif b a -> Clif b a Source #

General product or contraction of Clifs using a given grade function. Given a function f :: Int -> Int -> Int and p, q-grade Clifs A and B, contractWith returns the f(p,q)-grade projection of the Clif A times B.

Properties

filledGrades :: (Eq a, Basis b a) => Clif b a -> [Int] Source #

List of nonzero grades.

Note that this always calculates the canonical form of a Clif before recovering the filled grades.

filledGrades' :: (Eq a, Basis b a) => Map [b] a -> [Int] Source #

List of nonzero grades

Note that this always calculates the canonical form of a Clif before recovering the filled grades.

grades :: (Eq a, Basis b a) => Clif b a -> [(Int, Clif b a)] Source #

Returns a list containing each non-zero grade component of a Clif and it's grade as an Int.

Note that this always calculates the canonical form of a Clif before testing any operations.

isScalar :: (Eq a, Basis b a) => Clif b a -> Bool Source #

True if the Clif contains no nonzero blades of grade greater than zero.

Note that this always calculates the canonical form of a Clif before testing whether it is scalar.

isZero :: (Eq a, Basis b a) => Clif b a -> Bool Source #

True for a zero multivector.

Note that this always calculates the canonical form of a Clif before testing whether it is zero.

maxGrade :: (Eq a, Basis b a) => Clif b a -> Int Source #

The highest nonempty nonzero grade of a Clif.

Note that this always calculates the canonical form of a Clif before recovering the highest grade.

Utility functions

(.:) :: (a -> b) -> (c -> d -> a) -> c -> d -> b infixl 8 Source #

Composition of unary and binary functions, highly useful since two-parameter constructors are ubiquitous here. Redefined here to skip extra dependencies.

(f .: g) x y = f (g x y)