backprop-0.2.6.1: Heterogeneous automatic differentation

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

Numeric.Backprop

Contents

Description

Automatic differentation and backpropagation.

Main idea: Write a function computing what you want, and the library automatically provies the gradient of that function as well, for usage with gradient descent and other training methods.

See the homepage for an introduction and walkthrough.

In more detail: instead of working directly with values to produce your result, you work with BVars containing those values. Working with these BVars is made smooth with the usage of lenses and other combinators, and libraries can offer operatons on BVars instead of those on normal types directly.

Then, you can use:

evalBP :: (forall s. Reifies s W. BVar s a -> BVar s b) -> (a -> b)

to turn a BVar function into the function on actual values a -> b. This has virtually zero overhead over writing the actual function directly.

Then, there's:

gradBP :: (forall s. Reifies s W. BVar s a -> BVar s b) -> (a -> a)

to automatically get the gradient, as well, for a given input.

Refer to the homepage for more information and links to demonstrations and tutorials, or dive striaght in by reading the docs for BVar.

If you are writing a library, see https://backprop.jle.im/08-equipping-your-library.html for a guide for equipping your library with backpropatable operations.

In the original version 0.1, this module required Num instances for methods instead of Backprop instances. This interface is still available in Numeric.Backprop.Num, which has the same API as this module, except with Num constraints on all values instead of Backprop constraints.

See Prelude.Backprop.Explicit for a version allowing you to provide zero, add, and one explicitly, which can be useful when attempting to avoid orphan instances or when mixing both Backprop and Num styles.

Synopsis

Types

data BVar s a Source #

A BVar s a is a value of type a that can be "backpropagated".

Functions referring to BVars are tracked by the library and can be automatically differentiated to get their gradients and results.

For simple numeric values, you can use its Num, Fractional, and Floating instances to manipulate them as if they were the numbers they represent.

If a contains items, the items can be accessed and extracted using lenses. A Lens' b a can be used to access an a inside a b, using ^^. (viewVar):

(^.)  ::        a -> Lens' a b ->        b
(^^.) :: BVar s a -> Lens' a b -> BVar s b

There is also ^^? (previewVar), to use a Prism' or Traversal' to extract a target that may or may not be present (which can implement pattern matching), ^^.. (toListOfVar) to use a Traversal' to extract all targets inside a BVar, and .~~ (setVar) to set and update values inside a BVar.

If you have control over your data type definitions, you can also use splitBV and joinBV to manipulate data types by easily extracting fields out of a BVar of data types and creating BVars of data types out of BVars of their fields. See Numeric.Backprop for a tutorial on this use pattern.

For more complex operations, libraries can provide functions on BVars using liftOp and related functions. This is how you can create primitive functions that users can use to manipulate your library's values. See https://backprop.jle.im/08-equipping-your-library.html for a detailed guide.

For example, the hmatrix library has a matrix-vector multiplication function, #> :: L m n -> R n -> L m.

A library could instead provide a function #> :: BVar (L m n) -> BVar (R n) -> BVar (R m), which the user can then use to manipulate their BVars of L m ns and R ns, etc.

See Numeric.Backprop and documentation for liftOp for more information.

Instances
BVGroup s ([] :: [*]) (K1 i a :: * -> *) (K1 i (BVar s a) :: * -> *) Source # 
Instance details

Defined in Numeric.Backprop.Explicit

Methods

gsplitBV :: Rec AddFunc [] -> Rec ZeroFunc [] -> BVar s (K1 i a ()) -> K1 i (BVar s a) ()

gjoinBV :: Rec AddFunc [] -> Rec ZeroFunc [] -> K1 i (BVar s a) () -> BVar s (K1 i a ())

Eq a => Eq (BVar s a) Source #

Compares the values inside the BVar.

Since: backprop-0.1.5.0

Instance details

Defined in Numeric.Backprop.Internal

Methods

(==) :: BVar s a -> BVar s a -> Bool #

(/=) :: BVar s a -> BVar s a -> Bool #

(Floating a, Reifies s W) => Floating (BVar s a) Source # 
Instance details

Defined in Numeric.Backprop.Internal

Methods

pi :: BVar s a #

exp :: BVar s a -> BVar s a #

log :: BVar s a -> BVar s a #

sqrt :: BVar s a -> BVar s a #

(**) :: BVar s a -> BVar s a -> BVar s a #

logBase :: BVar s a -> BVar s a -> BVar s a #

sin :: BVar s a -> BVar s a #

cos :: BVar s a -> BVar s a #

tan :: BVar s a -> BVar s a #

asin :: BVar s a -> BVar s a #

acos :: BVar s a -> BVar s a #

atan :: BVar s a -> BVar s a #

sinh :: BVar s a -> BVar s a #

cosh :: BVar s a -> BVar s a #

tanh :: BVar s a -> BVar s a #

asinh :: BVar s a -> BVar s a #

acosh :: BVar s a -> BVar s a #

atanh :: BVar s a -> BVar s a #

log1p :: BVar s a -> BVar s a #

expm1 :: BVar s a -> BVar s a #

log1pexp :: BVar s a -> BVar s a #

log1mexp :: BVar s a -> BVar s a #

(Fractional a, Reifies s W) => Fractional (BVar s a) Source # 
Instance details

Defined in Numeric.Backprop.Internal

Methods

(/) :: BVar s a -> BVar s a -> BVar s a #

recip :: BVar s a -> BVar s a #

fromRational :: Rational -> BVar s a #

(Num a, Reifies s W) => Num (BVar s a) Source # 
Instance details

Defined in Numeric.Backprop.Internal

Methods

(+) :: BVar s a -> BVar s a -> BVar s a #

(-) :: BVar s a -> BVar s a -> BVar s a #

(*) :: BVar s a -> BVar s a -> BVar s a #

negate :: BVar s a -> BVar s a #

abs :: BVar s a -> BVar s a #

signum :: BVar s a -> BVar s a #

fromInteger :: Integer -> BVar s a #

Ord a => Ord (BVar s a) Source #

Compares the values inside the BVar.

Since: backprop-0.1.5.0

Instance details

Defined in Numeric.Backprop.Internal

Methods

compare :: BVar s a -> BVar s a -> Ordering #

(<) :: BVar s a -> BVar s a -> Bool #

(<=) :: BVar s a -> BVar s a -> Bool #

(>) :: BVar s a -> BVar s a -> Bool #

