[commit: ghc] wip/ghc-8.8-merges: Test that hsc2hs works with promoted data constructors (805681e)

git at git.haskell.org git at git.haskell.org
Thu Feb 21 15:08:46 UTC 2019


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/ghc-8.8-merges
Link       : http://ghc.haskell.org/trac/ghc/changeset/805681e816a8677e341144d596d65edd29866246/ghc

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

commit 805681e816a8677e341144d596d65edd29866246
Author: Andrew Martin <andrew.thaddeus at gmail.com>
Date:   Mon Jan 21 16:04:30 2019 -0500

    Test that hsc2hs works with promoted data constructors
    
    (cherry picked from commit 79a5afb613235e93bc2c580987595b9c1324db15)


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

805681e816a8677e341144d596d65edd29866246
 testsuite/tests/hsc2hs/Makefile   |  5 +++++
 testsuite/tests/hsc2hs/T11004.hsc | 13 +++++++++++++
 testsuite/tests/hsc2hs/all.T      |  2 ++
 utils/hsc2hs                      |  2 +-
 4 files changed, 21 insertions(+), 1 deletion(-)

diff --git a/testsuite/tests/hsc2hs/Makefile b/testsuite/tests/hsc2hs/Makefile
index b0751f1..9291e4b 100644
--- a/testsuite/tests/hsc2hs/Makefile
+++ b/testsuite/tests/hsc2hs/Makefile
@@ -41,6 +41,11 @@ T10272:
 	'$(TEST_HC)' $(TEST_HC_OPTS) -v0 --make $@
 	./$@
 
+.PHONY: T11004
+T11004:
+	LANG=C '$(HSC2HS)' $@.hsc
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c $@.hs
+
 .PHONY: T12504
 T12504:
 	'$(HSC2HS)' T12504/path/to/$@.hsc
diff --git a/testsuite/tests/hsc2hs/T11004.hsc b/testsuite/tests/hsc2hs/T11004.hsc
new file mode 100644
index 0000000..796d35a
--- /dev/null
+++ b/testsuite/tests/hsc2hs/T11004.hsc
@@ -0,0 +1,13 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE KindSignatures #-}
+
+module T11004 where
+
+import Data.Kind (Type)
+
+data Foo = Foo' | Bar
+
+data Indexed :: Foo -> Type where
+  IndexedA :: Indexed ' Foo'
+  IndexedB :: Indexed 'Bar
diff --git a/testsuite/tests/hsc2hs/all.T b/testsuite/tests/hsc2hs/all.T
index f237d9a..d42f385 100644
--- a/testsuite/tests/hsc2hs/all.T
+++ b/testsuite/tests/hsc2hs/all.T
@@ -14,6 +14,8 @@ test('T4340', [], run_command, ['$MAKE -s --no-print-directory T4340'])
 
 test('T10272', [], run_command, ['$MAKE -s --no-print-directory T10272'])
 
+test('T11004', [], run_command, ['$MAKE -s --no-print-directory T11004'])
+
 test('T12504', [extra_files(['T12504']), ignore_stdout], run_command,
      ['$MAKE -s --no-print-directory T12504'])
 
diff --git a/utils/hsc2hs b/utils/hsc2hs
index a816333..fac8b62 160000
--- a/utils/hsc2hs
+++ b/utils/hsc2hs
@@ -1 +1 @@
-Subproject commit a816333ae67c54b98cce4ed22621242714967b3e
+Subproject commit fac8b62e48f4c99cfe8f3efff63c8fcd94b2a1d6



More information about the ghc-commits mailing list