backprop-0.2.5.0: Heterogeneous automatic differentation

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

Numeric.Backprop.Explicit

Contents

Description

Provides "explicit" versions of all of the functions in Numeric.Backprop. Instead of relying on a Backprop instance, allows you to manually provide zero, add, and one on a per-value basis.

It is recommended you use Numeric.Backprop or Numeric.Backprop.Num instead, unless your type has no Num instance, or you else you want to avoid defining orphan Backprop instances for external types. Can also be useful if mixing and matching styles.

See Numeric.Backprop for fuller documentation on using these functions.

WARNING: API of this module can be considered only "semi-stable"; while the API of Numeric.Backprop and Numeric.Backprop.Num are kept consistent, some argument order changes might happen in this module to reflect changes in underlying implementation.

Since: 0.2.0.0

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 # 

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: 0.1.5.0

Methods

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

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

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

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 Type s W) => Fractional (BVar s a) Source # 

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 Type s W) => Num (BVar s a) Source # 

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: 0.1.5.0

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.

Methods

rnf :: BVar s a -> () #

(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 #

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: 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 # 
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 Expr Source #

Since: 0.2.4.0

Methods

zero :: Expr -> Expr Source #

add :: Expr -> Expr -> Expr Source #

one :: Expr -> Expr 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 #

(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 #

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

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

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 (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 #

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 f => Monad (ABP f) Source # 

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 # 

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

Alternative f => Alternative (ABP f) Source # 

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 # 

Methods

mzero :: ABP f a #

mplus :: ABP f a -> ABP f a -> 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.5.0-2YkU6km7bk21njdKt9CEC" 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.5.0-2YkU6km7bk21njdKt9CEC" True) (C1 * (MetaCons "NumBP" PrefixI True) (S1 * (MetaSel (Just Symbol "runNumBP") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)))

Explicit zero, add, and one

newtype ZeroFunc 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: Applying the function twice is the same as applying it just once.

Each type should ideally only have one ZeroFunc. This coherence constraint is given by the typeclass Backprop.

Since: 0.2.0.0

Constructors

ZF 

Fields

zfNum :: Num a => ZeroFunc a Source #

If a type has a Num instance, this is the canonical ZeroFunc.

Since: 0.2.0.0

zfNums :: (RecApplicative as, AllConstrained Num as) => Rec ZeroFunc as Source #

ZeroFuncs for every item in a type level list based on their Num instances

Since: 0.2.0.0

zeroFunc :: Backprop a => ZeroFunc a Source #

The canonical ZeroFunc for instances of Backprop.

Since: 0.2.0.0

zeroFuncs :: (RecApplicative as, AllConstrained Backprop as) => Rec ZeroFunc as Source #

Generate an ZeroFunc for every type in a type-level list, if every type has an instance of Backprop.

Since: 0.2.0.0

zfFunctor :: (Backprop a, Functor f) => ZeroFunc (f a) Source #

zeroFunc for instances of Functor

Since: 0.2.1.0

newtype AddFunc a Source #

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

See laws for Backprop for the laws this should be expected to preserve. Namely, it should be commutative and associative, with an identity for a valid ZeroFunc.

Each type should ideally only have one AddFunc. This coherence constraint is given by the typeclass Backprop.

Since: 0.2.0.0

Constructors

AF 

Fields

afNum :: Num a => AddFunc a Source #

If a type has a Num instance, this is the canonical AddFunc.

Since: 0.2.0.0

afNums :: (RecApplicative as, AllConstrained Num as) => Rec AddFunc as Source #

ZeroFuncs for every item in a type level list based on their Num instances

Since: 0.2.0.0

addFunc :: Backprop a => AddFunc a Source #

The canonical AddFunc for instances of Backprop.

Since: 0.2.0.0

addFuncs :: (RecApplicative as, AllConstrained Backprop as) => Rec AddFunc as Source #

Generate an AddFunc for every type in a type-level list, if every type has an instance of Backprop.

Since: 0.2.0.0

newtype OneFunc 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: Applying the function twice is the same as applying it just once.

Each type should ideally only have one OneFunc. This coherence constraint is given by the typeclass Backprop.

Since: 0.2.0.0

Constructors

OF 

Fields

ofNum :: Num a => OneFunc a Source #

If a type has a Num instance, this is the canonical OneFunc.

Since: 0.2.0.0

ofNums :: (RecApplicative as, AllConstrained Num as) => Rec OneFunc as Source #

ZeroFuncs for every item in a type level list based on their Num instances

Since: 0.2.0.0

oneFunc :: Backprop a => OneFunc a Source #

The canonical OneFunc for instances of Backprop.

Since: 0.2.0.0

oneFuncs :: (RecApplicative as, AllConstrained Backprop as) => Rec OneFunc as Source #

Generate an OneFunc for every type in a type-level list, if every type has an instance of Backprop.

Since: 0.2.0.0

ofFunctor :: (Backprop a, Functor f) => OneFunc (f a) Source #

OneFunc for instances of Functor

Since: 0.2.1.0

Running

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

backprop, but with explicit zero and one.

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 :: ZeroFunc a -> OneFunc b -> (forall s. Reifies s W => BVar s a -> BVar s b) -> a -> a Source #

gradBP, but with explicit zero and one.

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

backpropWith, but with explicit zero.

Note that argument order changed in v0.2.4.

Multiple inputs

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

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

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

backprop2, but with explicit zero and one.

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 :: ZeroFunc a -> ZeroFunc b -> OneFunc c -> (forall s. Reifies s W => BVar s a -> BVar s b -> BVar s c) -> a -> b -> (a, b) Source #

gradBP2 with explicit zero and one.

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

backpropWith2, but with explicit zero.

Note that argument order changed in v0.2.4.

Since: 0.2.0.0

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

backpropN, but with explicit zero and one.

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 :: Rec ZeroFunc as -> OneFunc b -> (forall s. Reifies s W => Rec (BVar s) as -> BVar s b) -> Rec Identity as -> Rec Identity as Source #

gradBP, Nbut with explicit zero and one.

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

backpropWithN, but with explicit zero and one.

Note that argument order changed in v0.2.4.

Since: 0.2.0.0

class RecApplicative u (rs :: [u]) #

Given a section of some functor, records in that functor of any size are inhabited.

Minimal complete definition

rpure

Instances

RecApplicative u ([] u) 

Methods

rpure :: (forall (x :: [u]). f x) -> Rec [u] f rs #

RecApplicative u rs => RecApplicative u ((:) u r rs) 

Methods

rpure :: (forall (x :: (u ': r) rs). f x) -> Rec ((u ': r) rs) f rs #

type family AllConstrained k (c :: k -> Constraint) (ts :: [k]) :: Constraint where ... #

Constraint that all types in a type-level list satisfy a constraint.

Equations

AllConstrained k c ([] k) = () 
AllConstrained k c ((:) k t ts) = (c t, AllConstrained k c ts) 

Manipulating BVar

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: 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: 0.1.5.2

viewVar :: forall a b s. Reifies s W => AddFunc a -> ZeroFunc b -> Lens' b a -> BVar s b -> BVar s a Source #

viewVar, but with explicit add and zero.

setVar :: forall a b s. Reifies s W => AddFunc a -> AddFunc b -> ZeroFunc a -> Lens' b a -> BVar s a -> BVar s b -> BVar s b Source #

setVar, but with explicit add and zero.

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

overVar with explicit add and zero.

Since: 0.2.4.0

sequenceVar :: forall t a s. (Reifies s W, Traversable t) => AddFunc a -> ZeroFunc a -> BVar s (t a) -> t (BVar s a) Source #

sequenceVar, but with explicit add and zero.

collectVar :: forall t a s. (Reifies s W, Foldable t, Functor t) => AddFunc a -> ZeroFunc a -> t (BVar s a) -> BVar s (t a) Source #

collectVar, but with explicit add and zero.

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

previewVar, but with explicit add and zero.

toListOfVar :: forall b a s. Reifies s W => AddFunc a -> ZeroFunc b -> Traversal' b a -> BVar s b -> [BVar s a] Source #

toListOfVar, but with explicit add and zero.

With Isomorphisms

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

isoVar with explicit add and zero.

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

isoVar2 with explicit add and zero.

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

isoVar3 with explicit add and zero.

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

isoVarN with explicit add and zero.

With Ops

liftOp :: forall as b s. Reifies s W => Rec AddFunc as -> Op as b -> Rec (BVar s) as -> BVar s b Source #

liftOp, but with explicit add and zero.

liftOp1 :: forall a b s. Reifies s W => AddFunc a -> Op '[a] b -> BVar s a -> BVar s b Source #

liftOp1, but with explicit add and zero.

liftOp2 :: forall a b c s. Reifies s W => AddFunc a -> AddFunc b -> Op '[a, b] c -> BVar s a -> BVar s b -> BVar s c Source #

liftOp2, but with explicit add and zero.

liftOp3 :: forall a b c d s. Reifies s W => AddFunc a -> AddFunc b -> AddFunc c -> Op '[a, b, c] d -> BVar s a -> BVar s b -> BVar s c -> BVar s d Source #

liftOp3, but with explicit add and zero.

Generics

splitBV Source #

Arguments

:: (Generic (z f), Generic (z (BVar s)), BVGroup s as (Rep (z f)) (Rep (z (BVar s))), Reifies s W) 
=> AddFunc (Rep (z f) ()) 
-> Rec AddFunc as 
-> ZeroFunc (z f) 
-> Rec ZeroFunc as 
-> BVar s (z f)

BVar of value

-> z (BVar s)

BVars of fields

splitBV with explicit add and zero.

Since: 0.2.2.0

joinBV Source #

Arguments

:: (Generic (z f), Generic (z (BVar s)), BVGroup s as (Rep (z f)) (Rep (z (BVar s))), Reifies s W) 
=> AddFunc (z f) 
-> Rec AddFunc as 
-> ZeroFunc (Rep (z f) ()) 
-> Rec ZeroFunc as 
-> z (BVar s)

BVars of fields

-> BVar s (z f)

BVar of combined value

joinBV with explicit add and zero.

Since: 0.2.2.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: 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 # 

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 # 

Methods

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

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

BVGroup s ([] *) (V1 *) (V1 *) Source # 

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 # 

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 Type 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

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 Type 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 # 

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

(RecApplicative * as, AllConstrained * Floating as, AllConstrained * Fractional as, AllConstrained * Num as, Floating a) => Floating (Op as a) Source # 

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 #

(RecApplicative * as, AllConstrained * Num as, Fractional a) => Fractional (Op as a) Source # 

Methods

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

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

fromRational :: Rational -> Op as a #

(RecApplicative * as, AllConstrained * Num as, Num a) => Num (Op as a) Source # 

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. (AllConstrained Num as, RecApplicative 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 :: Rec ZeroFunc as -> (forall s. Reifies s W => Rec (BVar s) as -> BVar s b) -> Op as b Source #

bpOp with explicit zero.

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: 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: 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: 0.1.3.0

Utility

data Rec u (a :: u -> *) (b :: [u]) :: forall u. (u -> *) -> [u] -> * where #

A record is parameterized by a universe u, an interpretation f and a list of rows rs. The labels or indices of the record are given by inhabitants of the kind u; the type of values at any label r :: u is given by its interpretation f r :: *.

Constructors

RNil :: Rec u a ([] u) 
(:&) :: Rec u a ((:) u r rs) infixr 7 

Instances

TestCoercion u f => TestCoercion [u] (Rec u f) 

Methods

testCoercion :: f a -> f b -> Maybe (Coercion (Rec u f) a b) #

TestEquality u f => TestEquality [u] (Rec u f) 

Methods

testEquality :: f a -> f b -> Maybe ((Rec u f :~: a) b) #

Eq (Rec u f ([] u)) 

Methods

(==) :: Rec u f [u] -> Rec u f [u] -> Bool #

(/=) :: Rec u f [u] -> Rec u f [u] -> Bool #

(Eq (f r), Eq (Rec a f rs)) => Eq (Rec a f ((:) a r rs)) 

Methods

(==) :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Bool #

(/=) :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Bool #

Ord (Rec u f ([] u)) 

Methods

compare :: Rec u f [u] -> Rec u f [u] -> Ordering #

(<) :: Rec u f [u] -> Rec u f [u] -> Bool #

(<=) :: Rec u f [u] -> Rec u f [u] -> Bool #

(>) :: Rec u f [u] -> Rec u f [u] -> Bool #

(>=) :: Rec u f [u] -> Rec u f [u] -> Bool #

max :: Rec u f [u] -> Rec u f [u] -> Rec u f [u] #

min :: Rec u f [u] -> Rec u f [u] -> Rec u f [u] #

(Ord (f r), Ord (Rec a f rs)) => Ord (Rec a f ((:) a r rs)) 

Methods

compare :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Ordering #

(<) :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Bool #

(<=) :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Bool #

(>) :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Bool #

(>=) :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Bool #

max :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) #

min :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) #

RecAll u f rs Show => Show (Rec u f rs)

Records may be shown insofar as their points may be shown. reifyConstraint is used to great effect here.

Methods

showsPrec :: Int -> Rec u f rs -> ShowS #

show :: Rec u f rs -> String #

showList :: [Rec u f rs] -> ShowS #

Semigroup (Rec u f ([] u)) 

Methods

(<>) :: Rec u f [u] -> Rec u f [u] -> Rec u f [u] #

sconcat :: NonEmpty (Rec u f [u]) -> Rec u f [u] #

stimes :: Integral b => b -> Rec u f [u] -> Rec u f [u] #

(Monoid (f r), Monoid (Rec a f rs)) => Semigroup (Rec a f ((:) a r rs)) 

Methods

(<>) :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) #

sconcat :: NonEmpty (Rec a f ((a ': r) rs)) -> Rec a f ((a ': r) rs) #

stimes :: Integral b => b -> Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) #

Monoid (Rec u f ([] u)) 

Methods

mempty :: Rec u f [u] #

mappend :: Rec u f [u] -> Rec u f [u] -> Rec u f [u] #

mconcat :: [Rec u f [u]] -> Rec u f [u] #

(Monoid (f r), Monoid (Rec a f rs)) => Monoid (Rec a f ((:) a r rs)) 

Methods

mempty :: Rec a f ((a ': r) rs) #

mappend :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) #

mconcat :: [Rec a f ((a ': r) rs)] -> Rec a f ((a ': r) rs) #

Storable (Rec u f ([] u)) 

Methods

sizeOf :: Rec u f [u] -> Int #

alignment :: Rec u f [u] -> Int #

peekElemOff :: Ptr (Rec u f [u]) -> Int -> IO (Rec u f [u]) #

pokeElemOff :: Ptr (Rec u f [u]) -> Int -> Rec u f [u] -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rec u f [u]) #

pokeByteOff :: Ptr b -> Int -> Rec u f [u] -> IO () #

peek :: Ptr (Rec u f [u]) -> IO (Rec u f [u]) #

poke :: Ptr (Rec u f [u]) -> Rec u f [u] -> IO () #

(Storable (f r), Storable (Rec a f rs)) => Storable (Rec a f ((:) a r rs)) 

Methods

sizeOf :: Rec a f ((a ': r) rs) -> Int #

alignment :: Rec a f ((a ': r) rs) -> Int #

peekElemOff :: Ptr (Rec a f ((a ': r) rs)) -> Int -> IO (Rec a f ((a ': r) rs)) #

pokeElemOff :: Ptr (Rec a f ((a ': r) rs)) -> Int -> Rec a f ((a ': r) rs) -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rec a f ((a ': r) rs)) #

pokeByteOff :: Ptr b -> Int -> Rec a f ((a ': r) rs) -> IO () #

peek :: Ptr (Rec a f ((a ': r) rs)) -> IO (Rec a f ((a ': r) rs)) #

poke :: Ptr (Rec a f ((a ': r) rs)) -> Rec a f ((a ': r) rs) -> IO () #

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

Minimal complete definition

reflect

Instances

KnownNat n => Reifies Nat n Integer 

Methods

reflect :: proxy Integer -> a #

KnownSymbol n => Reifies Symbol n String 

Methods

reflect :: proxy String -> a #

Reifies * Z Int 

Methods

reflect :: proxy Int -> a #

Reifies * n Int => Reifies * (D n) Int 

Methods

reflect :: proxy Int -> a #

Reifies * n Int => Reifies * (SD n) Int 

Methods

reflect :: proxy Int -> a #

Reifies * n Int => Reifies * (PD n) Int 

Methods

reflect :: proxy Int -> a #

(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 

Methods

reflect :: proxy a -> a #