goal-geometry-0.1: Scientific computing on geometric objects

Safe HaskellNone
LanguageHaskell2010

Goal.Geometry.Map.Multilinear

Contents

Description

The Map module provides tools for developing function space Manifolds. A map is a Manifold where the Points of the Manifold represent parametric functions between Manifolds. The defining feature of Maps is that they have a particular Domain and Codomain, which themselves are Manifolds.

Synopsis

Tensors

data Tensor m n Source

Manifold of Tensors given by the tensor product of the underlying pair of Manifolds.

Constructors

Tensor m n 

Instances

(Manifold m, Manifold n) => Apply c d (Tensor m n) Source 
(Eq m, Eq n) => Eq (Tensor m n) Source 
(Read m, Read n) => Read (Tensor m n) Source 
(Show m, Show n) => Show (Tensor m n) Source 
(Manifold m, Manifold n) => Manifold (Tensor n m) Source 
(Manifold m, Manifold n) => Map (Tensor m n) Source 
type Domain (Tensor m n) = n Source 
type Codomain (Tensor m n) = m Source 

Construction

(>.<) :: (Manifold m, Manifold n) => (d :#: m) -> (c :#: n) -> Function (Dual c) d :#: Tensor m n Source

>.< denotes the outer product between two points. It provides a way of constructing matrices of the Tensor product space.

Matrix Operations

(<#>) :: (Manifold m, Manifold n, Manifold o) => (Function d e :#: Tensor m n) -> (Function c d :#: Tensor n o) -> Function c e :#: Tensor m o Source

Tensor product composition.

matrixRank :: (Manifold m, Manifold n) => (c :#: Tensor m n) -> Int Source

matrixInverse :: (Manifold n, Manifold m) => (Function c d :#: Tensor m n) -> Function d c :#: Tensor n m Source

The inverse of a given Tensor point.

matrixTranspose :: (Manifold m, Manifold n) => (Function c d :#: Tensor m n) -> Function (Dual d) (Dual c) :#: Tensor n m Source

The transpose of a given Tensor point.

matrixSquareRoot :: Manifold m => (c :#: Tensor m m) -> c :#: Tensor m m Source

The square root of a matrix.

matrixApply :: (Manifold m, Manifold n) => (Function c d :#: Tensor n m) -> (c :#: m) -> d :#: n Source

Matrix vector multiplication.

matrixMap :: (Manifold m, Manifold n) => (Function c d :#: Tensor m n) -> [c :#: n] -> [d :#: m] Source

Mapped matrix vector multiplication, where we first turn the input vectors into a matrix itself (this can greatly improve computation time).

matrixDiagonalConcatenate :: (Manifold m, Manifold n, Manifold o, Manifold p) => (Function c d :#: Tensor m n) -> (Function e f :#: Tensor o p) -> Function (c, e) (d, f) :#: Tensor (m, o) (n, p) Source

Creates a block diagonal matrix.

Cartesian

coordinateTransform :: Manifold m => [c :#: m] -> Function Cartesian c :#: Tensor m Euclidean Source

Returns the coordinate transformation from Euclidean space into the space defined by the given basis vectors. This is a glorified fromColumns function.

linearProjection :: Manifold m => [Cartesian :#: m] -> Function Cartesian Cartesian :#: Tensor m m Source

Returns the linear projection operator for the given subset of basis vectors.

HMatrix Conversion

toHMatrix :: Manifold n => (c :#: Tensor m n) -> Matrix Double Source

Converts a point on a Tensor product manifold to a matrix for snappy calculation.

Affine Functions

data Affine m n Source

Manifolds of Affine functions.

Constructors

Affine m n 

Instances

(Manifold m, Manifold n) => Apply c d (Affine m n) Source 
(Eq m, Eq n) => Eq (Affine m n) Source 
(Read m, Read n) => Read (Affine m n) Source 
(Show m, Show n) => Show (Affine m n) Source 
(Manifold m, Manifold n) => Manifold (Affine m n) Source 
(Manifold m, Manifold n) => Map (Affine m n) Source 
type Domain (Affine m n) = n Source 
type Codomain (Affine m n) = m Source 

splitAffine :: (Manifold m, Manifold n) => (Function c d :#: Affine m n) -> (d :#: m, Function c d :#: Tensor m n) Source

Splits an Point on an Affine space into a matrix and a constant.

joinAffine :: (Manifold m, Manifold n) => (d :#: m) -> (Function c d :#: Tensor m n) -> Function c d :#: Affine m n Source

Combines a matrix and a constant into Point on an Affine space.