(>=) :: BVar s a -> BVar s a -> Bool #

max :: BVar s a -> BVar s a -> BVar s a #

min :: BVar s a -> BVar s a -> BVar s a #

NFData a => NFData (BVar s a) Source #

This will force the value inside, as well.

Instance details

Defined in Numeric.Backprop.Internal

Methods

rnf :: BVar s a -> () #

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

Since: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Internal

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 #

data W Source #

An ephemeral Wengert Tape in the environment. Used internally to track of the computational graph of variables.

For the end user, one can just imagine Reifies s W as a required constraint on s that allows backpropagation to work.

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
unital

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: backprop-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 addIsList for a definition for instances of IsList. 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.

As the library uses it, the most important law is:

That is, one x is the gradient of the identity function with respect to its input.

Ideally 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 addIsList for a definition for instances of IsList. 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.

As the library uses it, the most important law is:

That is, one x is the gradient of the identity function with respect to its input.

Ideally 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 # 
Instance details

Defined in Numeric.Backprop.Class

Backprop Float Source # 
Instance details

Defined in Numeric.Backprop.Class

Backprop Int Source # 
Instance details

Defined in Numeric.Backprop.Class

Methods

zero :: Int -> Int Source #

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

one :: Int -> Int Source #

Backprop Integer Source # 
Instance details

Defined in Numeric.Backprop.Class

Backprop Natural Source #

Since: backprop-0.2.1.0

Instance details

Defined in Numeric.Backprop.Class

Backprop Word Source #

Since: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

Methods

zero :: Word -> Word Source #

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

one :: Word -> Word Source #

Backprop Word8 Source #

Since: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

Backprop Word16 Source #

Since: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

Backprop Word32 Source #

Since: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

Backprop Word64 Source #

Since: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

Backprop () Source #

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

Instance details

Defined in Numeric.Backprop.Class

Methods

zero :: () -> () Source #

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

one :: () -> () Source #

Backprop Void Source # 
Instance details

Defined in Numeric.Backprop.Class

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.

Instance details

Defined in Numeric.Backprop.Class

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.

Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

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: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

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: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

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: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

Methods

zero :: Option a -> Option a Source #

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

one :: Option a -> Option a Source #

Backprop a => Backprop (Identity a) Source # 
Instance details

Defined in Numeric.Backprop.Class

Backprop a => Backprop (First a) Source #

Since: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

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: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

Methods

zero :: Last a -> Last a Source #

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

one :: Last a -> Last a Source #

Backprop a => Backprop (Dual a) Source #

Since: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

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: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

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: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

Methods

zero :: Product a -> Product a Source #

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

one :: Product a -> Product 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.

Instance details

Defined in Numeric.Backprop.Class

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.

Instance details

Defined in Numeric.Backprop.Class

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.

Instance details

Defined in Numeric.Backprop.Class

Methods

zero :: Seq a -> Seq a Source #

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

one :: Seq a -> Seq a Source #

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

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

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: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

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: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

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: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

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

Instance details

Defined in Numeric.Backprop.Class

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: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

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.

Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

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 #

(Vector v a, Num a) => Backprop (NumVec v a) Source # 
Instance details

Defined in Numeric.Backprop.Class

Methods

zero :: NumVec v a -> NumVec v a Source #

add :: NumVec v a -> NumVec v a -> NumVec v a Source #

one :: NumVec v a -> NumVec v a Source #

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

Since: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Internal

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

Instance details

Defined in Numeric.Backprop.Class

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: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

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: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

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 #

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

Since: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

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: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

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

Instance details

Defined in Numeric.Backprop.Class

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: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

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 (f p) => Backprop (M1 i c f p) Source #

Since: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

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

Instance details

Defined in Numeric.Backprop.Class

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: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Class

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 #

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: backprop-0.2.1.0

Constructors

ABP 

Fields

Instances
Monad f => Monad (ABP f) Source # 
Instance details

Defined in Numeric.Backprop.Class

Methods

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

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

return :: a -> ABP f a #

fail :: String -> ABP f a #

Functor f => Functor (ABP f) Source # 
Instance details

Defined in Numeric.Backprop.Class

Methods

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

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

Applicative f => Applicative (ABP f) Source # 
Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

Methods

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

sequenceA :: Applicative f0 => ABP f (f0 a) -> f0 (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) #

Alternative f => Alternative (ABP f) Source # 
Instance details

Defined in Numeric.Backprop.Class

Methods

empty :: ABP f a #

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

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

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

MonadPlus f => MonadPlus (ABP f) Source # 
Instance details

Defined in Numeric.Backprop.Class

Methods

mzero :: ABP f a #

mplus :: ABP f a -> ABP f a -> ABP f a #

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

Defined in Numeric.Backprop.Class

Methods

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

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

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

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

Methods

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

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

fromRational :: Rational -> ABP f a #

(Typeable f, Typeable a, Data (f a)) => Data (ABP f a) Source # 
Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

Methods

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

show :: ABP f a -> String #

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

Generic (ABP f a) Source # 
Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

Methods

rnf :: ABP f a -> () #

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

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

