diff options
Diffstat (limited to 'lib/Data')
-rw-r--r-- | lib/Data/Packed/Foreign.hs | 13 |
1 files changed, 10 insertions, 3 deletions
diff --git a/lib/Data/Packed/Foreign.hs b/lib/Data/Packed/Foreign.hs index a94a979..efa51ca 100644 --- a/lib/Data/Packed/Foreign.hs +++ b/lib/Data/Packed/Foreign.hs | |||
@@ -6,7 +6,12 @@ | |||
6 | -- @ glUniformMatrix4fv 0 1 (fromIntegral gl_TRUE) \`appMatrix\` perspective 0.01 100 (pi\/2) (4\/3) | 6 | -- @ glUniformMatrix4fv 0 1 (fromIntegral gl_TRUE) \`appMatrix\` perspective 0.01 100 (pi\/2) (4\/3) |
7 | -- @ | 7 | -- @ |
8 | -- | 8 | -- |
9 | module Data.Packed.Foreign where | 9 | module Data.Packed.Foreign |
10 | ( app | ||
11 | , appVector, appVectorLen | ||
12 | , appMatrix, appMatrixLen, appMatrixRaw, appMatrixRawLen | ||
13 | , unsafeMatrixToVector, unsafeMatrixToForeignPtr | ||
14 | ) where | ||
10 | import Data.Packed.Internal | 15 | import Data.Packed.Internal |
11 | import qualified Data.Vector.Storable as S | 16 | import qualified Data.Vector.Storable as S |
12 | import Foreign (Ptr, ForeignPtr, Storable) | 17 | import Foreign (Ptr, ForeignPtr, Storable) |
@@ -14,6 +19,8 @@ import Foreign.C.Types (CInt) | |||
14 | import GHC.Base (IO(..), realWorld#) | 19 | import GHC.Base (IO(..), realWorld#) |
15 | 20 | ||
16 | {-# INLINE unsafeInlinePerformIO #-} | 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. | ||
17 | unsafeInlinePerformIO :: IO a -> a | 24 | unsafeInlinePerformIO :: IO a -> a |
18 | unsafeInlinePerformIO (IO f) = case f realWorld# of | 25 | unsafeInlinePerformIO (IO f) = case f realWorld# of |
19 | (# _, x #) -> x | 26 | (# _, x #) -> x |
@@ -65,8 +72,8 @@ appMatrixLen f x = unsafeInlinePerformIO (S.unsafeWith (flatten x) (return . f r | |||
65 | c = fromIntegral (cols x) | 72 | c = fromIntegral (cols x) |
66 | 73 | ||
67 | {-# INLINE appMatrixRaw #-} | 74 | {-# INLINE appMatrixRaw #-} |
68 | appMatrixRaw :: Storable a => Matrix a -> (Ptr a -> b) -> b | 75 | appMatrixRaw :: Storable a => (Ptr a -> b) -> Matrix a -> b |
69 | appMatrixRaw x f = unsafeInlinePerformIO (S.unsafeWith (xdat x) (return . f)) | 76 | appMatrixRaw f x = unsafeInlinePerformIO (S.unsafeWith (xdat x) (return . f)) |
70 | 77 | ||
71 | {-# INLINE appMatrixRawLen #-} | 78 | {-# INLINE appMatrixRawLen #-} |
72 | appMatrixRawLen :: Element a => (CInt -> CInt -> Ptr a -> b) -> Matrix a -> b | 79 | appMatrixRawLen :: Element a => (CInt -> CInt -> Ptr a -> b) -> Matrix a -> b |