Portability | GHC only |
---|---|
Stability | experimental |
Maintainer | ekmett@gmail.com |
Numeric.AD.Types
Contents
Description
- newtype AD f a = AD {
- runAD :: f a
- type UU a = forall s. Mode s => AD s a -> AD s a
- type UF f a = forall s. Mode s => AD s a -> f (AD s a)
- type FU f a = forall s. Mode s => f (AD s a) -> AD s a
- type FF f g a = forall s. Mode s => f (AD s a) -> g (AD s a)
- data Tensors f a = a :- (Tensors f (f a))
- headT :: Tensors f a -> a
- tailT :: Tensors f a -> Tensors f (f a)
- tensors :: Functor f => Stream f a -> Tensors f a
- data Stream f a = a :< (f (Stream f a))
- headS :: Stream f a -> a
- tailS :: Stream f a -> f (Stream f a)
- unfoldS :: Functor f => (a -> (b, f a)) -> a -> Stream f b
- newtype Id a = Id a
- probe :: a -> AD Id a
- unprobe :: AD Id a -> a
- probed :: f a -> f (AD Id a)
- unprobed :: f (AD Id a) -> f a
- lowerUU :: UU a -> a -> a
- lowerUF :: UF f a -> a -> f a
- lowerFU :: FU f a -> f a -> a
- lowerFF :: FF f g a -> f a -> g a
Documentation
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.
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) | |
Num a => Grad (AD Reverse a) [a] (a, [a]) a | |
Num a => Grad (AD Sparse a) [a] (a, [a]) a | |
Grads i o a => Grads (AD Sparse a -> i) (a -> o) a | |
Num a => Grads (AD Sparse a) (Stream [] a) a | |
Grad i o o' a => Grad (AD Reverse a -> i) (a -> o) (a -> o') a | |
Grad i o o' a => Grad (AD Sparse a -> i) (a -> o) (a -> o') 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
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 |
(Typeable1 f, Typeable a) => Typeable (Tensors f a) |
f-Branching Streams
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) | |
Num a => Grads (AD Sparse a) (Stream [] a) a |
An Identity Mode.
Constructors
Id a |
Instances
Monad Id | |
Functor Id | |
Typeable1 Id | |
Applicative Id | |
Foldable Id | |
Traversable Id | |
Primal Id | |
Mode Id | |
Lifted Id | |
Iso a (Id a) | |
Bounded a => Bounded (Id a) | |
Enum a => Enum (Id a) | |
Eq a => Eq (Id a) | |
Floating a => Floating (Id a) | |
Fractional a => Fractional (Id a) | |
Data a => Data (Id a) | |
Num a => Num (Id a) | |
Ord a => Ord (Id a) | |
Real a => Real (Id a) | |
RealFloat a => RealFloat (Id a) | |
RealFrac a => RealFrac (Id a) | |
Show a => Show (Id a) | |
Monoid a => Monoid (Id a) |