ad-3.3.1: Automatic Differentiation

PortabilityGHC only
Stabilityexperimental
Maintainerekmett@gmail.com
Safe HaskellNone

Numeric.AD.Internal.Kahn

Description

This module provides reverse-mode Automatic Differentiation implementation using linear time topological sorting after the fact.

For this form of 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 Kahn a 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.

Constructors

Kahn (Tape a (Kahn a)) 

Instances

Typeable1 Kahn 
(Mode Kahn, Mode (D Kahn), Lifted Kahn) => Jacobian Kahn 
Primal Kahn 
Lifted Kahn => Mode Kahn 
Lifted Kahn 
Var Kahn 
Show a => Show (Kahn a) 
MuRef (Kahn a) 
Num a => Grad (AD Kahn a) [a] (a, [a]) a 
(Num a, Grad i o o' a) => Grad (AD Kahn 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 
(Typeable (Tape a t), Data a, Data t) => Data (Tape a t) 
(Show a, Show t) => Show (Tape a t) 

partials :: forall a. Num a => AD Kahn 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 Kahn a -> Array Int aSource

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

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

Return an IntMap of sparse partials

derivative :: Num a => AD Kahn a -> aSource

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

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 Kahn a] -> AD Kahn aSource

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

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

Instances

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