hmatrix-sundials-0.19.0.0: hmatrix interface to sundials

CopyrightDominic Steinitz 2018
Novadiscovery 2018
LicenseBSD
MaintainerDominic Steinitz
Stabilityprovisional
Safe HaskellNone
LanguageHaskell2010

Numeric.Sundials.ARKode.ODE

Description

Solution of ordinary differential equation (ODE) initial value problems.

https://computation.llnl.gov/projects/sundials/sundials-software

A simple example:

import           Numeric.Sundials.ARKode.ODE
import           Numeric.LinearAlgebra

import           Plots as P
import qualified Diagrams.Prelude as D
import           Diagrams.Backend.Rasterific

brusselator :: Double -> [Double] -> [Double]
brusselator _t x = [ a - (w + 1) * u + v * u * u
                   , w * u - v * u * u
                   , (b - w) / eps - w * u
                   ]
  where
    a = 1.0
    b = 3.5
    eps = 5.0e-6
    u = x !! 0
    v = x !! 1
    w = x !! 2

lSaxis :: [[Double]] -> P.Axis B D.V2 Double
lSaxis xs = P.r2Axis &~ do
  let ts = xs!!0
      us = xs!!1
      vs = xs!!2
      ws = xs!!3
  P.linePlot' $ zip ts us
  P.linePlot' $ zip ts vs
  P.linePlot' $ zip ts ws

main = do
  let res1 = odeSolve brusselator [1.2, 3.1, 3.0] (fromList [0.0, 0.1 .. 10.0])
  renderRasterific "diagrams/brusselator.png"
                   (D.dims2D 500.0 500.0)
                   (renderAxis $ lSaxis $ [0.0, 0.1 .. 10.0]:(toLists $ tr res1))

KVAERNO_4_2_3

\[ \begin{array}{c|cccc} 0.0 & 0.0 & 0.0 & 0.0 & 0.0 \\ 0.871733043 & 0.4358665215 & 0.4358665215 & 0.0 & 0.0 \\ 1.0 & 0.490563388419108 & 7.3570090080892e-2 & 0.4358665215 & 0.0 \\ 1.0 & 0.308809969973036 & 1.490563388254106 & -1.235239879727145 & 0.4358665215 \\ \hline & 0.308809969973036 & 1.490563388254106 & -1.235239879727145 & 0.4358665215 \\ & 0.490563388419108 & 7.3570090080892e-2 & 0.4358665215 & 0.0 \\ \end{array} \]

SDIRK_2_1_2

\[ \begin{array}{c|cc} 1.0 & 1.0 & 0.0 \\ 0.0 & -1.0 & 1.0 \\ \hline & 0.5 & 0.5 \\ & 1.0 & 0.0 \\ \end{array} \]

SDIRK_5_3_4

\[ \begin{array}{c|ccccc} 0.25 & 0.25 & 0.0 & 0.0 & 0.0 & 0.0 \\ 0.75 & 0.5 & 0.25 & 0.0 & 0.0 & 0.0 \\ 0.55 & 0.34 & -4.0e-2 & 0.25 & 0.0 & 0.0 \\ 0.5 & 0.2727941176470588 & -5.036764705882353e-2 & 2.7573529411764705e-2 & 0.25 & 0.0 \\ 1.0 & 1.0416666666666667 & -1.0208333333333333 & 7.8125 & -7.083333333333333 & 0.25 \\ \hline & 1.0416666666666667 & -1.0208333333333333 & 7.8125 & -7.083333333333333 & 0.25 \\ & 1.2291666666666667 & -0.17708333333333334 & 7.03125 & -7.083333333333333 & 0.0 \\ \end{array} \]

Synopsis

Documentation

odeSolve Source #

Arguments

:: (Double -> [Double] -> [Double])

The RHS of the system \(\dot{y} = f(t,y)\)

-> [Double]

initial conditions

-> Vector Double

desired solution times

-> Matrix Double

solution

A version of odeSolveV with reasonable default parameters and system of equations defined using lists. FIXME: we should say something about the fact we could use the Jacobian but don't for compatibility with hmatrix-gsl.