type Rep (ABP f a) = D1 (MetaData "ABP" "Numeric.Backprop.Class" "backprop-0.2.6.1-E0SDrLVuBFXD6eRdeNmaqa" True) (C1 (MetaCons "ABP" PrefixI True) (S1 (MetaSel (Just "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: backprop-0.2.1.0

Constructors

NumBP 

Fields

Instances
Monad NumBP Source # 
Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

Methods

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

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

Applicative NumBP Source # 
Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

Methods

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

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

Floating a => Floating (NumBP a) Source # 
Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

Methods

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

recip :: NumBP a -> NumBP a #

fromRational :: Rational -> NumBP a #

Data a => Data (NumBP a) Source # 
Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

Show a => Show (NumBP a) Source # 
Instance details

Defined in Numeric.Backprop.Class

Methods

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

show :: NumBP a -> String #

showList :: [NumBP a] -> ShowS #

Generic (NumBP a) Source # 
Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

Methods

rnf :: NumBP a -> () #

Num a => Backprop (NumBP a) Source # 
Instance details

Defined in Numeric.Backprop.Class

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 # 
Instance details

Defined in Numeric.Backprop.Class

type Rep (NumBP a) = D1 (MetaData "NumBP" "Numeric.Backprop.Class" "backprop-0.2.6.1-E0SDrLVuBFXD6eRdeNmaqa" True) (C1 (MetaCons "NumBP" PrefixI True) (S1 (MetaSel (Just "runNumBP") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

Running

backprop :: (Backprop a, Backprop b) => (forall s. Reifies s W => BVar s a -> BVar s b) -> a -> (b, a) Source #

Turn a function BVar s a -> BVar s b into the function a -> b that it represents, also computing its gradient a as well.

The Rank-N type forall s. Reifies s W => ... is used to ensure that BVars do not leak out of the context (similar to how it is used in Control.Monad.ST), and also as a reference to an ephemeral Wengert tape used to track the graph of references.

evalBP :: (forall s. Reifies s W => BVar s a -> BVar s b) -> a -> b Source #

Turn a function BVar s a -> BVar s b into the function a -> b that it represents.

Benchmarks show that this should have virtually no overhead over directly writing a a -> b. BVar is, in this situation, a zero-cost abstraction, performance-wise.

See documentation of backprop for more information.

gradBP :: (Backprop a, Backprop b) => (forall s. Reifies s W => BVar s a -> BVar s b) -> a -> a Source #

Take a function BVar s a -> BVar s b, interpreted as a function a -> b, and compute its gradient with respect to its input.

The resulting a -> a tells how the input (and its components) affects the output. Positive numbers indicate that the result will vary in the same direction as any adjustment in the input. Negative numbers indicate that the result will vary in the opposite direction as any adjustment in the input. Larger numbers indicate a greater sensitivity of change, and small numbers indicate lower sensitivity.

See documentation of backprop for more information.

If you want to provide an explicit "final gradient" for the end, see backpropWith.

backpropWith :: Backprop a => (forall s. Reifies s W => BVar s a -> BVar s b) -> a -> (b, b -> a) Source #

A version of backprop that allows you to specify the gradent of your "final result" in with respect to the output of your function.

Typically, this is just the scalar 1, or a value of components that are all 1.

Instead of taking the b gradient, the you may provide a b -> b, which backpropWith calls with the result of your function as the argument. This allows you to return something with the correct "shape", if not a scalar.

backprop is essentially backpropWith with const 1 for scalars and Num instances.

Note that argument order changed in v0.2.4

Since: backprop-0.2.0.0

Multiple inputs

backprop2 :: (Backprop a, Backprop b, Backprop c) => (forall s. Reifies s W => BVar s a -> BVar s b -> BVar s c) -> a -> b -> (c, (a, b)) Source #

backprop for a two-argument function.

Not strictly necessary, because you can always uncurry a function by passing in all of the argument inside a data type, or just use a tuple. However, this could potentially be more performant.

For 3 and more arguments, consider using backpropN.

evalBP2 :: (forall s. Reifies s W => BVar s a -> BVar s b -> BVar s c) -> a -> b -> c Source #

evalBP for a two-argument function. See backprop2 for notes.

gradBP2 :: (Backprop a, Backprop b, Backprop c) => (forall s. Reifies s W => BVar s a -> BVar s b -> BVar s c) -> a -> b -> (a, b) Source #

gradBP for a two-argument function. See backprop2 for notes.

backpropWith2 :: (Backprop a, Backprop b) => (forall s. Reifies s W => BVar s a -> BVar s b -> BVar s c) -> a -> b -> (c, c -> (a, b)) Source #

backprop2, but allows you to provide the gradient of the "final result" with respect to the output of your function. See backpropWith for more details.

Note that argument order changed in v0.2.4

Since: backprop-0.2.0.0

backpropN :: (RPureConstrained Backprop as, Backprop b) => (forall s. Reifies s W => Rec (BVar s) as -> BVar s b) -> Rec Identity as -> (b, Rec Identity as) Source #

backprop generalized to multiple inputs of different types. See the Numeric.Backprop.Op for a mini-tutorial on heterogeneous lists.

Not strictly necessary, because you can always uncurry a function by passing in all of the inputs in a data type containing all of the arguments or a giant tuple. However, this could potentially also be more performant.

A Rec (BVar s) '[Double, Float, Double], for instance, is a tuple of BVar s Double, BVar s Float, and BVar s Double, and can be pattern matched on using :< (cons) and Ø (nil).

The RPureConstrained Backprop as in the constraint says that every value in the type-level list as must have a Backprop instance. This means you can use, say, '[Double, Float, Int], but not '[Double, Bool, String].

If you stick to concerete, monomorphic usage of this (with specific types, typed into source code, known at compile-time), then RPureConstrained Backprop as should be fulfilled automatically.

evalBPN :: forall as b. (forall s. Reifies s W => Rec (BVar s) as -> BVar s b) -> Rec Identity as -> b Source #

evalBP generalized to multiple inputs of different types. See documentation for backpropN for more details.

gradBPN :: (RPureConstrained Backprop as, Backprop b) => (forall s. Reifies s W => Rec (BVar s) as -> BVar s b) -> Rec Identity as -> Rec Identity as Source #

gradBP generalized to multiple inputs of different types. See documentation for backpropN for more details.

backpropWithN :: RPureConstrained Backprop as => (forall s. Reifies s W => Rec (BVar s) as -> BVar s b) -> Rec Identity as -> (b, b -> Rec Identity as) Source #

backpropN, but allows you to provide the gradient of the "final result" with respect to the output of your function. See backpropWith for more details.

Note that argument order changed in v0.2.4.

Since: backprop-0.2.0.0

Manipulating BVar

evalBP0 :: (forall s. Reifies s W => BVar s a) -> a Source #

evalBP but with no arguments. Useful when everything is just given through constVar.

constVar :: a -> BVar s a Source #

Lift a value into a BVar representing a constant value.

This value will not be considered an input, and its gradients will not be backpropagated.

auto :: a -> BVar s a Source #

Shorter alias for constVar, inspired by the ad library.

Since: backprop-0.2.0.0

coerceVar :: Coercible a b => BVar s a -> BVar s b Source #

Coerce a BVar contents. Useful for things like newtype wrappers.

Since: backprop-0.1.5.2

(^^.) :: forall b a s. (Backprop b, Backprop a, Reifies s W) => BVar s b -> Lens' b a -> BVar s a infixl 8 Source #

An infix version of viewVar, meant to evoke parallels to ^. from lens.

With normal values, you can extract something from that value with a lens:

x ^. myLens

would extract a piece of x :: b, specified by myLens :: Lens' b a. The result has type a.

xVar ^^. myLens

would extract a piece out of xVar :: BVar s b (a BVar holding a b), specified by myLens :: Lens' b a. The result has type BVar s a (a BVar holding a a)

This is the main way to pull out values from BVar of container types.

If you have control of your data type definitions, consider using splitBV, which lets you break out BVars of values into BVars of their individual fields automatically without requiring lenses.

NOTE: Usage of ^^. on many fields from the same item is usually the main source of overhead in backprop code, if you are looking to optimize your code. See <https://backprop.jle.im/07-performance.html this performance guide> for more information, and details on mitigating this overhead.

WARNING: Do not use with any lenses that operate "numerically" on the contents (like multiplying).

(.~~) :: (Backprop a, Backprop b, Reifies s W) => Lens' b a -> BVar s a -> BVar s b -> BVar s b infixl 8 Source #

An infix version of setVar, meant to evoke parallels to .~ from lens.

With normal values, you can set something in a value with a lens:

x & myLens .~ y

would "set" a part of x :: b, specified by myLens :: Lens' a b, to a new value y :: a.

xVar & myLens .~~ yVar

would "set" a part of xVar :: BVar s b (a BVar holding a b), specified by myLens :: Lens' a b, to a new value given by yVar :: BVar s a. The result is a new (updated) value of type BVar s b.

This is the main way to set values inside BVars of container types.

Note that this does not incurr the performance overhead issues of viewVar and ^^., and is fairly cheap.

(%~~) :: (Backprop a, Backprop b, Reifies s W) => Lens' b a -> (BVar s a -> BVar s a) -> BVar s b -> BVar s b infixr 4 Source #

An infix version of overVar, meant to evoke parallels to %~ from lens.

With normal values, you can set modify in a value with a lens:

x & myLens %~ negate

would "modify" a part of x :: b, specified by myLens :: Lens' a b, using the function negate :: a -> a.

xVar & myLens %~~ negate

would "modify" a part of xVar :: BVar s b (a BVar holding a b), specified by myLens :: Lens' a b, using the function negate :: BVar s a -> BVar s . The result is a new (updated) value of type BVar s b.

Is essentially a convenient wrapper over a viewVar followed by a setVar.

Since: backprop-0.2.4.0

(^^?) :: forall b a s. (Backprop b, Backprop a, Reifies s W) => BVar s b -> Traversal' b a -> Maybe (BVar s a) infixl 8 Source #

An infix version of previewVar, meant to evoke parallels to ^? from lens.

With normal values, you can (potentially) extract something from that value with a lens:

x ^? myPrism

would (potentially) extract a piece of x :: b, specified by myPrism :: Traversal' b a. The result has type Maybe a.

xVar ^^? myPrism

would (potentially) extract a piece out of xVar :: BVar s b (a BVar holding a b), specified by myPrism :: Prism' b a. The result has type Maybe (BVar s a) (Maybe a BVar holding a a).

This is intended to be used with Prism's (which hits at most one target), but will actually work with any Traversal'. If the traversal hits more than one target, the first one found will be extracted.

This can be used to "pattern match" on BVars, by using prisms on constructors.

NOTE: Has the same potential of performance overhead issues as ^^.; see documentation of ^^. for more details.

(^^..) :: forall b a s. (Backprop b, Backprop a, Reifies s W) => BVar s b -> Traversal' b a -> [BVar s a] Source #

An infix version of toListOfVar, meant to evoke parallels to ^.. from lens.

With normal values, you can extract all targets of a Traversal from that value with a:

x ^.. myTraversal

would extract all targets inside of x :: b, specified by myTraversal :: Traversal' b a. The result has type [a].

xVar ^^.. myTraversal

would extract all targets inside of xVar :: BVar s b (a BVar holding a b), specified by myTraversal :: Traversal' b a. The result has type [BVar s a] (A list of BVars holding as).

NOTE: Has all of the performance overhead issues of sequenceVar; see documentation for sequenceVar for more information.

(^^?!) :: forall b a s. (Backprop b, Backprop a, Reifies s W) => BVar s b -> Traversal' b a -> BVar s a infixl 8 Source #

An *UNSAFE* version of ^^? and previewVar assuming that the value is there.

Is undefined if the Traversal hits no targets.

Is essentially ^^? with fromJust, or ^^.. with head.

Since: backprop-0.2.1.0

viewVar :: forall b a s. (Backprop a, Backprop b, Reifies s W) => Lens' b a -> BVar s b -> BVar s a Source #

Using a Lens', extract a value inside a BVar. Meant to evoke parallels to view from lens.

See documentation for ^^. for more information, caveats, and warnings.

setVar :: (Backprop a, Backprop b, Reifies s W) => Lens' b a -> BVar s a -> BVar s b -> BVar s b Source #

Using a Lens', set a value inside a BVar. Meant to evoke parallels to "set" from lens.

See documentation for .~~ for more information.

overVar :: (Backprop a, Backprop b, Reifies s W) => Lens' b a -> (BVar s a -> BVar s a) -> BVar s b -> BVar s b Source #

Using a Lens', modify a value inzide a BVar. Meant to evoke parallels to "over" from lens. See documentation for %~~ for more information.

Since: backprop-0.2.4.0

sequenceVar :: (Traversable t, Backprop a, Reifies s W) => BVar s (t a) -> t (BVar s a) Source #

Extract all of the BVars out of a Traversable container of BVars.

Note that this associates gradients in order of occurrence in the original data structure; the second item in the gradient is assumed to correspond with the second item in the input, etc.; this can cause unexpected behavior in Foldable instances that don't have a fixed number of items.

NOTE: A potential source of performance overhead. If there are \(n\) total elements, and you use \(m\) of them, then there is an overhead cost on the order of \(\mathcal{O}(m n)\), with a constant factor dependent on the cost of add. Should be negligible for types with cheap add (like Double), but may be costly for things like large matrices. See <https://backprop.jle.im/07-performance.html the performance guide> for for details.

collectVar :: (Foldable t, Functor t, Backprop a, Reifies s W) => t (BVar s a) -> BVar s (t a) Source #

Collect all of the BVars in a container into a BVar of that container's contents.

Note that this associates gradients in order of occurrence in the original data structure; the second item in the total derivative and gradient is assumed to correspond with the second item in the input, etc.; this can cause unexpected behavior in Foldable instances that don't have a fixed number of items.

Note that this does not suffer from the same performance overhead issues as sequenceVar. collectVar is \(\mathcal{O}(n)\), with a very small constant factor that consistent for all types. This reveals a general property of reverse-mode automatic differentiation; "many to one" is cheap, but "one to many" is expensive.

previewVar :: forall b a s. (Backprop b, Backprop a, Reifies s W) => Traversal' b a -> BVar s b -> Maybe (BVar s a) Source #

Using a Traversal', extract a single value inside a BVar, if it exists. If more than one traversal target exists, returns te first. Meant to evoke parallels to preview from lens. Really only intended to be used wth Prism's, or up-to-one target traversals.

See documentation for ^^? for more information, warnings, and caveats.

toListOfVar :: forall b a s. (Backprop b, Backprop a, Reifies s W) => Traversal' b a -> BVar s b -> [BVar s a] Source #

Using a Traversal', extract all targeted values inside a BVar. Meant to evoke parallels to toListOf from lens.

See documentation for ^^.. for more information, warnings, and caveats.

pattern T2 :: (Backprop a, Backprop b, Reifies s W) => BVar s a -> BVar s b -> BVar s (a, b) Source #

Useful pattern for constructing and deconstructing BVars of two-tuples.

Since: backprop-0.2.1.0

pattern T3 :: (Backprop a, Backprop b, Backprop c, Reifies s W) => BVar s a -> BVar s b -> BVar s c -> BVar s (a, b, c) Source #

Useful pattern for constructing and deconstructing BVars three-tuples.

Since: backprop-0.2.1.0

With Isomorphisms

isoVar :: (Backprop a, Reifies s W) => (a -> b) -> (b -> a) -> BVar s a -> BVar s b Source #

Convert the value inside a BVar using a given isomorphism. Useful for things like constructors.

If you have control of your data type definitions, consider using joinBV, which lets you use your data type constructors themselves to join together BVars as their fields.

Warning: This is unsafe! It assumes that the isomorphisms themselves have derivative 1, so will break for things like exp & log. Basically, don't use this for any "numeric" isomorphisms.

Since: backprop-0.1.4.0

isoVar2 :: (Backprop a, Backprop b, Reifies s W) => (a -> b -> c) -> (c -> (a, b)) -> BVar s a -> BVar s b -> BVar s c Source #

Convert the values inside two BVars using a given isomorphism. Useful for things like constructors. See isoVar for caveats.

If you have control of your data type definitions, consider using joinBV, which lets you use your data type constructors themselves to join together BVars as their fields.

Since: backprop-0.1.4.0

isoVar3 :: (Backprop a, Backprop b, Backprop c, Reifies s W) => (a -> b -> c -> d) -> (d -> (a, b, c)) -> BVar s a -> BVar s b -> BVar s c -> BVar s d Source #

Convert the values inside three BVars using a given isomorphism. Useful for things like constructors. See isoVar for caveats.

Since: backprop-0.1.4.0

isoVarN :: (RPureConstrained Backprop as, Reifies s W) => (Rec Identity as -> b) -> (b -> Rec Identity as) -> Rec (BVar s) as -> BVar s b Source #

Convert the values inside a tuple of BVars using a given isomorphism. Useful for things like constructors. See isoVar for caveats.

If you have control of your data type definitions, consider using joinBV, which lets you use your data type constructors themselves to join together BVars as their fields.

Since: backprop-0.1.4.0

With Ops

This library provides a few primitive actions for manipulating BVars and the values inside them, including its Num, Fractional, and Floating instances, and lens-based operations like ^^., .~~ ^^?, and ^^...

However, the power of this library comes from manipulating many different types from libraries, like matrices and vectors. Libraries can provide their own BVar s a -> BVar s b functions, alongside (or in lieu of) a -> b functions for their types.

The easiest way to create a BVar function is to use liftOp with an Op constructor. For example, imagine a vector library providing a dot product function. We can write this using liftOp2 and op2:

dot :: BVar s Vec -> BVar s Vec -> BVar s Double
dot = liftOp2 . op2 $ \xs ys ->
        ( sum (zipWith (*) xs ys)
        , \g -> (map (*g) ys, map (*g) xs)
        )

We provide a function that, given the two inputs, returns:

  1. The result of the function on those two inputs
  2. A function taking the "total derivative", and returning the gradient with respect to each of the inputs.

See documentation in Numeric.Backprop.Op for more information on the second part (the gradient).

Nice Ops are how backprop links together BVars and tracks them to determine their gradient. Ideally, users would never have to deal with these when backpropagating their own functions, and library authors providing their matrix and vector operations, etc. would provide BVar variants of their normal operations.

In fact, BVar operations could even be defined instead of normal operations, since it is easy to go from BVar s a -> BVar s b to a -> b, using evalBP, and this carries virtually zero overhead, so some libraries might even provide BVar versions by default.

liftOp :: (RPureConstrained Backprop as, Reifies s W) => Op as b -> Rec (BVar s) as -> BVar s b Source #

Lift an Op with an arbitrary number of inputs to a function on the appropriate number of BVars.

Should preferably be used only by libraries to provide primitive BVar functions for their types for users.

See Numeric.Backprop and documentation for liftOp for more information, and Numeric.Backprop.Op for a mini-tutorial on using Rec.

liftOp1 :: (Backprop a, Reifies s W) => Op '[a] b -> BVar s a -> BVar s b Source #

Lift an Op with a single input to be a function on a single BVar.

Should preferably be used only by libraries to provide primitive BVar functions for their types for users.

See Numeric.Backprop and documentation for liftOp for more information.

liftOp2 :: (Backprop a, Backprop b, Reifies s W) => Op '[a, b] c -> BVar s a -> BVar s b -> BVar s c Source #

Lift an Op with two inputs to be a function on a two BVars.

Should preferably be used only by libraries to provide primitive BVar functions for their types for users.

See Numeric.Backprop and documentation for liftOp for more information.

liftOp3 :: (Backprop a, Backprop b, Backprop c, Reifies s W) => Op '[a, b, c] d -> BVar s a -> BVar s b -> BVar s c -> BVar s d Source #

Lift an Op with three inputs to be a function on a three BVars.

Should preferably be used only by libraries to provide primitive BVar functions for their types for users.

See Numeric.Backprop and documentation for liftOp for more information.

Generics

splitBV and joinBV let you split out a BVar of a data type and join together a data type of BVars using the "higher-kinded data type" technique, a la http://reasonablypolymorphic.com/blog/higher-kinded-data/.

It will let you take a data type like

data MyType = MT { mtX :: Double, mtY :: [Double] }

-- | Automatic instance
instance Backprop MyType

And automatically let you turn a BVar s MyType into a BVar s Double and BVar s [Double], without munging around with lenses and viewVar. It'll also let you take a BVar s Double and a BVar s [Double] and turn it into a BVar s MyType without messing around with manually lifting ops or isoVar.

To do this, rewrite MyType to take a Functor argument:

-- | Can be re-used for every data type you use this trick with
type family HKD f a where
    HKD Identity a = a
    HKD f        a =  f a

data MyType' f = MT { mtX :: HKD f Double, mtY :: HKD f [Double] }
  deriving Generic

-- | This is the original data type, which can be used the same way as
-- before
type MyType = MyType' Identity

-- | Automatic instance
instance Backprop MyType

Now, splitBV can be used, with type:

splitBV :: BVar s MyType -> MyType' (BVar s)

So you can use it lke:

myFunction :: BVar s MyType -> BVar s Double
myFunction (splitBV -> MT x y) =  x + sum y

Or also, using the BV pattern synonym:

myFunction :: BVar s MyType -> BVar s Double
myFunction (BV (MT x y)) =  x + sum y

If you use splitBV, the contents will be a BVar s Double and a BVar s [Double]. It lets you "extract" the fields, because your MyType' constructor now holds a BVar s Double and a BVar s [Double], instead of just a normal Double and [Double].

Note that access using splitBV and pattern matching is slightly slower than access using lenses (by about 10-20%).

With this trick, joinBV can also be used, with the type:

joinBV :: MyType' (BVar s) -> BVar s MyType

So you can take a bunch of BVars and turn them into a BVar of a MyType:

myOtherFunction :: BVar s Double -> BVar s [Double] -> BVar s MyType
myOtherFunction x y = joinBV $ MT x y

The BV pattern synonym abstracts over manual application of splitBV and joinBV as a pattern.

This will work with all data types made with a single constructor, whose fields are all instances of Backprop, where the type itself has an instance of Backprop.

splitBV Source #

Arguments

:: (Generic (z f), Generic (z (BVar s)), BVGroup s as (Rep (z f)) (Rep (z (BVar s))), Backprop (z f), Backprop (Rep (z f) ()), RPureConstrained Backprop as, Reifies s W) 
=> BVar s (z f)

BVar of value

-> z (BVar s)

BVars of fields

Split out a BVar of "higher-kinded data type", a la http://reasonablypolymorphic.com/blog/higher-kinded-data/

Lets you take BVar of a value into a separate BVar of every field of that value.

See Numeric.Backprop for a tutorial on usage.

This will work with all data types made with a single constructor, whose fields are all instances of Backprop, where the type itself has an instance of Backprop. The type also must derive Generic.

Note that access using splitBV and pattern matching is slightly slower than access using lenses (by about 10-20%).

See also BV, pattern synonym version where the deconstructor is exactly a view into splitBV.

NOTE: Like ^^. and viewVar, splitBV usage could potentially be the main source of performance overhead in your program. If your data type has \(n\) fields, and you use splitBV to later use \(m\) of those fields, there is an overhead cost on the order of \(\mathcal{O}(m n)\), with a constant factor dependent on the cost of add for your original data type. Should be negligible for types with cheap add (like Double), but may be costly for things like large matrices. See the performance guide for for details.

However, there is some potential opportunities to re-write some core library functionality that would allow splitBV to avoid all of the significant performance overhead issues of ^^.. Contact me if you are interested in helping out!

Since: backprop-0.2.2.0

joinBV Source #

Arguments

:: (Generic (z f), Generic (z (BVar s)), BVGroup s as (Rep (z f)) (Rep (z (BVar s))), Backprop (z f), Backprop (Rep (z f) ()), RPureConstrained Backprop as, Reifies s W) 
=> z (BVar s)

BVars of fields

-> BVar s (z f)

BVar of combined value

Assemble a BVar of "higher-kinded data type", a la http://reasonablypolymorphic.com/blog/higher-kinded-data/

It lets you take a BVar of every field of a value, and join them into a BVar of that value.

See Numeric.Backprop for a tutorial on usage.

This will work with all data types made with a single constructor, whose fields are all instances of Backprop, where the type itself has an instance of Backprop.

See also BV, a pattern synonym version where the constructor is exactly joinBV.

Note that joinBV does not suffer the major performance overhead issues of splitBV. This is a general property of reverse-mode automatic differentiation: "many to one" is cheap, but "one to many" is expensive.

Since: backprop-0.2.2.0

pattern BV :: (Generic (z f), Generic (z (BVar s)), BVGroup s as (Rep (z f)) (Rep (z (BVar s))), Backprop (Rep (z f) ()), Backprop (z f), RPureConstrained Backprop as, RecApplicative as, Reifies s W) => z (BVar s) -> BVar s (z f) Source #

Pattern synonym wrapping manual usage of splitBV and joinBV. It is a pattern for a BVar s (z f) containing a z (BVar s)

Since: backprop-0.2.3.0

class BVGroup s as i o | o -> i, i -> as Source #

Helper class for generically "splitting" and "joining" BVars into constructors. See splitBV and joinBV.

See Numeric.Backprop for a tutorial on how to use this.

Instances should be available for types made with one constructor whose fields are all instances of Backprop, with a Generic instance.

Since: backprop-0.2.2.0

Minimal complete definition

gsplitBV, gjoinBV

Instances
BVGroup s as i o => BVGroup s as (M1 p c i) (M1 p c o) Source # 
Instance details

Defined in Numeric.Backprop.Explicit

Methods

gsplitBV :: Rec AddFunc as -> Rec ZeroFunc as -> BVar s (M1 p c i ()) -> M1 p c o ()

gjoinBV :: Rec AddFunc as -> Rec ZeroFunc as -> M1 p c o () -> BVar s (M1 p c i ())

BVGroup s ([] :: [*]) (U1 :: * -> *) (U1 :: * -> *) Source # 
Instance details

Defined in Numeric.Backprop.Explicit

Methods

gsplitBV :: Rec AddFunc [] -> Rec ZeroFunc [] -> BVar s (U1 ()) -> U1 ()

gjoinBV :: Rec AddFunc [] -> Rec ZeroFunc [] -> U1 () -> BVar s (U1 ())

BVGroup s ([] :: [*]) (V1 :: * -> *) (V1 :: * -> *) Source # 
Instance details

Defined in Numeric.Backprop.Explicit

Methods

gsplitBV :: Rec AddFunc [] -> Rec ZeroFunc [] -> BVar s (V1 ()) -> V1 ()

gjoinBV :: Rec AddFunc [] -> Rec ZeroFunc [] -> V1 () -> BVar s (V1 ())

BVGroup s ([] :: [*]) (K1 i a :: * -> *) (K1 i (BVar s a) :: * -> *) Source # 
Instance details

Defined in Numeric.Backprop.Explicit

Methods

gsplitBV :: Rec AddFunc [] -> Rec ZeroFunc [] -> BVar s (K1 i a ()) -> K1 i (BVar s a) ()

gjoinBV :: Rec AddFunc [] -> Rec ZeroFunc [] -> K1 i (BVar s a) () -> BVar s (K1 i a ())

(Reifies s W, BVGroup s as i1 o1, BVGroup s bs i2 o2, cs ~ (as ++ bs), RecApplicative as) => BVGroup s (i1 () ': (i2 () ': cs)) (i1 :+: i2) (o1 :+: o2) Source #

This instance is possible but it is not clear when it would be useful

Instance details

Defined in Numeric.Backprop.Explicit

Methods

gsplitBV :: Rec AddFunc (i1 () ': (i2 () ': cs)) -> Rec ZeroFunc (i1 () ': (i2 () ': cs)) -> BVar s ((i1 :+: i2) ()) -> (o1 :+: o2) ()

gjoinBV :: Rec AddFunc (i1 () ': (i2 () ': cs)) -> Rec ZeroFunc (i1 () ': (i2 () ': cs)) -> (o1 :+: o2) () -> BVar s ((i1 :+: i2) ())

(Reifies s W, BVGroup s as i1 o1, BVGroup s bs i2 o2, cs ~ (as ++ bs), RecApplicative as) => BVGroup s (i1 () ': (i2 () ': cs)) (i1 :*: i2) (o1 :*: o2) Source # 
Instance details

Defined in Numeric.Backprop.Explicit

Methods

gsplitBV :: Rec AddFunc (i1 () ': (i2 () ': cs)) -> Rec ZeroFunc (i1 () ': (i2 () ': cs)) -> BVar s ((i1 :*: i2) ()) -> (o1 :*: o2) ()

