downhill-0.1.0.0: Reverse mode automatic differentiation
Safe HaskellSafe-Inferred
LanguageHaskell2010

Downhill.Grad

Synopsis

Documentation

class (AdditiveGroup s, VectorSpace v, VectorSpace dv, Scalar v ~ s, Scalar dv ~ s) => Dual s v dv where Source #

Dual of a vector v is a linear map v -> Scalar v.

Methods

evalGrad :: dv -> v -> s Source #

Instances

Instances details
Dual Double Double Double Source # 
Instance details

Defined in Downhill.Grad

Dual Float Float Float Source # 
Instance details

Defined in Downhill.Grad

Methods

evalGrad :: Float -> Float -> Float Source #

Dual Integer Integer Integer Source # 
Instance details

Defined in Downhill.Grad

(Dual s a da, Dual s b db) => Dual s (a, b) (da, db) Source # 
Instance details

Defined in Downhill.Grad

Methods

evalGrad :: (da, db) -> (a, b) -> s Source #

(Dual s a da, Dual s b db, Dual s c dc) => Dual s (a, b, c) (da, db, dc) Source # 
Instance details

Defined in Downhill.Grad

Methods

evalGrad :: (da, db, dc) -> (a, b, c) -> s Source #

Num a => Dual (AsNum a) (AsNum a) (AsNum a) Source # 
Instance details

Defined in Downhill.BVar.Num

Methods

evalGrad :: AsNum a -> AsNum a -> AsNum a Source #

class (Dual (Scalar g) (MtVector g) (MtCovector g), VectorSpace g) => MetricTensor g where Source #

MetricTensor converts gradients to vectors.

It is really inverse of a metric tensor, because it maps cotangent space into tangent space. Gradient descent doesn't need metric tensor, it needs inverse.

Minimal complete definition

evalMetric

Associated Types

type MtVector g :: Type Source #

type MtCovector g :: Type Source #

Methods

evalMetric :: g -> MtCovector g -> MtVector g Source #

m must be symmetric:

evalGrad x (evalMetric m y) = evalGrad y (evalMetric m x)

innerProduct :: g -> MtCovector g -> MtCovector g -> Scalar g Source #

innerProduct m x y = evalGrad x (evalMetric m y)

sqrNorm :: g -> MtCovector g -> Scalar g Source #

sqrNorm m x = innerProduct m x x

Instances

Instances details
MetricTensor Double Source # 
Instance details

Defined in Downhill.Grad

Associated Types

type MtVector Double Source #

type MtCovector Double Source #

MetricTensor Float Source # 
Instance details

Defined in Downhill.Grad

Associated Types

type MtVector Float Source #

type MtCovector Float Source #

MetricTensor Integer Source # 
Instance details

Defined in Downhill.Grad

Associated Types

type MtVector Integer Source #

type MtCovector Integer Source #

Num a => MetricTensor (AsNum a) Source # 
Instance details

Defined in Downhill.BVar.Num

Associated Types

type MtVector (AsNum a) Source #

type MtCovector (AsNum a) Source #

(MetricTensor ma, MetricTensor mb, Scalar ma ~ Scalar mb) => MetricTensor (ma, mb) Source # 
Instance details

Defined in Downhill.Grad

Associated Types

type MtVector (ma, mb) Source #

type MtCovector (ma, mb) Source #

Methods

evalMetric :: (ma, mb) -> MtCovector (ma, mb) -> MtVector (ma, mb) Source #

innerProduct :: (ma, mb) -> MtCovector (ma, mb) -> MtCovector (ma, mb) -> Scalar (ma, mb) Source #

sqrNorm :: (ma, mb) -> MtCovector (ma, mb) -> Scalar (ma, mb) Source #

(MetricTensor ma, MetricTensor mb, MetricTensor mc, Scalar ma ~ Scalar mb, Scalar ma ~ Scalar mc) => MetricTensor (ma, mb, mc) Source # 
Instance details

Defined in Downhill.Grad

Associated Types

type MtVector (ma, mb, mc) Source #

type MtCovector (ma, mb, mc) Source #

Methods

evalMetric :: (ma, mb, mc) -> MtCovector (ma, mb, mc) -> MtVector (ma, mb, mc) Source #

innerProduct :: (ma, mb, mc) -> MtCovector (ma, mb, mc) -> MtCovector (ma, mb, mc) -> Scalar (ma, mb, mc) Source #

sqrNorm :: (ma, mb, mc) -> MtCovector (ma, mb, mc) -> Scalar (ma, mb, mc) Source #

class (Dual (MScalar p) (Tang p) (Grad p), MetricTensor (Metric p), MtVector (Metric p) ~ Tang p, MtCovector (Metric p) ~ Grad p, BasicVector (Tang p), BasicVector (Grad p)) => HasGrad p Source #

HasGrad is a collection of types and constraints that are useful in many places. It helps to keep type signatures short.

Associated Types

type MScalar p :: Type Source #

Scalar of Tang p and Grad p.

type Tang p :: Type Source #

Tangent vector of manifold p. If p is AffineSpace, Tang p should be Diff p. If p is VectorSpace, Tang p might be the same as p itself.

type Grad p :: Type Source #

Dual of tangent space of p.

type Metric p :: Type Source #

Instances

Instances details
HasGrad Double Source # 
Instance details

Defined in Downhill.Grad

HasGrad Float Source # 
Instance details

Defined in Downhill.Grad

Associated Types

type MScalar Float Source #

type Tang Float Source #

type Grad Float Source #

type Metric Float Source #

HasGrad Integer Source # 
Instance details

Defined in Downhill.Grad

Num a => HasGrad (AsNum a) Source # 
Instance details

Defined in Downhill.BVar.Num

Associated Types

type MScalar (AsNum a) Source #

type Tang (AsNum a) Source #

type Grad (AsNum a) Source #

type Metric (AsNum a) Source #

(HasGrad a, HasGrad b, MScalar b ~ MScalar a) => HasGrad (a, b) Source # 
Instance details

Defined in Downhill.Grad

Associated Types

type MScalar (a, b) Source #

type Tang (a, b) Source #

type Grad (a, b) Source #

type Metric (a, b) Source #

(HasGrad a, HasGrad b, HasGrad c, MScalar b ~ MScalar a, MScalar c ~ MScalar a) => HasGrad (a, b, c) Source # 
Instance details

Defined in Downhill.Grad

Associated Types

type MScalar (a, b, c) Source #

type Tang (a, b, c) Source #

type Grad (a, b, c) Source #

type Metric (a, b, c) Source #

HasGrad a => HasGrad (TraversableVar f a) Source # 
Instance details

Defined in Downhill.BVar.Traversable

Associated Types

type MScalar (TraversableVar f a) Source #

type Tang (TraversableVar f a) Source #

type Grad (TraversableVar f a) Source #

type Metric (TraversableVar f a) Source #

type HasGradAffine p = (AffineSpace p, HasGrad p, HasGrad (Tang p), Tang p ~ Diff p, Tang (Tang p) ~ Tang p, Grad (Tang p) ~ Grad p) Source #