subhask-0.1.1.0: Type safe interface for programming in subcategories of Hask

Safe HaskellNone
LanguageHaskell2010

SubHask.Category.Trans.Derivative

Description

This module provides a category transformer for automatic differentiation.

There are many alternative notions of a generalized derivative. Perhaps the most common is the differential Ring. In Haskell, this might be defined as:

class Field r => Differential r where
   derivative :: r -> r

type Diff cat = forall a b. (Category cat, Differential cat a b)

But this runs into problems with the lack of polymorphic constraints in GHC. See, for example GHC ticket #2893.

References:

Synopsis

Documentation

data Forward a Source

This is essentially just a translation of the Numeric.AD.Forward.Forward type for use with the SubHask numeric hierarchy.

FIXME:

Add reverse mode auto-differentiation for vectors. Apply the ProofOf framework from Monotonic

Constructors

Forward 

Fields

val :: !a
 
val' :: a
 

proveC1 :: (a ~ (a >< a), Rig a) => (Forward a -> Forward a) -> C1 (a -> a) Source

proveC2 :: (a ~ (a >< a), Rig a) => (Forward (Forward a) -> Forward (Forward a)) -> C2 (a -> a) Source

class C cat where Source

Associated Types

type D cat :: * -> * -> * Source

Methods

derivative :: cat a b -> D cat a (a >< b) Source

Instances

(<=) 1 n => C (Diff n) Source 

data Diff n a b where Source

Constructors

Diff0 :: (a -> b) -> Diff 0 a b 
Diffn :: (a -> b) -> Diff (n - 1) a (a >< b) -> Diff n a b 

Instances

(<=) 1 n => C (Diff n) Source 
Sup (* -> * -> *) (->) (Diff n) (->) Source 
(<:) (* -> * -> *) (Diff n) (->) Source 
(<:) (* -> * -> *) (Diff 0) (->) Source 
Sup (* -> * -> *) (Diff n) (->) (->) Source 
(<:) (* -> * -> *) (Diff 1) (Diff 0) Source 
(<:) (* -> * -> *) (Diff 2) (Diff 0) Source 
(<:) (* -> * -> *) (Diff 2) (Diff 1) Source 
Sup (* -> * -> *) (Diff 0) (Diff 1) (Diff 0) Source 
Sup (* -> * -> *) (Diff 0) (Diff 2) (Diff 0) Source 
Sup (* -> * -> *) (Diff 1) (Diff 0) (Diff 0) Source 
Sup (* -> * -> *) (Diff 1) (Diff 2) (Diff 1) Source 
Sup (* -> * -> *) (Diff 2) (Diff 0) (Diff 0) Source 
Sup (* -> * -> *) (Diff 2) (Diff 1) (Diff 1) Source 
IsMutable (Diff n a b) Source 
Monoid b => Monoid (Diff 0 a b) Source 
(Monoid b, Monoid ((><) * * a b)) => Monoid (Diff 1 a b) Source 
(Monoid b, Monoid ((><) * * a b), Monoid ((><) * * a ((><) * * a b))) => Monoid (Diff 2 a b) Source 
Semigroup b => Semigroup (Diff 0 a b) Source 
(Semigroup b, Semigroup ((><) * * a b)) => Semigroup (Diff 1 a b) Source 
(Semigroup b, Semigroup ((><) * * a b), Semigroup ((><) * * a ((><) * * a b))) => Semigroup (Diff 2 a b) Source 
data Mutable m (Diff n0 a0 b0) = Mutable_AppT__AppT__AppT__ConT_SubHask_Category_Trans_Derivative_Diff___VarT_n_1628013694____VarT_a_1628013695____VarT_b_1628013696_ (PrimRef m (Diff n a b)) Source 
type D (Diff n) = Diff ((-) n 1) Source 

unsafeProveC0 :: (a -> b) -> Diff 0 a b Source

unsafeProveC1 Source

Arguments

:: (a -> b)

f(x)

-> (a -> a >< b)

f'(x)

-> C1 (a -> b) 

unsafeProveC2 Source

Arguments

:: (a -> b)

f(x)

-> (a -> a >< b)

f'(x)

-> (a -> a >< (a >< b))

f''(x)

-> C2 (a -> b) 

type C0 a = C0_ a Source

type family C0_ f :: * Source

Equations

C0_ (a -> b) = Diff 0 a b 

type C1 a = C1_ a Source

type family C1_ f :: * Source

Equations

C1_ (a -> b) = Diff 1 a b 

type C2 a = C2_ a Source

type family C2_ f :: * Source

Equations

C2_ (a -> b) = Diff 2 a b