odeSolveV Source #

Arguments

:: ODEMethod 
-> Maybe Double

initial step size - by default, ARKode estimates the initial step size to be the solution \(h\) of the equation \(\|\frac{h^2\ddot{y}}{2}\| = 1\), where \(\ddot{y}\) is an estimated value of the second derivative of the solution at \(t_0\)

-> Double

absolute tolerance for the state vector

-> Double

relative tolerance for the state vector

-> (Double -> Vector Double -> Vector Double)

The RHS of the system \(\dot{y} = f(t,y)\)

-> Vector Double

initial conditions

-> Vector Double

desired solution times

-> Matrix Double

solution

A version of odeSolveVWith with reasonable default step control.

odeSolveVWith Source #

Arguments

:: ODEMethod 
-> StepControl 
-> Maybe Double

initial step size - by default, ARKode estimates the initial step size to be the solution \(h\) of the equation \(\|\frac{h^2\ddot{y}}{2}\| = 1\), where \(\ddot{y}\) is an estimated value of the second derivative of the solution at \(t_0\)

-> (Double -> Vector Double -> Vector Double)

The RHS of the system \(\dot{y} = f(t,y)\)

-> Vector Double

Initial conditions

-> Vector Double

Desired solution times

-> Either Int (Vector Double, SundialsDiagnostics)

Error code or solution

odeSolveVWith' Source #

Arguments

:: ODEMethod 
-> StepControl 
-> Maybe Double

initial step size - by default, ARKode estimates the initial step size to be the solution \(h\) of the equation \(\|\frac{h^2\ddot{y}}{2}\| = 1\), where \(\ddot{y}\) is an estimated value of the second derivative of the solution at \(t_0\)

-> (Double -> Vector Double -> Vector Double)

The RHS of the system \(\dot{y} = f(t,y)\)

-> Vector Double

Initial conditions

-> Vector Double

Desired solution times

-> Matrix Double

Error code or solution

data ODEMethod Source #

Stepping functions

Instances

Show ODEMethod Source # 
Generic ODEMethod Source # 

Associated Types

type Rep ODEMethod :: * -> * #

