aern2-mfun-0.2.9.0: Multi-variate real function optimisation and proving
Safe HaskellNone
LanguageHaskell2010

AERN2.AD.Type

Documentation

data Differential a Source #

Constructors

OrderZero 

Fields

OrderOne 

Fields

OrderTwo 

Fields

Instances

Instances details
Functor Differential Source # 
Instance details

Defined in AERN2.AD.Type

Methods

fmap :: (a -> b) -> Differential a -> Differential b #

(<$) :: a -> Differential b -> Differential a #

CanDiv Integer (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type DivType Integer (Differential (CN MPBall)) #

CanDiv MPBall (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type DivType MPBall (Differential (CN MPBall)) #

CanMulAsymmetric Integer (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type MulType Integer (Differential (CN MPBall)) #

CanMulAsymmetric MPBall (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type MulType MPBall (Differential (CN MPBall)) #

CanAddAsymmetric Integer (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type AddType Integer (Differential (CN MPBall)) #

CanAddAsymmetric MPBall (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type AddType MPBall (Differential (CN MPBall)) #

CanSub Integer (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type SubType Integer (Differential (CN MPBall)) #

CanSub MPBall (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type SubType MPBall (Differential (CN MPBall)) #

Show a => Show (Differential a) Source # 
Instance details

Defined in AERN2.AD.Type

HasPrecision a => HasPrecision (Differential a) Source # 
Instance details

Defined in AERN2.AD.Type

CanSetPrecision a => CanSetPrecision (Differential a) Source # 
Instance details

Defined in AERN2.AD.Type

(CanSqrtSameType a, CanMulSameType a, CanNegSameType a, CanAddSameType a, CanMulBy a Integer, CanRecipSameType a) => CanSqrt (Differential a) Source # 
Instance details

Defined in AERN2.AD.GenericOperations

Associated Types

type SqrtType (Differential a) #

(CanExpSameType a, CanMulSameType a, CanAddSameType a) => CanExp (Differential a) Source # 
Instance details

Defined in AERN2.AD.GenericOperations

Associated Types

type ExpType (Differential a) #

(CanSinCosSameType a, CanMulSameType a, CanNegSameType a, CanSubSameType a, CanAddSameType a, HasIntegers a, CanMinMaxSameType a) => CanSinCos (Differential a) Source # 
Instance details

Defined in AERN2.AD.GenericOperations

Associated Types

type SinCosType (Differential a) #

CanAbs (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type AbsType (Differential (CN MPBall)) #

CanMulBy (Differential a) Integer => CanNeg (Differential a) Source # 
Instance details

Defined in AERN2.AD.GenericOperations

Associated Types

type NegType (Differential a) #

CanDiv (Differential (CN MPBall)) Integer Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type DivType (Differential (CN MPBall)) Integer #

CanDiv (Differential (CN MPBall)) MPBall Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type DivType (Differential (CN MPBall)) MPBall #

CanPow (Differential (CN MPBall)) Integer Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

CanMulAsymmetric (Differential (CN MPBall)) Integer Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type MulType (Differential (CN MPBall)) Integer #

CanMulAsymmetric (Differential (CN MPBall)) MPBall Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type MulType (Differential (CN MPBall)) MPBall #

CanAddAsymmetric (Differential (CN MPBall)) Integer Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type AddType (Differential (CN MPBall)) Integer #

CanAddAsymmetric (Differential (CN MPBall)) MPBall Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type AddType (Differential (CN MPBall)) MPBall #

CanSub (Differential (CN MPBall)) Integer Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type SubType (Differential (CN MPBall)) Integer #

CanSub (Differential (CN MPBall)) MPBall Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type SubType (Differential (CN MPBall)) MPBall #

CanBeMPBall a => CanDiv (CN a) (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type DivType (CN a) (Differential (CN MPBall)) #

(CanDiv a a, CanSubSameType a, CanMulSameType a, CanMulBy a Integer, CanAddSameType a, CanSubSameType (DivType a a)) => CanDiv (Differential a) (Differential a) Source # 
Instance details

Defined in AERN2.AD.GenericOperations

Associated Types

type DivType (Differential a) (Differential a) #

CanBeMPBall a => CanDiv (Differential (CN MPBall)) (CN a) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type DivType (Differential (CN MPBall)) (CN a) #

(CanMulSameType a, CanAddSameType a, CanPowBy a a, CanSubThis a Integer, CanLogSameType a, CanDivSameType a) => CanPow (Differential a) (Differential a) Source # 
Instance details

Defined in AERN2.AD.GenericOperations

Associated Types

type PowType (Differential a) (Differential a) #

type PPowType (Differential a) (Differential a) #

CanDivIMod (Differential (CN MPBall)) (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

CanBeMPBall a => CanMulAsymmetric (CN a) (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type MulType (CN a) (Differential (CN MPBall)) #

Methods

mul :: CN a -> Differential (CN MPBall) -> MulType (CN a) (Differential (CN MPBall)) #

(CanMulSameType a, CanAddSameType a) => CanMulAsymmetric (Differential a) (Differential a) Source # 
Instance details

Defined in AERN2.AD.GenericOperations

Associated Types

type MulType (Differential a) (Differential a) #

CanBeMPBall a => CanMulAsymmetric (Differential (CN MPBall)) (CN a) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type MulType (Differential (CN MPBall)) (CN a) #

Methods

mul :: Differential (CN MPBall) -> CN a -> MulType (Differential (CN MPBall)) (CN a) #

CanBeMPBall a => CanAddAsymmetric (CN a) (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type AddType (CN a) (Differential (CN MPBall)) #

Methods

add :: CN a -> Differential (CN MPBall) -> AddType (CN a) (Differential (CN MPBall)) #

CanAddSameType a => CanAddAsymmetric (Differential a) (Differential a) Source # 
Instance details

Defined in AERN2.AD.GenericOperations

Associated Types

type AddType (Differential a) (Differential a) #

CanBeMPBall a => CanAddAsymmetric (Differential (CN MPBall)) (CN a) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type AddType (Differential (CN MPBall)) (CN a) #

Methods

add :: Differential (CN MPBall) -> CN a -> AddType (Differential (CN MPBall)) (CN a) #

CanBeMPBall a => CanSub (CN a) (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type SubType (CN a) (Differential (CN MPBall)) #

Methods

sub :: CN a -> Differential (CN MPBall) -> SubType (CN a) (Differential (CN MPBall)) #

CanSubSameType a => CanSub (Differential a) (Differential a) Source # 
Instance details

Defined in AERN2.AD.GenericOperations

Associated Types

type SubType (Differential a) (Differential a) #

CanBeMPBall a => CanSub (Differential (CN MPBall)) (CN a) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

Associated Types

type SubType (Differential (CN MPBall)) (CN a) #

Methods

sub :: Differential (CN MPBall) -> CN a -> SubType (Differential (CN MPBall)) (CN a) #

CanMinMaxSameType a => CanMinMaxAsymmetric (Differential a) (Differential a) Source # 
Instance details

Defined in AERN2.AD.GenericOperations

Associated Types

type MinMaxType (Differential a) (Differential a) #

type DivType Integer (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type DivType MPBall (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type MulType Integer (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type MulType MPBall (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type AddType Integer (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type AddType MPBall (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type SubType Integer (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type SubType MPBall (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type SqrtType (Differential a) Source # 
Instance details

Defined in AERN2.AD.GenericOperations

type ExpType (Differential a) Source # 
Instance details

Defined in AERN2.AD.GenericOperations

type SinCosType (Differential a) Source # 
Instance details

Defined in AERN2.AD.GenericOperations

type AbsType (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type NegType (Differential a) Source # 
Instance details

Defined in AERN2.AD.GenericOperations

type DivType (Differential (CN MPBall)) Integer Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type DivType (Differential (CN MPBall)) MPBall Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type PPowType (Differential (CN MPBall)) Integer Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type PowType (Differential (CN MPBall)) Integer Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type MulType (Differential (CN MPBall)) Integer Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type MulType (Differential (CN MPBall)) MPBall Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type AddType (Differential (CN MPBall)) Integer Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type AddType (Differential (CN MPBall)) MPBall Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type SubType (Differential (CN MPBall)) Integer Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type SubType (Differential (CN MPBall)) MPBall Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type DivType (CN a) (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type DivType (Differential a) (Differential a) Source # 
Instance details

Defined in AERN2.AD.GenericOperations

type DivType (Differential (CN MPBall)) (CN a) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type PPowType (Differential a) (Differential a) Source # 
Instance details

Defined in AERN2.AD.GenericOperations

type PowType (Differential a) (Differential a) Source # 
Instance details

Defined in AERN2.AD.GenericOperations

type ModType (Differential (CN MPBall)) (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type DivIType (Differential (CN MPBall)) (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type MulType (CN a) (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type MulType (Differential a) (Differential a) Source # 
Instance details

Defined in AERN2.AD.GenericOperations

type MulType (Differential (CN MPBall)) (CN a) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type AddType (CN a) (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type AddType (Differential a) (Differential a) Source # 
Instance details

Defined in AERN2.AD.GenericOperations

type AddType (Differential (CN MPBall)) (CN a) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type SubType (CN a) (Differential (CN MPBall)) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type SubType (Differential a) (Differential a) Source # 
Instance details

Defined in AERN2.AD.GenericOperations

type SubType (Differential (CN MPBall)) (CN a) Source # 
Instance details

Defined in AERN2.AD.MPBallOperations

type MinMaxType (Differential a) (Differential a) Source # 
Instance details

Defined in AERN2.AD.GenericOperations

class CanBeDifferential a where Source #

Instances

Instances details
HasIntegers a => CanBeDifferential a Source # 
Instance details

Defined in AERN2.AD.Type