module AERN2.AD.Type where
import MixedTypesNumPrelude
import AERN2.MP.Precision
data Differential a =
OrderZero {Differential a -> a
diff_x :: a}
| OrderOne {diff_x :: a, Differential a -> a
diff_dx :: a}
| OrderTwo {diff_x :: a, diff_dx :: a, Differential a -> a
diff_dxt :: a, Differential a -> a
diff_d2x :: a}
deriving (Int -> Differential a -> ShowS
[Differential a] -> ShowS
Differential a -> String
(Int -> Differential a -> ShowS)
-> (Differential a -> String)
-> ([Differential a] -> ShowS)
-> Show (Differential a)
forall a. Show a => Int -> Differential a -> ShowS
forall a. Show a => [Differential a] -> ShowS
forall a. Show a => Differential a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Differential a] -> ShowS
$cshowList :: forall a. Show a => [Differential a] -> ShowS
show :: Differential a -> String
$cshow :: forall a. Show a => Differential a -> String
showsPrec :: Int -> Differential a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Differential a -> ShowS
Show)
order :: Differential a -> Integer
order :: Differential a -> Integer
order (OrderZero a
_) = Integer
0
order (OrderOne a
_ a
_) = Integer
1
order (OrderTwo a
_ a
_ a
_ a
_) = Integer
2
class CanBeDifferential a where
differential :: Integer -> a -> Differential a
instance
(HasIntegers a) =>
CanBeDifferential a
where
differential :: Integer -> a -> Differential a
differential Integer
0 a
a = a -> Differential a
forall a. a -> Differential a
OrderZero a
a
differential Integer
1 a
a = a -> a -> Differential a
forall a. a -> a -> Differential a
OrderOne a
a (Integer -> a
forall t1 t2. ConvertibleExactly t1 t2 => t1 -> t2
convertExactly Integer
0)
differential Integer
_ a
a = a -> a -> a -> a -> Differential a
forall a. a -> a -> a -> a -> Differential a
OrderTwo a
a (Integer -> a
forall t1 t2. ConvertibleExactly t1 t2 => t1 -> t2
convertExactly Integer
0) (Integer -> a
forall t1 t2. ConvertibleExactly t1 t2 => t1 -> t2
convertExactly Integer
0) (Integer -> a
forall t1 t2. ConvertibleExactly t1 t2 => t1 -> t2
convertExactly Integer
0)
instance Functor Differential where
fmap :: (a -> b) -> Differential a -> Differential b
fmap a -> b
f (OrderZero a
x) = b -> Differential b
forall a. a -> Differential a
OrderZero (a -> b
f a
x)
fmap a -> b
f (OrderOne a
x a
dx) = b -> b -> Differential b
forall a. a -> a -> Differential a
OrderOne (a -> b
f a
x) (a -> b
f a
dx)
fmap a -> b
f (OrderTwo a
x a
dx a
dxt a
d2x) = b -> b -> b -> b -> Differential b
forall a. a -> a -> a -> a -> Differential a
OrderTwo (a -> b
f a
x) (a -> b
f a
dx) (a -> b
f a
dxt) (a -> b
f a
d2x)
instance
(HasPrecision a) => (HasPrecision (Differential a))
where
getPrecision :: Differential a -> Precision
getPrecision Differential a
a = a -> Precision
forall t. HasPrecision t => t -> Precision
getPrecision (Differential a -> a
forall a. Differential a -> a
diff_x Differential a
a)
instance
(CanSetPrecision a) => (CanSetPrecision (Differential a))
where
setPrecision :: Precision -> Differential a -> Differential a
setPrecision Precision
p = (a -> a) -> Differential a -> Differential a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Precision -> a -> a
forall t. CanSetPrecision t => Precision -> t -> t
setPrecision Precision
p)
setValue :: Differential a -> a -> Differential a
setValue :: Differential a -> a -> Differential a
setValue (OrderZero a
_x) a
v = a -> Differential a
forall a. a -> Differential a
OrderZero a
v
setValue (OrderOne a
_x a
dx) a
v = a -> a -> Differential a
forall a. a -> a -> Differential a
OrderOne a
v a
dx
setValue (OrderTwo a
_x a
dx a
dxt a
d2x) a
v = a -> a -> a -> a -> Differential a
forall a. a -> a -> a -> a -> Differential a
OrderTwo a
v a
dx a
dxt a
d2x