roots-0.1.1.1: Root-finding algorithms (1-dimensional)

Math.Root.Finder

Synopsis

Documentation

class RootFinder r a b whereSource

General interface for numerical root finders.

Methods

initRootFinder :: (a -> b) -> a -> a -> r a bSource

initRootFinder f x0 x1: Initialize a root finder for the given function with the initial bracketing interval (x0,x1).

stepRootFinder :: (a -> b) -> r a b -> r a bSource

Step a root finder for the given function (which should generally be the same one passed to initRootFinder), refining the finder's estimate of the location of a root.

estimateRoot :: r a b -> aSource

Extract the finder's current estimate of the position of a root.

estimateError :: r a b -> aSource

Extract the finder's current estimate of the upper bound of the distance from estimateRoot to an actual root in the function.

Generally, estimateRoot r +- estimateError r should bracket a root of the function.

converged :: (Num a, Ord a) => a -> r a b -> BoolSource

Test whether a root finding algorithm has converged to a given relative accuracy.

defaultNSteps :: Tagged (r a b) IntSource

Default number of steps after which root finding will be deemed to have failed. Purely a convenience used to control the behavior of built-in functions such as findRoot and traceRoot. The default value is 250.

getDefaultNSteps :: RootFinder r a b => r a b -> IntSource

Convenience function to access defaultNSteps for a root finder, which requires a little bit of type-gymnastics.

This function does not evaluate its argument.

runRootFinder :: RootFinder r a b => (Int -> r a b -> c -> c) -> (a -> b) -> r a b -> cSource

General-purpose driver for stepping a root finder. Given a "control" function, the function being searched, and an initial RootFinder state, runRootFinder step f state repeatedly steps the root-finder and passes each intermediate state, along with a count of steps taken, to step.

The step funtion will be called with the following arguments:

n :: Int
The number of steps taken thus far
currentState :: r a b
The current state of the root finder
continue :: c
The result of the "rest" of the iteration

For example, the following function simply iterates a root finder and returns every intermediate state (similar to traceRoot):

 iterateRoot :: RootFinder r a b => (a -> b) -> a -> a -> [r a b]
 iterateRoot f a b = runRootFinder (const (:)) f (initRootFinder f a b)

And the following function simply iterates the root finder to convergence or throws an error after a given number of steps:

 solve :: (RootFinder r a b, RealFloat a)
       => Int -> (a -> b) -> a -> a -> r a b
 solve maxN f a b = runRootFinder step f (initRootFinder f a b)
    where
        step n x continue
            | converged eps x   = x
            | n > maxN          = error "solve: step limit exceeded"
            | otherwise         = continue

traceRoot :: (Eq (r a b), RootFinder r a b, Num a, Ord a) => (a -> b) -> a -> a -> Maybe a -> [r a b]Source

traceRoot f x0 x1 mbEps initializes a root finder and repeatedly steps it, returning each step of the process in a list. No step limit is imposed.

Termination criteria depends on mbEps; if it is of the form Just eps then convergence to eps is used (using the converged method of the root finder). Otherwise, the trace is not terminated until subsequent states are equal (according to ==). This is a stricter condition than convergence to 0; subsequent states may have converged to zero but as long as any internal state changes the trace will continue.

findRoot :: (RootFinder r a b, Num a, Ord a) => (a -> b) -> a -> a -> a -> Either (r a b) (r a b)Source

findRoot f x0 x1 eps initializes a root finder and repeatedly steps it. When the algorithm converges to eps or the defaultNSteps limit is exceeded, the current best guess is returned, with the Right constructor indicating successful convergence or the Left constructor indicating failure to converge.

findRootN :: (RootFinder r a b, Num a, Ord a) => Int -> (a -> b) -> a -> a -> a -> Either (r a b) (r a b)Source

Like findRoot but with a specified limit on the number of steps (rather than using defaultNSteps).

eps :: RealFloat a => aSource

A useful constant: eps is (for most RealFloat types) the smallest positive number such that 1 + eps /= 1.

realFloatDefaultNSteps :: RealFloat a => Float -> Tagged (r a b) IntSource

For RealFloat types, computes a suitable default step limit based on the precision of the type and a margin of error.