backprop-0.2.3.0: Heterogeneous automatic differentation

Copyright(c) Justin Le 2018
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Numeric.Backprop.Class

Contents

Description

Provides the Backprop typeclass, a class for values that can be used for backpropagation.

This class replaces the old (version 0.1) API relying on Num.

Since: 0.2.0.0

Synopsis

Backpropagatable types

class Backprop a where Source #

Class of values that can be backpropagated in general.

For instances of Num, these methods can be given by zeroNum, addNum, and oneNum. There are also generic options given in Numeric.Backprop.Class for functors, IsList instances, and Generic instances.

instance Backprop Double where
    zero = zeroNum
    add = addNum
    one = oneNum

If you leave the body of an instance declaration blank, GHC Generics will be used to derive instances if the type has a single constructor and each field is an instance of Backprop.

To ensure that backpropagation works in a sound way, should obey the laws:

identity

Also implies preservation of information, making zipWith (+) an illegal implementation for lists and vectors.

This is only expected to be true up to potential "extra zeroes" in x and y in the result.

commutativity
associativity
idempotence

Note that not all values in the backpropagation process needs all of these methods: Only the "final result" needs one, for example. These are all grouped under one typeclass for convenience in defining instances, and also to talk about sensible laws. For fine-grained control, use the "explicit" versions of library functions (for example, in Numeric.Backprop.Explicit) instead of Backprop based ones.

This typeclass replaces the reliance on Num of the previous API (v0.1). Num is strictly more powerful than Backprop, and is a stronger constraint on types than is necessary for proper backpropagating. In particular, fromInteger is a problem for many types, preventing useful backpropagation for lists, variable-length vectors (like Data.Vector) and variable-size matrices from linear algebra libraries like hmatrix and accelerate.

Since: 0.2.0.0

Methods

zero :: a -> a Source #

"Zero out" all components of a value. For scalar values, this should just be const 0. For vectors and matrices, this should set all components to zero, the additive identity.

Should be idempotent:

Should be as lazy as possible. This behavior is observed for all instances provided by this library.

See zeroNum for a pre-built definition for instances of Num and zeroFunctor for a definition for instances of Functor. If left blank, will automatically be genericZero, a pre-built definition for instances of Generic whose fields are all themselves instances of Backprop.

add :: a -> a -> a Source #

Add together two values of a type. To combine contributions of gradients, so should be information-preserving:

Should be as strict as possible. This behavior is observed for all instances provided by this library.

See addNum for a pre-built definition for instances of Num and addFunctor for a definition for instances of Functor. If left blank, will automatically be genericAdd, a pre-built definition for instances of Generic with one constructor whose fields are all themselves instances of Backprop.

one :: a -> a Source #

One all components of a value. For scalar values, this should just be const 1. For vectors and matrices, this should set all components to one, the multiplicative identity.

Should be idempotent:

Should be as lazy as possible. This behavior is observed for all instances provided by this library.

See oneNum for a pre-built definition for instances of Num and oneFunctor for a definition for instances of Functor. If left blank, will automatically be genericOne, a pre-built definition for instances of Generic whose fields are all themselves instances of Backprop.

zero :: (Generic a, GZero (Rep a)) => a -> a Source #

"Zero out" all components of a value. For scalar values, this should just be const 0. For vectors and matrices, this should set all components to zero, the additive identity.

Should be idempotent:

Should be as lazy as possible. This behavior is observed for all instances provided by this library.

See zeroNum for a pre-built definition for instances of Num and zeroFunctor for a definition for instances of Functor. If left blank, will automatically be genericZero, a pre-built definition for instances of Generic whose fields are all themselves instances of Backprop.

add :: (Generic a, GAdd (Rep a)) => a -> a -> a Source #

Add together two values of a type. To combine contributions of gradients, so should be information-preserving:

Should be as strict as possible. This behavior is observed for all instances provided by this library.

See addNum for a pre-built definition for instances of Num and addFunctor for a definition for instances of Functor. If left blank, will automatically be genericAdd, a pre-built definition for instances of Generic with one constructor whose fields are all themselves instances of Backprop.

one :: (Generic a, GOne (Rep a)) => a -> a Source #

One all components of a value. For scalar values, this should just be const 1. For vectors and matrices, this should set all components to one, the multiplicative identity.

Should be idempotent:

Should be as lazy as possible. This behavior is observed for all instances provided by this library.

See oneNum for a pre-built definition for instances of Num and oneFunctor for a definition for instances of Functor. If left blank, will automatically be genericOne, a pre-built definition for instances of Generic whose fields are all themselves instances of Backprop.

Instances

Backprop Double Source # 
Backprop Float Source # 
Backprop Int Source # 

Methods

zero :: Int -> Int Source #

add :: Int -> Int -> Int Source #

one :: Int -> Int Source #

Backprop Integer Source # 
Backprop Natural Source #

Since: 0.2.1.0

Backprop Word Source #

Since: 0.2.2.0

Methods

zero :: Word -> Word Source #

add :: Word -> Word -> Word Source #

