Skip to content

Commit 888a2ae

Browse files
Some examples and a new version number
1 parent 433d39d commit 888a2ae

File tree

3 files changed

+122
-1
lines changed

3 files changed

+122
-1
lines changed

examples/ButcherTableau.hs

Lines changed: 47 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,47 @@
1+
{-# OPTIONS_GHC -Wall #-}
2+
3+
import Numeric.Sundials.ARKode.ODE
4+
import Numeric.LinearAlgebra
5+
6+
import Data.List (intercalate)
7+
8+
import Text.PrettyPrint.HughesPJClass
9+
10+
11+
butcherTableauTex :: ButcherTable -> String
12+
butcherTableauTex (ButcherTable m c b b2) =
13+
render $
14+
vcat [ text ("\n\\begin{array}{c|" ++ (concat $ replicate n "c") ++ "}")
15+
, us
16+
, text "\\hline"
17+
, text bs <+> text "\\\\"
18+
, text b2s <+> text "\\\\"
19+
, text "\\end{array}"
20+
]
21+
where
22+
n = rows m
23+
rs = toLists m
24+
ss = map (\r -> intercalate " & " $ map show r) rs
25+
ts = zipWith (\i r -> show i ++ " & " ++ r) (toList c) ss
26+
us = vcat $ map (\r -> text r <+> text "\\\\") ts
27+
bs = " & " ++ (intercalate " & " $ map show $ toList b)
28+
b2s = " & " ++ (intercalate " & " $ map show $ toList b2)
29+
30+
main :: IO ()
31+
main = do
32+
33+
let res = butcherTable (SDIRK_2_1_2 undefined)
34+
putStrLn $ show res
35+
putStrLn $ butcherTableauTex res
36+
37+
let resA = butcherTable (KVAERNO_4_2_3 undefined)
38+
putStrLn $ show resA
39+
putStrLn $ butcherTableauTex resA
40+
41+
let resB = butcherTable (SDIRK_5_3_4 undefined)
42+
putStrLn $ show resB
43+
putStrLn $ butcherTableauTex resB
44+
45+
let resC = butcherTable (FEHLBERG_6_4_5 undefined)
46+
putStrLn $ show resC
47+
putStrLn $ butcherTableauTex resC

examples/sundials.hs

Lines changed: 56 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,56 @@
1+
{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
2+
3+
{-# LANGUAGE ViewPatterns #-}
4+
5+
import Numeric.Sundials.ARKode.ODE
6+
import Numeric.LinearAlgebra
7+
import Graphics.Plot
8+
9+
vanderpol mu = do
10+
let xdot nu _t [x,v] = [v, -x + nu * v * (1-x*x)]
11+
xdot _ _ _ = error "vanderpol RHS not defined"
12+
ts = linspace 1000 (0,50)
13+
sol = toColumns $ odeSolve (xdot mu) [1,0] ts
14+
mplot (ts : sol)
15+
mplot sol
16+
17+
18+
harmonic w d = do
19+
let xdot u dd _t [x,v] = [v, a*x + b*v] where a = -u*u; b = -2*dd*u
20+
xdot _ _ _ _ = error "harmonic RHS not defined"
21+
ts = linspace 100 (0,20)
22+
sol = odeSolve (xdot w d) [1,0] ts
23+
mplot (ts : toColumns sol)
24+
25+
26+
kepler v a = mplot (take 2 $ toColumns sol) where
27+
xdot _t [x,y,vx,vy] = [vx,vy,x*k,y*k]
28+
where g=1
29+
k=(-g)*(x*x+y*y)**(-1.5)
30+
xdot _ _ = error "kepler RHS not defined"
31+
ts = linspace 100 (0,30)
32+
sol = odeSolve xdot [4, 0, v * cos (a*degree), v * sin (a*degree)] ts
33+
degree = pi/180
34+
35+
36+
main = do
37+
vanderpol 2
38+
harmonic 1 0
39+
harmonic 1 0.1
40+
kepler 0.3 60
41+
kepler 0.4 70
42+
vanderpol' 2
43+
44+
-- example of odeSolveV with jacobian
45+
vanderpol' mu = do
46+
let xdot nu _t (toList->[x,v]) = fromList [v, -x + nu * v * (1-x*x)]
47+
xdot _ _ _ = error "vanderpol' RHS not defined"
48+
jac _ (toList->[x,v]) = (2><2) [ 0 , 1
49+
, -1-2*x*v*mu, mu*(1-x**2) ]
50+
jac _ _ = error "vanderpol' Jacobian not defined"
51+
ts = linspace 1000 (0,50)
52+
hi = pure $ (ts!1 - ts!0) / 100.0
53+
sol = toColumns $ odeSolveV (SDIRK_5_3_4 jac) hi 1E-8 1E-8 (xdot mu) (fromList [1,0]) ts
54+
mplot sol
55+
56+

hmatrix-sundials.cabal

Lines changed: 19 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
name: hmatrix-sundials
2-
version: 0.19.1.0
2+
version: 0.20.0.0
33
synopsis: hmatrix interface to sundials
44
description: An interface to the solving suite SUNDIALS. Currently, it
55
mimics the solving interface in hmstrix-gsl but
@@ -61,3 +61,21 @@ test-suite hmatrix-sundials-testsuite
6161
sundials_cvode
6262
c-sources: src/helpers.c
6363
default-language: Haskell2010
64+
65+
executable sundials
66+
main-is: sundials.hs
67+
build-depends: base >=4.10 && <4.11,
68+
hmatrix,
69+
hmatrix-sundials,
70+
hmatrix-gsl
71+
hs-source-dirs: examples
72+
default-language: Haskell2010
73+
74+
executable butcherTableau
75+
main-is: ButcherTableau.hs
76+
build-depends: base >=4.10 && <4.11,
77+
hmatrix,
78+
hmatrix-sundials,
79+
pretty
80+
hs-source-dirs: examples
81+
default-language: Haskell2010

0 commit comments

Comments
 (0)