diff options
author | Alberto Ruiz <aruiz@um.es> | 2013-06-24 07:37:40 -0700 |
---|---|---|
committer | Alberto Ruiz <aruiz@um.es> | 2013-06-24 07:37:40 -0700 |
commit | 2c06aabae5d50164ae520c70c9dc61aefc09cb72 (patch) | |
tree | 1a2a6780d40b04fde19c8b6a407ecec1542fee3d | |
parent | ea2e0fad701d6dcacc99a17034d68ccb11532e43 (diff) | |
parent | 027fa6391bc7b21a8aecbdc577ad485aee274333 (diff) |
Merge pull request #43 from mikeplus64/master
Add FFI helpers
-rw-r--r-- | hmatrix.cabal | 1 | ||||
-rw-r--r-- | lib/Data/Packed/Foreign.hs | 99 | ||||
-rw-r--r-- | lib/Data/Packed/Internal/Matrix.hs | 10 |
3 files changed, 104 insertions, 6 deletions
diff --git a/hmatrix.cabal b/hmatrix.cabal index 800e7b0..65cdce9 100644 --- a/hmatrix.cabal +++ b/hmatrix.cabal | |||
@@ -98,6 +98,7 @@ library | |||
98 | Exposed-modules: Data.Packed, | 98 | Exposed-modules: Data.Packed, |
99 | Data.Packed.Vector, | 99 | Data.Packed.Vector, |
100 | Data.Packed.Matrix, | 100 | Data.Packed.Matrix, |
101 | Data.Packed.Foreign, | ||
101 | Numeric.GSL.Differentiation, | 102 | Numeric.GSL.Differentiation, |
102 | Numeric.GSL.Integration, | 103 | Numeric.GSL.Integration, |
103 | Numeric.GSL.Fourier, | 104 | Numeric.GSL.Fourier, |
diff --git a/lib/Data/Packed/Foreign.hs b/lib/Data/Packed/Foreign.hs new file mode 100644 index 0000000..efa51ca --- /dev/null +++ b/lib/Data/Packed/Foreign.hs | |||
@@ -0,0 +1,99 @@ | |||
1 | {-# LANGUAGE MagicHash, UnboxedTuples #-} | ||
2 | -- | FFI and hmatrix helpers. | ||
3 | -- | ||
4 | -- Sample usage, to upload a perspective matrix to a shader. | ||
5 | -- | ||
6 | -- @ glUniformMatrix4fv 0 1 (fromIntegral gl_TRUE) \`appMatrix\` perspective 0.01 100 (pi\/2) (4\/3) | ||
7 | -- @ | ||
8 | -- | ||
9 | module Data.Packed.Foreign | ||
10 | ( app | ||
11 | , appVector, appVectorLen | ||
12 | , appMatrix, appMatrixLen, appMatrixRaw, appMatrixRawLen | ||
13 | , unsafeMatrixToVector, unsafeMatrixToForeignPtr | ||
14 | ) where | ||
15 | import Data.Packed.Internal | ||
16 | import qualified Data.Vector.Storable as S | ||
17 | import Foreign (Ptr, ForeignPtr, Storable) | ||
18 | import Foreign.C.Types (CInt) | ||
19 | import GHC.Base (IO(..), realWorld#) | ||
20 | |||
21 | {-# INLINE unsafeInlinePerformIO #-} | ||
22 | -- | If we use unsafePerformIO, it may not get inlined, so in a function that returns IO (which are all safe uses of app* in this module), there would be | ||
23 | -- unecessary calls to unsafePerformIO or its internals. | ||
24 | unsafeInlinePerformIO :: IO a -> a | ||
25 | unsafeInlinePerformIO (IO f) = case f realWorld# of | ||
26 | (# _, x #) -> x | ||
27 | |||
28 | {-# INLINE app #-} | ||
29 | -- | Only useful since it is left associated with a precedence of 1, unlike 'Prelude.$', which is right associative. | ||
30 | -- e.g. | ||
31 | -- | ||
32 | -- @ | ||
33 | -- someFunction | ||
34 | -- \`appMatrixLen\` m | ||
35 | -- \`appVectorLen\` v | ||
36 | -- \`app\` other | ||
37 | -- \`app\` arguments | ||
38 | -- \`app\` go here | ||
39 | -- @ | ||
40 | -- | ||
41 | -- One could also write: | ||
42 | -- | ||
43 | -- @ | ||
44 | -- (someFunction | ||
45 | -- \`appMatrixLen\` m | ||
46 | -- \`appVectorLen\` v) | ||
47 | -- other | ||
48 | -- arguments | ||
49 | -- (go here) | ||
50 | -- @ | ||
51 | -- | ||
52 | app :: (a -> b) -> a -> b | ||
53 | app f = f | ||
54 | |||
55 | {-# INLINE appVector #-} | ||
56 | appVector :: Storable a => (Ptr a -> b) -> Vector a -> b | ||
57 | appVector f x = unsafeInlinePerformIO (S.unsafeWith x (return . f)) | ||
58 | |||
59 | {-# INLINE appVectorLen #-} | ||
60 | appVectorLen :: Storable a => (CInt -> Ptr a -> b) -> Vector a -> b | ||
61 | appVectorLen f x = unsafeInlinePerformIO (S.unsafeWith x (return . f (fromIntegral (S.length x)))) | ||
62 | |||
63 | {-# INLINE appMatrix #-} | ||
64 | appMatrix :: Element a => (Ptr a -> b) -> Matrix a -> b | ||
65 | appMatrix f x = unsafeInlinePerformIO (S.unsafeWith (flatten x) (return . f)) | ||
66 | |||
67 | {-# INLINE appMatrixLen #-} | ||
68 | appMatrixLen :: Element a => (CInt -> CInt -> Ptr a -> b) -> Matrix a -> b | ||
69 | appMatrixLen f x = unsafeInlinePerformIO (S.unsafeWith (flatten x) (return . f r c)) | ||
70 | where | ||
71 | r = fromIntegral (rows x) | ||
72 | c = fromIntegral (cols x) | ||
73 | |||
74 | {-# INLINE appMatrixRaw #-} | ||
75 | appMatrixRaw :: Storable a => (Ptr a -> b) -> Matrix a -> b | ||
76 | appMatrixRaw f x = unsafeInlinePerformIO (S.unsafeWith (xdat x) (return . f)) | ||
77 | |||
78 | {-# INLINE appMatrixRawLen #-} | ||
79 | appMatrixRawLen :: Element a => (CInt -> CInt -> Ptr a -> b) -> Matrix a -> b | ||
80 | appMatrixRawLen f x = unsafeInlinePerformIO (S.unsafeWith (xdat x) (return . f r c)) | ||
81 | where | ||
82 | r = fromIntegral (rows x) | ||
83 | c = fromIntegral (cols x) | ||
84 | |||
85 | infixl 1 `app` | ||
86 | infixl 1 `appVector` | ||
87 | infixl 1 `appMatrix` | ||
88 | infixl 1 `appMatrixRaw` | ||
89 | |||
90 | {-# INLINE unsafeMatrixToVector #-} | ||
91 | -- | This will disregard the order of the matrix, and simply return it as-is. | ||
92 | -- If the order of the matrix is RowMajor, this function is identical to 'flatten'. | ||
93 | unsafeMatrixToVector :: Matrix a -> Vector a | ||
94 | unsafeMatrixToVector = xdat | ||
95 | |||
96 | {-# INLINE unsafeMatrixToForeignPtr #-} | ||
97 | unsafeMatrixToForeignPtr :: Storable a => Matrix a -> (ForeignPtr a, Int) | ||
98 | unsafeMatrixToForeignPtr m = S.unsafeToForeignPtr0 (xdat m) | ||
99 | |||
diff --git a/lib/Data/Packed/Internal/Matrix.hs b/lib/Data/Packed/Internal/Matrix.hs index 367c189..255009c 100644 --- a/lib/Data/Packed/Internal/Matrix.hs +++ b/lib/Data/Packed/Internal/Matrix.hs | |||
@@ -132,12 +132,10 @@ mat a f = | |||
132 | let m g = do | 132 | let m g = do |
133 | g (fi (rows a)) (fi (cols a)) p | 133 | g (fi (rows a)) (fi (cols a)) p |
134 | f m | 134 | f m |
135 | 135 | -- | Creates a vector by concatenation of rows. If the matrix is ColumnMajor, this operation requires a transpose. | |
136 | {- | Creates a vector by concatenation of rows | 136 | -- |
137 | 137 | -- @\> flatten ('ident' 3) | |
138 | @\> flatten ('ident' 3) | 138 | -- 9 |> [1.0,0.0,0.0,0.0,1.0,0.0,0.0,0.0,1.0]@ |
139 | 9 |> [1.0,0.0,0.0,0.0,1.0,0.0,0.0,0.0,1.0]@ | ||
140 | -} | ||
141 | flatten :: Element t => Matrix t -> Vector t | 139 | flatten :: Element t => Matrix t -> Vector t |
142 | flatten = xdat . cmat | 140 | flatten = xdat . cmat |
143 | 141 | ||