gjoinBV :: Rec AddFunc (i1 () ': (i2 () ': cs)) -> Rec ZeroFunc (i1 () ': (i2 () ': cs)) -> (o1 :*: o2) () -> BVar s ((i1 :*: i2) ())

Op

newtype Op as a Source #

An Op as a describes a differentiable function from as to a.

For example, a value of type

Op '[Int, Bool] Double

is a function from an Int and a Bool, returning a Double. It can be differentiated to give a gradient of an Int and a Bool if given a total derivative for the Double. If we call Bool \(2\), then, mathematically, it is akin to a:

\[ f : \mathbb{Z} \times 2 \rightarrow \mathbb{R} \]

See runOp, gradOp, and gradOpWith for examples on how to run it, and Op for instructions on creating it.

It is simpler to not use this type constructor directly, and instead use the op2, op1, op2, and op3 helper smart constructors.

See Numeric.Backprop.Op for a mini-tutorial on using Rec and 'Rec Identity'.

To use an Op with the backprop library, see liftOp, liftOp1, liftOp2, and liftOp3.

Constructors

Op

Construct an Op by giving a function creating the result, and also a continuation on how to create the gradient, given the total derivative of a.

See the module documentation for Numeric.Backprop.Op for more details on the function that this constructor and Op expect.