one :: Word -> Word Source #

Backprop Word8 Source #

Since: 0.2.2.0

Backprop Word16 Source #

Since: 0.2.2.0

Backprop Word32 Source #

Since: 0.2.2.0

Backprop Word64 Source #

Since: 0.2.2.0

Backprop () Source #

add is strict, but zero and one are lazy in their arguments.

Methods

zero :: () -> () Source #

add :: () -> () -> () Source #

one :: () -> () Source #

Backprop Void Source # 

Methods

zero :: Void -> Void Source #

add :: Void -> Void -> Void Source #

one :: Void -> Void Source #

Backprop a => Backprop [a] Source #

add assumes the shorter list has trailing zeroes, and the result has the length of the longest input.

Methods

zero :: [a] -> [a] Source #

add :: [a] -> [a] -> [a] Source #

one :: [a] -> [a] Source #

Backprop a => Backprop (Maybe a) Source #

Nothing is treated the same as Just 0. However, zero, add, and one preserve Nothing if all inputs are also Nothing.

Methods

zero :: Maybe a -> Maybe a Source #

add :: Maybe a -> Maybe a -> Maybe a Source #

one :: Maybe a -> Maybe a Source #

Integral a => Backprop (Ratio a) Source # 

Methods

zero :: Ratio a -> Ratio a Source #

add :: Ratio a -> Ratio a -> Ratio a Source #

one :: Ratio a -> Ratio a Source #

RealFloat a => Backprop (Complex a) Source # 

Methods

zero :: Complex a -> Complex a Source #

add :: Complex a -> Complex a -> Complex a Source #

one :: Complex a -> Complex a Source #

Backprop a => Backprop (First a) Source #

Since: 0.2.2.0

Methods

zero :: First a -> First a Source #

add :: First a -> First a -> First a Source #

one :: First a -> First a Source #

Backprop a => Backprop (Last a) Source #

Since: 0.2.2.0

Methods

zero :: Last a -> Last a Source #

add :: Last a -> Last a -> Last a Source #

one :: Last a -> Last a Source #

Backprop a => Backprop (Option a) Source #

Since: 0.2.2.0

Methods

zero :: Option a -> Option a Source #

add :: Option a -> Option a -> Option a Source #

one :: Option a -> Option a Source #

Backprop a => Backprop (NonEmpty a) Source #

add assumes the shorter list has trailing zeroes, and the result has the length of the longest input.

Backprop a => Backprop (Identity a) Source # 
Backprop a => Backprop (Dual a) Source #

Since: 0.2.2.0

Methods

zero :: Dual a -> Dual a Source #

add :: Dual a -> Dual a -> Dual a Source #

one :: Dual a -> Dual a Source #

Backprop a => Backprop (Sum a) Source #

Since: 0.2.2.0

Methods

zero :: Sum a -> Sum a Source #

add :: Sum a -> Sum a -> Sum a Source #

one :: Sum a -> Sum a Source #

Backprop a => Backprop (Product a) Source #

Since: 0.2.2.0

Methods

zero :: Product a -> Product a Source #

add :: Product a -> Product a -> Product a Source #

one :: Product a -> Product a Source #

Backprop a => Backprop (First a) Source #

Since: 0.2.2.0

Methods

zero :: First a -> First a Source #

add :: First a -> First a -> First a Source #

one :: First a -> First a Source #

Backprop a => Backprop (Last a) Source #

Since: 0.2.2.0

Methods

zero :: Last a -> Last a Source #

add :: Last a -> Last a -> Last a Source #

one :: Last a -> Last a Source #

Backprop a => Backprop (IntMap a) Source #

zero and one replace all current values, and add merges keys from both maps, adding in the case of double-occurrences.

Methods

zero :: IntMap a -> IntMap a Source #

add :: IntMap a -> IntMap a -> IntMap a Source #

one :: IntMap a -> IntMap a Source #

Backprop a => Backprop (Seq a) Source #

add assumes the shorter sequence has trailing zeroes, and the result has the length of the longest input.

Methods

zero :: Seq a -> Seq a Source #

add :: Seq a -> Seq a -> Seq a Source #

one :: Seq a -> Seq a Source #

Backprop a => Backprop (I a) Source # 

Methods

zero :: I a -> I a Source #

add :: I a -> I a -> I a Source #

one :: I a -> I a Source #

(Unbox a, Backprop a) => Backprop (Vector a) Source # 

Methods

zero :: Vector a -> Vector a Source #

add :: Vector a -> Vector a -> Vector a Source #

one :: Vector a -> Vector a Source #

(Storable a, Backprop a) => Backprop (Vector a) Source # 

Methods

zero :: Vector a -> Vector a Source #

add :: Vector a -> Vector a -> Vector a Source #

one :: Vector a -> Vector a Source #

(Prim a, Backprop a) => Backprop (Vector a) Source # 

Methods

zero :: Vector a -> Vector a Source #

add :: Vector a -> Vector a -> Vector a Source #

one :: Vector a -> Vector a Source #

Backprop a => Backprop (Vector a) Source # 

Methods

