Safe Haskell | None |
---|---|
Language | Haskell2010 |
Goal.Geometry.Differential
Description
Tools for modelling the differential and Riemannian geometry of a
Manifold
.
Synopsis
- class (Primal c, Manifold x) => Riemannian c x where
- euclideanDistance :: Manifold x => (c # x) -> (c # x) -> Double
- class Map c f y x => Propagate c f y x where
- backpropagation :: Propagate c f y x => (a -> (c # y) -> c #* y) -> [(a, c #* x)] -> (c # f y x) -> c #* f y x
- type family PotentialCoordinates x :: Type
- class (Primal (PotentialCoordinates x), Manifold x) => Legendre x where
- potential :: (PotentialCoordinates x # x) -> Double
- class Legendre x => DuallyFlat x where
- dualPotential :: (PotentialCoordinates x #* x) -> Double
- canonicalDivergence :: DuallyFlat x => (PotentialCoordinates x # x) -> (PotentialCoordinates x #* x) -> Double
- differential :: Manifold x => (forall a. RealFloat a => Vector (Dimension x) a -> a) -> (c # x) -> c #* x
- hessian :: Manifold x => (forall a. RealFloat a => Vector (Dimension x) a -> a) -> (c # x) -> c #* Tensor x x
Riemannian Manifolds
class (Primal c, Manifold x) => Riemannian c x where Source #
Riemannian
Manifold
s are differentiable Manifold
s associated with a
smoothly varying Tensor
known as the Riemannian metric
. flat
and
sharp
correspond to applying this metric
to elements of the Primal
and
Dual
spaces, respectively.
Minimal complete definition
Instances
KnownNat k => Riemannian Cartesian (Euclidean k) Source # | |
Defined in Goal.Geometry.Differential Methods metric :: (Cartesian # Euclidean k) -> Cartesian #* Tensor (Euclidean k) (Euclidean k) Source # flat :: (Cartesian # Euclidean k) -> (Cartesian # Euclidean k) -> Cartesian #* Euclidean k Source # sharp :: (Cartesian # Euclidean k) -> (Cartesian #* Euclidean k) -> Cartesian # Euclidean k Source # |
Backpropagation
class Map c f y x => Propagate c f y x where Source #
A class of Map
s which can propagate
errors. That is, given an error
derivative on the output, the input which caused the output, and a
Map
to derive, return the derivative of the error with respect to the
parameters of the Map
, as well as the output of the Map
.
Methods
Instances
(Bilinear Tensor y x, Primal c) => Propagate c Tensor y 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 # | |
(Propagate c f z y, Propagate c (NeuralNetwork gys g) y x, Map c f y z, Transition c (Dual c) y, Legendre y, Riemannian c y, Bilinear f z y) => Propagate c (NeuralNetwork ('(g, y) ': gys) f) z x Source # | |
Defined in Goal.Geometry.Map.NeuralNetwork Methods propagate :: [c #* z] -> [c #* x] -> (c # NeuralNetwork ('(g, y) ': gys) f z x) -> (c #* NeuralNetwork ('(g, y) ': gys) f z x, [c # z]) Source # | |
Propagate c f z x => Propagate c (NeuralNetwork ('[] :: [(Type -> Type -> Type, Type)]) f) z x Source # | |
Defined in Goal.Geometry.Map.NeuralNetwork Methods propagate :: [c #* z] -> [c #* x] -> (c # NeuralNetwork '[] f z x) -> (c #* NeuralNetwork '[] f z x, [c # z]) Source # | |
KnownConvolutional rd r c z x => Propagate a (Convolutional rd r c) z x Source # | |
Defined in Goal.Geometry.Map.Linear.Convolutional Methods propagate :: [a #* z] -> [a #* x] -> (a # Convolutional rd r c z x) -> (a #* Convolutional rd r c z x, [a # z]) Source # |
backpropagation :: Propagate c f y x => (a -> (c # y) -> c #* y) -> [(a, c #* x)] -> (c # f y x) -> c #* f y x Source #
An implementation of backpropagation using the Propagate
class. The first
argument is a function which takes a generalized target output and function
output and returns an error. The second argument is a list of target outputs
and function inputs. The third argument is the parameteric function to be
optimized, and its differential is what is returned.
Legendre Manifolds
type family PotentialCoordinates x :: Type Source #
Instances
type PotentialCoordinates (x, y) Source # | |
Defined in Goal.Geometry.Differential | |
type PotentialCoordinates (Replicated k x) Source # | |
Defined in Goal.Geometry.Differential |
class (Primal (PotentialCoordinates x), Manifold x) => Legendre x where Source #
Although convex analysis is usually developed seperately from differential
geometry, it arises naturally out of the theory of dually flat Manifold
s (Amari and Nagaoka, 2000).
A Manifold
is Legendre
if it is associated with a particular convex
function known as a potential
.
Instances
(Legendre x, Legendre y, PotentialCoordinates x ~ PotentialCoordinates y) => Legendre (x, y) Source # | |
Defined in Goal.Geometry.Differential | |
(Legendre x, KnownNat k) => Legendre (Replicated k x) Source # | |
Defined in Goal.Geometry.Differential Methods potential :: (PotentialCoordinates (Replicated k x) # Replicated k x) -> Double Source # |
class Legendre x => DuallyFlat x where Source #
A Manifold
is DuallyFlat
when we can describe the dualPotential
, which
is the convex conjugate of potential
.
Methods
dualPotential :: (PotentialCoordinates x #* x) -> Double Source #
Instances
(DuallyFlat x, KnownNat k) => DuallyFlat (Replicated k x) Source # | |
Defined in Goal.Geometry.Differential Methods dualPotential :: (PotentialCoordinates (Replicated k x) #* Replicated k x) -> Double Source # |
canonicalDivergence :: DuallyFlat x => (PotentialCoordinates x # x) -> (PotentialCoordinates x #* x) -> Double Source #
Computes the canonicalDivergence
between two points. Note that relative
to the typical definition of the KL-Divergence/relative entropy, the
arguments of this function are flipped.