backprop-0.1.5.2: Heterogeneous automatic differentation (backpropagation)

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.

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.

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

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.

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.

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

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

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.

Running

backprop :: forall a b. (Num a, Num 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.

Note that every type involved has to be an instance of Num. This is because gradients all need to be "summable" (which is implemented using sum and +), and we also need to able to generate gradients of 1 and 0. Really, only + and fromInteger methods are used from the Num typeclass.

This might change in the future, to allow easier integration with tuples (which typically do not have a Num instance), and potentially make types easier to use (by only requiring +, 0, and 1, and not the rest of the Num class).

See the README for a more detailed discussion on this issue.

If you need a Num instance for tuples, you can use the canonical 2- and 3-tuples for the library in Numeric.Backprop.Tuple. If you need one for larger tuples, consider making a custom product type instead (making Num instances with something like one-liner-instances). You can also use the orphan instances in the NumInstances package (in particular, Data.NumInstances.Tuple) if you are writing an application and do not have to worry about orphan instances.

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.

Has a nice advantage over using backprop in that it doesn't require Num constraints on the input and output.

See documentation of backprop for more information.

gradBP :: forall a b. (Num a, Num 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.

Multiple inputs

backprop2 :: forall a b c. (Num a, Num b, Num 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 use T2. 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 :: (Num a, Num b, Num 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.

backpropN :: forall as b. (Every Num as, Num b) => (forall s. Reifies s W => Prod (BVar s) as -> BVar s b) -> Tuple as -> (b, Tuple 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 tuple from Numeric.Backprop.Tuple. You could also pass in a giant tuple with NumInstances. However, this can be convenient if you don't want to make a custom larger tuple type or pull in orphan instances. This could potentially also be more performant.

A Prod (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).

Tuples can be built and pattern matched on using ::< (cons) and 'Ø' (nil), as well.

The Every Num as in the constraint says that every value in the type-level list as must have a Num 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 Every Num as should be fulfilled automatically.

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

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

gradBPN :: forall as b. (Every Num as, Num b) => (forall s. Reifies s W => Prod (BVar s) as -> BVar s b) -> Tuple as -> Tuple as Source #

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

class EveryC k c as => Every k (c :: k -> Constraint) (as :: [k]) #

Minimal complete definition

every

Instances

Every k c (Ø k) 

Associated Types

type EveryC c (Ø k :: c -> Constraint) (as :: [c]) :: Constraint #

Methods

every :: Index c as a -> Wit (Ø k a) #

(c a2, Every a1 c as) => Every a1 c ((:<) a1 a2 as) 

Associated Types

type EveryC c ((a1 :< a2) as :: c -> Constraint) (as :: [c]) :: Constraint #

Methods

every :: Index c as a -> Wit ((a1 :< a2) as a) #

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.

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

(^^.) :: forall a b s. (Reifies s W, Num a) => 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.

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

(.~~) :: forall a b s. (Reifies s W, Num a, Num b) => 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: 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.

(^^?) :: forall b a s. (Num a, Reifies s W) => BVar s b -> Traversal' b a -> Maybe (BVar s a) 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 that many automatically-generated prisms by the lens package use tuples, which cannot normally be backpropagated (because they do not have a Num instance).

If you are writing an application or don't have to worry about orphan instances, you can pull in the orphan instances from NumInstances. Alternatively, you can chain those prisms with conversions to the anonymous canonical strict tuple types in Numeric.Backprop.Tuple, which do have Num instances.

myPrism                   :: Prism' c (a, b)
myPrism . iso tupT2 t2Tup :: Prism' c (T2 a b)

(^^..) :: forall b a s. (Num 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).

viewVar :: forall a b s. (Reifies s W, Num a) => 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.

setVar :: forall a b s. (Reifies s W, Num a, Num b) => 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.

sequenceVar :: forall t a s. (Reifies s W, Traversable t, Num a) => 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.

collectVar :: forall t a s. (Reifies s W, Foldable t, Functor t, Num (t a), Num a) => 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 requires t a to have a Num instance. If you are using a list, I recommend using vector-sized instead: it's a fixed-length vector type with a very appropriate Num instance!

previewVar :: forall b a s. (Num 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.

toListOfVar :: forall b a s. (Num 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.

With Isomorphisms

isoVar :: (Num a, Num b, 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.

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

isoVar2 :: (Num a, Num b, Num c, 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.

Since: 0.1.4.0

isoVar3 :: (Num a, Num b, Num c, Num d, 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: 0.1.4.0

isoVarN :: (Every Num as, Num b, Reifies s W) => (Tuple as -> b) -> (b -> Tuple as) -> Prod (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.

Since: 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 :: forall as b s. (Reifies s W, Num b, Every Num as) => Op as b -> Prod (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 Prod and Tuple.

liftOp1 :: forall a b s. (Reifies s W, Num a, Num b) => 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 :: forall a b c s. (Reifies s W, Num a, Num b, Num c) => 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 :: forall a b c d s. (Reifies s W, Num a, Num b, Num c, Num d) => 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.

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 Prod and Tuple.

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

  • runOpWith :: Tuple as -> (a, a -> Tuple as)

    Run the function that the Op encodes, returning a continuation to compute the gradient, given the total derivative of a. See documentation for Numeric.Backprop.Op for more information.

Instances

(Known [*] (Length *) as, Every * Floating as, Every * Fractional as, Every * 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 #

(Known [*] (Length *) as, Every * Fractional as, Every * 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 #

(Known [*] (Length *) as, Every * 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) Ø
(10, Ø)

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

opConst :: (Every Num as, Known Length 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 ::< Ø)
(10, 0 ::< 0 ::< 0 ::< Ø)

idOp :: Op '[a] a Source #

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

idOp = opIso id id

opConst' :: Every Num as => Length as -> a -> Op as a Source #

A version of opConst taking explicit Length, indicating the number of inputs and their types.

Requiring an explicit Length is mostly useful for rare "extremely polymorphic" situations, where GHC can't infer the type and length of the the expected input tuple. If you ever actually explicitly write down as as a list of types, you should be able to just use opConst.

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 (Tuple as) Source #

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

>>> gradOp' opTup (1 ::< 2 ::< 3 ::< Ø)
(1 ::< 2 ::< 3 ::< Ø, 1 ::< 1 ::< 1 ::< Ø)

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 :: (Tuple as -> b) -> (b -> Tuple 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 :: (Tuple 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

Inductive tuples/heterogeneous lists

data Prod k (f :: k -> *) (a :: [k]) :: forall k. (k -> *) -> [k] -> * where #

Constructors

Ø :: Prod k f ([] k) 
(:<) :: Prod k f ((:) k a1 as) infixr 5 

Instances

Witness ØC ØC (Prod k f (Ø k)) 

Associated Types

type WitnessC ØC ØC (Prod k f (Ø k)) :: Constraint #

Methods

(\\) :: ØC => (ØC -> r) -> Prod k f (Ø k) -> r #

Functor1 k [k] (Prod k) 

Methods

map1 :: (forall (a :: Prod k). f a -> g a) -> t f b -> t g b #

Foldable1 k [k] (Prod k) 

Methods

foldMap1 :: Monoid m => (forall (a :: Prod k). f a -> m) -> t f b -> m #

Traversable1 k [k] (Prod k) 

Methods

traverse1 :: Applicative h => (forall (a :: Prod k). f a -> h (g a)) -> t f b -> h (t g b) #

IxFunctor1 k [k] (Index k) (Prod k) 

Methods

imap1 :: (forall (a :: Index k). i b a -> f a -> g a) -> t f b -> t g b #

IxFoldable1 k [k] (Index k) (Prod k) 

Methods

ifoldMap1 :: Monoid m => (forall (a :: Index k). i b a -> f a -> m) -> t f b -> m #

IxTraversable1 k [k] (Index k) (Prod k) 

Methods

itraverse1 :: Applicative h => (forall (a :: Index k). i b a -> f a -> h (g a)) -> t f b -> h (t g b) #

TestEquality k f => TestEquality [k] (Prod k f) 

Methods

testEquality :: f a -> f b -> Maybe ((Prod k f :~: a) b) #

BoolEquality k f => BoolEquality [k] (Prod k f) 

Methods

boolEquality :: f a -> f b -> Boolean ((Prod k f == a) b) #

Eq1 k f => Eq1 [k] (Prod k f) 

Methods

eq1 :: f a -> f a -> Bool #

neq1 :: f a -> f a -> Bool #

Ord1 k f => Ord1 [k] (Prod k f) 

Methods

compare1 :: f a -> f a -> Ordering #

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

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

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

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

Show1 k f => Show1 [k] (Prod k f) 

Methods

showsPrec1 :: Int -> f a -> ShowS #

show1 :: f a -> String #

Read1 k f => Read1 [k] (Prod k f) 

Methods

readsPrec1 :: Int -> ReadS (Some (Prod k f) f) #

(Known [k] (Length k) as, Every k (Known k f) as) => Known [k] (Prod k f) as 

Associated Types

type KnownC (Prod k f) (as :: Prod k f -> *) (a :: Prod k f) :: Constraint #

Methods

known :: as a #

(Witness p q (f a2), Witness s t (Prod a1 f as)) => Witness (p, s) (q, t) (Prod a1 f ((:<) a1 a2 as)) 

Associated Types

type WitnessC (p, s) (q, t) (Prod a1 f ((a1 :< a2) as)) :: Constraint #

Methods

(\\) :: (p, s) => ((q, t) -> r) -> Prod a1 f ((a1 :< a2) as) -> r #

ListC ((<$>) * Constraint Eq ((<$>) k * f as)) => Eq (Prod k f as) 

Methods

(==) :: Prod k f as -> Prod k f as -> Bool #

(/=) :: Prod k f as -> Prod k f as -> Bool #

(ListC ((<$>) * Constraint Eq ((<$>) k * f as)), ListC ((<$>) * Constraint Ord ((<$>) k * f as))) => Ord (Prod k f as) 

Methods

compare :: Prod k f as -> Prod k f as -> Ordering #

(<) :: Prod k f as -> Prod k f as -> Bool #

(<=) :: Prod k f as -> Prod k f as -> Bool #

(>) :: Prod k f as -> Prod k f as -> Bool #

(>=) :: Prod k f as -> Prod k f as -> Bool #

max :: Prod k f as -> Prod k f as -> Prod k f as #

min :: Prod k f as -> Prod k f as -> Prod k f as #

ListC ((<$>) * Constraint Show ((<$>) k * f as)) => Show (Prod k f as) 

Methods

showsPrec :: Int -> Prod k f as -> ShowS #

show :: Prod k f as -> String #

showList :: [Prod k f as] -> ShowS #

type WitnessC ØC ØC (Prod k f (Ø k)) 
type WitnessC ØC ØC (Prod k f (Ø k)) = ØC
type KnownC [k] (Prod k f) as 
type KnownC [k] (Prod k f) as = (Known [k] (Length k) as, Every k (Known k f) as)
type WitnessC (p, s) (q, t) (Prod a1 f ((:<) a1 a2 as)) 
type WitnessC (p, s) (q, t) (Prod a1 f ((:<) a1 a2 as)) = (Witness p q (f a2), Witness s t (Prod a1 f as))

pattern (:>) :: forall k (f :: k -> *) (a :: k) (b :: k). f a -> f b -> Prod k f ((:) k a ((:) k b ([] k))) infix 6 #

Construct a two element Prod. Since the precedence of (:>) is higher than (:<), we can conveniently write lists like:

>>> a :< b :> c

Which is identical to:

>>> a :< b :< c :< Ø

only :: f a -> Prod k f ((:) k a ([] k)) #

Build a singleton Prod.

head' :: Prod k f ((:<) k a as) -> f a #

type Tuple = Prod * I #

A Prod of simple Haskell types.

pattern (::<) :: forall a (as :: [*]). a -> Tuple as -> Tuple ((:<) * a as) infixr 5 #

Cons onto a Tuple.

only_ :: a -> Tuple ((:) * a ([] *)) #

Singleton Tuple.

newtype I a :: * -> * #

Constructors

I 

Fields

Instances

Monad I 

Methods

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

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

return :: a -> I a #

fail :: String -> I a #

Functor I 

Methods

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

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

Applicative I 

Methods

pure :: a -> I a #

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

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

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

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

Foldable I 

Methods

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

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

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

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

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

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

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

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

toList :: I a -> [a] #

null :: I a -> Bool #

length :: I a -> Int #

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

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

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

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

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

Traversable I 

Methods

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

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

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

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

Witness p q a => Witness p q (I a) 

Associated Types

type WitnessC p q (I a) :: Constraint #

Methods

(\\) :: p => (q -> r) -> I a -> r #

Eq a => Eq (I a) 

Methods

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

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

Num a => Num (I a) 

Methods

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

(-) :: I a -> I a -> I a #

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

negate :: I a -> I a #

abs :: I a -> I a #

signum :: I a -> I a #

fromInteger :: Integer -> I a #

Ord a => Ord (I a) 

Methods

compare :: I a -> I a -> Ordering #

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

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

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

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

max :: I a -> I a -> I a #

min :: I a -> I a -> I a #

Show a => Show (I a) 

Methods

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

show :: I a -> String #

showList :: [I a] -> ShowS #

type WitnessC p q (I a) 
type WitnessC p q (I a) = Witness p q a

Misc

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 #