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

Numeric.AD.Internal.Kahn.Float

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

Instances

Instances details
Jacobian KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Associated Types

type D KahnFloat Source #

Mode KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Associated Types

type Scalar KahnFloat Source #

Enum KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Floating KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

RealFloat KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Num KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Fractional KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Real KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

RealFrac KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Show KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

MuRef KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Associated Types

type DeRef KahnFloat :: Type -> Type #

Methods

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

Erf KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

InvErf KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Eq KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Ord KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Grad i o o' => Grad (KahnFloat -> i) (Float -> o) (Float -> o') Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Methods

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

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

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

type D KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

type Scalar KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

type DeRef KahnFloat Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

data Tape t Source #

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

Constructors

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

Instances

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

Defined in Numeric.AD.Internal.Kahn.Float

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

Methods

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

show :: Tape t -> String #

showList :: [Tape t] -> ShowS #

partials :: KahnFloat -> [(Int, Float)] Source #

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

partialArray :: (Int, Int) -> KahnFloat -> UArray Int Float Source #

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

partialMap :: KahnFloat -> IntMap Float 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 -> [KahnFloat] -> KahnFloat Source #

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

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

Instances

Instances details
Grad i o o' => Grad (KahnFloat -> i) (Float -> o) (Float -> o') Source # 
Instance details

Defined in Numeric.AD.Internal.Kahn.Float

Methods

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

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

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

bind :: Traversable f => f Float -> (f KahnFloat, (Int, Int)) Source #

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

unbindWithArray :: Functor f => (Float -> b -> c) -> f KahnFloat -> Array Int b -> f c Source #

unbindMapWithDefault :: Functor f => b -> (Float -> b -> c) -> f KahnFloat -> IntMap b -> f c Source #