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

On branch  : master

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

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

commit bcbed05836149bbd56002a30216b41f0b69ed294
Author: Ian Lynagh <[email protected]>
Date:   Fri Sep 30 20:23:04 2011 +0100

    Add a test for newtypes and the FFI
    
    You can only use newtypes in the FFI if the constructor is visible

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

 tests/ffi/should_fail/Ccfail004A.hs    |    7 +++++++
 tests/ffi/should_fail/all.T            |    1 +
 tests/ffi/should_fail/ccfail004.hs     |   10 ++++++++++
 tests/ffi/should_fail/ccfail004.stderr |   16 ++++++++++++++++
 4 files changed, 34 insertions(+), 0 deletions(-)

diff --git a/tests/ffi/should_fail/Ccfail004A.hs 
b/tests/ffi/should_fail/Ccfail004A.hs
new file mode 100644
index 0000000..106c272
--- /dev/null
+++ b/tests/ffi/should_fail/Ccfail004A.hs
@@ -0,0 +1,7 @@
+
+module Ccfail004A (NInt, NIO) where
+
+newtype NInt = NInt Int
+
+newtype NIO a = NIO (IO a)
+
diff --git a/tests/ffi/should_fail/all.T b/tests/ffi/should_fail/all.T
index bc6ee95..4793379 100644
--- a/tests/ffi/should_fail/all.T
+++ b/tests/ffi/should_fail/all.T
@@ -6,3 +6,4 @@ test('ccfail001', only_compiler_types(['ghc']), compile_fail, 
[''])
 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'])
diff --git a/tests/ffi/should_fail/ccfail004.hs 
b/tests/ffi/should_fail/ccfail004.hs
new file mode 100644
index 0000000..5676d7c
--- /dev/null
+++ b/tests/ffi/should_fail/ccfail004.hs
@@ -0,0 +1,10 @@
+
+module Ccfail004 where
+
+import Ccfail004A
+
+-- Both these should be rejected as the NInt constructor isn't in scope
+foreign import ccall f1 :: NInt -> IO Int
+foreign import ccall f2 :: Int -> IO NInt
+foreign import ccall f3 :: Int -> NIO Int
+
diff --git a/tests/ffi/should_fail/ccfail004.stderr 
b/tests/ffi/should_fail/ccfail004.stderr
new file mode 100644
index 0000000..08e3f4f
--- /dev/null
+++ b/tests/ffi/should_fail/ccfail004.stderr
@@ -0,0 +1,16 @@
+
+ccfail004.hs:7:1:
+    Unacceptable argument type in foreign declaration: NInt
+    When checking declaration:
+      foreign import ccall safe "static f1" f1 :: NInt -> IO Int
+
+ccfail004.hs:8:1:
+    Unacceptable result type in foreign declaration: IO NInt
+    When checking declaration:
+      foreign import ccall safe "static f2" f2 :: Int -> IO NInt
+
+ccfail004.hs:9:1:
+    Unacceptable result type in foreign declaration: NIO Int
+    When checking declaration:
+      foreign import ccall safe "static f3" f3 :: Int -> NIO Int
+



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

Reply via email to