Fields

Instances
(RPureConstrained Num as, Floating a) => Floating (Op as a) Source # 
Instance details

Defined in Numeric.Backprop.Op

Methods

pi :: Op as a #

exp :: Op as a -> Op as a #

log :: Op as a -> Op as a #

sqrt :: Op as a -> Op as a #

(**) :: Op as a -> Op as a -> Op as a #

logBase :: Op as a -> Op as a -> Op as a #

sin :: Op as a -> Op as a #

cos :: Op as a -> Op as a #

tan :: Op as a -> Op as a #

asin :: Op as a -> Op as a #

acos :: Op as a -> Op as a #

atan :: Op as a -> Op as a #

sinh :: Op as a -> Op as a #

cosh :: Op as a -> Op as a #

tanh :: Op as a -> Op as a #

asinh :: Op as a -> Op as a #

acosh :: Op as a -> Op as a #

atanh :: Op as a -> Op as a #

log1p :: Op as a -> Op as a #

expm1 :: Op as a -> Op as a #

log1pexp :: Op as a -> Op as a #

log1mexp :: Op as a -> Op as a #

(RPureConstrained Num as, Fractional a) => Fractional (Op as a) Source # 
Instance details

Defined in Numeric.Backprop.Op

Methods

(/) :: Op as a -> Op as a -> Op as a #

