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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/71ed5be91d35f3ba0a6786f89a1571a420e15581

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

commit 71ed5be91d35f3ba0a6786f89a1571a420e15581
Author: Ian Lynagh <[email protected]>
Date:   Sat Oct 1 13:31:00 2011 +0100

    Add a test highlighting a messy case for FFI type errors

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

 tests/ffi/should_fail/all.T            |    1 +
 tests/ffi/should_fail/ccfail005.hs     |   16 ++++++++++++++++
 tests/ffi/should_fail/ccfail005.stderr |   10 ++++++++++
 3 files changed, 27 insertions(+), 0 deletions(-)

diff --git a/tests/ffi/should_fail/all.T b/tests/ffi/should_fail/all.T
index 4793379..abba1b5 100644
--- a/tests/ffi/should_fail/all.T
+++ b/tests/ffi/should_fail/all.T
@@ -7,3 +7,4 @@ test('ccfail002', only_compiler_types(['ghc']), compile_fail, 
[''])
 test('ccfail003', only_compiler_types(['ghc']), compile_fail, [''])
 test('T3066', only_compiler_types(['ghc']), compile_fail, [''])
 test('ccfail004', only_compiler_types(['ghc']), multimod_compile_fail, 
['ccfail004', '-v0'])
+test('ccfail005', only_compiler_types(['ghc']), compile_fail, [''])
diff --git a/tests/ffi/should_fail/ccfail005.hs 
b/tests/ffi/should_fail/ccfail005.hs
new file mode 100644
index 0000000..3ba29a6
--- /dev/null
+++ b/tests/ffi/should_fail/ccfail005.hs
@@ -0,0 +1,16 @@
+
+{-# LANGUAGE TypeFamilies #-}
+
+module Ccfail005 where
+
+type family F a
+type instance F Bool = D -> IO Int
+type instance F Char = Int -> IO D
+data D = D
+
+-- These should be rejected as D isn't a type we can use with the FFI.
+-- Note that, in the signature the user writes, there aren't an
+-- "argument type" and "result type" to complain about, though.
+foreign import ccall f1 :: F Bool
+foreign import ccall f2 :: F Char
+
diff --git a/tests/ffi/should_fail/ccfail005.stderr 
b/tests/ffi/should_fail/ccfail005.stderr
new file mode 100644
index 0000000..0d96fe9
--- /dev/null
+++ b/tests/ffi/should_fail/ccfail005.stderr
@@ -0,0 +1,10 @@
+
+ccfail005.hs:14:1:
+    Unacceptable argument type in foreign declaration: D
+    When checking declaration:
+      foreign import ccall safe "static f1" f1 :: F Bool
+
+ccfail005.hs:15:1:
+    Unacceptable result type in foreign declaration: IO D
+    When checking declaration:
+      foreign import ccall safe "static f2" f2 :: F Char



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

Reply via email to