ad-1.0.4: Automatic Differentiation

PortabilityGHC only
Stabilityexperimental
Maintainerekmett@gmail.com

Numeric.AD.Halley

Contents

Description

Root finding using Halley's rational method (the second in the class of Householder methods). Assumes the function is three times continuously differentiable and converges cubically when progress can be made.

Synopsis

Halley's Method (Tower AD)

findZero :: Fractional a => UU a -> a -> [a]Source

The findZero function finds a zero of a scalar function using Halley's method; its output is a stream of increasingly accurate results. (Modulo the usual caveats.)

Examples:

 take 10 $ findZero (\\x->x^2-4) 1  -- converge to 2.0
 module Data.Complex
 take 10 $ findZero ((+1).(^2)) (1 :+ 1)  -- converge to (0 :+ 1)@

inverse :: Fractional a => UU a -> a -> a -> [a]Source

The inverse function inverts a scalar function using Halley's method; its output is a stream of increasingly accurate results. (Modulo the usual caveats.)

Note: the take 10 $ inverse sqrt 1 (sqrt 10) example that works for Newton's method fails with Halley's method because the preconditions do not hold.

fixedPoint :: Fractional a => UU a -> a -> [a]Source

The fixedPoint function find a fixedpoint of a scalar function using Halley's method; its output is a stream of increasingly accurate results. (Modulo the usual caveats.)

 take 10 $ fixedPoint cos 1 -- converges to 0.7390851332151607

extremum :: Fractional a => UU a -> a -> [a]Source

The extremum function finds an extremum of a scalar function using Halley's method; produces a stream of increasingly accurate results. (Modulo the usual caveats.)

 take 10 $ extremum cos 1 -- convert to 0 

Exposed Types

type UU a = forall s. Mode s => AD s a -> AD s aSource

A scalar-to-scalar automatically-differentiable function.

type UF f a = forall s. Mode s => AD s a -> f (AD s a)Source

A scalar-to-non-scalar automatically-differentiable function.

type FU f a = forall s. Mode s => f (AD s a) -> AD s aSource

A non-scalar-to-scalar automatically-differentiable function.

type FF f g a = forall s. Mode s => f (AD s a) -> g (AD s a)Source

A non-scalar-to-non-scalar automatically-differentiable function.

newtype AD f a Source

AD serves as a common wrapper for different Mode instances, exposing a traditional numerical tower. Universal quantification is used to limit the actions in user code to machinery that will return the same answers under all AD modes, allowing us to use modes interchangeably as both the type level "brand" and dictionary, providing a common API.

Constructors

AD 

Fields

runAD :: f a
 

Instances

Typeable1 f => Typeable1 (AD f) 
Primal f => Primal (AD f) 
Mode f => Mode (AD f) 
Lifted f => Lifted (AD f) 
Var (AD Reverse) 
Iso (f a) (AD f a) 
(Num a, Lifted f, Bounded a) => Bounded (AD f a) 
(Num a, Lifted f, Enum a) => Enum (AD f a) 
(Num a, Lifted f, Eq a) => Eq (AD f a) 
(Lifted f, Floating a) => Floating (AD f a) 
(Lifted f, Fractional a) => Fractional (AD f a) 
(Typeable1 f, Typeable a, Data (f a), Data a) => Data (AD f a) 
(Lifted f, Num a) => Num (AD f a) 
(Num a, Lifted f, Ord a) => Ord (AD f a) 
(Lifted f, Real a) => Real (AD f a) 
(Lifted f, RealFloat a) => RealFloat (AD f a) 
(Lifted f, RealFrac a) => RealFrac (AD f a) 
(Num a, Lifted f, Show a) => Show (AD f a) 
Num a => Grad (AD Reverse a) [a] (a, [a]) a 
Num a => Grad (AD Sparse a) [a] (a, [a]) a 
Grads i o a => Grads (AD Sparse a -> i) (a -> o) a 
Num a => Grads (AD Sparse a) (Stream [] a) a 
Grad i o o' a => Grad (AD Reverse a -> i) (a -> o) (a -> o') a 
Grad i o o' a => Grad (AD Sparse a -> i) (a -> o) (a -> o') a 

class Lifted t => Mode t whereSource

Methods

lift :: Num a => a -> t aSource

Embed a constant

(<+>) :: Num a => t a -> t a -> t aSource

Vector sum

(*^) :: Num a => a -> t a -> t aSource

Scalar-vector multiplication

(^*) :: Num a => t a -> a -> t aSource

Vector-scalar multiplication

(^/) :: Fractional a => t a -> a -> t aSource

Scalar division

zero :: Num a => t aSource

 'zero' = 'lift' 0