ad-3.0.1: Automatic Differentiation

PortabilityGHC only
Stabilityexperimental
Maintainerekmett@gmail.com
Safe HaskellNone

Numeric.AD.Internal.Reverse

Description

Reverse-Mode Automatic Differentiation implementation details

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

newtype Reverse a Source

Reverse 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.

Constructors

Reverse (Tape a (Reverse a)) 

Instances

Typeable1 Reverse 
Lifted Reverse => Jacobian Reverse 
Primal Reverse 
Lifted Reverse => Mode Reverse 
Lifted Reverse 
Var Reverse 
Show a => Show (Reverse a) 
MuRef (Reverse a) 
Var (AD Reverse) 
Num a => Grad (AD Reverse a) [a] (a, [a]) a 
Grad i o o' a => Grad (AD Reverse a -> i) (a -> o) (a -> o') a 

data Tape a t Source

A Tape records the information needed back propagate from the output to each input during Reverse Mode AD.

Constructors

Zero 
Lift !a 
Var !a !Int 
Binary !a a a t t 
Unary !a a t 

Instances

Typeable2 Tape 
(Data a, Data t) => Data (Tape a t) 
(Show a, Show t) => Show (Tape a t) 

partials :: Num a => AD Reverse a -> [(Int, a)]Source

This returns a list of contributions to the partials. The variable ids returned in the list are likely not unique!

partialArray :: Num a => (Int, Int) -> AD Reverse a -> Array Int aSource

Return an Array of partials given bounds for the variable IDs.

partialMap :: Num a => AD Reverse a -> IntMap aSource

Return an IntMap of sparse partials

derivative' :: Num a => AD Reverse a -> (a, a)Source

class Primal v => Var v whereSource

Used to mark variables for inspection during the reverse pass

Methods

var :: a -> Int -> v aSource

varId :: v a -> IntSource

Instances

bind :: (Traversable f, Var v) => f a -> (f (v a), (Int, Int))Source

unbind :: (Functor f, Var v) => f (v a) -> Array Int a -> f aSource

unbindMap :: (Functor f, Var v, Num a) => f (v a) -> IntMap a -> f aSource

unbindWith :: (Functor f, Var v, Num a) => (a -> b -> c) -> f (v a) -> Array Int b -> f cSource

unbindMapWithDefault :: (Functor f, Var v, Num a) => b -> (a -> b -> c) -> f (v a) -> IntMap b -> f cSource

vgrad :: Grad i o o' a => i -> oSource

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

class Num a => Grad i o o' a | i -> a o o', o -> a i o', o' -> a i o whereSource

Methods

pack :: i -> [AD Reverse a] -> AD Reverse aSource

unpack :: ([a] -> [a]) -> oSource

unpack' :: ([a] -> (a, [a])) -> o'Source

Instances

Num a => Grad (AD Reverse a) [a] (a, [a]) a 
Grad i o o' a => Grad (AD Reverse a -> i) (a -> o) (a -> o') a