[commit: ghc] master: Beef up tc124 (1251518)
git at git.haskell.org
git at git.haskell.org
Fri Feb 12 17:35:44 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/125151870de63de4a227afc2c1e38802009bc7e5/ghc
>---------------------------------------------------------------
commit 125151870de63de4a227afc2c1e38802009bc7e5
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Fri Feb 12 13:41:39 2016 +0000
Beef up tc124
Makes it a slightly more stringent test of record pattern bindings
>---------------------------------------------------------------
125151870de63de4a227afc2c1e38802009bc7e5
testsuite/tests/typecheck/should_compile/tc124.hs | 14 ++++++++++----
1 file changed, 10 insertions(+), 4 deletions(-)
diff --git a/testsuite/tests/typecheck/should_compile/tc124.hs b/testsuite/tests/typecheck/should_compile/tc124.hs
index 658b29c..a832cd3 100644
--- a/testsuite/tests/typecheck/should_compile/tc124.hs
+++ b/testsuite/tests/typecheck/should_compile/tc124.hs
@@ -7,13 +7,19 @@
module Foo where
-data T = T { t1 :: forall a. a -> a , t2 :: forall a b. a->b->b }
+data T = T { t1 :: forall a. a -> a
+ , t2 :: forall b c. b->c->c }
-- Test pattern bindings for polymorphic fields
-f :: T -> (Int,Char)
-f t = let T { t1 = my_t1 } = t
+f :: T -> (Int,Char, Char)
+f t = let T { t1 = my_t1, t2 = my_t2 } = t
in
- (my_t1 3, my_t1 'c')
+ (my_t1 3, my_t1 'c', my_t2 2 'c')
+
+f2 :: T -> (Int,Char, Char)
+f2 t = let T { t1 = my_t1, t2 = my_t2 } = t
+ in
+ (my_t1 3, my_t1 'c', my_t2 2 'c')
-- Test record update with polymorphic fields
g :: T -> T
More information about the ghc-commits
mailing list