backprop-0.2.1.0: Heterogeneous automatic differentation (backpropagation)

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 Backprop or 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.

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.

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.

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

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

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 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 const 1. For vectors and matrices, this should set all components to one, the multiplicative identity.

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

Backprop a => Backprop (I a) Source # 

Methods

zero :: I a -> I a Source #

add :: I a -> I a -> I a Source #

one :: I a -> I 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 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 (Proxy * a) Source #

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

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 #

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

ListC ((<$>) * Constraint Backprop ((<$>) * * f as)) => Backprop (Prod * f as) Source # 

Methods

zero :: Prod * f as -> Prod * f as Source #

add :: Prod * f as -> Prod * f as -> Prod * f as Source #

one :: Prod * f as -> Prod * f as Source #

MaybeC ((<$>) * Constraint Backprop ((<$>) * * f a)) => Backprop (Option * f a) Source # 

Methods

zero :: Option * f a -> Option * f a Source #

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

one :: Option * f a -> Option * f a 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 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 #

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

Methods

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

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

return :: a -> ABP m a #

fail :: String -> ABP m 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) #

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.1.0-3cxmKcBToiX2y9THONyvPW" 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.1.0-3cxmKcBToiX2y9THONyvPW" 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 :: (Every Num as, Known Length as) => Prod 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 :: (Every Backprop as, Known Length as) => Prod 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 :: (Every Num as, Known Length as) => Prod 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 :: (Every Backprop as, Known Length as) => Prod 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 :: (Every Num as, Known Length as) => Prod 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 :: (Every Backprop as, Known Length as) => Prod 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 Source #

Arguments

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

Gradient of final result with respect to output of function

-> (b, a) 

backpropWith, but with explicit zero.

Multiple inputs

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 #

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

backpropWith2 Source #

Arguments

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

Gradient of final result with respect to output of function

-> (c, (a, b)) 

backpropWith2, but with explicit zero.

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

backpropN, but with explicit zero and one.

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

gradBP, Nbut with explicit zero and one.

backpropWithN Source #

Arguments

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

Gradient of final result with respect to output of function

-> (b, Tuple as) 

backpropWithN, but with explicit zero.

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.

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 a -> 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 -> ZeroFunc b -> Lens' b a -> BVar s a -> BVar s b -> BVar s b Source #

setVar, but with explicit add and zero.

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 -> ZeroFunc (t 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 a -> 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 a -> 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 -> ZeroFunc b -> (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 -> ZeroFunc c -> (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 -> ZeroFunc d -> (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 => Prod AddFunc as -> ZeroFunc b -> (Tuple as -> b) -> (b -> Tuple as) -> Prod (BVar s) as -> BVar s b Source #

isoVarN with explicit add and zero.

With Ops

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

liftOp, but with explicit add and zero.

liftOp1 :: forall a b s. Reifies s W => AddFunc a -> ZeroFunc b -> 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 -> ZeroFunc c -> 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 -> ZeroFunc d -> 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.

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.

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

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

ListC ((<$>) * Constraint Backprop ((<$>) * * f as)) => Backprop (Prod * f as) Source # 

Methods

zero :: Prod * f as -> Prod * f as Source #

add :: Prod * f as -> Prod * f as -> Prod * f as Source #

one :: Prod * f as -> Prod * f as Source #

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 #

Backprop a => Backprop (I a) Source # 

Methods

zero :: I a -> I a Source #

add :: I a -> I a -> I a Source #

one :: I a -> I a Source #

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 #