vector-space-0.0: Vector & affine spaces, plusSource codeContentsIndex
Data.Derivative
Stabilityexperimental
Maintainerconal@conal.net
Description
Infinite derivative towers via linear maps. See blog posts http://conal.net/blog/tag/derivatives/
Synopsis
data a :> b = D b (a :> (a :-* b))
type ::> a b = a -> a :> b
dZero :: VectorSpace b s => a :> b
dConst :: VectorSpace b s => b -> a :> b
dId :: VectorSpace v s => v -> v :> v
bilinearD :: VectorSpace w s => (u -> v -> w) -> (t :> u) -> (t :> v) -> t :> w
(>*<) :: (b -> c) -> (b -> b :-* c) -> (a :> b) -> a :> c
(>-<) :: VectorSpace b s => (b -> b) -> (b -> s) -> (a :> b) -> a :> b
Documentation
data a :> b Source

Tower of derivatives. Values look like b D b' D b'' D .... The type of an nth derivative is a :-* a :-* ... :-* b, where there are n levels of a :-*, i.e., (a :-*)^n b.

Warning, the Applicative instance is missing its pure (due to a VectorSpace type constraint). Use dConst instead.

Constructors
D b (a :> (a :-* b))
show/hide Instances
Functor (:> a)
Applicative (:> a)
Eq b => Eq (a :> b)
(Floating b, VectorSpace b b) => Floating (a :> b)
(Fractional b, VectorSpace b b) => Fractional (a :> b)
(Num b, VectorSpace b b) => Num (a :> b)
Ord b => Ord (a :> b)
Show b => Show (a :> b)
VectorSpace u s => VectorSpace (a :> u) (a :> s)
type ::> a b = a -> a :> bSource
Infinitely differentiable functions
dZero :: VectorSpace b s => a :> bSource
Derivative tower full of zeroV.
dConst :: VectorSpace b s => b -> a :> bSource
Constant derivative tower.
dId :: VectorSpace v s => v -> v :> vSource
Tower of derivatives of the identity function. Sometimes called the derivation variable or similar, but it's not really a variable.
bilinearD :: VectorSpace w s => (u -> v -> w) -> (t :> u) -> (t :> v) -> t :> wSource
(>*<) :: (b -> c) -> (b -> b :-* c) -> (a :> b) -> a :> cSource
Convenient encapsulation of the chain rule. Combines value function and derivative function, to get a infinitely differentiability function, which is then applied to a derivative tower.
(>-<) :: VectorSpace b s => (b -> b) -> (b -> s) -> (a :> b) -> a :> bSource
Specialized form of '(>*<)', convenient for functions with scalar values. Uses the more common view of derivatives as rate-of-change.
Produced by Haddock version 2.4.2