ad-0.44.0: Automatic Differentiation

PortabilityGHC only
Stabilityexperimental
Maintainerekmett@gmail.com

Numeric.AD.Internal.Classes

Contents

Description

 

Synopsis

AD modes

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

one :: (Mode t, Num a) => t aSource

Automatically Deriving AD

class (Mode t, Mode (D t)) => Jacobian t whereSource

Jacobian is used by deriveMode but is not exposed via Mode to prevent its abuse by end users via the AD data type.

Associated Types

type D t :: * -> *Source

Methods

unary :: Num a => (a -> a) -> D t a -> t a -> t aSource

lift1 :: Num a => (a -> a) -> (D t a -> D t a) -> t a -> t aSource

lift1_ :: Num a => (a -> a) -> (D t a -> D t a -> D t a) -> t a -> t aSource

binary :: Num a => (a -> a -> a) -> D t a -> D t a -> t a -> t a -> t aSource

lift2 :: Num a => (a -> a -> a) -> (D t a -> D t a -> (D t a, D t a)) -> t a -> t a -> t aSource

lift2_ :: Num a => (a -> a -> a) -> (D t a -> D t a -> D t a -> (D t a, D t a)) -> t a -> t a -> t aSource

class Primal t whereSource

Primal is used by deriveMode but is not exposed via the Mode class to prevent its abuse by end users via the AD data type.

It provides direct access to the result, stripped of its derivative information, but this is unsafe in general as (lift . primal) would discard derivative information. The end user is protected from accidentally using this function by the universal quantification on the various combinators we expose.

Methods

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

deriveLifted :: ([Q Pred] -> [Q Pred]) -> Q Type -> Q [Dec]Source

deriveLifted t provides

 instance Lifted $t

given supplied instances for

 instance Lifted $t => Primal $t where ...
 instance Lifted $t => Jacobian $t where ...

The seemingly redundant Lifted $t constraints are caused by Template Haskell staging restrictions.

deriveNumeric :: ([Q Pred] -> [Q Pred]) -> Q Type -> Q [Dec]Source

deriveNumeric f g provides the following instances:

 instance ('Lifted' $f, 'Num' a, 'Enum' a) => 'Enum' ($g a)
 instance ('Lifted' $f, 'Num' a, 'Eq' a) => 'Eq' ($g a)
 instance ('Lifted' $f, 'Num' a, 'Ord' a) => 'Ord' ($g a)
 instance ('Lifted' $f, 'Num' a, 'Bounded' a) => 'Bounded' ($g a)
 instance ('Lifted' $f, 'Show' a) => 'Show' ($g a)
 instance ('Lifted' $f, 'Num' a) => 'Num' ($g a)
 instance ('Lifted' $f, 'Fractional' a) => 'Fractional' ($g a)
 instance ('Lifted' $f, 'Floating' a) => 'Floating' ($g a)
 instance ('Lifted' $f, 'RealFloat' a) => 'RealFloat' ($g a)
 instance ('Lifted' $f, 'RealFrac' a) => 'RealFrac' ($g a)
 instance ('Lifted' $f, 'Real' a) => 'Real' ($g a)

class Lifted t whereSource

Methods

showsPrec1 :: Show a => Int -> t a -> ShowSSource

(==!) :: (Num a, Eq a) => t a -> t a -> BoolSource

compare1 :: (Num a, Ord a) => t a -> t a -> OrderingSource

fromInteger1 :: Num a => Integer -> t aSource

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

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

(-!) :: Num a => t a -> t a -> t aSource

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

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

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

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

recip1 :: Fractional a => t a -> t aSource

fromRational1 :: Fractional a => Rational -> t aSource

toRational1 :: Real a => t a -> RationalSource

pi1 :: Floating a => t aSource

exp1 :: Floating a => t a -> t aSource

sqrt1 :: Floating a => t a -> t aSource

log1 :: Floating a => t a -> t aSource

(**!) :: Floating a => t a -> t a -> t aSource

logBase1 :: Floating a => t a -> t a -> t aSource

sin1 :: Floating a => t a -> t aSource

atan1 :: Floating a => t a -> t aSource

acos1 :: Floating a => t a -> t aSource

asin1 :: Floating a => t a -> t aSource

tan1 :: Floating a => t a -> t aSource

cos1 :: Floating a => t a -> t aSource

sinh1 :: Floating a => t a -> t aSource

atanh1 :: Floating a => t a -> t aSource

acosh1 :: Floating a => t a -> t aSource

asinh1 :: Floating a => t a -> t aSource

tanh1 :: Floating a => t a -> t aSource

cosh1 :: Floating a => t a -> t aSource

properFraction1 :: (RealFrac a, Integral b) => t a -> (b, t a)Source

truncate1 :: (RealFrac a, Integral b) => t a -> bSource

floor1 :: (RealFrac a, Integral b) => t a -> bSource

ceiling1 :: (RealFrac a, Integral b) => t a -> bSource

round1 :: (RealFrac a, Integral b) => t a -> bSource

floatRadix1 :: RealFloat a => t a -> IntegerSource

floatDigits1 :: RealFloat a => t a -> IntSource

floatRange1 :: RealFloat a => t a -> (Int, Int)Source

decodeFloat1 :: RealFloat a => t a -> (Integer, Int)Source

encodeFloat1 :: RealFloat a => Integer -> Int -> t aSource

exponent1 :: RealFloat a => t a -> IntSource

significand1 :: RealFloat a => t a -> t aSource

scaleFloat1 :: RealFloat a => Int -> t a -> t aSource

isNaN1 :: RealFloat a => t a -> BoolSource

isIEEE1 :: RealFloat a => t a -> BoolSource

isNegativeZero1 :: RealFloat a => t a -> BoolSource

isDenormalized1 :: RealFloat a => t a -> BoolSource

isInfinite1 :: RealFloat a => t a -> BoolSource

atan21 :: RealFloat a => t a -> t a -> t aSource

succ1 :: (Num a, Enum a) => t a -> t aSource

pred1 :: (Num a, Enum a) => t a -> t aSource

toEnum1 :: (Num a, Enum a) => Int -> t aSource

fromEnum1 :: (Num a, Enum a) => t a -> IntSource

enumFrom1 :: (Num a, Enum a) => t a -> [t a]Source

enumFromThen1 :: (Num a, Enum a) => t a -> t a -> [t a]Source

enumFromTo1 :: (Num a, Enum a) => t a -> t a -> [t a]Source

enumFromThenTo1 :: (Num a, Enum a) => t a -> t a -> t a -> [t a]Source

minBound1 :: (Num a, Bounded a) => t aSource

maxBound1 :: (Num a, Bounded a) => t aSource

class Iso a b whereSource

Methods

iso :: f a -> f bSource

osi :: f b -> f aSource

Instances

Iso a a 
Iso a (Id a) 
Iso (f a) (AD f a)