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

On branch  : master

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

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

commit a5181856ac58816b057a07bbb027d113369e0439
Author: Ian Lynagh <[email protected]>
Date:   Fri Sep 30 23:29:36 2011 +0100

    Add a test for types of GHC FFI primitive imports

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

 tests/ffi/should_compile/all.T    |    1 +
 tests/ffi/should_compile/cc016.hs |   15 +++++++++++++++
 2 files changed, 16 insertions(+), 0 deletions(-)

diff --git a/tests/ffi/should_compile/all.T b/tests/ffi/should_compile/all.T
index 0c97827..f4b4cdd 100644
--- a/tests/ffi/should_compile/all.T
+++ b/tests/ffi/should_compile/all.T
@@ -37,3 +37,4 @@ test('1357', normal, compile, [''])
 test('3624', normal, compile, [''])
 test('3742', normal, compile, [''])
 test('cc015', normal, compile, [''])
+test('cc016', normal, compile, [''])
diff --git a/tests/ffi/should_compile/cc016.hs 
b/tests/ffi/should_compile/cc016.hs
new file mode 100644
index 0000000..549dc15
--- /dev/null
+++ b/tests/ffi/should_compile/cc016.hs
@@ -0,0 +1,15 @@
+
+{-# LANGUAGE TypeFamilies, GHCForeignImportPrim, MagicHash,
+             UnliftedFFITypes #-}
+
+module Cc015 where
+
+import Foreign
+import Foreign.C.Types
+import GHC.Prim
+
+type family F a
+type instance F Int = Int# -> Int#
+
+foreign import prim "f" f :: F Int
+



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

Reply via email to