summaryrefslogtreecommitdiff
path: root/packages/hmatrix/src/Numeric/GSL/Internal.hs
diff options
context:
space:
mode:
Diffstat (limited to 'packages/hmatrix/src/Numeric/GSL/Internal.hs')
-rw-r--r--packages/hmatrix/src/Numeric/GSL/Internal.hs76
1 files changed, 76 insertions, 0 deletions
diff --git a/packages/hmatrix/src/Numeric/GSL/Internal.hs b/packages/hmatrix/src/Numeric/GSL/Internal.hs
new file mode 100644
index 0000000..69a9750
--- /dev/null
+++ b/packages/hmatrix/src/Numeric/GSL/Internal.hs
@@ -0,0 +1,76 @@
1-- Module : Numeric.GSL.Internal
2-- Copyright : (c) Alberto Ruiz 2009
3-- License : GPL
4--
5-- Maintainer : Alberto Ruiz (aruiz at um dot es)
6-- Stability : provisional
7-- Portability : uses ffi
8--
9-- Auxiliary functions.
10--
11-- #hide
12
13module Numeric.GSL.Internal where
14
15import Data.Packed.Internal
16
17import Foreign.Marshal.Array(copyArray)
18import Foreign.Ptr(Ptr, FunPtr)
19import Foreign.C.Types
20import System.IO.Unsafe(unsafePerformIO)
21
22iv :: (Vector Double -> Double) -> (CInt -> Ptr Double -> Double)
23iv f n p = f (createV (fromIntegral n) copy "iv") where
24 copy n' q = do
25 copyArray q p (fromIntegral n')
26 return 0
27
28-- | conversion of Haskell functions into function pointers that can be used in the C side
29foreign import ccall safe "wrapper"
30 mkVecfun :: (CInt -> Ptr Double -> Double)
31 -> IO( FunPtr (CInt -> Ptr Double -> Double))
32
33foreign import ccall safe "wrapper"
34 mkVecVecfun :: TVV -> IO (FunPtr TVV)
35
36foreign import ccall safe "wrapper"
37 mkDoubleVecVecfun :: (Double -> TVV) -> IO (FunPtr (Double -> TVV))
38
39foreign import ccall safe "wrapper"
40 mkDoublefun :: (Double -> Double) -> IO (FunPtr (Double -> Double))
41
42aux_vTov :: (Vector Double -> Vector Double) -> TVV
43aux_vTov f n p nr r = g where
44 v = f x
45 x = createV (fromIntegral n) copy "aux_vTov"
46 copy n' q = do
47 copyArray q p (fromIntegral n')
48 return 0
49 g = do unsafeWith v $ \p' -> copyArray r p' (fromIntegral nr)
50 return 0
51
52foreign import ccall safe "wrapper"
53 mkVecMatfun :: TVM -> IO (FunPtr TVM)
54
55foreign import ccall safe "wrapper"
56 mkDoubleVecMatfun :: (Double -> TVM) -> IO (FunPtr (Double -> TVM))
57
58aux_vTom :: (Vector Double -> Matrix Double) -> TVM
59aux_vTom f n p rr cr r = g where
60 v = flatten $ f x
61 x = createV (fromIntegral n) copy "aux_vTov"
62 copy n' q = do
63 copyArray q p (fromIntegral n')
64 return 0
65 g = do unsafeWith v $ \p' -> copyArray r p' (fromIntegral $ rr*cr)
66 return 0
67
68createV n fun msg = unsafePerformIO $ do
69 r <- createVector n
70 app1 fun vec r msg
71 return r
72
73createMIO r c fun msg = do
74 res <- createMatrix RowMajor r c
75 app1 fun mat res msg
76 return res