ad-4.5: Automatic Differentiation
Copyright(c) Edward Kmett 2010-2021
LicenseBSD3
Maintainerekmett@gmail.com
Stabilityexperimental
PortabilityGHC only
Safe HaskellNone
LanguageHaskell2010

Numeric.AD.Rank1.Kahn.Float

Description

This module provides reverse-mode Automatic Differentiation using post-hoc linear time topological sorting.

For reverse mode AD we use StableName to recover sharing information from the tape to avoid combinatorial explosion, and thus run asymptotically faster than it could without such sharing information, but the use of side-effects contained herein is benign.

Synopsis

Documentation

data KahnFloat Source #

Kahn is a Mode using reverse-mode automatic differentiation that provides fast diffFU, diff2FU, grad, grad2 and a fast jacobian when you have a significantly smaller number of outputs than inputs.

Instances

Instances details
Enum KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Eq KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Floating KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Fractional KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Num KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Ord KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Real KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

RealFloat KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

RealFrac KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Show KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

MuRef KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Associated Types

type DeRef KahnFloat :: Type -> Type #

Methods

mapDeRef :: Applicative f => (forall b. (MuRef b, DeRef KahnFloat ~ DeRef b) => b -> f u) -> KahnFloat -> f (DeRef KahnFloat u) #

Erf KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

InvErf KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Mode KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Associated Types

type Scalar KahnFloat Source #

Jacobian KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Associated Types

type D KahnFloat Source #

Grad i o o' => Grad (KahnFloat -> i) (Float -> o) (Float -> o') Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Methods

pack :: (KahnFloat -> i) -> [KahnFloat] -> KahnFloat Source #

unpack :: (List -> List) -> Float -> o Source #

unpack' :: (List -> (Float, List)) -> Float -> o' Source #

type DeRef KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

type Scalar KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

type D KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

auto :: Mode t => Scalar t -> t Source #

Embed a constant

Gradient

grad :: Traversable f => (f KahnFloat -> KahnFloat) -> f Float -> f Float Source #

The grad function calculates the gradient of a non-scalar-to-scalar function with kahn-mode AD in a single pass.

>>> grad (\[x,y,z] -> x*y+z) [1.0,2.0,3.0]
[2.0,1.0,1.0]

grad' :: Traversable f => (f KahnFloat -> KahnFloat) -> f Float -> (Float, f Float) Source #

The grad' function calculates the result and gradient of a non-scalar-to-scalar function with kahn-mode AD in a single pass.

>>> grad' (\[x,y,z] -> x*y+z) [1.0,2.0,3.0]
(5.0,[2.0,1.0,1.0])

gradWith :: Traversable f => (Float -> Float -> b) -> (f KahnFloat -> KahnFloat) -> f Float -> f b Source #

grad g f function calculates the gradient of a non-scalar-to-scalar function f with kahn-mode AD in a single pass. The gradient is combined element-wise with the argument using the function g.

grad = gradWith (_ dx -> dx)
id = gradWith const

gradWith' :: Traversable f => (Float -> Float -> b) -> (f KahnFloat -> KahnFloat) -> f Float -> (Float, f b) Source #

grad' g f calculates the result and gradient of a non-scalar-to-scalar function f with kahn-mode AD in a single pass the gradient is combined element-wise with the argument using the function g.

grad' == gradWith' (_ dx -> dx)

Jacobian

jacobian :: (Traversable f, Functor g) => (f KahnFloat -> g KahnFloat) -> f Float -> g (f Float) Source #

The jacobian function calculates the jacobian of a non-scalar-to-non-scalar function with kahn AD lazily in m passes for m outputs.

>>> jacobian (\[x,y] -> [y,x,x*y]) [2.0,1.0]
[[0.0,1.0],[1.0,0.0],[1.0,2.0]]

jacobian' :: (Traversable f, Functor g) => (f KahnFloat -> g KahnFloat) -> f Float -> g (Float, f Float) Source #

The jacobian' function calculates both the result and the Jacobian of a nonscalar-to-nonscalar function, using m invocations of kahn AD, where m is the output dimensionality. Applying fmap snd to the result will recover the result of jacobian | An alias for gradF'

