[commit: ghc] ghc-7.8: Fix #8758 by assuming RankNTypes when checking GND code. (c032967)

git at git.haskell.org git at git.haskell.org
Mon Feb 17 09:15:15 UTC 2014


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

On branch  : ghc-7.8
Link       : http://ghc.haskell.org/trac/ghc/changeset/c0329679818f873ed65b23f4d7e1f72c8b2dd26a/ghc

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

commit c0329679818f873ed65b23f4d7e1f72c8b2dd26a
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Sun Feb 9 11:08:07 2014 -0500

    Fix #8758 by assuming RankNTypes when checking GND code.
    
    (cherry picked from commit 8cc398ff8b3f7408327d99347f440693cb204c0a)


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

c0329679818f873ed65b23f4d7e1f72c8b2dd26a
 compiler/typecheck/TcDeriv.lhs                    |    3 ++-
 testsuite/tests/deriving/should_compile/T8758.hs  |    9 +++++++++
 testsuite/tests/deriving/should_compile/T8758a.hs |    8 ++++++++
 testsuite/tests/deriving/should_compile/all.T     |    1 +
 4 files changed, 20 insertions(+), 1 deletion(-)

diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs
index f9f7c0a..8a4c19c 100644
--- a/compiler/typecheck/TcDeriv.lhs
+++ b/compiler/typecheck/TcDeriv.lhs
@@ -1969,7 +1969,8 @@ genInst standalone_deriv oflag comauxs
                     , iBinds  = InstBindings
                         { ib_binds = gen_Newtype_binds loc clas tvs tys rhs_ty
                         , ib_pragmas = []
-                        , ib_extensions = [Opt_ImpredicativeTypes]
+                        , ib_extensions = [ Opt_ImpredicativeTypes
+                                          , Opt_RankNTypes ]
                         , ib_standalone_deriving = standalone_deriv } }
                 , emptyBag
                 , Just $ getName $ head $ tyConDataCons rep_tycon ) }
diff --git a/testsuite/tests/deriving/should_compile/T8758.hs b/testsuite/tests/deriving/should_compile/T8758.hs
new file mode 100644
index 0000000..86c54c4
--- /dev/null
+++ b/testsuite/tests/deriving/should_compile/T8758.hs
@@ -0,0 +1,9 @@
+{-# LANGUAGE RankNTypes #-}
+
+module T8758 where
+
+class C m where
+  foo :: (forall b. b -> m b) -> c -> m c
+
+instance C [] where
+  foo f c = f c
\ No newline at end of file
diff --git a/testsuite/tests/deriving/should_compile/T8758a.hs b/testsuite/tests/deriving/should_compile/T8758a.hs
new file mode 100644
index 0000000..4b7fe44
--- /dev/null
+++ b/testsuite/tests/deriving/should_compile/T8758a.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+
+module T8758a where
+
+import T8758
+
+newtype MyList a = Mk [a]
+  deriving C
\ No newline at end of file
diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T
index 02b067e..a7cc3df 100644
--- a/testsuite/tests/deriving/should_compile/all.T
+++ b/testsuite/tests/deriving/should_compile/all.T
@@ -43,3 +43,4 @@ test('AutoDeriveTypeable', normal, compile, [''])
 
 test('T8138', reqlib('primitive'), compile, ['-O2'])
 test('T8631', normal, compile, [''])
+test('T8758', extra_clean(['T8758a.o', 'T8758a.hi']), multimod_compile, ['T8758a', '-v0'])
\ No newline at end of file



More information about the ghc-commits mailing list