zero :: Vector a -> Vector a Source #

add :: Vector a -> Vector a -> Vector a Source #

one :: Vector a -> Vector a Source #

Num a => Backprop (NumBP a) Source # 

Methods

zero :: NumBP a -> NumBP a Source #

add :: NumBP a -> NumBP a -> NumBP a Source #

one :: NumBP a -> NumBP a Source #

Backprop a => Backprop (r -> a) Source #

add adds together results; zero and one act on results.

Since: 0.2.2.0

Methods

zero :: (r -> a) -> r -> a Source #

add :: (r -> a) -> (r -> a) -> r -> a Source #

one :: (r -> a) -> r -> a Source #

Backprop (V1 * p) Source #

Since: 0.2.2.0

Methods

zero :: V1 * p -> V1 * p Source #

add :: V1 * p -> V1 * p -> V1 * p Source #

one :: V1 * p -> V1 * p Source #

Backprop (U1 * p) Source #

Since: 0.2.2.0

Methods

zero :: U1 * p -> U1 * p Source #

add :: U1 * p -> U1 * p -> U1 * p Source #

one :: U1 * p -> U1 * p Source #

(Backprop a, Backprop b) => Backprop (a, b) Source #

add is strict

Methods

zero :: (a, b) -> (a, b) Source #

add :: (a, b) -> (a, b) -> (a, b) Source #

one :: (a, b) -> (a, b) Source #

(Backprop a, Backprop b) => Backprop (Arg a b) Source #

Since: 0.2.2.0

Methods

zero :: Arg a b -> Arg a b Source #

add :: Arg a b -> Arg a b -> Arg a b Source #

one :: Arg a b -> Arg a b Source #

Backprop (Proxy * a) Source # 

Methods

zero :: Proxy * a -> Proxy * a Source #

add :: Proxy * a -> Proxy * a -> Proxy * a Source #

one :: Proxy * a -> Proxy * a Source #

(Backprop a, Ord k) => Backprop (Map k a) Source #

zero and one replace all current values, and add merges keys from both maps, adding in the case of double-occurrences.

Methods

zero :: Map k a -> Map k a Source #

add :: Map k a -> Map k a -> Map k a Source #

one :: Map k a -> Map k a Source #

(Applicative f, Backprop a) => Backprop (ABP f a) Source # 

Methods

zero :: ABP f a -> ABP f a Source #

add :: ABP f a -> ABP f a -> ABP f a Source #

one :: ABP f a -> ABP f a Source #

(Backprop a, Reifies Type s W) => Backprop (BVar s a) Source #

Since: 0.2.2.0

Methods

zero :: BVar s a -> BVar s a Source #

add :: BVar s a -> BVar s a -> BVar s a Source #

one :: BVar s a -> BVar s a Source #

(Backprop a, Backprop b, Backprop c) => Backprop (a, b, c) Source #

add is strict

Methods

zero :: (a, b, c) -> (a, b, c) Source #

add :: (a, b, c) -> (a, b, c) -> (a, b, c) Source #

one :: (a, b, c) -> (a, b, c) Source #

(Backprop a, Applicative m) => Backprop (Kleisli m r a) Source #

Since: 0.2.2.0

Methods

zero :: Kleisli m r a -> Kleisli m r a Source #

add :: Kleisli m r a -> Kleisli m r a -> Kleisli m r a Source #

one :: Kleisli m r a -> Kleisli m r a Source #

Backprop w => Backprop (Const * w a) Source #

Since: 0.2.2.0

Methods

zero :: Const * w a -> Const * w a Source #

add :: Const * w a -> Const * w a -> Const * w a Source #

one :: Const * w a -> Const * w a Source #

ListC ((<$>) * Constraint Backprop ((<$>) * * f as)) => Backprop (Prod * f as) Source # 

Methods

zero :: Prod * f as -> Prod * f as Source #

add :: Prod * f as -> Prod * f as -> Prod * f as Source #

one :: Prod * f as -> Prod * f as Source #

Backprop w => Backprop (C * w a) Source #

Since: 0.2.2.0

Methods

zero :: C * w a -> C * w a Source #

add :: C * w a -> C * w a -> C * w a Source #

one :: C * w a -> C * w a Source #

Backprop (f a a) => Backprop (Join * f a) Source #

Since: 0.2.2.0

Methods

zero :: Join * f a -> Join * f a Source #

add :: Join * f a -> Join * f a -> Join * f a Source #

one :: Join * f a -> Join * f a Source #

MaybeC ((<$>) * Constraint Backprop ((<$>) * * f a)) => Backprop (Option * f a) Source # 

Methods

zero :: Option * f a -> Option * f a Source #

add :: Option * f a -> Option * f a -> Option * f a Source #

one :: Option * f a -> Option * f a Source #

Backprop a => Backprop (K1 * i a p) Source #

Since: 0.2.2.0

Methods

zero :: K1 * i a p -> K1 * i a p Source #

add :: K1 * i a p -> K1 * i a p -> K1 * i a p Source #

one :: K1 * i a p -> K1 * i a p Source #

