Copyright | (c) Justin Le 2023 |
---|---|
License | BSD3 |
Maintainer | justin@jle.im |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Numeric.Backprop.Class
Description
Synopsis
- 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
- zeroVecNum :: (Vector v a, Num a) => v a -> v a
- oneVecNum :: (Vector v a, Num 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
- newtype ABP (f :: Type -> Type) a = ABP {
- runABP :: f a
- newtype NumBP a = NumBP {
- runNumBP :: a
- newtype NumVec (v :: Type -> Type) a = NumVec {
- runNumVec :: v a
- class GZero (f :: Type -> Type)
- class GAdd (f :: Type -> Type)
- class GOne (f :: Type -> Type)
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.
instanceBackprop
Double
wherezero
=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
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
- 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
Minimal complete definition
Nothing
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 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 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
As the library uses it, the most important law is:
That is,
is the gradient of the identity function with respect to its input.one
x
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 Void Source # | |
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 Word8 Source # | Since: 0.2.2.0 |
Backprop Integer Source # | |
Backprop Natural Source # | Since: 0.2.1.0 |
Backprop () Source # |
|
Backprop Double Source # | |
Backprop Float Source # | |
Backprop Int Source # | |
Backprop Word Source # | Since: 0.2.2.0 |
Num a => Backprop (NumBP a) Source # | |
RealFloat a => Backprop (Complex a) Source # | |
Backprop a => Backprop (Identity a) Source # | |
Backprop a => Backprop (First a) Source # | Since: 0.2.2.0 |
Backprop a => Backprop (Last a) Source # | Since: 0.2.2.0 |
Backprop a => Backprop (First a) Source # | Since: 0.2.2.0 |
Backprop a => Backprop (Last a) Source # | Since: 0.2.2.0 |
Backprop a => Backprop (Dual a) Source # | Since: 0.2.2.0 |
Backprop a => Backprop (Product a) Source # | Since: 0.2.2.0 |
Backprop a => Backprop (Sum a) Source # | Since: 0.2.2.0 |
Backprop a => Backprop (NonEmpty a) Source # |
|
Integral a => Backprop (Ratio a) Source # | |
Backprop a => Backprop (IntMap a) Source # |
|
Backprop a => Backprop (Seq a) Source # |
|
Backprop a => Backprop (Vector a) Source # | |
(Prim a, Backprop a) => Backprop (Vector a) Source # | |
(Storable a, Backprop a) => Backprop (Vector a) Source # | |
(Unbox a, Backprop a) => Backprop (Vector a) Source # | |
Backprop (Label field) Source # | Since: 0.2.6.3 |
Backprop t => Backprop (ElField '(s, t)) Source # | Since: 0.2.6.3 |
Backprop a => Backprop (Identity a) Source # | Since: 0.2.6.3 |
Backprop a => Backprop (Thunk a) Source # | Since: 0.2.6.3 |
Backprop a => Backprop (Maybe a) Source # |
|
Backprop a => Backprop [a] Source # |
|
(Applicative f, Backprop a) => Backprop (ABP f a) Source # | |
(Vector v a, Num a) => Backprop (NumVec v a) Source # | |
(Backprop a, Reifies s W) => Backprop (BVar s a) Source # | Since: 0.2.2.0 |
Backprop (Proxy a) Source # | |
(Backprop a, Backprop b) => Backprop (Arg a b) Source # | Since: 0.2.2.0 |
Backprop (U1 p) Source # | Since: 0.2.2.0 |
Backprop (V1 p) Source # | Since: 0.2.2.0 |
(Backprop a, Ord k) => Backprop (Map k a) Source # |
|
Backprop (SField field) Source # | Since: 0.2.6.3 |
(Backprop a, Backprop b) => Backprop (a, b) Source # |
|
Backprop a => Backprop (r -> a) Source # |
Since: 0.2.2.0 |
(Backprop a, Applicative m) => Backprop (Kleisli m r a) Source # | Since: 0.2.2.0 |
Backprop w => Backprop (Const w a) Source # | Since: 0.2.2.0 |
(ReifyConstraint Backprop f rs, RMap rs, RApply rs, RecApplicative rs, NatToInt (RLength rs), RPureConstrained (IndexableField rs) rs, ToARec rs) => Backprop (ARec f rs) Source # | Since: 0.2.6.3 |
(ReifyConstraint Backprop f rs, RMap rs, RApply rs) => Backprop (Rec f rs) Source # | Since: 0.2.6.3 |
Backprop w => Backprop (Const w a) Source # | Since: 0.2.6.3 |
(ReifyConstraint Backprop f rs, RMap rs, RApply rs, Storable (Rec f rs)) => Backprop (SRec f rs) Source # | Since: 0.2.6.3 |
Backprop (HKD t a) => Backprop (XData t a) Source # | Since: 0.2.6.3 |
(ReifyConstraint Backprop f rs, RMap rs, RApply rs, IsoXRec f rs) => Backprop (XRec f rs) Source # | Since: 0.2.6.3 |
(Backprop a, Backprop b, Backprop c) => Backprop (a, b, c) Source # |
|
(Backprop (f a), Backprop (g a)) => Backprop (Product f g a) Source # | Since: 0.2.2.0 |
(Backprop (f p), Backprop (g p)) => Backprop ((f :*: g) p) Source # | Since: 0.2.2.0 |
Backprop a => Backprop (K1 i a p) Source # | Since: 0.2.2.0 |
(Backprop a, Backprop b, Backprop c, Backprop d) => Backprop (a, b, c, d) Source # |
|
Backprop (f (g a)) => Backprop (Compose f g a) Source # | Since: 0.2.2.0 |
Backprop (f (g a)) => Backprop ((f :.: g) a) Source # | Since: 0.2.6.3 |
Backprop (f p) => Backprop (M1 i c f p) Source # | Since: 0.2.2.0 |
Backprop (f (g a)) => Backprop (Compose f g a) Source # | Since: 0.2.6.3 |
(Backprop a, Backprop b, Backprop c, Backprop d, Backprop e) => Backprop (a, b, c, d, e) Source # |
|
Backprop (op (f a) (g a)) => Backprop (Lift op f g a) Source # | Since: 0.2.6.3 |
Derived methods
zeroVecNum :: (Vector v a, Num a) => v a -> v a Source #
Arguments
:: Backprop b | |
=> (a -> [b]) | convert to list (should form isomorphism) |
-> ([b] -> a) | convert from list (should form isomorphism) |
-> a | |
-> a | |
-> a |
add
for types that are isomorphic to a list. Automatically pads the end of the "shorter" value with zeroes.
Newtype
newtype ABP (f :: Type -> Type) a Source #
A newtype wrapper over an f a
for
that gives a free Applicative
fBackprop
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
Instances
Foldable f => Foldable (ABP f) Source # | |||||
Defined in Numeric.Backprop.Class Methods fold :: Monoid m => ABP f m -> m # foldMap :: Monoid m => (a -> m) -> ABP f a -> 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 # elem :: Eq a => a -> ABP f a -> Bool # maximum :: Ord a => ABP f a -> a # minimum :: Ord a => ABP f a -> a # | |||||
Traversable f => Traversable (ABP f) Source # | |||||
Alternative f => Alternative (ABP f) Source # | |||||
Applicative f => Applicative (ABP f) Source # | |||||
Functor f => Functor (ABP f) Source # | |||||
Monad f => Monad (ABP f) Source # | |||||
MonadPlus f => MonadPlus (ABP f) Source # | |||||
(Applicative f, Backprop a) => Backprop (ABP f a) Source # | |||||
(Typeable f, Typeable a, Data (f a)) => Data (ABP f a) Source # | |||||
Defined in Numeric.Backprop.Class Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ABP f a -> c (ABP f a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ABP f a) # toConstr :: ABP f a -> Constr # dataTypeOf :: ABP f a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ABP f a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ABP f a)) # gmapT :: (forall b. Data b => b -> b) -> ABP f a -> ABP f a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ABP f a -> r # gmapQr :: forall r r'. (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, Floating a) => Floating (ABP f a) Source # | |||||
Generic (ABP f a) Source # | |||||
Defined in Numeric.Backprop.Class Associated Types
| |||||
(Applicative f, Num a) => Num (ABP f a) Source # | |||||
Read (f a) => Read (ABP f a) Source # | |||||
(Applicative f, Fractional a) => Fractional (ABP f a) Source # | |||||
Show (f a) => Show (ABP f a) Source # | |||||
NFData (f a) => NFData (ABP f a) Source # | |||||
Defined in Numeric.Backprop.Class | |||||
Eq (f a) => Eq (ABP f a) Source # | |||||
Ord (f a) => Ord (ABP f a) Source # | |||||
Defined in Numeric.Backprop.Class | |||||
type Rep (ABP f a) Source # | |||||
Defined in Numeric.Backprop.Class |
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
Instances
Foldable NumBP Source # | |||||
Defined in Numeric.Backprop.Class Methods fold :: Monoid m => NumBP m -> m # foldMap :: Monoid m => (a -> m) -> NumBP a -> 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 # elem :: Eq a => a -> NumBP a -> Bool # maximum :: Ord a => NumBP a -> a # minimum :: Ord a => NumBP a -> a # | |||||
Traversable NumBP Source # | |||||
Applicative NumBP Source # | |||||
Functor NumBP Source # | |||||
Monad NumBP Source # | |||||
Num a => Backprop (NumBP a) Source # | |||||
Data a => Data (NumBP a) Source # | |||||
Defined in Numeric.Backprop.Class Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NumBP a -> c (NumBP a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NumBP a) # toConstr :: NumBP a -> Constr # dataTypeOf :: NumBP a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NumBP a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NumBP a)) # gmapT :: (forall b. Data b => b -> b) -> NumBP a -> NumBP a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NumBP a -> r # gmapQr :: forall r r'. (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) # | |||||
Floating a => Floating (NumBP a) Source # | |||||
Generic (NumBP a) Source # | |||||
Defined in Numeric.Backprop.Class Associated Types
| |||||
Num a => Num (NumBP a) Source # | |||||
Read a => Read (NumBP a) Source # | |||||
Fractional a => Fractional (NumBP a) Source # | |||||
Show a => Show (NumBP a) Source # | |||||
NFData a => NFData (NumBP a) Source # | |||||
Defined in Numeric.Backprop.Class | |||||
Eq a => Eq (NumBP a) Source # | |||||
Ord a => Ord (NumBP a) Source # | |||||
Defined in Numeric.Backprop.Class | |||||
type Rep (NumBP a) Source # | |||||
Defined in Numeric.Backprop.Class |
newtype NumVec (v :: Type -> Type) a Source #
Newtype wrapper around a v a
for
, that gives a more efficient Vector
v aBackprop
instance for long vectors when a
is an instance of Num
. The normal Backprop
instance for vectors will map zero
or one
over all items; this instance will completely ignore the contents of the original vector and instead produce a new vector of the same length, with all 0
or 1
using the Num
instance of a
(essentially using zeroVecNum
and oneVecNum
instead of zeroVec
and oneVec
).
add
is essentially the same as normal, but using +
instead of the type's add
.
Since: 0.2.4.0
Instances
Foldable v => Foldable (NumVec v) Source # | |||||
Defined in Numeric.Backprop.Class Methods fold :: Monoid m => NumVec v m -> m # foldMap :: Monoid m => (a -> m) -> NumVec v a -> m # foldMap' :: Monoid m => (a -> m) -> NumVec v a -> m # foldr :: (a -> b -> b) -> b -> NumVec v a -> b # foldr' :: (a -> b -> b) -> b -> NumVec v a -> b # foldl :: (b -> a -> b) -> b -> NumVec v a -> b # foldl' :: (b -> a -> b) -> b -> NumVec v a -> b # foldr1 :: (a -> a -> a) -> NumVec v a -> a # foldl1 :: (a -> a -> a) -> NumVec v a -> a # elem :: Eq a => a -> NumVec v a -> Bool # maximum :: Ord a => NumVec v a -> a # minimum :: Ord a => NumVec v a -> a # | |||||
Traversable v => Traversable (NumVec v) Source # | |||||
Alternative v => Alternative (NumVec v) Source # | |||||
Applicative v => Applicative (NumVec v) Source # | |||||
Functor v => Functor (NumVec v) Source # | |||||
Monad v => Monad (NumVec v) Source # | |||||
MonadPlus v => MonadPlus (NumVec v) Source # | |||||
(Vector v a, Num a) => Backprop (NumVec v a) Source # | |||||
(Typeable v, Typeable a, Data (v a)) => Data (NumVec v a) Source # | |||||
Defined in Numeric.Backprop.Class Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NumVec v a -> c (NumVec v a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NumVec v a) # toConstr :: NumVec v a -> Constr # dataTypeOf :: NumVec v a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NumVec v a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NumVec v a)) # gmapT :: (forall b. Data b => b -> b) -> NumVec v a -> NumVec v a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NumVec v a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NumVec v a -> r # gmapQ :: (forall d. Data d => d -> u) -> NumVec v a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NumVec v a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NumVec v a -> m (NumVec v a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NumVec v a -> m (NumVec v a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NumVec v a -> m (NumVec v a) # | |||||
Generic (NumVec v a) Source # | |||||
Defined in Numeric.Backprop.Class Associated Types
| |||||
Read (v a) => Read (NumVec v a) Source # | |||||
Show (v a) => Show (NumVec v a) Source # | |||||
NFData (v a) => NFData (NumVec v a) Source # | |||||
Defined in Numeric.Backprop.Class | |||||
Eq (v a) => Eq (NumVec v a) Source # | |||||
Ord (v a) => Ord (NumVec v a) Source # | |||||
Defined in Numeric.Backprop.Class | |||||
type Rep (NumVec v a) Source # | |||||
Defined in Numeric.Backprop.Class |
Generics
class GZero (f :: Type -> Type) Source #
Helper class for automatically deriving zero
using GHC Generics.
Minimal complete definition
gzero
Instances
GZero (U1 :: Type -> Type) Source # | |
Defined in Numeric.Backprop.Class | |
GZero (V1 :: Type -> Type) Source # | |
Defined in Numeric.Backprop.Class | |
(GZero f, GZero g) => GZero (f :*: g) Source # | |
Defined in Numeric.Backprop.Class | |
(GZero f, GZero g) => GZero (f :+: g) Source # | |
Defined in Numeric.Backprop.Class | |
Backprop a => GZero (K1 i a :: Type -> Type) Source # | |
Defined in Numeric.Backprop.Class | |
GZero f => GZero (f :.: g) Source # | |
Defined in Numeric.Backprop.Class | |
GZero f => GZero (M1 i c f) Source # | |
Defined in Numeric.Backprop.Class |
class GAdd (f :: Type -> Type) Source #
Helper class for automatically deriving add
using GHC Generics.
Minimal complete definition
gadd
Instances
GAdd (U1 :: Type -> Type) Source # | |
Defined in Numeric.Backprop.Class | |
GAdd (V1 :: Type -> Type) Source # | |
Defined in Numeric.Backprop.Class | |
(GAdd f, GAdd g) => GAdd (f :*: g) Source # | |
Defined in Numeric.Backprop.Class | |
Backprop a => GAdd (K1 i a :: Type -> Type) Source # | |
Defined in Numeric.Backprop.Class | |
GAdd f => GAdd (f :.: g) Source # | |
Defined in Numeric.Backprop.Class | |
GAdd f => GAdd (M1 i c f) Source # | |
Defined in Numeric.Backprop.Class |
class GOne (f :: Type -> Type) Source #
Helper class for automatically deriving one
using GHC Generics.
Minimal complete definition
gone
Instances
GOne (U1 :: Type -> Type) Source # | |
Defined in Numeric.Backprop.Class | |
GOne (V1 :: Type -> Type) Source # | |
Defined in Numeric.Backprop.Class | |
(GOne f, GOne g) => GOne (f :*: g) Source # | |
Defined in Numeric.Backprop.Class | |
(GOne f, GOne g) => GOne (f :+: g) Source # | |
Defined in Numeric.Backprop.Class | |
Backprop a => GOne (K1 i a :: Type -> Type) Source # | |
Defined in Numeric.Backprop.Class | |
GOne f => GOne (f :.: g) Source # | |
Defined in Numeric.Backprop.Class | |
GOne f => GOne (M1 i c f) Source # | |
Defined in Numeric.Backprop.Class |