ad-4.5: Automatic Differentiation
Copyright(c) Edward Kmett 2010-2021
LicenseBSD3
Maintainerekmett@gmail.com
Stabilityexperimental
PortabilityGHC only
Safe HaskellNone
LanguageHaskell2010

Numeric.AD.Internal.Tower.Double

Description

 
Synopsis

Documentation

newtype TowerDouble Source #

Tower is an AD Mode that calculates a tangent tower by forward AD, and provides fast diffsUU, diffsUF

Constructors

Tower 

Fields

Instances

Instances details
Enum TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Eq TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Floating TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Fractional TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Data TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TowerDouble -> c TowerDouble #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TowerDouble #

toConstr :: TowerDouble -> Constr #

dataTypeOf :: TowerDouble -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TowerDouble) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TowerDouble) #

gmapT :: (forall b. Data b => b -> b) -> TowerDouble -> TowerDouble #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TowerDouble -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TowerDouble -> r #

gmapQ :: (forall d. Data d => d -> u) -> TowerDouble -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TowerDouble -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TowerDouble -> m TowerDouble #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TowerDouble -> m TowerDouble #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TowerDouble -> m TowerDouble #

Num TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Ord TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Real TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

RealFloat TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

RealFrac TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Show TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Erf TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

InvErf TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Mode TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Associated Types

type Scalar TowerDouble Source #

Jacobian TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Associated Types

type D TowerDouble Source #

type Scalar TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

type D TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

data List Source #

Constructors

Nil 
!Double :! List infixr 5 

Instances

Instances details
IsList List Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Associated Types

type Item List #

Methods

fromList :: [Item List] -> List #

fromListN :: Int -> [Item List] -> List #

toList :: List -> [Item List] #

Eq List Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Methods

(==) :: List -> List -> Bool #

(/=) :: List -> List -> Bool #

Data List Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> List -> c List #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c List #

toConstr :: List -> Constr #

dataTypeOf :: List -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c List) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c List) #

gmapT :: (forall b. Data b => b -> b) -> List -> List #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> List -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> List -> r #

gmapQ :: (forall d. Data d => d -> u) -> List -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> List -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> List -> m List #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> List -> m List #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> List -> m List #

Ord List Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Methods

compare :: List -> List -> Ordering #

(<) :: List -> List -> Bool #

(<=) :: List -> List -> Bool #

(>) :: List -> List -> Bool #

(>=) :: List -> List -> Bool #

max :: List -> List -> List #

min :: List -> List -> List #

Read List Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Show List Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Methods

showsPrec :: Int -> List -> ShowS #

show :: List -> String #

showList :: [List] -> ShowS #

Semigroup List Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Methods

(<>) :: List -> List -> List #

sconcat :: NonEmpty List -> List #

stimes :: Integral b => b -> List -> List #

Monoid List Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Methods

mempty :: List #

mappend :: List -> List -> List #

mconcat :: [List] -> List #

type Item List Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

zeroPad :: Num a => [a] -> [a] Source #

zeroPadF :: (Functor f, Num a) => [f a] -> [f a] Source #

d :: Num a => [a] -> a Source #

d' :: Num a => [a] -> (a, a) Source #

apply :: (TowerDouble -> b) -> Double -> b Source #