(Backprop (f p), Backprop (g p)) => Backprop ((:*:) * f g p) Source #

Since: 0.2.2.0

Methods

zero :: (* :*: f) g p -> (* :*: f) g p Source #

add :: (* :*: f) g p -> (* :*: f) g p -> (* :*: f) g p Source #

one :: (* :*: f) g p -> (* :*: f) g p Source #

(Backprop a, Backprop b, Backprop c, Backprop d) => Backprop (a, b, c, d) Source #

add is strict

Methods

zero :: (a, b, c, d) -> (a, b, c, d) Source #

add :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source #

one :: (a, b, c, d) -> (a, b, c, d) Source #

(Backprop (f a), Backprop (g a)) => Backprop (Product * f g a) Source #

Since: 0.2.2.0

Methods

zero :: Product * f g a -> Product * f g a Source #

add :: Product * f g a -> Product * f g a -> Product * f g a Source #

one :: Product * f g a -> Product * f g a Source #

Backprop (p a b) => Backprop (Uncur * * p ((,) * * a b)) Source #

Since: 0.2.2.0

Methods

zero :: Uncur * * p ((*, *) a b) -> Uncur * * p ((*, *) a b) Source #

add :: Uncur * * p ((*, *) a b) -> Uncur * * p ((*, *) a b) -> Uncur * * p ((*, *) a b) Source #

one :: Uncur * * p ((*, *) a b) -> Uncur * * p ((*, *) a b) Source #

(Backprop (f a), Backprop (g a)) => Backprop ((:&:) * f g a) Source #

Since: 0.2.2.0

Methods

zero :: (* :&: f) g a -> (* :&: f) g a Source #

add :: (* :&: f) g a -> (* :&: f) g a -> (* :&: f) g a Source #

one :: (* :&: f) g a -> (* :&: f) g a Source #

Backprop (f p) => Backprop (M1 * i c f p) Source #

Since: 0.2.2.0

Methods

zero :: M1 * i c f p -> M1 * i c f p Source #

add :: M1 * i c f p -> M1 * i c f p -> M1 * i c f p Source #

one :: M1 * i c f p -> M1 * i c f p Source #

(Backprop a, Backprop b, Backprop c, Backprop d, Backprop e) => Backprop (a, b, c, d, e) Source #

add is strict

Methods

zero :: (a, b, c, d, e) -> (a, b, c, d, e) Source #

add :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

one :: (a, b, c, d, e) -> (a, b, c, d, e) Source #

Backprop (f (g a)) => Backprop (Compose * * f g a) Source #

Since: 0.2.2.0

Methods

zero :: Compose * * f g a -> Compose * * f g a Source #

add :: Compose * * f g a -> Compose * * f g a -> Compose * * f g a Source #

one :: Compose * * f g a -> Compose * * f g a Source #

Backprop (f (g a)) => Backprop ((:.:) * * f g a) Source #

Since: 0.2.2.0

Methods

zero :: (* :.: *) f g a -> (* :.: *) f g a Source #

add :: (* :.: *) f g a -> (* :.: *) f g a -> (* :.: *) f g a Source #

one :: (* :.: *) f g a -> (* :.: *) f g a Source #

Backprop (p a b) => Backprop (Flip * * p b a) Source #

Since: 0.2.2.0

Methods

zero :: Flip * * p b a -> Flip * * p b a Source #

add :: Flip * * p b a -> Flip * * p b a -> Flip * * p b a Source #

one :: Flip * * p b a -> Flip * * p b a Source #

Backprop (p ((,) * * a b)) => Backprop (Cur * * p a b) Source #

Since: 0.2.2.0

Methods

zero :: Cur * * p a b -> Cur * * p a b Source #

add :: Cur * * p a b -> Cur * * p a b -> Cur * * p a b Source #

one :: Cur * * p a b -> Cur * * p a b Source #

Backprop (p a b c) => Backprop (Uncur3 * * * p ((,,) * * * a b c)) Source #

Since: 0.2.2.0

Methods

zero :: Uncur3 * * * p ((*, *, *) a b c) -> Uncur3 * * * p ((*, *, *) a b c) Source #

add :: Uncur3 * * * p ((*, *, *) a b c) -> Uncur3 * * * p ((*, *, *) a b c) -> Uncur3 * * * p ((*, *, *) a b c) Source #

one :: Uncur3 * * * p ((*, *, *) a b c) -> Uncur3 * * * p ((*, *, *) a b c) Source #

Backprop (c (f a)) => Backprop (LL * * c a f) Source #

Since: 0.2.2.0

Methods

zero :: LL * * c a f -> LL * * c a f Source #

add :: LL * * c a f -> LL * * c a f -> LL * * c a f Source #

one :: LL * * c a f -> LL * * c a f Source #

Backprop (c (f a)) => Backprop (RR * * c f a) Source #

Since: 0.2.2.0

Methods

zero :: RR * * c f a -> RR * * c f a Source #

add :: RR * * c f a -> RR * * c f a -> RR * * c f a Source #

