Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/c440bb002fc886b687f53ec1dddbaaf5871bcc71

>---------------------------------------------------------------

commit c440bb002fc886b687f53ec1dddbaaf5871bcc71
Author: Paolo Capriotti <[email protected]>
Date:   Tue Apr 3 10:41:08 2012 +0100

    Add testcase for #5664.

>---------------------------------------------------------------

 tests/ffi/should_fail/T5664.hs     |   25 +++++++++++++++++++++++++
 tests/ffi/should_fail/T5664.stderr |   13 +++++++++++++
 tests/ffi/should_fail/all.T        |    1 +
 3 files changed, 39 insertions(+), 0 deletions(-)

diff --git a/tests/ffi/should_fail/T5664.hs b/tests/ffi/should_fail/T5664.hs
new file mode 100644
index 0000000..4966f3a
--- /dev/null
+++ b/tests/ffi/should_fail/T5664.hs
@@ -0,0 +1,25 @@
+module T5664 where
+
+import Foreign
+import Foreign.C
+
+data D = D
+newtype I = I CInt
+
+foreign import ccall "dynamic"
+  mkFun1 :: FunPtr (CInt -> IO ()) -> CInt -> IO ()
+
+foreign import ccall "dynamic"
+  mkFun2 :: FunPtr (I -> IO ()) -> CInt -> IO ()
+
+foreign import ccall "dynamic"
+  mkFun3 :: FunPtr (D -> IO ()) -> CInt -> IO ()
+
+foreign import ccall "wrapper"
+  mkCallBack1 :: IO CInt -> IO (FunPtr (IO CInt))
+
+foreign import ccall "wrapper"
+  mkCallBack2 :: IO CInt -> IO (FunPtr (IO I))
+
+foreign import ccall "wrapper"
+  mkCallBack3 :: IO CInt -> IO (FunPtr (IO D))
diff --git a/tests/ffi/should_fail/T5664.stderr 
b/tests/ffi/should_fail/T5664.stderr
new file mode 100644
index 0000000..30bd017
--- /dev/null
+++ b/tests/ffi/should_fail/T5664.stderr
@@ -0,0 +1,13 @@
+
+T5664.hs:15:1:
+    Unacceptable argument type in foreign declaration:
+      FunPtr (D -> IO ())
+    When checking declaration:
+      foreign import ccall safe "dynamic" mkFun3
+        :: FunPtr (D -> IO ()) -> CInt -> IO ()
+
+T5664.hs:24:1:
+    Unacceptable result type in foreign declaration: IO (FunPtr (IO D))
+    When checking declaration:
+      foreign import ccall safe "wrapper" mkCallBack3
+        :: IO CInt -> IO (FunPtr (IO D))
diff --git a/tests/ffi/should_fail/all.T b/tests/ffi/should_fail/all.T
index 188ef99..8da2702 100644
--- a/tests/ffi/should_fail/all.T
+++ b/tests/ffi/should_fail/all.T
@@ -10,3 +10,4 @@ test('ccfail004', only_compiler_types(['ghc']), 
multimod_compile_fail, ['ccfail0
 test('ccfail005', only_compiler_types(['ghc']), compile_fail, [''])
 test('ccall_value', normal, compile_fail, [''])
 test('capi_value_function', normal, compile_fail, [''])
+test('T5664', normal, compile_fail, ['-v0'])



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to