inf-backprop-0.1.0.2: Automatic differentiation and backpropagation.
Copyright(C) 2023 Alexey Tochin
LicenseBSD3 (see the file LICENSE)
MaintainerAlexey Tochin <Alexey.Tochin@gmail.com>
Safe HaskellNone
LanguageHaskell2010
Extensions
  • MonoLocalBinds
  • ScopedTypeVariables
  • TypeFamilies
  • GADTs
  • GADTSyntax
  • ConstraintKinds
  • InstanceSigs
  • DeriveFunctor
  • TypeSynonymInstances
  • FlexibleContexts
  • FlexibleInstances
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • KindSignatures
  • TupleSections
  • RankNTypes
  • ExplicitNamespaces
  • ExplicitForAll

Prelude.InfBackprop

Description

Backpropagation differentiable versions of basic functions.

Synopsis

Elementary functions

linear :: forall x. Distributive x => x -> BackpropFunc x x Source #

Linear differentiable function.

Examples of usage

Expand
>>> import Prelude (fmap, Float)
>>> import InfBackprop (pow, call, derivative)
>>> myFunc = linear 2 :: BackpropFunc Float Float
>>> f = call myFunc :: Float -> Float
>>> fmap f [-3, -2, -1, 0, 1, 2, 3]
[-6.0,-4.0,-2.0,0.0,2.0,4.0,6.0]
>>> df = derivative myFunc :: Float -> Float
>>> fmap df [-3, -2, -1, 0, 1, 2, 3]
[2.0,2.0,2.0,2.0,2.0,2.0,2.0]

(+) :: forall x. Additive x => BackpropFunc (x, x) x Source #

Summation differentiable binary operation.

Examples of usage

Expand
>>> import Prelude (Float)
>>> import InfBackprop (call, derivative)
>>> call (+) (2, 3) :: Float
5.0
>>> import Debug.SimpleExpr.Expr (variable)
>>> x = variable "x"
>>> y = variable "y"
>>> derivative (+) (x, y)
(1,1)

(-) :: forall x. Subtractive x => BackpropFunc (x, x) x Source #

Subtraction differentiable binary operation.

Examples of usage

Expand
>>> import Prelude (Float)
>>> import InfBackprop (call, derivative)
>>> call (-) (5, 3) :: Float
2.0
>>> import Debug.SimpleExpr.Expr (variable)
>>> x = variable "x"
>>> y = variable "y"
>>> derivative (-) (x, y)
(1,-(1))

negate :: forall x. Subtractive x => BackpropFunc x x Source #

Negate differentiable function.

Examples of usage

Expand
>>> import Prelude (Float, ($))
>>> import InfBackprop (call, derivative)
>>> call negate 42 :: Float
-42.0
>>> derivative negate 42 :: Float
-1.0

(*) :: Distributive x => BackpropFunc (x, x) x Source #

Product binnary operation

Examples of usage

Expand
>>> import Prelude (Float)
>>> import InfBackprop (call, derivative)
>>> call (*) (2, 3) :: Float
6.0
>>> import Debug.SimpleExpr.Expr (variable)
>>> x = variable "x"
>>> y = variable "y"
>>> derivative (*) (x, y)
(1·y,1·x)

(/) :: forall x. (Divisive x, Distributive x, Subtractive x) => BackpropFunc (x, x) x Source #

Division binary differentiable operation

Examples of usage

Expand
>>> import Prelude (Float)
>>> import InfBackprop (call, derivative)
>>> call (/) (6, 3) :: Float
2.0
>>> import Debug.SimpleExpr.Expr (variable)
>>> x = variable "x"
>>> y = variable "y"
>>> derivative (/) (x, y)
(1·(1/y),1·(-(x)·(1/(y·y))))

Tuple manipulations

dup :: forall x. Additive x => BackpropFunc x (x, x) Source #

Duplication differentiable operation.

Examples of usage

Expand
>>> import Prelude (Float)
>>> import InfBackprop (call, derivative)
>>> call dup (42.0 :: Float)
(42.0,42.0)
>>> import Debug.SimpleExpr.Expr (variable)
>>> x = variable "x"
>>> derivative (dup >>> (*)) x
(1·x)+(1·x)

setFirst :: forall x y c. Additive c => c -> BackpropFunc (c, x) y -> BackpropFunc x y Source #

Transforms a 2-argument differentiable function into a single argument function by fixing its first argument.

>>> import Prelude (Float)
>>> import InfBackprop (call, derivative)
>>> call (setFirst 8 (/)) 4 :: Float
2.0
>>> import Debug.SimpleExpr.Expr (variable)
>>> x = variable "x"
>>> y = variable "y"
>>> derivative (setFirst x (*)) y
1·x

setSecond :: forall x y c. Additive c => c -> BackpropFunc (x, c) y -> BackpropFunc x y Source #

Transforms a 2-argument differentiable function into a single argument function by fixing its second argument.

>>> import Prelude (Float)
>>> import InfBackprop (call, derivative)
>>> call (setSecond 4 (/)) 8 :: Float
2.0
>>> import Debug.SimpleExpr.Expr (variable)
>>> x = variable "x"
>>> y = variable "y"
>>> derivative (setSecond y (*)) x
1·y