recip :: Op as a -> Op as a #

fromRational :: Rational -> Op as a #

(RPureConstrained Num as, Num a) => Num (Op as a) Source # 
Instance details

Defined in Numeric.Backprop.Op

Methods

(+) :: Op as a -> Op as a -> Op as a #

(-) :: Op as a -> Op as a -> Op as a #

(*) :: Op as a -> Op as a -> Op as a #

negate :: Op as a -> Op as a #

abs :: Op as a -> Op as a #

signum :: Op as a -> Op as a #

fromInteger :: Integer -> Op as a #

Creation

op0 :: a -> Op '[] a Source #

Create an Op that takes no inputs and always returns the given value.

There is no gradient, of course (using gradOp will give you an empty tuple), because there is no input to have a gradient of.

>>> runOp (op0 10) RNil
(10, RNil)

For a constant Op that takes input and ignores it, see opConst and opConst'.

opConst :: forall as a. RPureConstrained Num as => a -> Op as a Source #

An Op that ignores all of its inputs and returns a given constant value.

>>> gradOp' (opConst 10) (1 :& 2 :& 3 :& RNil)
(10, 0 :& 0 :& 0 :& RNil)

idOp :: Op '[a] a Source #

An Op that just returns whatever it receives. The identity function.

idOp = opIso id id

