ad-0.40.1: Automatic Differentiation

PortabilityGHC only
Stabilityexperimental
Maintainerekmett@gmail.com

Numeric.AD.Types

Contents

Description

 

Synopsis

Documentation

newtype AD f a Source

AD serves as a common wrapper for different Mode instances, exposing a traditional numerical tower. Universal quantification is used to limit the actions in user code to machinery that will return the same answers under all AD modes, allowing us to use modes interchangeably as both the type level "brand" and dictionary, providing a common API.

Constructors

AD 

Fields

runAD :: f a
 

Instances

Typeable1 f => Typeable1 (AD f) 
Primal f => Primal (AD f) 
Mode f => Mode (AD f) 
Lifted f => Lifted (AD f) 
Var (AD Reverse) 
Iso (f a) (AD f a) 
(Num a, Lifted f, Bounded a) => Bounded (AD f a) 
(Num a, Lifted f, Enum a) => Enum (AD f a) 
(Num a, Lifted f, Eq a) => Eq (AD f a) 
(Lifted f, Floating a) => Floating (AD f a) 
(Lifted f, Fractional a) => Fractional (AD f a) 
(Typeable1 f, Typeable a, Data (f a), Data a) => Data (AD f a) 
(Lifted f, Num a) => Num (AD f a) 
(Num a, Lifted f, Ord a) => Ord (AD f a) 
(Lifted f, Real a) => Real (AD f a) 
(Lifted f, RealFloat a) => RealFloat (AD f a) 
(Lifted f, RealFrac a) => RealFrac (AD f a) 
(Lifted f, Show a) => Show (AD f a) 
(Typeable1 f, Typeable a) => Typeable (AD f a) 

Differentiable Functions

type UU a = forall s. Mode s => AD s a -> AD s aSource

A scalar-to-scalar automatically-differentiable function.

type UF f a = forall s. Mode s => AD s a -> f (AD s a)Source

A scalar-to-non-scalar automatically-differentiable function.

type FU f a = forall s. Mode s => f (AD s a) -> AD s aSource

A non-scalar-to-scalar automatically-differentiable function.

type FF f g a = forall s. Mode s => f (AD s a) -> g (AD s a)Source

A non-scalar-to-non-scalar automatically-differentiable function.

Tensors

data Tensors f a Source

Constructors

a :- (Tensors f (f a)) 

Instances

Functor f => Functor (Tensors f) 
Typeable1 f => Typeable1 (Tensors f) 
Foldable f => Foldable (Tensors f) 
Traversable f => Traversable (Tensors f) 
Functor f => Copointed (Tensors f)

While we can not be a Comonad without a fzip-like operation, you can use the comonad for Stream f a to manipulate a structure comonadically that you can turn into Tensors.

(Typeable1 f, Typeable a) => Typeable (Tensors f a) 

headT :: Tensors f a -> aSource

tailT :: Tensors f a -> Tensors f (f a)Source

tensors :: Functor f => Stream f a -> Tensors f aSource

f-Branching Streams

data Stream f a Source

Constructors

a :< (f (Stream f a)) 

Instances

Functor f => Functor (Stream f) 
Typeable1 f => Typeable1 (Stream f) 
Foldable f => Foldable (Stream f) 
Traversable f => Traversable (Stream f) 
Functor f => Comonad (Stream f) 
Functor f => Copointed (Stream f) 
(Typeable1 f, Data (f (Stream f a)), Data a) => Data (Stream f a) 
(Show a, Show (f (Stream f a))) => Show (Stream f a) 
(Typeable1 f, Typeable a) => Typeable (Stream f a) 

headS :: Stream f a -> aSource

tailS :: Stream f a -> f (Stream f a)Source

unfoldS :: Functor f => (a -> (b, f a)) -> a -> Stream f bSource