one :: RR * * c f a -> RR * * c f a Source #

(Backprop (f a), Backprop (g b)) => Backprop ((:*:) * * f g ((,) * * a b)) Source #

Since: 0.2.2.0

Methods

zero :: (* :*: *) f g ((*, *) a b) -> (* :*: *) f g ((*, *) a b) Source #

add :: (* :*: *) f g ((*, *) a b) -> (* :*: *) f g ((*, *) a b) -> (* :*: *) f g ((*, *) a b) Source #

one :: (* :*: *) f g ((*, *) a b) -> (* :*: *) f g ((*, *) a b) Source #

Backprop (f (g h) a) => Backprop (Comp1 * * * f g h a) Source #

Since: 0.2.2.0

Methods

zero :: Comp1 * * * f g h a -> Comp1 * * * f g h a Source #

add :: Comp1 * * * f g h a -> Comp1 * * * f g h a -> Comp1 * * * f g h a Source #

one :: Comp1 * * * f g h a -> Comp1 * * * f g h a Source #

Backprop (p ((,,) * * * a b c)) => Backprop (Cur3 * * * p a b c) Source #

Since: 0.2.2.0

Methods

zero :: Cur3 * * * p a b c -> Cur3 * * * p a b c Source #

add :: Cur3 * * * p a b c -> Cur3 * * * p a b c -> Cur3 * * * p a b c Source #

one :: Cur3 * * * p a b c -> Cur3 * * * p a b c Source #

Backprop (t (Flip * * f b) a) => Backprop (Conj * * * t f a b) Source #

Since: 0.2.2.0

Methods

zero :: Conj * * * t f a b -> Conj * * * t f a b Source #

add :: Conj * * * t f a b -> Conj * * * t f a b -> Conj * * * t f a b Source #

one :: Conj * * * t f a b -> Conj * * * t f a b Source #

Derived methods

zeroNum :: Num a => a -> a Source #

zero for instances of Num.

Is lazy in its argument.

addNum :: Num a => a -> a -> a Source #

add for instances of Num.

oneNum :: Num a => a -> a Source #

one for instances of Num.

Is lazy in its argument.

zeroVec :: (Vector v a, Backprop a) => v a -> v a Source #

zero for instances of Vector.

addVec :: (Vector v a, Backprop a) => v a -> v a -> v a Source #

add for instances of Vector. Automatically pads the end of the shorter vector with zeroes.

oneVec :: (Vector v a, Backprop a) => v a -> v a Source #

one for instances of Vector.

zeroFunctor :: (Functor f, Backprop a) => f a -> f a Source #

zero for Functor instances.

addIsList :: (IsList a, Backprop (Item a)) => a -> a -> a Source #

add for instances of IsList. Automatically pads the end of the "shorter" value with zeroes.

addAsList Source #

Arguments

:: Backprop b 
=> (a -> [b])

convert to list (should form isomorphism)

-> ([b] -> a)

convert from list (should form isomorphism)

-> a 
-> a 
-> a 

add for types that are isomorphic to a list. Automatically pads the end of the "shorter" value with zeroes.

oneFunctor :: (Functor f, Backprop a) => f a -> f a Source #

one for instances of Functor.

genericZero :: (Generic a, GZero (Rep a)) => a -> a Source #

zero using GHC Generics; works if all fields are instances of Backprop.

genericAdd :: (Generic a, GAdd (Rep a)) => a -> a -> a Source #

add using GHC Generics; works if all fields are instances of Backprop, but only for values with single constructors.

genericOne :: (Generic a, GOne (Rep a)) => a -> a Source #

one using GHC Generics; works if all fields are instaces of Backprop.

Newtype

newtype ABP f a Source #

A newtype wrapper over an f a for Applicative f that gives a free Backprop instance (as well as Num etc. instances).

Useful for performing backpropagation over functions that require some monadic context (like IO) to perform.

Since: 0.2.1.0

Constructors

ABP 

Fields

Instances

Monad m => Monad (ABP m) Source # 

Methods

(>>=) :: ABP m a -> (a -> ABP m b) -> ABP m b #

(>>) :: ABP m a -> ABP m b -> ABP m b #

return :: a -> ABP m a #

fail :: String -> ABP m a #

Functor f => Functor (ABP f) Source # 

Methods

fmap :: (a -> b) -> ABP f a -> ABP f b #

(<$) :: a -> ABP f b -> ABP f a #

Applicative f => Applicative (ABP f) Source # 

Methods

pure :: a -> ABP f a #

(<*>) :: ABP f (a -> b) -> ABP f a -> ABP f b #

liftA2 :: (a -> b -> c) -> ABP f a -> ABP f b -> ABP f c #

(*>) :: ABP f a -> ABP f b -> ABP f b #

(<*) :: ABP f a -> ABP f b -> ABP f a #

Foldable f => Foldable (ABP f) Source # 

Methods

fold :: Monoid m => ABP f m -> m #

foldMap :: Monoid m => (a -> m) -> ABP f a -> m #

foldr :: (a -> b -> b) -> b -> ABP f a -> b #