bpOp :: RPureConstrained Backprop as => (forall s. Reifies s W => Rec (BVar s) as -> BVar s b) -> Op as b Source #

Create an Op from a backpropagatable function. Can be useful for "storing" an otherwise Rank-N backpropagatable function in order to avoid impredicative types. But this is pretty uncommon, so this is mostly just used for low-level internal situations.

liftOp . bpOp = id
bpOp . liftOp = id

Giving gradients directly

op1 :: (a -> (b, b -> a)) -> Op '[a] b Source #

Create an Op of a function taking one input, by giving its explicit derivative. The function should return a tuple containing the result of the function, and also a function taking the derivative of the result and return the derivative of the input.

If we have

\[ \eqalign{ f &: \mathbb{R} \rightarrow \mathbb{R}\cr y &= f(x)\cr z &= g(y) } \]

Then the derivative \( \frac{dz}{dx} \), it would be:

\[ \frac{dz}{dx} = \frac{dz}{dy} \frac{dy}{dx} \]

If our Op represents \(f\), then the second item in the resulting tuple should be a function that takes \(\frac{dz}{dy}\) and returns \(\frac{dz}{dx}\).

As an example, here is an Op that squares its input:

square :: Num a => Op '[a] a
square = op1 $ \x -> (x*x, \d -> 2 * d * x
                     )