ghci> jacobian' ([x,y] -> [y,x,x*y]) [2.0,1.0] [(1.0,[0.0,1.0]),(2.0,[1.0,0.0]),(2.0,[1.0,2.0])]

jacobianWith :: (Traversable f, Functor g) => (Float -> Float -> b) -> (f KahnFloat -> g KahnFloat) -> f Float -> g (f b) Source #

'jacobianWith g f' calculates the Jacobian of a non-scalar-to-non-scalar function f with kahn AD lazily in m passes for m outputs.

Instead of returning the Jacobian matrix, the elements of the matrix are combined with the input using the g.

jacobian = jacobianWith (_ dx -> dx)
jacobianWith const = (f x -> const x <$> f x)

jacobianWith' :: (Traversable f, Functor g) => (Float -> Float -> b) -> (f KahnFloat -> g KahnFloat) -> f Float -> g (Float, f b) Source #

jacobianWith g f' calculates both the result and the Jacobian of a nonscalar-to-nonscalar function f, using m invocations of kahn AD, where m is the output dimensionality. Applying fmap snd to the result will recover the result of jacobianWith

Instead of returning the Jacobian matrix, the elements of the matrix are combined with the input using the g.

jacobian' == jacobianWith' (_ dx -> dx)

Hessian

hessian :: Traversable f => (f (On (Kahn KahnFloat)) -> On (Kahn KahnFloat)) -> f Float -> f (f Float) Source #

Compute the hessian via the jacobian of the gradient. gradient is computed in Kahn mode and then the jacobian is computed in Kahn mode.

However, since the grad f :: f a -> f a is square this is not as fast as using the forward-mode jacobian of a reverse mode gradient provided by hessian.

>>> hessian (\[x,y] -> x*y) [1.0,2.0]
[[0.0,1.0],[1.0,0.0]]

hessianF :: (Traversable f, Functor g) => (f (On (Kahn KahnFloat)) -> g (On (Kahn KahnFloat))) -> f Float -> g (f (f Float)) Source #

Compute the order 3 Hessian tensor on a non-scalar-to-non-scalar function via the Kahn-mode Jacobian of the Kahn-mode Jacobian of the function.

Less efficient than hessianF.

Derivatives

diff :: (KahnFloat -> KahnFloat) -> Float -> Float Source #

Compute the derivative of a function.

>>> diff sin 0
1.0
>>> cos 0
1.0

diff' :: (KahnFloat -> KahnFloat) -> Float -> (Float, Float) Source #

The diff' function calculates the value and derivative, as a pair, of a scalar-to-scalar function.

>>> diff' sin 0
(0.0,1.0)

diffF :: Functor f => (KahnFloat -> f KahnFloat) -> Float -> f Float Source #

Compute the derivatives of a function that returns a vector with regards to its single input.

>>> diffF (\a -> [sin a, cos a]) 0
[1.0,0.0]

diffF' :: Functor f => (KahnFloat -> f KahnFloat) -> Float -> f (Float, Float) Source #

Compute the derivatives of a function that returns a vector with regards to its single input as well as the primal answer.

>>> diffF' (\a -> [sin a, cos a]) 0
[(0.0,1.0),(1.0,0.0)]

Unsafe Variadic Gradient

Variadic combinators for variadic mixed-mode automatic differentiation.

Unfortunately, variadicity comes at the expense of being able to use quantification to avoid sensitivity confusion, so be careful when counting the number of auto calls you use when taking the gradient of a function that takes gradients!

vgrad :: Grad i o o' => i -> o Source #

vgrad' :: Grad i o o' => i -> o' Source #

class Grad i o o' | i -> o o', o -> i o', o' -> i o Source #

Minimal complete definition

pack, unpack, unpack'

Instances

Instances details
Grad i o o' => Grad (KahnFloat -> i) (Float -> o) (Float -> o') Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Methods

pack :: (KahnFloat -> i) -> [KahnFloat] -> KahnFloat Source #

unpack :: (List -> List) -> Float -> o Source #

unpack' :: (List -> (Float, List)) -> Float -> o' Source #