Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides tools for working with linear and affine transformations.
Synopsis
- class (Bilinear f x y, Manifold x, Manifold y, Manifold (f x y)) => Bilinear f y x where
- (<.<) :: (Map c f x y, Bilinear f y x) => (c #* y) -> (c # f y x) -> c # x
- (<$<) :: (Map c f x y, Bilinear f y x) => [c #* y] -> (c # f y x) -> [c # x]
- data Tensor y x
- toMatrix :: (Manifold x, Manifold y) => (c # Tensor y x) -> Matrix (Dimension y) (Dimension x) Double
- fromMatrix :: Matrix (Dimension y) (Dimension x) Double -> c # Tensor y x
- toRows :: (Manifold x, Manifold y) => (c # Tensor y x) -> Vector (Dimension y) (c # x)
- toColumns :: (Manifold x, Manifold y) => (c # Tensor y x) -> Vector (Dimension x) (c # y)
- fromRows :: (Manifold x, Manifold y) => Vector (Dimension y) (c # x) -> c # Tensor y x
- fromColumns :: (Manifold x, Manifold y) => Vector (Dimension x) (c # y) -> c # Tensor y x
- inverse :: (Manifold x, Manifold y, Dimension x ~ Dimension y) => (c # Tensor y x) -> c #* Tensor x y
- determinant :: (Manifold x, Manifold y, Dimension x ~ Dimension y) => (c # Tensor y x) -> Double
- newtype Affine f y z x = Affine (z, f y x)
- class (Manifold y, Manifold z) => Translation z y where
- (>.+>) :: (Map c f y x, Translation z x) => (c # f y x) -> (c #* z) -> c # y
- (>$+>) :: (Map c f y x, Translation z x) => (c # f y x) -> [c #* z] -> [c # y]
- type (<*) y x = Affine Tensor y y x
Bilinear Forms
class (Bilinear f x y, Manifold x, Manifold y, Manifold (f x y)) => Bilinear f y x where Source #
(>.<) :: (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
(Manifold x, Manifold y) => Bilinear Tensor y x Source # | |
KnownConvolutional rd r c z x => Bilinear (Convolutional rd r c) z x Source # | |
Defined in Goal.Geometry.Map.Linear.Convolutional |
(<.<) :: (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
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.
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.
Affine (z, f y x) |
Instances
(Translation z y, Map c f y x) => Map c (Affine f y) z x Source # | |
(Translation z y, Map c (Affine f y) z x, Propagate c f y x) => Propagate c (Affine f y) z x Source # | |
(Manifold z, Manifold (f y x)) => Product (Affine f y z x) Source # | |
Defined in Goal.Geometry.Map.Linear | |
(Manifold z, Manifold (f y x)) => Manifold (Affine f y z x) Source # | |
type First (Affine f y z x) Source # | |
Defined in Goal.Geometry.Map.Linear | |
type Second (Affine f y z x) Source # | |
Defined in Goal.Geometry.Map.Linear | |
type Dimension (Affine f y z x) Source # | |
Defined in Goal.Geometry.Map.Linear |
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.
(>+>) :: (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
Manifold z => Translation z z Source # | |
(Manifold z, Manifold y) => Translation (y, z) 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.