[commit: ghc] wip/type-app: Test pushing into conditionals (5dc5624)

git at git.haskell.org git at git.haskell.org
Fri Aug 7 12:07:28 UTC 2015


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

On branch  : wip/type-app
Link       : http://ghc.haskell.org/trac/ghc/changeset/5dc5624964120799b1c84f2b37f00bb905fb80bc/ghc

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

commit 5dc5624964120799b1c84f2b37f00bb905fb80bc
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Wed Aug 5 13:17:38 2015 -0400

    Test pushing into conditionals


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

5dc5624964120799b1c84f2b37f00bb905fb80bc
 testsuite/tests/typecheck/should_compile/PushHRIf.hs | 7 +++++++
 testsuite/tests/typecheck/should_compile/all.T       | 1 +
 2 files changed, 8 insertions(+)

diff --git a/testsuite/tests/typecheck/should_compile/PushHRIf.hs b/testsuite/tests/typecheck/should_compile/PushHRIf.hs
new file mode 100644
index 0000000..f683913
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/PushHRIf.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE RankNTypes #-}
+
+module PushHRIf where
+
+foo = (if True then id else id) :: forall a. a -> a
+
+bar = (foo 'x', foo True)
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index 0b014c4..b334b00 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -468,3 +468,4 @@ test('T10564', normal, compile, [''])
 test('Vta1', normal, compile, [''])
 test('Vta2', normal, compile, [''])
 test('VtaInvis', normal, compile, [''])
+test('PushHRIf', normal, compile, [''])



More information about the ghc-commits mailing list