forget :: forall x. Additive x => BackpropFunc x () Source #

Transforms any function to unit (). It is not differentiable until StartBackprop is defined for (). However forget is useful if need to remove some data in the differentiable pipeline.

Examples of usage

Expand
>>> import InfBackprop (call, derivative)
>>> f = first forget >>> (iso :: BackpropFunc ((), a) a) :: Additive a => BackpropFunc (a, a) a
>>> call f (24, 42)
42
>>> derivative f (24, 42)
(0,1)

forgetFirst :: forall x y. Additive x => BackpropFunc (x, y) y Source #

Remove the first element of a tuple.

Examples of usage

Expand
>>> import InfBackprop (call, derivative)
>>> call forgetFirst (24, 42)
42
>>> derivative forgetFirst (24, 42)
(0,1)

forgetSecond :: forall x y. Additive y => BackpropFunc (x, y) x Source #

Remove the second element of a tuple.

Examples of usage

Expand
>>> import InfBackprop (call, derivative)
>>> call forgetSecond (24, 42)
24
>>> derivative forgetSecond (24, 42)
(1,0)

Exponential family functions

log :: ExpField x => BackpropFunc x x Source #

Natural logarithm differentiable function.

Examples of usage

Expand
>>> import Prelude (Float)
>>> import InfBackprop (call, derivative)
>>> call log 10 :: Float
2.3025851
>>> derivative log 10 :: Float
0.1

logBase :: ExpField a => BackpropFunc (a, a) a Source #

Natural logarithm differentiable function.

Examples of usage

Expand
>>> import Prelude (Float)
>>> import InfBackprop (call, derivative)
>>> call logBase (2, 8) :: Float
3.0
>>> import Debug.SimpleExpr.Expr (variable)
>>> x = variable "x"
>>> n = variable "n"
>>> derivative logBase (n, x)
((1·(-(log(x))·(1/(log(n)·log(n)))))·(1/n),(1·(1/log(n)))·(1/x))

exp :: forall x. ExpField x => BackpropFunc x x Source #

Natural logarithm differentiable function.

Examples of usage

Expand
>>> import Prelude (Float)
>>> import InfBackprop (call, derivative)
>>> call exp 2
7.38905609893065
>>> import Debug.SimpleExpr.Expr (variable)
>>> x = variable "x"
>>> derivative exp x
1·exp(x)

(**) :: forall a. (ExpField a, FromIntegral a Integer) => BackpropFunc (a, a) a Source #

Power binary differentiable operation.

Examples of usage

Expand
>>> import Prelude (Float)
>>> import NumHask (half)
>>> import InfBackprop (call, derivative)
>>> call (**) (0.5, 9) :: Float
3.0
>>> import Debug.SimpleExpr.Expr (variable)
>>> x = variable "x"
>>> n = variable "n"
>>> derivative (**) (n, x)
(1·(n·(x^(n-1))),1·((x^n)·log(x)))

pow :: forall x. (Divisive x, Distributive x, Subtractive x, FromIntegral x Integer) => Integer -> BackpropFunc x x Source #

Integer power differentiable operation

Examples of usage

Expand
>>> import Prelude (Float)
>>> import InfBackprop (call, derivative)
>>> call (pow 3) 2 :: Float
8.0
>>> derivative (pow 3) 2 :: Float
12.0

Trigonometric functions

cos :: TrigField x => BackpropFunc x x Source #

Cosine differentiable function.

sin :: TrigField x => BackpropFunc x x Source #

Sine differentiable function

tan :: TrigField x => BackpropFunc x x Source #

Tangent differentiable function.

asin :: (TrigField x, ExpField x) => BackpropFunc x x Source #

Arcsine differentiable function.

acos :: (TrigField x, ExpField x) => BackpropFunc x x Source #

Arccosine differentiable function.

atan :: TrigField x => BackpropFunc x x Source #

Arctangent differentiable function.

atan2 :: TrigField a => BackpropFunc (a, a) a Source #

2-argument arctangent differentiable function.

sinh :: TrigField x => BackpropFunc x x Source #

Hyperbolic sine differentiable function.

cosh :: TrigField x => BackpropFunc x x Source #

Hyperbolic cosine differentiable function.

tanh :: TrigField x => BackpropFunc x x Source #

Hyperbolic tanget differentiable function.

asinh :: (TrigField x, ExpField x) => BackpropFunc x x Source #

Hyperbolic arcsine differentiable function.

acosh :: (TrigField x, ExpField x) => BackpropFunc x x Source #

Hyperbolic arccosine differentiable function.

atanh :: TrigField x => BackpropFunc x x Source #

Hyperbolic arctangent differentiable function.

Tools

simpleDifferentiable :: forall x. Distributive x => (x -> x) -> BackpropFunc x x -> BackpropFunc x x Source #

Returns a differentiable morphism given forward function and backpropagation derivative differential morphism.

Examples of usage

Expand
>>> import qualified NumHask as NH
>>> cos = simpleDifferentiable NH.cos (sin >>> negate)