summaryrefslogtreecommitdiff
path: root/examples/devel/example/wrappers.hs
diff options
context:
space:
mode:
Diffstat (limited to 'examples/devel/example/wrappers.hs')
-rw-r--r--examples/devel/example/wrappers.hs45
1 files changed, 45 insertions, 0 deletions
diff --git a/examples/devel/example/wrappers.hs b/examples/devel/example/wrappers.hs
new file mode 100644
index 0000000..f4e0f0b
--- /dev/null
+++ b/examples/devel/example/wrappers.hs
@@ -0,0 +1,45 @@
1{-# LANGUAGE ForeignFunctionInterface #-}
2{-# LANGUAGE TypeOperators #-}
3{-# LANGUAGE GADTs #-}
4
5{-
6 $ ghc -O2 wrappers.hs functions.c
7 $ ./wrappers
8-}
9
10import Numeric.LinearAlgebra
11import Numeric.LinearAlgebra.Devel
12import System.IO.Unsafe(unsafePerformIO)
13import Foreign.C.Types(CInt(..))
14import Foreign.Ptr(Ptr)
15
16
17infixl 1 #
18a # b = apply a b
19{-# INLINE (#) #-}
20
21infixr 5 :>, ::>
22type (:>) t r = CInt -> Ptr t -> r
23type (::>) t r = CInt -> CInt -> CInt -> CInt -> Ptr t -> r
24type Ok = IO CInt
25
26-----------------------------------------------------
27
28x = (3><5) [1..]
29
30main = do
31 print x
32 print $ myDiag x
33 print $ myDiag (tr x)
34
35-----------------------------------------------------
36foreign import ccall unsafe "c_diag" cDiag :: Double ::> Double :> Double ::> Ok
37
38myDiag m = unsafePerformIO $ do
39 y <- createVector (min r c)
40 z <- createMatrix RowMajor r c
41 cDiag # m # y # z #| "cDiag"
42 return (y,z)
43 where
44 (r,c) = size m
45