|
| Data.Derivative | | Stability | experimental | | Maintainer | conal@conal.net |
|
|
|
| Description |
| This module is a wrapper around Data.Maclaurin or Data.Horner, to
change the VectorSpace instance for '(:>)'.
|
|
| Synopsis |
|
| data a :> b | | | powVal :: (a :> b) -> b | | | derivative :: (VectorSpace b s, LMapDom a s) => (a :> b) -> a :-* (a :> b) | | | derivativeAt :: (LMapDom a s, VectorSpace b s) => (a :> b) -> a -> a :> b | | | type :~> a b = a -> a :> b | | | dZero :: (LMapDom a s, VectorSpace b s) => a :> b | | | pureD :: (LMapDom a s, VectorSpace b s) => b -> a :> b | | | (<$>>) :: (LMapDom a s, VectorSpace b s) => (b -> c) -> (a :> b) -> a :> c | | | liftD2 :: (VectorSpace b s, LMapDom a s, VectorSpace c s, VectorSpace d s) => (b -> c -> d) -> (a :> b) -> (a :> c) -> a :> d | | | liftD3 :: (LMapDom a s, VectorSpace b s, VectorSpace c s, VectorSpace d s, VectorSpace e s) => (b -> c -> d -> e) -> (a :> b) -> (a :> c) -> (a :> d) -> a :> e | | | idD :: (LMapDom u s, VectorSpace u s) => u :~> u | | | fstD :: (VectorSpace a s, LMapDom b s, LMapDom a s) => (a, b) :~> a | | | sndD :: (VectorSpace b s, LMapDom b s, LMapDom a s) => (a, b) :~> b | | | linearD :: (LMapDom u s, VectorSpace v s) => (u -> v) -> u :~> v | | | distrib :: (LMapDom a s, VectorSpace b s, VectorSpace c s, VectorSpace u s) => (b -> c -> u) -> (a :> b) -> (a :> c) -> a :> u | | | (@.) :: (LMapDom b s, LMapDom a s, VectorSpace c s) => (b :~> c) -> (a :~> b) -> a :~> c | | | (>-<) :: (LMapDom a s, VectorSpace s s, VectorSpace u s) => (u -> u) -> ((a :> u) -> a :> s) -> (a :> u) -> a :> u |
|
|
| Documentation |
|
|
| Tower of derivatives.
| Instances | | Eq b => Eq (a :> b) | | (VectorSpace b b, LMapDom a b, Floating b) => Floating (a :> b) | | (VectorSpace b b, LMapDom a b, Fractional b) => Fractional (a :> b) | | (VectorSpace b b, LMapDom a b, Num b) => Num (a :> b) | | Ord b => Ord (a :> b) | | Show b => Show (a :> b) | | (VectorSpace b s, LMapDom a s) => AdditiveGroup (a :> b) | | (LMapDom a s, VectorSpace v s, HasCross3 v) => HasCross3 (a :> v) | | (LMapDom a s, VectorSpace v s, HasCross2 v) => HasCross2 (a :> v) | | (Num s, LMapDom s s) => HasNormal (Two s :> Three s) | | (Num s, LMapDom s s) => HasNormal (One s :> Two s) | | (InnerSpace u s, InnerSpace s s', VectorSpace s s, LMapDom a s) => InnerSpace (a :> u) (a :> s) | | (LMapDom a s, VectorSpace u s, VectorSpace s s) => VectorSpace (a :> u) (a :> s) |
|
|
|
|
| Extract the value from a derivative tower
|
|
|
| Extract the derivative from a derivative tower
|
|
|
| Sampled derivative. For avoiding an awkward typing problem related
to the two required VectorSpace instances.
|
|
|
| Infinitely differentiable functions
|
|
|
| Derivative tower full of zeroV.
|
|
|
| Constant derivative tower.
|
|
|
| Map a linear function over a derivative tower.
|
|
|
| Apply a linear binary function over derivative towers.
|
|
|
| Apply a linear ternary function over derivative towers.
|
|
|
| Differentiable identity function. Sometimes called the
derivation variable or similar, but it's not really a variable.
|
|
|
| Differentiable version of fst
|
|
|
| Differentiable version of snd
|
|
|
| Every linear function has a constant derivative equal to the function
itself (as a linear map).
|
|
|
| Derivative tower for applying a binary function that distributes over
addition, such as multiplication. A bit weaker assumption than
bilinearity.
|
|
|
| Chain rule.
|
|
|
| Specialized chain rule.
|
|
| Produced by Haddock version 2.3.0 |