diff options
author | Alberto Ruiz <aruiz@um.es> | 2014-05-08 12:16:42 +0200 |
---|---|---|
committer | Alberto Ruiz <aruiz@um.es> | 2014-05-08 12:16:42 +0200 |
commit | 5992d92357cfd911c8f2e9f5faaa4fd8a323fd9a (patch) | |
tree | c6cdc40bc0121fd87a5137d8b7cb4d9f064cab47 /packages/hmatrix/src/Data/Packed/Foreign.hs | |
parent | d558f5165e7e7f4daffadae1197e53618727971d (diff) |
Data.Packed -> base (I)
Diffstat (limited to 'packages/hmatrix/src/Data/Packed/Foreign.hs')
-rw-r--r-- | packages/hmatrix/src/Data/Packed/Foreign.hs | 100 |
1 files changed, 0 insertions, 100 deletions
diff --git a/packages/hmatrix/src/Data/Packed/Foreign.hs b/packages/hmatrix/src/Data/Packed/Foreign.hs deleted file mode 100644 index 1ec3694..0000000 --- a/packages/hmatrix/src/Data/Packed/Foreign.hs +++ /dev/null | |||
@@ -1,100 +0,0 @@ | |||
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 | {-# OPTIONS_HADDOCK hide #-} | ||
10 | module Data.Packed.Foreign | ||
11 | ( app | ||
12 | , appVector, appVectorLen | ||
13 | , appMatrix, appMatrixLen, appMatrixRaw, appMatrixRawLen | ||
14 | , unsafeMatrixToVector, unsafeMatrixToForeignPtr | ||
15 | ) where | ||
16 | import Data.Packed.Internal | ||
17 | import qualified Data.Vector.Storable as S | ||
18 | import Foreign (Ptr, ForeignPtr, Storable) | ||
19 | import Foreign.C.Types (CInt) | ||
20 | import GHC.Base (IO(..), realWorld#) | ||
21 | |||
22 | {-# INLINE unsafeInlinePerformIO #-} | ||
23 | -- | 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 | ||
24 | -- unecessary calls to unsafePerformIO or its internals. | ||
25 | unsafeInlinePerformIO :: IO a -> a | ||
26 | unsafeInlinePerformIO (IO f) = case f realWorld# of | ||
27 | (# _, x #) -> x | ||
28 | |||
29 | {-# INLINE app #-} | ||
30 | -- | Only useful since it is left associated with a precedence of 1, unlike 'Prelude.$', which is right associative. | ||
31 | -- e.g. | ||
32 | -- | ||
33 | -- @ | ||
34 | -- someFunction | ||
35 | -- \`appMatrixLen\` m | ||
36 | -- \`appVectorLen\` v | ||
37 | -- \`app\` other | ||
38 | -- \`app\` arguments | ||
39 | -- \`app\` go here | ||
40 | -- @ | ||
41 | -- | ||
42 | -- One could also write: | ||
43 | -- | ||
44 | -- @ | ||
45 | -- (someFunction | ||
46 | -- \`appMatrixLen\` m | ||
47 | -- \`appVectorLen\` v) | ||
48 | -- other | ||
49 | -- arguments | ||
50 | -- (go here) | ||
51 | -- @ | ||
52 | -- | ||
53 | app :: (a -> b) -> a -> b | ||
54 | app f = f | ||
55 | |||
56 | {-# INLINE appVector #-} | ||
57 | appVector :: Storable a => (Ptr a -> b) -> Vector a -> b | ||
58 | appVector f x = unsafeInlinePerformIO (S.unsafeWith x (return . f)) | ||
59 | |||
60 | {-# INLINE appVectorLen #-} | ||
61 | appVectorLen :: Storable a => (CInt -> Ptr a -> b) -> Vector a -> b | ||
62 | appVectorLen f x = unsafeInlinePerformIO (S.unsafeWith x (return . f (fromIntegral (S.length x)))) | ||
63 | |||
64 | {-# INLINE appMatrix #-} | ||
65 | appMatrix :: Element a => (Ptr a -> b) -> Matrix a -> b | ||
66 | appMatrix f x = unsafeInlinePerformIO (S.unsafeWith (flatten x) (return . f)) | ||
67 | |||
68 | {-# INLINE appMatrixLen #-} | ||
69 | appMatrixLen :: Element a => (CInt -> CInt -> Ptr a -> b) -> Matrix a -> b | ||
70 | appMatrixLen f x = unsafeInlinePerformIO (S.unsafeWith (flatten x) (return . f r c)) | ||
71 | where | ||
72 | r = fromIntegral (rows x) | ||
73 | c = fromIntegral (cols x) | ||
74 | |||
75 | {-# INLINE appMatrixRaw #-} | ||
76 | appMatrixRaw :: Storable a => (Ptr a -> b) -> Matrix a -> b | ||
77 | appMatrixRaw f x = unsafeInlinePerformIO (S.unsafeWith (xdat x) (return . f)) | ||
78 | |||
79 | {-# INLINE appMatrixRawLen #-} | ||
80 | appMatrixRawLen :: Element a => (CInt -> CInt -> Ptr a -> b) -> Matrix a -> b | ||
81 | appMatrixRawLen f x = unsafeInlinePerformIO (S.unsafeWith (xdat x) (return . f r c)) | ||
82 | where | ||
83 | r = fromIntegral (rows x) | ||
84 | c = fromIntegral (cols x) | ||
85 | |||
86 | infixl 1 `app` | ||
87 | infixl 1 `appVector` | ||
88 | infixl 1 `appMatrix` | ||
89 | infixl 1 `appMatrixRaw` | ||
90 | |||
91 | {-# INLINE unsafeMatrixToVector #-} | ||
92 | -- | This will disregard the order of the matrix, and simply return it as-is. | ||
93 | -- If the order of the matrix is RowMajor, this function is identical to 'flatten'. | ||
94 | unsafeMatrixToVector :: Matrix a -> Vector a | ||
95 | unsafeMatrixToVector = xdat | ||
96 | |||
97 | {-# INLINE unsafeMatrixToForeignPtr #-} | ||
98 | unsafeMatrixToForeignPtr :: Storable a => Matrix a -> (ForeignPtr a, Int) | ||
99 | unsafeMatrixToForeignPtr m = S.unsafeToForeignPtr0 (xdat m) | ||
100 | |||