ad-3.3.1.1: Automatic Differentiation

PortabilityGHC only
Stabilityexperimental
Maintainerekmett@gmail.com
Safe HaskellNone

Numeric.AD.Internal.Reverse

Description

Reverse-Mode Automatic Differentiation using a single Wengert list (or "tape").

This version uses Data.Reflection to find and update the tape.

This is asymptotically faster than using Reverse, which is forced to reify and topologically sort the graph, but it requires a fairly expensive rendezvous during construction when updated using multiple threads.

Synopsis

Documentation

data Reverse s a whereSource

Constructors

Zero :: Reverse s a 
Lift :: a -> Reverse s a 
Reverse :: !Int -> a -> Reverse s a 

Instances

newtype Tape Source

Constructors

Tape 

Fields

getTape :: IORef Head
 

data Head Source

Constructors

Head !Int Cells 

data Cells whereSource

Constructors

Nil :: Cells 
Unary :: !Int -> a -> Cells -> Cells 
Binary :: !Int -> !Int -> a -> a -> Cells -> Cells 

reifyTape :: Int -> (forall s. Reifies s Tape => Proxy s -> r) -> rSource

Construct a tape that starts with n variables.

partials :: forall s a. (Reifies s Tape, Num a) => AD (Reverse s) a -> [a]Source

Extract the partials from the current chain for a given AD variable.

partialArrayOf :: (Reifies s Tape, Num a) => Proxy s -> (Int, Int) -> AD (Reverse s) a -> Array Int aSource

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

partialMapOf :: (Reifies s Tape, Num a) => Proxy s -> AD (Reverse s) a -> IntMap aSource

Return an IntMap of sparse partials

derivativeOf :: (Reifies s Tape, Num a) => Proxy s -> AD (Reverse s) a -> aSource

Helper that extracts the derivative of a chain when the chain was constructed with one variable.

derivativeOf' :: (Reifies s Tape, Num a) => Proxy s -> AD (Reverse s) a -> (a, a)Source

Helper that extracts both the primal and derivative of a chain when the chain was constructed with one variable.