[commit: ghc] wip/T2893: Add test for Trac #14835 (36bae41)

git at git.haskell.org git at git.haskell.org
Tue Feb 27 13:49:59 UTC 2018


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

On branch  : wip/T2893
Link       : http://ghc.haskell.org/trac/ghc/changeset/36bae41c5e7abf8895e515e295aabac22a6d67df/ghc

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

commit 36bae41c5e7abf8895e515e295aabac22a6d67df
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Tue Feb 27 13:49:37 2018 +0000

    Add test for Trac #14835


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

36bae41c5e7abf8895e515e295aabac22a6d67df
 .../tests/{ado => quantified-constraints}/Makefile     |  0
 .../quantified-constraints/{T14833.hs => T14835.hs}    | 18 +++++-------------
 testsuite/tests/quantified-constraints/all.T           |  1 +
 3 files changed, 6 insertions(+), 13 deletions(-)

diff --git a/testsuite/tests/ado/Makefile b/testsuite/tests/quantified-constraints/Makefile
similarity index 100%
copy from testsuite/tests/ado/Makefile
copy to testsuite/tests/quantified-constraints/Makefile
diff --git a/testsuite/tests/quantified-constraints/T14833.hs b/testsuite/tests/quantified-constraints/T14835.hs
similarity index 65%
copy from testsuite/tests/quantified-constraints/T14833.hs
copy to testsuite/tests/quantified-constraints/T14835.hs
index 6e70196..de9b450 100644
--- a/testsuite/tests/quantified-constraints/T14833.hs
+++ b/testsuite/tests/quantified-constraints/T14835.hs
@@ -5,7 +5,7 @@
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE QuantifiedConstraints #-}
 {-# LANGUAGE UndecidableInstances #-}
-module T14833 where
+module Bug where
 
 data Dict c where
   Dict :: c => Dict c
@@ -13,16 +13,8 @@ data Dict c where
 class    (a => b) => Implies a b
 instance (a => b) => Implies a b
 
--- Works ok
-iota1 :: (() => a) => Dict a
-iota1 = Dict
+curryC1 :: ((a, b) => c) => Dict (Implies a (Implies b c))
+curryC1 = Dict
 
-iota2 :: Implies () a => Dict a
-iota2 = Dict
-
-{-
-[G] Implies () a
-[G] (() => a)      -- By superclass
-
-[W] a
--}
\ No newline at end of file
+curryC2 :: Implies (a, b) c => Dict (Implies a (Implies b c))
+curryC2 = Dict
diff --git a/testsuite/tests/quantified-constraints/all.T b/testsuite/tests/quantified-constraints/all.T
index 9e69942..b67ec99 100644
--- a/testsuite/tests/quantified-constraints/all.T
+++ b/testsuite/tests/quantified-constraints/all.T
@@ -1,4 +1,5 @@
 
 test('T14833', normal, compile, [''])
+test('T14835', normal, compile, [''])
 test('T2893', normal, compile, [''])
 test('T2893a', normal, compile, [''])



More information about the ghc-commits mailing list