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

Numeric.AD.Internal.Kahn.Double

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 KahnDouble 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 KahnDouble) 

Instances

Instances details
Enum KahnDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

Eq KahnDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

Floating KahnDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

Fractional KahnDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

Num KahnDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

Ord KahnDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

Real KahnDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

RealFloat KahnDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

RealFrac KahnDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

Show KahnDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

MuRef KahnDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

Associated Types

type DeRef KahnDouble :: Type -> Type #

Methods

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

Erf KahnDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

InvErf KahnDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

Mode KahnDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

Associated Types

type Scalar KahnDouble Source #

Jacobian KahnDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

Associated Types

type D KahnDouble Source #

Grad i o o' => Grad (KahnDouble -> i) (Double -> o) (Double -> o') Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

Methods

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

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

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

type DeRef KahnDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

type Scalar KahnDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

type D KahnDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

data Tape t Source #

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

Instances

Instances details
Data t => Data (Tape t) Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tape t -> c (Tape t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Tape t) #

toConstr :: Tape t -> Constr #

dataTypeOf :: Tape t -> DataType #

dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Tape t)) #

dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Tape t)) #

gmapT :: (forall b. Data b => b -> b) -> Tape t -> Tape t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tape t -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tape t -> r #

gmapQ :: (forall d. Data d => d -> u) -> Tape t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tape t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tape t -> m (Tape t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tape t -> m (Tape t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tape t -> m (Tape t) #

Show t => Show (Tape t) Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

Methods

showsPrec :: Int -> Tape t -> ShowS #

show :: Tape t -> String #

showList :: [Tape t] -> ShowS #

partials :: KahnDouble -> [(Int, Double)] Source #

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

partialArray :: (Int, Int) -> KahnDouble -> UArray Int Double Source #

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

partialMap :: KahnDouble -> IntMap Double Source #

Return an IntMap of sparse partials

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 where Source #

Methods

pack :: i -> [KahnDouble] -> KahnDouble Source #

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

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

Instances

Instances details
Grad i o o' => Grad (KahnDouble -> i) (Double -> o) (Double -> o') Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Double

Methods

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

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

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

unbindWithUArray :: (Functor f, IArray UArray b) => (Double -> b -> c) -> f KahnDouble -> UArray Int b -> f c Source #

unbindWithArray :: Functor f => (Double -> b -> c) -> f KahnDouble -> Array Int b -> f c Source #

unbindMapWithDefault :: Functor f => b -> (Double -> b -> c) -> f KahnDouble -> IntMap b -> f c Source #