foldr' :: (a -> b -> b) -> b -> ABP f a -> b #

foldl :: (b -> a -> b) -> b -> ABP f a -> b #

foldl' :: (b -> a -> b) -> b -> ABP f a -> b #

foldr1 :: (a -> a -> a) -> ABP f a -> a #

foldl1 :: (a -> a -> a) -> ABP f a -> a #

toList :: ABP f a -> [a] #

null :: ABP f a -> Bool #

length :: ABP f a -> Int #

elem :: Eq a => a -> ABP f a -> Bool #

maximum :: Ord a => ABP f a -> a #

minimum :: Ord a => ABP f a -> a #

sum :: Num a => ABP f a -> a #

product :: Num a => ABP f a -> a #

Traversable f => Traversable (ABP f) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> ABP f a -> f (ABP f b) #

sequenceA :: Applicative f => ABP f (f a) -> f (ABP f a) #

mapM :: Monad m => (a -> m b) -> ABP f a -> m (ABP f b) #

sequence :: Monad m => ABP f (m a) -> m (ABP f a) #

Eq (f a) => Eq (ABP f a) Source # 

Methods

(==) :: ABP f a -> ABP f a -> Bool #

(/=) :: ABP f a -> ABP f a -> Bool #

(Applicative f, Floating a) => Floating (ABP f a) Source # 

Methods

pi :: ABP f a #

exp :: ABP f a -> ABP f a #

log :: ABP f a -> ABP f a #

sqrt :: ABP f a -> ABP f a #

(**) :: ABP f a -> ABP f a -> ABP f a #

logBase :: ABP f a -> ABP f a -> ABP f a #

sin :: ABP f a -> ABP f a #

cos :: ABP f a -> ABP f a #

tan :: ABP f a -> ABP f a #

asin :: ABP f a -> ABP f a #

acos :: ABP f a -> ABP f a #

atan :: ABP f a -> ABP f a #

sinh :: ABP f a -> ABP f a #

cosh :: ABP f a -> ABP f a #

tanh :: ABP f a -> ABP f a #

asinh :: ABP f a -> ABP f a #

acosh :: ABP f a -> ABP f a #

atanh :: ABP f a -> ABP f a #

log1p :: ABP f a -> ABP f a #

expm1 :: ABP f a -> ABP f a #

log1pexp :: ABP f a -> ABP f a #

log1mexp :: ABP f a -> ABP f a #

(Applicative f, Fractional a) => Fractional (ABP f a) Source # 

Methods

(/) :: ABP f a -> ABP f a -> ABP f a #

recip :: ABP f a -> ABP f a #

fromRational :: Rational -> ABP f a #

(Data (f a), Typeable * a, Typeable (* -> *) f) => Data (ABP f a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ABP f a -> c (ABP f a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ABP f a) #

toConstr :: ABP f a -> Constr #

dataTypeOf :: ABP f a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (ABP f a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ABP f a)) #

gmapT :: (forall b. Data b => b -> b) -> ABP f a -> ABP f a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ABP f a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ABP f a -> r #

