From 2fc97b003f704d57ac7f798ed881f8c9ccab9918 Mon Sep 17 00:00:00 2001 From: Dominic Steinitz Date: Mon, 2 Apr 2018 08:09:24 +0100 Subject: Fix warnings --- packages/sundials/src/Arkode.hsc | 4 +++- packages/sundials/src/Main.hs | 14 ++++++++------ packages/sundials/src/Numeric/Sundials/ARKode/ODE.hs | 8 ++++---- 3 files changed, 15 insertions(+), 11 deletions(-) (limited to 'packages/sundials') diff --git a/packages/sundials/src/Arkode.hsc b/packages/sundials/src/Arkode.hsc index ae2b40f..83d1127 100644 --- a/packages/sundials/src/Arkode.hsc +++ b/packages/sundials/src/Arkode.hsc @@ -4,7 +4,6 @@ module Arkode where import Foreign import Foreign.C.Types -import Foreign.C.String #include @@ -14,12 +13,14 @@ import Foreign.C.String #include #include + #def typedef struct _generic_N_Vector SunVector; #def typedef struct _N_VectorContent_Serial SunContent; #def typedef struct _generic_SUNMatrix SunMatrix; #def typedef struct _SUNMatrixContent_Dense SunMatrixContent; +getContentMatrixPtr :: Storable a => Ptr b -> IO a getContentMatrixPtr ptr = (#peek SunMatrix, content) ptr getNRows :: Ptr b -> IO CInt @@ -32,6 +33,7 @@ getNCols ptr = (#peek SunMatrixContent, N) ptr putNCols :: CInt -> Ptr b -> IO () putNCols nc ptr = (#poke SunMatrixContent, N) ptr nc +getMatrixData :: Storable a => Ptr b -> IO a getMatrixData ptr = (#peek SunMatrixContent, data) ptr getContentPtr :: Storable a => Ptr b -> IO a diff --git a/packages/sundials/src/Main.hs b/packages/sundials/src/Main.hs index 01d3595..4e0cf4b 100644 --- a/packages/sundials/src/Main.hs +++ b/packages/sundials/src/Main.hs @@ -1,6 +1,5 @@ {-# OPTIONS_GHC -Wall #-} -import qualified Data.Vector.Storable as V import Numeric.Sundials.Arkode.ODE import Numeric.LinearAlgebra @@ -9,14 +8,14 @@ import qualified Diagrams.Prelude as D import Diagrams.Backend.Rasterific import Control.Lens -import Data.List (zip4) +import Data.List (intercalate) import Text.PrettyPrint.HughesPJClass -import Data.List (intercalate) -brusselator _t x = [ a - (w + 1) * u + v * u^2 - , w * u - v * u^2 +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 @@ -27,6 +26,7 @@ brusselator _t x = [ a - (w + 1) * u + v * u^2 v = x !! 1 w = x !! 2 +brussJac :: Double -> Vector Double -> Matrix Double brussJac _t x = (3><3) [ (-(w + 1.0)) + 2.0 * u * v, w - 2.0 * u * v, (-w) , u * u , (-(u * u)) , 0.0 , (-u) , u , (-1.0) / eps - u @@ -38,11 +38,13 @@ brussJac _t x = (3><3) [ (-(w + 1.0)) + 2.0 * u * v, w - 2.0 * u * v, (-w) w = y !! 2 eps = 5.0e-6 +stiffish :: Double -> [Double] -> [Double] stiffish t v = [ lamda * u + 1.0 / (1.0 + t * t) - lamda * atan t ] where lamda = -100.0 u = v !! 0 +stiffJac :: Double -> Vector Double -> Matrix Double stiffJac _t _v = (1><1) [ lamda ] where lamda = -100.0 @@ -71,7 +73,7 @@ butcherTableauTex m = render $ n = rows m rs = toLists m ss = map (\r -> intercalate " & " $ map show r) rs - ts = zipWith (\n r -> "c_" ++ show n ++ " & " ++ r) [1..n] ss + ts = zipWith (\i r -> "c_" ++ show i ++ " & " ++ r) [1..n] ss us = vcat $ map (\r -> text r <+> text "\\\\") ts main :: IO () diff --git a/packages/sundials/src/Numeric/Sundials/ARKode/ODE.hs b/packages/sundials/src/Numeric/Sundials/ARKode/ODE.hs index 5af9e41..b419843 100644 --- a/packages/sundials/src/Numeric/Sundials/ARKode/ODE.hs +++ b/packages/sundials/src/Numeric/Sundials/ARKode/ODE.hs @@ -87,8 +87,8 @@ getDataFromContents len ptr = do vectorFromC len rtr -- FIXME: Potentially an instance of Storable -getMatrixDataFromContents :: Ptr T.SunMatrix -> IO T.SunMatrix -getMatrixDataFromContents ptr = do +_getMatrixDataFromContents :: Ptr T.SunMatrix -> IO T.SunMatrix +_getMatrixDataFromContents ptr = do qtr <- B.getContentMatrixPtr ptr rs <- B.getNRows qtr cs <- B.getNCols qtr @@ -239,8 +239,8 @@ solveOdeC method jacH relTol absTol fun f0 ts = unsafePerformIO $ do Ptr () -> Ptr T.SunVector -> Ptr T.SunVector -> Ptr T.SunVector -> IO CInt jacIO t y _fy jacS _ptr _tmp1 _tmp2 _tmp3 = do - foo <- jacH t <$> getDataFromContents dim y - putMatrixDataFromContents foo jacS + j <- jacH t <$> getDataFromContents dim y + putMatrixDataFromContents j jacS -- FIXME: I don't understand what this comment means -- Unsafe since the function will be called many times. [CU.exp| int{ 0 } |] -- cgit v1.2.3