ad-4.3.1: Automatic Differentiation

Copyright(c) Edward Kmett 2010-2015
LicenseBSD3
Maintainerekmett@gmail.com
Stabilityexperimental
PortabilityGHC only
Safe HaskellNone
LanguageHaskell2010

Numeric.AD.Internal.Sparse

Description

Unsafe and often partial combinators intended for internal usage.

Handle with care.

Synopsis

Documentation

newtype Monomial Source

Constructors

Monomial (IntMap Int) 

data Sparse a Source

We only store partials in sorted order, so the map contained in a partial will only contain partials with equal or greater keys to that of the map in which it was found. This should be key for efficiently computing sparse hessians. there are only (n + k - 1) choose (k - 1) distinct nth partial derivatives of a function with k inputs.

Constructors

Sparse !a (IntMap (Sparse a)) 
Zero 

Instances

(Num a, Bounded a) => Bounded (Sparse a) 
(Num a, Enum a) => Enum (Sparse a) 
(Num a, Eq a) => Eq (Sparse a) 
Floating a => Floating (Sparse a) 
Fractional a => Fractional (Sparse a) 
Data a => Data (Sparse a) Source 
Num a => Num (Sparse a) 
(Num a, Ord a) => Ord (Sparse a) 
Real a => Real (Sparse a) 
RealFloat a => RealFloat (Sparse a) 
RealFrac a => RealFrac (Sparse a) 
Show a => Show (Sparse a) Source 
Erf a => Erf (Sparse a) 
InvErf a => InvErf (Sparse a) 
Num a => Mode (Sparse a) Source 
Num a => Jacobian (Sparse a) Source 
Num a => Grad (Sparse a) [a] (a, [a]) a Source 
Num a => Grads (Sparse a) (Cofree [] a) a Source 
Grads i o a => Grads (Sparse a -> i) (a -> o) a Source 
Grad i o o' a => Grad (Sparse a -> i) (a -> o) (a -> o') a Source 
type Scalar (Sparse a) = a Source 
type D (Sparse a) = Sparse a Source 

apply :: (Traversable f, Num a) => (f (Sparse a) -> b) -> f a -> b Source

vars :: (Traversable f, Num a) => f a -> f (Sparse a) Source

d :: (Traversable f, Num a) => f b -> Sparse a -> f a Source

d' :: (Traversable f, Num a) => f a -> Sparse a -> (a, f a) Source

ds :: (Traversable f, Num a) => f b -> Sparse a -> Cofree f a Source

skeleton :: Traversable f => f a -> f Int Source

spartial :: Num a => [Int] -> Sparse a -> Maybe a Source

partial :: Num a => [Int] -> Sparse a -> a Source

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

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

vgrads :: Grads i 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 where Source

Methods

pack :: i -> [Sparse a] -> Sparse a Source

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

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

Instances

Num a => Grad (Sparse a) [a] (a, [a]) a Source 
Grad i o o' a => Grad (Sparse a -> i) (a -> o) (a -> o') a Source 

class Num a => Grads i o a | i -> a o, o -> a i where Source

Methods

packs :: i -> [Sparse a] -> Sparse a Source

unpacks :: ([a] -> Cofree [] a) -> o Source

Instances

Num a => Grads (Sparse a) (Cofree [] a) a Source 
Grads i o a => Grads (Sparse a -> i) (a -> o) a Source 

terms :: Monomial -> [(Integer, Monomial, Monomial)] Source

The value of the derivative of (f*g) of order mi is

sum [a * primal (partialS (indices b) f) * primal (partialS (indices c) g) | (a,b,c) <- terms mi ]

It is a bit more complicated in mul below, since we build the whole tree of derivatives and want to prune the tree with Zeros as much as possible. The number of terms in the sum for order mi as of differentiation has sum (map (+1) as) terms, so this is *much* more efficient than the naive recursive differentiation with 2^sum as terms. The coefficients a, which collect equivalent derivatives, are suitable products of binomial coefficients.

primal :: Num a => Sparse a -> a Source