goal-geometry-0.20: The basic geometric type system of Goal
Safe HaskellNone
LanguageHaskell2010

Goal.Geometry.Map.Linear

Description

This module provides tools for working with linear and affine transformations.

Synopsis

Bilinear Forms

class (Bilinear f x y, Manifold x, Manifold y, Manifold (f x y)) => Bilinear f y x where Source #

A Manifold is Bilinear if its elements are bilinear forms.

Methods

(>.<) :: (c # y) -> (c # x) -> c # f y x Source #

Tensor outer product.

(>$<) :: [c # y] -> [c # x] -> c # f y x Source #

Average of tensor outer products.

transpose :: (c # f y x) -> c # f x y Source #

Tensor transpose.

Instances

Instances details
(Manifold x, Manifold y) => Bilinear Tensor y x Source # 
Instance details

Defined in Goal.Geometry.Map.Linear

Methods

(>.<) :: (c # y) -> (c # x) -> c # Tensor y x Source #

(>$<) :: [c # y] -> [c # x] -> c # Tensor y x Source #

transpose :: (c # Tensor y x) -> c # Tensor x y Source #

KnownConvolutional rd r c z x => Bilinear (Convolutional rd r c) z x Source # 
Instance details

Defined in Goal.Geometry.Map.Linear.Convolutional

Methods

(>.<) :: (c0 # z) -> (c0 # x) -> c0 # Convolutional rd r c z x Source #

(>$<) :: [c0 # z] -> [c0 # x] -> c0 # Convolutional rd r c z x Source #

transpose :: (c0 # Convolutional rd r c z x) -> c0 # Convolutional rd r c x z Source #

(<.<) :: (Map c f x y, Bilinear f y x) => (c #* y) -> (c # f y x) -> c # x Source #

Transposed application.

(<$<) :: (Map c f x y, Bilinear f y x) => [c #* y] -> (c # f y x) -> [c # x] Source #

Mapped transposed application.

Tensors

data Tensor y x Source #

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

Instances

Instances details
(Manifold x, Manifold y) => Bilinear Tensor y x Source # 
Instance details

Defined in Goal.Geometry.Map.Linear

Methods

(>.<) :: (c # y) -> (c # x) -> c # Tensor y x Source #

(>$<) :: [c # y] -> [c # x] -> c # Tensor y x Source #

transpose :: (c # Tensor y x) -> c # Tensor x y Source #

(Manifold x, Manifold y) => Map c Tensor y x Source # 
Instance details

Defined in Goal.Geometry.Map.Linear

Methods

(>.>) :: (c # Tensor y x) -> (c #* x) -> c # y Source #

(>$>) :: (c # Tensor y x) -> [c #* x] -> [c # y] Source #

(Bilinear Tensor y x, Primal c) => Propagate c Tensor y x Source # 
Instance details

Defined in Goal.Geometry.Differential

Methods

propagate :: [c #* y] -> [c #* x] -> (c # Tensor y x) -> (c #* Tensor y x, [c # y]) Source #

(Manifold x, Manifold y) => Manifold (Tensor y x) Source # 
Instance details

Defined in Goal.Geometry.Map.Linear

Associated Types

type Dimension (Tensor y x) :: Nat Source #

type Dimension (Tensor y x) Source # 
Instance details

Defined in Goal.Geometry.Map.Linear

Matrix Construction

toMatrix :: (Manifold x, Manifold y) => (c # Tensor y x) -> Matrix (Dimension y) (Dimension x) Double Source #

Converts a point on a 'Tensor manifold into a Matrix.

fromMatrix :: Matrix (Dimension y) (Dimension x) Double -> c # Tensor y x Source #

Converts a Matrix into a Point on a 'Tensor Manifold.

toRows :: (Manifold x, Manifold y) => (c # Tensor y x) -> Vector (Dimension y) (c # x) Source #

Converts a point on a Tensor manifold into a a vector of rows.

toColumns :: (Manifold x, Manifold y) => (c # Tensor y x) -> Vector (Dimension x) (c # y) Source #

Converts a point on a Tensor manifold into a a vector of rows.

fromRows :: (Manifold x, Manifold y) => Vector (Dimension y) (c # x) -> c # Tensor y x Source #

Converts a vector of rows into a Tensor.

fromColumns :: (Manifold x, Manifold y) => Vector (Dimension x) (c # y) -> c # Tensor y x Source #

Converts a vector of rows into a Tensor.

Computation

inverse :: (Manifold x, Manifold y, Dimension x ~ Dimension y) => (c # Tensor y x) -> c #* Tensor x y Source #

The inverse of a tensor.

determinant :: (Manifold x, Manifold y, Dimension x ~ Dimension y) => (c # Tensor y x) -> Double Source #

The determinant of a tensor.

Affine Functions

newtype Affine f y z x Source #

An Affine Manifold represents linear transformations followed by a translation. The First component is the translation, and the Second component is the linear transformation.

Constructors

Affine (z, f y x) 

Instances

Instances details
(Translation z y, Map c f y x) => Map c (Affine f y) z x Source # 
Instance details

Defined in Goal.Geometry.Map.Linear

Methods

(>.>) :: (c # Affine f y z x) -> (c #* x) -> c # z Source #

(>$>) :: (c # Affine f y z x) -> [c #* x] -> [c # z] Source #

(Translation z y, Map c (Affine f y) z x, Propagate c f y x) => Propagate c (Affine f y) z x Source # 
Instance details

Defined in Goal.Geometry.Differential

Methods

propagate :: [c #* z] -> [c #* x] -> (c # Affine f y z x) -> (c #* Affine f y z x, [c # z]) Source #

(Manifold z, Manifold (f y x)) => Product (Affine f y z x) Source # 
Instance details

Defined in Goal.Geometry.Map.Linear

Associated Types

type First (Affine f y z x) Source #

type Second (Affine f y z x) Source #

Methods

join :: (c # First (Affine f y z x)) -> (c # Second (Affine f y z x)) -> c # Affine f y z x Source #

split :: (c # Affine f y z x) -> (c # First (Affine f y z x), c # Second (Affine f y z x)) Source #

(Manifold z, Manifold (f y x)) => Manifold (Affine f y z x) Source # 
Instance details

Defined in Goal.Geometry.Map.Linear

Associated Types

type Dimension (Affine f y z x) :: Nat Source #

type First (Affine f y z x) Source # 
Instance details

Defined in Goal.Geometry.Map.Linear

type First (Affine f y z x) = First (z, f y x)
type Second (Affine f y z x) Source # 
Instance details

Defined in Goal.Geometry.Map.Linear

type Second (Affine f y z x) = Second (z, f y x)
type Dimension (Affine f y z x) Source # 
Instance details

Defined in Goal.Geometry.Map.Linear

type Dimension (Affine f y z x) = Dimension (z, f y x)

class (Manifold y, Manifold z) => Translation z y where Source #

The Translation class is used to define translations where we only want to translate a subset of the parameters of the given object.

Methods

(>+>) :: (c # z) -> (c # y) -> c # z Source #

Translates the the first argument by the second argument.

anchor :: (c # z) -> c # y Source #

Returns the subset of the parameters of the given Point that are translated in this instance.

Instances

Instances details
Manifold z => Translation z z Source # 
Instance details

Defined in Goal.Geometry.Map.Linear

Methods

(>+>) :: (c # z) -> (c # z) -> c # z Source #

anchor :: (c # z) -> c # z Source #

(Manifold z, Manifold y) => Translation (y, z) y Source # 
Instance details

Defined in Goal.Geometry.Map.Linear

Methods

(>+>) :: (c # (y, z)) -> (c # y) -> c # (y, z) Source #

anchor :: (c # (y, z)) -> c # y Source #

(>.+>) :: (Map c f y x, Translation z x) => (c # f y x) -> (c #* z) -> c # y Source #

Operator that applies a Map to a subset of an input's parameters.

(>$+>) :: (Map c f y x, Translation z x) => (c # f y x) -> [c #* z] -> [c # y] Source #

Operator that maps a Map over a subset of the parameters of a list of inputs.

type (<*) y x = Affine Tensor y y x infixr 6 Source #

Infix synonym for simple Affine transformations.