gmapQ :: (forall d. Data d => d -> u) -> ABP f a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ABP f a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ABP f a -> m (ABP f a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ABP f a -> m (ABP f a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ABP f a -> m (ABP f a) #

(Applicative f, Num a) => Num (ABP f a) Source # 

Methods

(+) :: ABP f a -> ABP f a -> ABP f a #

(-) :: ABP f a -> ABP f a -> ABP f a #

(*) :: ABP f a -> ABP f a -> ABP f a #

negate :: ABP f a -> ABP f a #

abs :: ABP f a -> ABP f a #

signum :: ABP f a -> ABP f a #

fromInteger :: Integer -> ABP f a #

Ord (f a) => Ord (ABP f a) Source # 

Methods

compare :: ABP f a -> ABP f a -> Ordering #

(<) :: ABP f a -> ABP f a -> Bool #

(<=) :: ABP f a -> ABP f a -> Bool #

(>) :: ABP f a -> ABP f a -> Bool #

(>=) :: ABP f a -> ABP f a -> Bool #

max :: ABP f a -> ABP f a -> ABP f a #

min :: ABP f a -> ABP f a -> ABP f a #

Read (f a) => Read (ABP f a) Source # 

Methods

readsPrec :: Int -> ReadS (ABP f a) #

readList :: ReadS [ABP f a] #

readPrec :: ReadPrec (ABP f a) #

readListPrec :: ReadPrec [ABP f a] #

Show (f a) => Show (ABP f a) Source # 

Methods

showsPrec :: Int -> ABP f a -> ShowS #

show :: ABP f a -> String #

showList :: [ABP f a] -> ShowS #

Generic (ABP f a) Source # 

Associated Types

type Rep (ABP f a) :: * -> * #

Methods

from :: ABP f a -> Rep (ABP f a) x #

to :: Rep (ABP f a) x -> ABP f a #

NFData (f a) => NFData (ABP f a) Source # 

Methods

rnf :: ABP f a -> () #

(Applicative f, Backprop a) => Backprop (ABP f a) Source # 

Methods

zero :: ABP f a -> ABP f a Source #

add :: ABP f a -> ABP f a -> ABP f a Source #

one :: ABP f a -> ABP f a Source #

type Rep (ABP f a) Source # 
type Rep (ABP f a) = D1 * (MetaData "ABP" "Numeric.Backprop.Class" "backprop-0.2.3.0-4xTgnnUpmK1AibXJBUeG1v" True) (C1 * (MetaCons "ABP" PrefixI True) (S1 * (MetaSel (Just Symbol "runABP") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f a))))

newtype NumBP a Source #

A newtype wrapper over an instance of Num that gives a free Backprop instance.

Useful for things like DerivingVia, or for avoiding orphan instances.

Since: 0.2.1.0

Constructors

NumBP 

Fields

Instances

Monad NumBP Source # 

Methods

(>>=) :: NumBP a -> (a -> NumBP b) -> NumBP b #

(>>) :: NumBP a -> NumBP b -> NumBP b #

return :: a -> NumBP a #

fail :: String -> NumBP a #

Functor NumBP Source # 

Methods

fmap :: (a -> b) -> NumBP a -> NumBP b #

(<$) :: a -> NumBP b -> NumBP a #

Applicative NumBP Source # 

Methods

pure :: a -> NumBP a #

(<*>) :: NumBP (a -> b) -> NumBP a -> NumBP b #

liftA2 :: (a -> b -> c) -> NumBP a -> NumBP b -> NumBP c #

(*>) :: NumBP a -> NumBP b -> NumBP b #

(<*) :: NumBP a -> NumBP b -> NumBP a #

Foldable NumBP Source # 

Methods

fold :: Monoid m => NumBP m -> m #

foldMap :: Monoid m => (a -> m) -> NumBP a -> m #

foldr :: (a -> b -> b) -> b -> NumBP a -> b #

foldr' :: (a -> b -> b) -> b -> NumBP a -> b #

foldl :: (b -> a -> b) -> b -> NumBP a -> b #

foldl' :: (b -> a -> b) -> b -> NumBP a -> b #

foldr1 :: (a -> a -> a) -> NumBP a -> a #

foldl1 :: (a -> a -> a) -> NumBP a -> a #

toList :: NumBP a -> [a] #

null :: NumBP a -> Bool #

length :: NumBP a -> Int #

elem :: Eq a => a -> NumBP a -> Bool #

maximum :: Ord a => NumBP a -> a #

minimum :: Ord a => NumBP a -> a #

sum :: Num a => NumBP a -> a #

product :: Num a => NumBP a -> a #

Traversable NumBP Source # 

Methods

traverse :: Applicative f => (a -> f b) -> NumBP a -> f (NumBP b) #

sequenceA :: Applicative f => NumBP (f a) -> f (NumBP a) #

mapM :: Monad m => (a -> m b) -> NumBP a -> m (NumBP b) #

sequence :: Monad m => NumBP (m a) -> m (NumBP a) #

Eq a => Eq (NumBP a) Source # 

Methods

(==) :: NumBP a -> NumBP a -> Bool #

(/=) :: NumBP a -> NumBP a -> Bool #

Floating a => Floating (NumBP a) Source # 

Methods

pi :: NumBP a #

exp :: NumBP a -> NumBP a #

log :: NumBP a -> NumBP a #

sqrt :: NumBP a -> NumBP a #

(**) :: NumBP a -> NumBP a -> NumBP a #

logBase :: NumBP a -> NumBP a -> NumBP a #

sin :: NumBP a -> NumBP a #

cos :: NumBP a -> NumBP a #

tan :: NumBP a -> NumBP a #

asin :: NumBP a -> NumBP a #

acos :: NumBP a -> NumBP a #

atan :: NumBP a -> NumBP a #

sinh :: NumBP a -> NumBP a #

cosh :: NumBP a -> NumBP a #

tanh :: NumBP a -> NumBP a #

asinh :: NumBP a -> NumBP a #

acosh :: NumBP a -> NumBP a #

atanh :: NumBP a -> NumBP a #

log1p :: NumBP a -> NumBP a #

expm1 :: NumBP a -> NumBP a #

log1pexp :: NumBP a -> NumBP a #

log1mexp :: NumBP a -> NumBP a #

Fractional a => Fractional (NumBP a) Source # 

Methods

(/) :: NumBP a -> NumBP a -> NumBP a #

recip :: NumBP a -> NumBP a #

fromRational :: Rational -> NumBP a #

Data a => Data (NumBP a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NumBP a -> c (NumBP a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NumBP a) #

toConstr :: NumBP a -> Constr #

dataTypeOf :: NumBP a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (NumBP a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NumBP a)) #

gmapT :: (forall b. Data b => b -> b) -> NumBP a -> NumBP a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NumBP a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NumBP a -> r #

gmapQ :: (forall d. Data d => d -> u) -> NumBP a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NumBP a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NumBP a -> m (NumBP a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NumBP a -> m (NumBP a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NumBP a -> m (NumBP a) #

Num a => Num (NumBP a) Source # 

Methods

(+) :: NumBP a -> NumBP a -> NumBP a #

(-) :: NumBP a -> NumBP a -> NumBP a #

(*) :: NumBP a -> NumBP a -> NumBP a #

negate :: NumBP a -> NumBP a #

abs :: NumBP a -> NumBP a #

signum :: NumBP a -> NumBP a #

fromInteger :: Integer -> NumBP a #

Ord a => Ord (NumBP a) Source # 

Methods

compare :: NumBP a -> NumBP a -> Ordering #

(<) :: NumBP a -> NumBP a -> Bool #

(<=) :: NumBP a -> NumBP a -> Bool #

(>) :: NumBP a -> NumBP a -> Bool #

(>=) :: NumBP a -> NumBP a -> Bool #

max :: NumBP a -> NumBP a -> NumBP a #

min :: NumBP a -> NumBP a -> NumBP a #

Read a => Read (NumBP a) Source # 
Show a => Show (NumBP a) Source # 

Methods

showsPrec :: Int -> NumBP a -> ShowS #

show :: NumBP a -> String #

showList :: [NumBP a] -> ShowS #

Generic (NumBP a) Source # 

Associated Types

type Rep (NumBP a) :: * -> * #

Methods

from :: NumBP a -> Rep (NumBP a) x #

to :: Rep (NumBP a) x -> NumBP a #

NFData a => NFData (NumBP a) Source # 

Methods

rnf :: NumBP a -> () #

Num a => Backprop (NumBP a) Source # 

Methods

zero :: NumBP a -> NumBP a Source #

add :: NumBP a -> NumBP a -> NumBP a Source #

one :: NumBP a -> NumBP a Source #

type Rep (NumBP a) Source # 
type Rep (NumBP a) = D1 * (MetaData "NumBP" "Numeric.Backprop.Class" "backprop-0.2.3.0-4xTgnnUpmK1AibXJBUeG1v" True) (C1 * (MetaCons "NumBP" PrefixI True) (S1 * (MetaSel (Just Symbol "runNumBP") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)))

Generics

class GZero f Source #

Helper class for automatically deriving zero using GHC Generics.

Minimal complete definition

gzero

Instances

GZero (V1 *) Source # 

Methods

gzero :: V1 * t -> V1 * t

GZero (U1 *) Source # 

Methods

gzero :: U1 * t -> U1 * t

Backprop a => GZero (K1 * i a) Source # 

Methods

gzero :: K1 * i a t -> K1 * i a t

(GZero f, GZero g) => GZero ((:+:) * f g) Source # 

Methods

gzero :: (* :+: f) g t -> (* :+: f) g t

(GZero f, GZero g) => GZero ((:*:) * f g) Source # 

Methods

gzero :: (* :*: f) g t -> (* :*: f) g t

GZero f => GZero (M1 * i c f) Source # 

Methods

gzero :: M1 * i c f t -> M1 * i c f t

GZero f => GZero ((:.:) * * f g) Source # 

Methods

gzero :: (* :.: *) f g t -> (* :.: *) f g t

class GAdd f Source #

Helper class for automatically deriving add using GHC Generics.

Minimal complete definition

gadd

Instances

GAdd (V1 *) Source # 

Methods

gadd :: V1 * t -> V1 * t -> V1 * t

GAdd (U1 *) Source # 

Methods

gadd :: U1 * t -> U1 * t -> U1 * t

Backprop a => GAdd (K1 * i a) Source # 

Methods

gadd :: K1 * i a t -> K1 * i a t -> K1 * i a t

(GAdd f, GAdd g) => GAdd ((:*:) * f g) Source # 

Methods

gadd :: (* :*: f) g t -> (* :*: f) g t -> (* :*: f) g t

GAdd f => GAdd (M1 * i c f) Source # 

Methods

gadd :: M1 * i c f t -> M1 * i c f t -> M1 * i c f t

GAdd f => GAdd ((:.:) * * f g) Source # 

Methods

gadd :: (* :.: *) f g t -> (* :.: *) f g t -> (* :.: *) f g t

class GOne f Source #

Helper class for automatically deriving one using GHC Generics.

Minimal complete definition

gone

Instances

GOne (V1 *) Source # 

Methods

gone :: V1 * t -> V1 * t

GOne (U1 *) Source # 

Methods

gone :: U1 * t -> U1 * t

Backprop a => GOne (K1 * i a) Source # 

Methods

gone :: K1 * i a t -> K1 * i a t

(GOne f, GOne g) => GOne ((:+:) * f g) Source # 

Methods

gone :: (* :+: f) g t -> (* :+: f) g t

(GOne f, GOne g) => GOne ((:*:) * f g) Source # 

Methods

gone :: (* :*: f) g t -> (* :*: f) g t

GOne f => GOne (M1 * i c f) Source # 

Methods

gone :: M1 * i c f t -> M1 * i c f t

GOne f => GOne ((:.:) * * f g) Source # 

Methods

gone :: (* :.: *) f g t -> (* :.: *) f g t