diff options
Diffstat (limited to 'packages/sundials/src/Numeric/Sundials/ARKode/ODE.hs')
-rw-r--r-- | packages/sundials/src/Numeric/Sundials/ARKode/ODE.hs | 45 |
1 files changed, 16 insertions, 29 deletions
diff --git a/packages/sundials/src/Numeric/Sundials/ARKode/ODE.hs b/packages/sundials/src/Numeric/Sundials/ARKode/ODE.hs index 58acef3..9de20b6 100644 --- a/packages/sundials/src/Numeric/Sundials/ARKode/ODE.hs +++ b/packages/sundials/src/Numeric/Sundials/ARKode/ODE.hs | |||
@@ -6,7 +6,7 @@ | |||
6 | {-# LANGUAGE OverloadedStrings #-} | 6 | {-# LANGUAGE OverloadedStrings #-} |
7 | {-# LANGUAGE ScopedTypeVariables #-} | 7 | {-# LANGUAGE ScopedTypeVariables #-} |
8 | 8 | ||
9 | module Numeric.Sundials.Arkode.ODE ( solveOdeC ) where | 9 | module Numeric.Sundials.Arkode.ODE ( solveOde ) where |
10 | 10 | ||
11 | import qualified Language.C.Inline as C | 11 | import qualified Language.C.Inline as C |
12 | import qualified Language.C.Inline.Unsafe as CU | 12 | import qualified Language.C.Inline.Unsafe as CU |
@@ -76,32 +76,21 @@ vectorToC vec len ptr = do | |||
76 | ptr' <- newForeignPtr_ ptr | 76 | ptr' <- newForeignPtr_ ptr |
77 | V.copy (VM.unsafeFromForeignPtr0 ptr' len) vec | 77 | V.copy (VM.unsafeFromForeignPtr0 ptr' len) vec |
78 | 78 | ||
79 | stiffish :: Double -> V.Vector Double -> V.Vector Double | ||
80 | stiffish t v = V.fromList [ lamda * u + 1.0 / (1.0 + t * t) - lamda * atan t ] | ||
81 | where | ||
82 | u = v V.! 0 | ||
83 | lamda = -100.0 | ||
84 | |||
85 | brusselator :: Double -> V.Vector Double -> V.Vector Double | ||
86 | brusselator _t x = V.fromList [ a - (w + 1) * u + v * u^2 | ||
87 | , w * u - v * u^2 | ||
88 | , (b - w) / eps - w * u | ||
89 | ] | ||
90 | where | ||
91 | a = 1.0 | ||
92 | b = 3.5 | ||
93 | eps = 5.0e-6 | ||
94 | u = x V.! 0 | ||
95 | v = x V.! 1 | ||
96 | w = x V.! 2 | ||
97 | |||
98 | |||
99 | odeSolve :: (Double -> [Double] -> [Double]) -- ^ The RHS of the system \(\dot{y} = f(t,y)\) | 79 | odeSolve :: (Double -> [Double] -> [Double]) -- ^ The RHS of the system \(\dot{y} = f(t,y)\) |
100 | -> [Double] -- ^ initial conditions | 80 | -> [Double] -- ^ initial conditions |
101 | -> Vector Double -- ^ desired solution times | 81 | -> Vector Double -- ^ desired solution times |
102 | -> Matrix Double -- ^ solution | 82 | -> Matrix Double -- ^ solution |
103 | odeSolve = undefined | 83 | odeSolve = undefined |
104 | 84 | ||
85 | solveOde :: | ||
86 | (Double -> V.Vector Double -> V.Vector Double) -- ^ The RHS of the system \(\dot{y} = f(t,y)\) | ||
87 | -> V.Vector Double -- ^ Initial conditions | ||
88 | -> V.Vector Double -- ^ Desired solution times | ||
89 | -> Either Int (V.Vector Double) -- ^ Error code or solution | ||
90 | solveOde f y0 tt = case solveOdeC (coerce f) (coerce y0) (coerce tt) of | ||
91 | Left c -> Left $ fromIntegral c | ||
92 | Right v -> Right $ coerce v | ||
93 | |||
105 | solveOdeC :: | 94 | solveOdeC :: |
106 | (CDouble -> V.Vector CDouble -> V.Vector CDouble) -- ^ The RHS of the system \(\dot{y} = f(t,y)\) | 95 | (CDouble -> V.Vector CDouble -> V.Vector CDouble) -- ^ The RHS of the system \(\dot{y} = f(t,y)\) |
107 | -> V.Vector CDouble -- ^ Initial conditions | 96 | -> V.Vector CDouble -- ^ Initial conditions |
@@ -111,7 +100,10 @@ solveOdeC fun f0 ts = unsafePerformIO $ do | |||
111 | let dim = V.length f0 | 100 | let dim = V.length f0 |
112 | nEq :: CLong | 101 | nEq :: CLong |
113 | nEq = fromIntegral dim | 102 | nEq = fromIntegral dim |
103 | nTs :: CInt | ||
104 | nTs = fromIntegral $ V.length ts | ||
114 | fMut <- V.thaw f0 | 105 | fMut <- V.thaw f0 |
106 | tMut <- V.thaw ts | ||
115 | -- We need the types that sundials expects. These are tied together | 107 | -- We need the types that sundials expects. These are tied together |
116 | -- in 'Types'. The Haskell type is currently empty! | 108 | -- in 'Types'. The Haskell type is currently empty! |
117 | let funIO :: CDouble -> Ptr T.BarType -> Ptr T.BarType -> Ptr () -> IO CInt | 109 | let funIO :: CDouble -> Ptr T.BarType -> Ptr T.BarType -> Ptr () -> IO CInt |
@@ -136,8 +128,8 @@ solveOdeC fun f0 ts = unsafePerformIO $ do | |||
136 | long int nst, nst_a, nfe, nfi, nsetups, nje, nfeLS, nni, ncfn, netf; | 128 | long int nst, nst_a, nfe, nfi, nsetups, nje, nfeLS, nni, ncfn, netf; |
137 | 129 | ||
138 | /* general problem parameters */ | 130 | /* general problem parameters */ |
139 | realtype T0 = RCONST(0.0); /* initial time */ | 131 | realtype T0 = RCONST(($vec-ptr:(double *tMut))[0]); /* initial time */ |
140 | realtype Tf = RCONST(10.0); /* final time */ | 132 | realtype Tf = RCONST(($vec-ptr:(double *tMut))[$(int nTs) - 1]); /* final time */ |
141 | realtype dTout = RCONST(1.0); /* time between outputs */ | 133 | realtype dTout = RCONST(1.0); /* time between outputs */ |
142 | sunindextype NEQ = $(sunindextype nEq); /* number of dependent vars. */ | 134 | sunindextype NEQ = $(sunindextype nEq); /* number of dependent vars. */ |
143 | realtype reltol = 1.0e-6; /* tolerances */ | 135 | realtype reltol = 1.0e-6; /* tolerances */ |
@@ -193,7 +185,7 @@ solveOdeC fun f0 ts = unsafePerformIO $ do | |||
193 | tout = T0+dTout; | 185 | tout = T0+dTout; |
194 | printf(" t u\n"); | 186 | printf(" t u\n"); |
195 | printf(" ---------------------\n"); | 187 | printf(" ---------------------\n"); |
196 | while (Tf - t > 1.0e-15) { | 188 | for (i = 0; i < $(int nTs); i++) { |
197 | 189 | ||
198 | flag = ARKode(arkode_mem, tout, y, &t, ARK_NORMAL); /* call integrator */ | 190 | flag = ARKode(arkode_mem, tout, y, &t, ARK_NORMAL); /* call integrator */ |
199 | if (check_flag(&flag, "ARKode", 1)) break; | 191 | if (check_flag(&flag, "ARKode", 1)) break; |
@@ -258,8 +250,3 @@ solveOdeC fun f0 ts = unsafePerformIO $ do | |||
258 | return $ Right v | 250 | return $ Right v |
259 | else do | 251 | else do |
260 | return $ Left res | 252 | return $ Left res |
261 | |||
262 | main :: IO () | ||
263 | main = do | ||
264 | let res = solveOdeC (coerce brusselator) (V.fromList [1.2, 3.1, 3.0]) undefined | ||
265 | putStrLn $ show res | ||