clifford-0.1.0.0: A Clifford algebra library

Safe HaskellNone

Numeric.Clifford.NumericIntegration

Documentation

elementAdd :: C c => [c] -> [c] -> [c]Source

elementScale :: C a c => [a] -> [c] -> [c]Source

elementSub :: C c => [c] -> [c] -> [c]Source

elementMul :: C c => [c] -> [c] -> [c]Source

sumVector :: (Ord t1, SingI Nat t, C t1) => Vector (Multivector t t1) -> Multivector t t1Source

systemBroydensMethod :: (Ord f, SingI Nat n, C f) => ([Multivector n f] -> [Multivector n f]) -> [Multivector n f] -> [Multivector n f] -> [[Multivector n f]]Source

convergeList :: (Show f, Ord f) => [[f]] -> [f]Source

showOutput :: Show a => [Char] -> a -> aSource

convergeTolLists :: (Ord f, C f, C f, Show f, SingI d) => f -> [[Multivector d f]] -> [Multivector d f]Source

type RKStepper d t stateType = (Ord t, Show t, C t (Multivector d t), C t) => t -> (t -> stateType -> stateType) -> ([Multivector d t] -> stateType) -> (stateType -> [Multivector d t]) -> (t, stateType) -> (t, stateType)Source

data ButcherTableau f Source

Constructors

ButcherTableau 

Fields

_tableauA :: [[f]]
 
_tableauB :: [f]
 
_tableauC :: [f]
 

tableauC :: forall f. Lens' (ButcherTableau f) [f]Source

tableauB :: forall f. Lens' (ButcherTableau f) [f]Source

tableauA :: forall f. Lens' (ButcherTableau f) [[f]]Source

type ConvergerFunction f = forall d f. [[Multivector d f]] -> [Multivector d f]Source

type AdaptiveStepSizeFunction f state = f -> state -> fSource

isStartingGuessMethod :: forall f_1627458391 state_1627458392. RKAttribute f_1627458391 state_1627458392 -> BoolSource

isUseAutomaticDifferentiationForRootSolver :: forall f_1627458391 state_1627458392. RKAttribute f_1627458391 state_1627458392 -> BoolSource

isRootSolver :: forall f_1627458391 state_1627458392. RKAttribute f_1627458391 state_1627458392 -> BoolSource

isConvergenceFunction :: forall f_1627458391 state_1627458392. RKAttribute f_1627458391 state_1627458392 -> BoolSource

isConvergenceTolerance :: forall f_1627458391 state_1627458392. RKAttribute f_1627458391 state_1627458392 -> BoolSource

isAdaptiveStepSize :: forall f_1627458391 state_1627458392. RKAttribute f_1627458391 state_1627458392 -> BoolSource

isHamiltonianFunction :: forall f_1627458391 state_1627458392. RKAttribute f_1627458391 state_1627458392 -> BoolSource

isExplicit :: forall f_1627458391 state_1627458392. RKAttribute f_1627458391 state_1627458392 -> BoolSource

genericRKMethod :: forall d t stateType. (Ord t, Show t, C t (Multivector d t), C t, C t, SingI d) => ButcherTableau t -> [RKAttribute t stateType] -> RKStepper d t stateTypeSource