numbers-3000.2.0.2: Various number types

Safe HaskellSafe
LanguageHaskell98

Data.Number.Dif

Description

The Dif module contains a data type, Dif, that allows for automatic forward differentiation.

All the ideas are from Jerzy Karczmarczuk's work, see http://users.info.unicaen.fr/~karczma/arpap/diffalg.pdf.

A simple example, if we define

foo x = x*x

then the function

foo' = deriv foo

will behave as if its body was 2*x.

Synopsis

Documentation

data Dif a Source #

The Dif type is the type of differentiable numbers. It's an instance of all the usual numeric classes. The computed derivative of a function is is correct except where the function is discontinuous, at these points the derivative should be a Dirac pulse, but it isn't.

The Dif numbers are printed with a trailing ~~ to indicate that there is a "tail" of derivatives.

Instances

Eq a => Eq (Dif a) Source # 

Methods

(==) :: Dif a -> Dif a -> Bool #

(/=) :: Dif a -> Dif a -> Bool #

(Floating a, Eq a) => Floating (Dif a) Source # 

Methods

pi :: Dif a #

exp :: Dif a -> Dif a #

log :: Dif a -> Dif a #

sqrt :: Dif a -> Dif a #

(**) :: Dif a -> Dif a -> Dif a #

logBase :: Dif a -> Dif a -> Dif a #

sin :: Dif a -> Dif a #

cos :: Dif a -> Dif a #

tan :: Dif a -> Dif a #

asin :: Dif a -> Dif a #

acos :: Dif a -> Dif a #

atan :: Dif a -> Dif a #

sinh :: Dif a -> Dif a #

cosh :: Dif a -> Dif a #

tanh :: Dif a -> Dif a #

asinh :: Dif a -> Dif a #

acosh :: Dif a -> Dif a #

atanh :: Dif a -> Dif a #

log1p :: Dif a -> Dif a #

expm1 :: Dif a -> Dif a #

log1pexp :: Dif a -> Dif a #

log1mexp :: Dif a -> Dif a #

(Fractional a, Eq a) => Fractional (Dif a) Source # 

Methods

(/) :: Dif a -> Dif a -> Dif a #

recip :: Dif a -> Dif a #

fromRational :: Rational -> Dif a #

(Num a, Eq a) => Num (Dif a) Source # 

Methods

(+) :: Dif a -> Dif a -> Dif a #

(-) :: Dif a -> Dif a -> Dif a #

(*) :: Dif a -> Dif a -> Dif a #

negate :: Dif a -> Dif a #

abs :: Dif a -> Dif a #

signum :: Dif a -> Dif a #

fromInteger :: Integer -> Dif a #

Ord a => Ord (Dif a) Source # 

Methods

compare :: Dif a -> Dif a -> Ordering #

(<) :: Dif a -> Dif a -> Bool #

(<=) :: Dif a -> Dif a -> Bool #

(>) :: Dif a -> Dif a -> Bool #

(>=) :: Dif a -> Dif a -> Bool #

max :: Dif a -> Dif a -> Dif a #

min :: Dif a -> Dif a -> Dif a #

Read a => Read (Dif a) Source # 
Real a => Real (Dif a) Source # 

Methods

toRational :: Dif a -> Rational #

RealFloat a => RealFloat (Dif a) Source # 

Methods

floatRadix :: Dif a -> Integer #

floatDigits :: Dif a -> Int #

floatRange :: Dif a -> (Int, Int) #

decodeFloat :: Dif a -> (Integer, Int) #

encodeFloat :: Integer -> Int -> Dif a #

exponent :: Dif a -> Int #

significand :: Dif a -> Dif a #

scaleFloat :: Int -> Dif a -> Dif a #

isNaN :: Dif a -> Bool #

isInfinite :: Dif a -> Bool #

isDenormalized :: Dif a -> Bool #

isNegativeZero :: Dif a -> Bool #

isIEEE :: Dif a -> Bool #

atan2 :: Dif a -> Dif a -> Dif a #

RealFrac a => RealFrac (Dif a) Source # 

Methods

properFraction :: Integral b => Dif a -> (b, Dif a) #

truncate :: Integral b => Dif a -> b #

round :: Integral b => Dif a -> b #

ceiling :: Integral b => Dif a -> b #

floor :: Integral b => Dif a -> b #

Show a => Show (Dif a) Source # 

Methods

showsPrec :: Int -> Dif a -> ShowS #

show :: Dif a -> String #

showList :: [Dif a] -> ShowS #

val :: Dif a -> a Source #

The val function takes a Dif number back to a normal number, thus forgetting about all the derivatives.

df :: (Num a, Eq a) => Dif a -> Dif a Source #

The df takes a Dif number and returns its first derivative. The function can be iterated to to get higher derivaties.

mkDif :: a -> Dif a -> Dif a Source #

The mkDif takes a value and Dif value and makes a Dif number that has the given value as its normal value, and the Dif number as its derivatives.

dCon :: Num a => a -> Dif a Source #

The dCon function turns a normal number into a Dif number with the same value. Not that numeric literals do not need an explicit conversion due to the normal Haskell overloading of literals.

dVar :: (Num a, Eq a) => a -> Dif a Source #

The dVar function turns a number into a variable number. This is the number with with respect to which the derivaticve is computed.

deriv :: (Num a, Num b, Eq a, Eq b) => (Dif a -> Dif b) -> a -> b Source #

The deriv function is a simple utility to take the derivative of a (single argument) function. It is simply defined as

 deriv f = val . df . f . dVar

unDif :: (Num a, Eq a) => (Dif a -> Dif b) -> a -> b Source #

Convert a Dif function to an ordinary function.