| Copyright | (c) Justin Le 2018 |
|---|---|
| License | BSD3 |
| Maintainer | justin@jle.im |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Numeric.Backprop.Class
Description
- class Backprop a where
- zeroNum :: Num a => a -> a
- addNum :: Num a => a -> a -> a
- oneNum :: Num a => a -> a
- zeroVec :: (Vector v a, Backprop a) => v a -> v a
- addVec :: (Vector v a, Backprop a) => v a -> v a -> v a
- oneVec :: (Vector v a, Backprop a) => v a -> v a
- zeroFunctor :: (Functor f, Backprop a) => f a -> f a
- addIsList :: (IsList a, Backprop (Item a)) => a -> a -> a
- addAsList :: Backprop b => (a -> [b]) -> ([b] -> a) -> a -> a -> a
- oneFunctor :: (Functor f, Backprop a) => f a -> f a
- genericZero :: (Generic a, GZero (Rep a)) => a -> a
- genericAdd :: (Generic a, GAdd (Rep a)) => a -> a -> a
- genericOne :: (Generic a, GOne (Rep a)) => a -> a
- class GZero f where
- class GAdd f where
- class GOne f where
Backpropagatable types
class Backprop a where Source #
Class of values that can be backpropagated in general.
For instances of Num, these methods can be given by zeroNum,
addNum, and oneNum. There are also generic options given in
Numeric.Backprop.Class for functors, IsList instances, and Generic
instances.
instanceBackpropDoublewherezero=zeroNumadd=addNumone=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 an
illegal implementation for lists and vectors.zipWith (+)
This is only expected to be true up to potential "extra zeroes" in x
and y in the result.
- commutativity
- associativity
- idempotence
Note that not all values in the backpropagation process needs all of
these methods: Only the "final result" needs one, for example. These
are all grouped under one typeclass for convenience in defining
instances, and also to talk about sensible laws. For fine-grained
control, use the "explicit" versions of library functions (for example,
in Numeric.Backprop.Explicit) instead of Backprop based ones.
This typeclass replaces the reliance on Num of the previous API
(v0.1). Num is strictly more powerful than Backprop, and is
a stronger constraint on types than is necessary for proper
backpropagating. In particular, fromInteger is a problem for many
types, preventing useful backpropagation for lists, variable-length
vectors (like Data.Vector) and variable-size matrices from linear
algebra libraries like hmatrix and accelerate.
Since: 0.2.0.0
Methods
"Zero out" all components of a value. For scalar values, this
should just be . For vectors and matrices, this should
set all components to zero, the additive identity.const 0
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 together two values of a type. To combine contributions of gradients, so should be information-preserving:
Should be as strict as possible. This behavior is observed for all instances provided by this library.
See addNum for a pre-built definition for instances of Num and
addFunctor for a definition for instances of Functor. If left
blank, will automatically be genericAdd, a pre-built definition
for instances of Generic with one constructor whose fields are
all themselves instances of Backprop.
One all components of a value. For scalar values, this should
just be . For vectors and matrices, this should set all
components to one, the multiplicative identity.const 1
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 . For vectors and matrices, this should
set all components to zero, the additive identity.const 0
Should be idempotent:
Should be as lazy as possible. This behavior is observed for all instances provided by this library.
See zeroNum for a pre-built definition for instances of Num and
zeroFunctor for a definition for instances of Functor. If left
blank, will automatically be genericZero, a pre-built definition
for instances of Generic whose fields are all themselves
instances of Backprop.
add :: (Generic a, GAdd (Rep a)) => a -> a -> a Source #
Add together two values of a type. To combine contributions of gradients, so should be information-preserving:
Should be as strict as possible. This behavior is observed for all instances provided by this library.
See addNum for a pre-built definition for instances of Num and
addFunctor for a definition for instances of Functor. If left
blank, will automatically be genericAdd, a pre-built definition
for instances of Generic with one constructor whose fields are
all themselves instances of Backprop.
one :: (Generic a, GOne (Rep a)) => a -> a Source #
One all components of a value. For scalar values, this should
just be . For vectors and matrices, this should set all
components to one, the multiplicative identity.const 1
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 # | |
| Backprop Integer Source # | |
| Backprop () Source # |
|
| Backprop Void Source # | |
| Backprop a => Backprop [a] Source # |
|
| Backprop a => Backprop (Maybe a) Source # |
|
| Integral a => Backprop (Ratio a) Source # | |
| RealFloat a => Backprop (Complex a) Source # | |
| Backprop a => Backprop (NonEmpty a) Source # |
|
| Backprop a => Backprop (Identity a) Source # | |
| Backprop a => Backprop (IntMap a) Source # |
|
| Backprop a => Backprop (Seq a) Source # |
|
| Backprop a => Backprop (I a) Source # | |
| (Unbox a, Backprop a) => Backprop (Vector a) Source # | |
| (Storable a, Backprop a) => Backprop (Vector a) Source # | |
| (Prim a, Backprop a) => Backprop (Vector a) Source # | |
| Backprop a => Backprop (Vector a) Source # | |
| (Backprop a, Backprop b) => Backprop (a, b) Source # |
|
| Backprop (Proxy * a) Source # |
|
| (Backprop a, Ord k) => Backprop (Map k a) Source # |
|
| (Backprop a, Backprop b, Backprop c) => Backprop (a, b, c) Source # |
|
| ListC ((<$>) * Constraint Backprop ((<$>) * * f as)) => Backprop (Prod * f as) Source # | |
| MaybeC ((<$>) * Constraint Backprop ((<$>) * * f a)) => Backprop (Option * f a) Source # | |
| (Backprop a, Backprop b, Backprop c, Backprop d) => Backprop (a, b, c, d) Source # |
|
| (Backprop a, Backprop b, Backprop c, Backprop d, Backprop e) => Backprop (a, b, c, d, e) Source # |
|
Derived methods
Arguments
| :: Backprop b | |
| => (a -> [b]) | convert to list (should form isomorphism) |
| -> ([b] -> a) | convert from list (should form isomorphism) |
| -> a | |
| -> a | |
| -> a |
add for types that are isomorphic to a list.
Automatically pads the end of the "shorter" value with zeroes.
Generics
Helper class for automatically deriving zero using GHC Generics.
Minimal complete definition
Helper class for automatically deriving add using GHC Generics.
Minimal complete definition
Helper class for automatically deriving one using GHC Generics.
Minimal complete definition