summaryrefslogtreecommitdiff
path: root/packages/hmatrix/src/Numeric/GSL/Internal.hs
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2014-05-08 13:43:07 +0200
committerAlberto Ruiz <aruiz@um.es>2014-05-08 13:43:07 +0200
commit551cf7498c33bc0948bb4cb8444ae6f8af7278ea (patch)
treeec86ff73151746f5e13b83549ea5c60ed442764d /packages/hmatrix/src/Numeric/GSL/Internal.hs
parent561a6c0e21bb77c21114ccbbd86d3af5ddb5a3f1 (diff)
separation ok
Diffstat (limited to 'packages/hmatrix/src/Numeric/GSL/Internal.hs')
-rw-r--r--packages/hmatrix/src/Numeric/GSL/Internal.hs62
1 files changed, 56 insertions, 6 deletions
diff --git a/packages/hmatrix/src/Numeric/GSL/Internal.hs b/packages/hmatrix/src/Numeric/GSL/Internal.hs
index 69a9750..a1c4e0c 100644
--- a/packages/hmatrix/src/Numeric/GSL/Internal.hs
+++ b/packages/hmatrix/src/Numeric/GSL/Internal.hs
@@ -1,23 +1,43 @@
1-- |
1-- Module : Numeric.GSL.Internal 2-- Module : Numeric.GSL.Internal
2-- Copyright : (c) Alberto Ruiz 2009 3-- Copyright : (c) Alberto Ruiz 2009
3-- License : GPL 4-- License : GPL
4-- 5-- Maintainer : Alberto Ruiz
5-- Maintainer : Alberto Ruiz (aruiz at um dot es)
6-- Stability : provisional 6-- Stability : provisional
7-- Portability : uses ffi 7--
8-- 8--
9-- Auxiliary functions. 9-- Auxiliary functions.
10-- 10--
11-- #hide
12 11
13module Numeric.GSL.Internal where
14 12
15import Data.Packed.Internal 13module Numeric.GSL.Internal(
14 iv,
15 mkVecfun,
16 mkVecVecfun,
17 mkDoubleVecVecfun,
18 mkDoublefun,
19 aux_vTov,
20 mkVecMatfun,
21 mkDoubleVecMatfun,
22 aux_vTom,
23 createV,
24 createMIO,
25 module Data.Packed.Development,
26 check,
27 Res,TV,TM,TCV,TCM
28) where
29
30import Data.Packed
31import Data.Packed.Development hiding (check)
32import Data.Complex
16 33
17import Foreign.Marshal.Array(copyArray) 34import Foreign.Marshal.Array(copyArray)
18import Foreign.Ptr(Ptr, FunPtr) 35import Foreign.Ptr(Ptr, FunPtr)
19import Foreign.C.Types 36import Foreign.C.Types
37import Foreign.C.String(peekCString)
20import System.IO.Unsafe(unsafePerformIO) 38import System.IO.Unsafe(unsafePerformIO)
39import Data.Vector.Storable(unsafeWith)
40import Control.Monad(when)
21 41
22iv :: (Vector Double -> Double) -> (CInt -> Ptr Double -> Double) 42iv :: (Vector Double -> Double) -> (CInt -> Ptr Double -> Double)
23iv f n p = f (createV (fromIntegral n) copy "iv") where 43iv f n p = f (createV (fromIntegral n) copy "iv") where
@@ -74,3 +94,33 @@ createMIO r c fun msg = do
74 res <- createMatrix RowMajor r c 94 res <- createMatrix RowMajor r c
75 app1 fun mat res msg 95 app1 fun mat res msg
76 return res 96 return res
97
98--------------------------------------------------------------------------------
99
100-- | check the error code
101check :: String -> IO CInt -> IO ()
102check msg f = do
103 err <- f
104 when (err/=0) $ do
105 ps <- gsl_strerror err
106 s <- peekCString ps
107 error (msg++": "++s)
108 return ()
109
110-- | description of GSL error codes
111foreign import ccall unsafe "gsl_strerror" gsl_strerror :: CInt -> IO (Ptr CChar)
112
113type PF = Ptr Float
114type PD = Ptr Double
115type PQ = Ptr (Complex Float)
116type PC = Ptr (Complex Double)
117
118type Res = IO CInt
119type TV x = CInt -> PD -> x
120type TM x = CInt -> CInt -> PD -> x
121type TCV x = CInt -> PC -> x
122type TCM x = CInt -> CInt -> PC -> x
123
124type TVV = TV (TV Res)
125type TVM = TV (TM Res)
126