Remember that, generally, end users shouldn't directly construct Ops; they should be provided by libraries or generated automatically.

op2 :: (a -> b -> (c, c -> (a, b))) -> Op '[a, b] c Source #

Create an Op of a function taking two inputs, by giving its explicit gradient. The function should return a tuple containing the result of the function, and also a function taking the derivative of the result and return the derivative of the input.

If we have

\[ \eqalign{ f &: \mathbb{R}^2 \rightarrow \mathbb{R}\cr z &= f(x, y)\cr k &= g(z) } \]

Then the gradient \( \left< \frac{\partial k}{\partial x}, \frac{\partial k}{\partial y} \right> \) would be:

\[ \left< \frac{\partial k}{\partial x}, \frac{\partial k}{\partial y} \right> = \left< \frac{dk}{dz} \frac{\partial z}{dx}, \frac{dk}{dz} \frac{\partial z}{dy} \right> \]

If our Op represents \(f\), then the second item in the resulting tuple should be a function that takes \(\frac{dk}{dz}\) and returns \( \left< \frac{\partial k}{dx}, \frac{\partial k}{dx} \right> \).

As an example, here is an Op that multiplies its inputs:

mul :: Num a => Op '[a, a] a
mul = op2' $ \x y -> (x*y, \d -> (d*y, x*d)
                     )

Remember that, generally, end users shouldn't directly construct Ops; they should be provided by libraries or generated automatically.

op3 :: (a -> b -> c -> (d, d -> (a, b, c))) -> Op '[a, b, c] d Source #

Create an Op of a function taking three inputs, by giving its explicit gradient. See documentation for op2 for more details.

From Isomorphisms

opCoerce :: Coercible a b => Op '[a] b Source #

An Op that coerces an item into another item whose type has the same runtime representation.

>>> gradOp' opCoerce (Identity 5) :: (Int, Identity Int)
(5, Identity 1)
opCoerce = opIso coerced coerce

opTup :: Op as (Rec Identity as) Source #

An Op that takes as and returns exactly the input tuple.

>>> gradOp' opTup (1 :& 2 :& 3 :& RNil)
(1 :& 2 :& 3 :& RNil, 1 :& 1 :& 1 :& RNil)

opIso :: (a -> b) -> (b -> a) -> Op '[a] b Source #

An Op that runs the input value through an isomorphism.

Warning: This is unsafe! It assumes that the isomorphisms themselves have derivative 1, so will break for things like exp & log. Basically, don't use this for any "numeric" isomorphisms.

opIsoN :: (Rec Identity as -> b) -> (b -> Rec Identity as) -> Op as b Source #

An Op that runs the input value through an isomorphism between a tuple of values and a value. See opIso for caveats.

In Numeric.Backprop.Op since version 0.1.2.0, but only exported from Numeric.Backprop since version 0.1.3.0.

Since: backprop-0.1.2.0

opLens :: Num a => Lens' a b -> Op '[a] b Source #

An Op that extracts a value from an input value using a Lens'.

Warning: This is unsafe! It assumes that it extracts a specific value unchanged, with derivative 1, so will break for things that numerically manipulate things before returning them.

No gradients

noGrad1 :: (a -> b) -> Op '[a] b Source #

Create an Op with no gradient. Can be evaluated with evalOp, but will throw a runtime exception when asked for the gradient.

Can be used with BVar with liftOp1, and evalBP will work fine. gradBP and backprop will also work fine if the result is never used in the final answer, but will throw a runtime exception if the final answer depends on the result of this operation.

Useful if your only API is exposed through backprop. Just be sure to tell your users that this will explode when finding the gradient if the result is used in the final result.

Since: backprop-0.1.3.0

noGrad :: (Rec Identity as -> b) -> Op as b Source #

Create an Op with no gradient. Can be evaluated with evalOp, but will throw a runtime exception when asked for the gradient.

Can be used with BVar with liftOp, and evalBP will work fine. gradBP and backprop will also work fine if the result is never used in the final answer, but will throw a runtime exception if the final answer depends on the result of this operation.

Useful if your only API is exposed through backprop. Just be sure to tell your users that this will explode when finding the gradient if the result is used in the final result.

Since: backprop-0.1.3.0

Utility

class Reifies (s :: k) a | s -> a #

Minimal complete definition

reflect

Instances
KnownNat n => Reifies (n :: Nat) Integer 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy n -> Integer #

KnownSymbol n => Reifies (n :: Symbol) String 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy n -> String #

Reifies Z Int 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy Z -> Int #

Reifies n Int => Reifies (D n :: *) Int 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy (D n) -> Int #

Reifies n Int => Reifies (SD n :: *) Int 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy (SD n) -> Int #

Reifies n Int => Reifies (PD n :: *) Int 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy (PD n) -> Int #

(B b0, B b1, B b2, B b3, B b4, B b5, B b6, B b7, w0 ~ W b0 b1 b2 b3, w1 ~ W b4 b5 b6 b7) => Reifies (Stable w0 w1 a :: *) a 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy (Stable w0 w1 a) -> a #