clifford-0.1.0.12: 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 t2, SingI Nat t, SingI Nat t1, C t2) => Vector (Multivector t t1 t2) -> Multivector t t1 t2Source

systemBroydensMethod :: (Ord t2, SingI Nat t, SingI Nat t1, C t2) => ([Multivector t t1 t2] -> [Multivector t t1 t2]) -> [Multivector t t1 t2] -> [Multivector t t1 t2] -> [[Multivector t t1 t2]]Source

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

showOutput :: Show t1 => [Char] -> t1 -> t1Source

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

type RKStepper p q t stateType = (Ord t, Show t, C t (Multivector p q t), C t) => t -> (t -> stateType -> stateType) -> ([Multivector p q t] -> stateType) -> (stateType -> [Multivector p q 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 p q f. [[Multivector p q f]] -> [Multivector p q f]Source

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

isStartingGuessMethod :: forall f_1627782570 state_1627782571. RKAttribute f_1627782570 state_1627782571 -> BoolSource

isUseAutomaticDifferentiationForRootSolver :: forall f_1627782570 state_1627782571. RKAttribute f_1627782570 state_1627782571 -> BoolSource

isRootSolver :: forall f_1627782570 state_1627782571. RKAttribute f_1627782570 state_1627782571 -> BoolSource

isConvergenceFunction :: forall f_1627782570 state_1627782571. RKAttribute f_1627782570 state_1627782571 -> BoolSource

isConvergenceTolerance :: forall f_1627782570 state_1627782571. RKAttribute f_1627782570 state_1627782571 -> BoolSource

isAdaptiveStepSize :: forall f_1627782570 state_1627782571. RKAttribute f_1627782570 state_1627782571 -> BoolSource

isHamiltonianFunction :: forall f_1627782570 state_1627782571. RKAttribute f_1627782570 state_1627782571 -> BoolSource

isExplicit :: forall f_1627782570 state_1627782571. RKAttribute f_1627782570 state_1627782571 -> BoolSource

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