vector-space-0.1: Vector & affine spaces, plus derivativesSource 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 {
dVal :: b
dDeriv :: 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) -> (a :~> b) -> a :~> c
(>-<) :: VectorSpace b s => (b -> b) -> ((a :> b) -> a :> s) -> (a :> b) -> a :> b
Documentation
data a :> b Source

Tower of derivatives.

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

Constructors
D
dVal :: b
dDeriv :: 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) -> (a :~> b) -> a :~> cSource
Chain rule.
(>-<) :: VectorSpace b s => (b -> b) -> ((a :> b) -> a :> s) -> (a :> b) -> a :> bSource
Produced by Haddock version 2.4.2