type Rep ODEMethod Source # 
type Rep ODEMethod = D1 * (MetaData "ODEMethod" "Numeric.Sundials.ARKode.ODE" "hmatrix-sundials-0.19.0.0-6AHUEstLRbX5eZnlgnO8Ag" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "SDIRK_2_1_2" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))) ((:+:) * (C1 * (MetaCons "SDIRK_2_1_2'" PrefixI False) (U1 *)) (C1 * (MetaCons "BILLINGTON_3_3_2" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))))) ((:+:) * (C1 * (MetaCons "BILLINGTON_3_3_2'" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "TRBDF2_3_3_2" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))) (C1 * (MetaCons "TRBDF2_3_3_2'" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "KVAERNO_4_2_3" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))) ((:+:) * (C1 * (MetaCons "KVAERNO_4_2_3'" PrefixI False) (U1 *)) (C1 * (MetaCons "ARK324L2SA_DIRK_4_2_3" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))))) ((:+:) * (C1 * (MetaCons "ARK324L2SA_DIRK_4_2_3'" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CASH_5_2_4" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))) (C1 * (MetaCons "CASH_5_2_4'" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "CASH_5_3_4" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))) ((:+:) * (C1 * (MetaCons "CASH_5_3_4'" PrefixI False) (U1 *)) (C1 * (MetaCons "SDIRK_5_3_4" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))))) ((:+:) * (C1 * (MetaCons "SDIRK_5_3_4'" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "KVAERNO_5_3_4" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))) (C1 * (MetaCons "KVAERNO_5_3_4'" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "ARK436L2SA_DIRK_6_3_4" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))) ((:+:) * (C1 * (MetaCons "ARK436L2SA_DIRK_6_3_4'" PrefixI False) (U1 *)) (C1 * (MetaCons "KVAERNO_7_4_5" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))))) ((:+:) * (C1 * (MetaCons "KVAERNO_7_4_5'" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ARK548L2SA_DIRK_8_4_5" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))) (C1 * (MetaCons "ARK548L2SA_DIRK_8_4_5'" PrefixI False) (U1 *))))))) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "HEUN_EULER_2_1_2" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))) ((:+:) * (C1 * (MetaCons "HEUN_EULER_2_1_2'" PrefixI False) (U1 *)) (C1 * (MetaCons "BOGACKI_SHAMPINE_4_2_3" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))))) ((:+:) * (C1 * (MetaCons "BOGACKI_SHAMPINE_4_2_3'" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ARK324L2SA_ERK_4_2_3" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))) (C1 * (MetaCons "ARK324L2SA_ERK_4_2_3'" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "ZONNEVELD_5_3_4" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))) ((:+:) * (C1 * (MetaCons "ZONNEVELD_5_3_4'" PrefixI False) (U1 *)) (C1 * (MetaCons "ARK436L2SA_ERK_6_3_4" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))))) ((:+:) * (C1 * (MetaCons "ARK436L2SA_ERK_6_3_4'" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "SAYFY_ABURUB_6_3_4" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))) (C1 * (MetaCons "SAYFY_ABURUB_6_3_4'" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "CASH_KARP_6_4_5" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))) ((:+:) * (C1 * (MetaCons "CASH_KARP_6_4_5'" PrefixI False) (U1 *)) (C1 * (MetaCons "FEHLBERG_6_4_5" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))))) ((:+:) * (C1 * (MetaCons "FEHLBERG_6_4_5'" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "DORMAND_PRINCE_7_4_5" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))) (C1 * (MetaCons "DORMAND_PRINCE_7_4_5'" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "ARK548L2SA_ERK_8_4_5" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))) ((:+:) * (C1 * (MetaCons "ARK548L2SA_ERK_8_4_5'" PrefixI False) (U1 *)) (C1 * (MetaCons "VERNER_8_5_6" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))))) ((:+:) * (C1 * (MetaCons "VERNER_8_5_6'" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "FEHLBERG_13_7_8" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Jacobian))) (C1 * (MetaCons "FEHLBERG_13_7_8'" PrefixI False) (U1 *))))))))

data StepControl Source #

Adaptive step-size control functions.

GSL allows the user to control the step size adjustment using \(D_i = \epsilon^{abs}s_i + \epsilon^{rel}(a_{y} |y_i| + a_{dy/dt} h |\dot{y}_i|)\) where \(\epsilon^{abs}\) is the required absolute error, \(\epsilon^{rel}\) is the required relative error, \(s_i\) is a vector of scaling factors, \(a_{y}\) is a scaling factor for the solution \(y\) and \(a_{dydt}\) is a scaling factor for the derivative of the solution \(dy/dt\).

ARKode allows the user to control the step size adjustment using \(\eta^{rel}|y_i| + \eta^{abs}_i\). For compatibility with hmatrix-gsl, tolerances for \(y\) and \(\dot{y}\) can be specified but the latter have no effect.

Constructors

X Double Double

absolute and relative tolerance for \(y\); in GSL terms, \(a_{y} = 1\) and \(a_{dy/dt} = 0\); in ARKode terms, the \(\eta^{abs}_i\) are identical

X' Double Double

absolute and relative tolerance for \(\dot{y}\); in GSL terms, \(a_{y} = 0\) and \(a_{dy/dt} = 1\); in ARKode terms, the latter is treated as the relative tolerance for \(y\) so this is the same as specifying X which may be entirely incorrect for the given problem

XX' Double Double Double Double

include both via relative tolerance scaling factors \(a_y\), \(a_{{dy}/{dt}}\); in ARKode terms, the latter is ignored and \(\eta^{rel} = a_{y}\epsilon^{rel}\)

ScXX' Double Double Double Double (Vector Double)

scale absolute tolerance of \(y_i\); in ARKode terms, \(a_{{dy}/{dt}}\) is ignored, \(\eta^{abs}_i = s_i \epsilon^{abs}\) and \(\eta^{rel} = a_{y}\epsilon^{rel}\)