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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/2ab4055320275256d4f4036e93d8ca778a1307e7

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

commit 2ab4055320275256d4f4036e93d8ca778a1307e7
Author: Ian Lynagh <[email protected]>
Date:   Fri Sep 30 20:27:50 2011 +0100

    Add another case to cc015

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

 tests/ffi/should_compile/cc015.hs |    6 ++++++
 1 files changed, 6 insertions(+), 0 deletions(-)

diff --git a/tests/ffi/should_compile/cc015.hs 
b/tests/ffi/should_compile/cc015.hs
index df724e0..f6aad23 100644
--- a/tests/ffi/should_compile/cc015.hs
+++ b/tests/ffi/should_compile/cc015.hs
@@ -3,6 +3,8 @@
 
 module Cc015 where
 
+import Foreign.C
+
 type S a = a
 type IOS a = IO a
 
@@ -15,6 +17,7 @@ newtype G1F = G1F (F (S Int))
 newtype G2  = G2  Char
 newtype G3  = G3  (IO Int)
 newtype G4  = G4  G3
+newtype NIO a = NIO (IO a)
 
 -- Type synonyms should be transparent to the typechecker
 foreign import ccall f1      :: S Int -> IOS Int
@@ -28,4 +31,7 @@ foreign export ccall "g3" f3 :: G1 -> G2 -> G4
 -- And a combination
 foreign import ccall f4      :: G1F -> F Bool -> S G4
 foreign export ccall "g4" f4 :: G1F -> F Bool -> S G4
+-- And a newtyped IO
+foreign import ccall f5      :: NIO Int
+foreign export ccall "g5" f5 :: NIO Int
 



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

Reply via email to