[commit: ghc] master: Fix #15828, from `More explicit foralls` (fe57a5b)

git at git.haskell.org git at git.haskell.org
Fri Nov 30 00:45:33 UTC 2018


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/fe57a5bae3f8cb87637359f615c77f4afae86d46/ghc

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

commit fe57a5bae3f8cb87637359f615c77f4afae86d46
Author: Matthew Yacavone <matthew at yacavone.net>
Date:   Thu Nov 29 18:42:39 2018 -0500

    Fix #15828, from `More explicit foralls`
    
    Summary:
    Fix a bug in commit 12eeb9 which permits the following:
    
    ```
    class C a where
      type T a b
    instance C (Maybe a) where
      type forall a b. T (Maybe a) b = b
    ```
    
    where instead, the user should write:
    
    ```
    instance C (Maybe a) where
      type forall b. T (Maybe a) b = b
    ```
    
    Update the users guide to discuss scoping of type variables in
    explicit foralls in type family instances.
    
    Test Plan: validate
    
    Reviewers: bgamari, goldfire, monoidal
    
    Reviewed By: goldfire
    
    Subscribers: monoidal, rwbarton, carter
    
    GHC Trac Issues: #15828
    
    Differential Revision: https://phabricator.haskell.org/D5283


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

fe57a5bae3f8cb87637359f615c77f4afae86d46
 compiler/rename/RnSource.hs                      | 7 ++++++-
 docs/users_guide/glasgow_exts.rst                | 6 +++---
 testsuite/tests/rename/should_fail/T15828.hs     | 9 +++++++++
 testsuite/tests/rename/should_fail/T15828.stderr | 9 +++++++++
 testsuite/tests/rename/should_fail/all.T         | 1 +
 5 files changed, 28 insertions(+), 4 deletions(-)

diff --git a/compiler/rename/RnSource.hs b/compiler/rename/RnSource.hs
index 7a205ba..6027110 100644
--- a/compiler/rename/RnSource.hs
+++ b/compiler/rename/RnSource.hs
@@ -738,7 +738,12 @@ rnFamInstEqn doc mb_cls rhs_kvars
        ; ((bndrs', pats', payload'), fvs)
               <- bindLocalNamesFV all_imp_var_names $
                  bindLHsTyVarBndrs doc (Just $ inHsDocContext doc)
-                                   mb_cls bndrs $ \bndrs' ->
+                                   Nothing bndrs $ \bndrs' ->
+                 -- Note: If we pass mb_cls instead of Nothing here,
+                 --  bindLHsTyVarBndrs will use class variables for any names
+                 --  the user meant to bring in scope here. This is an explicit
+                 --  forall, so we want fresh names, not class variables.
+                 --  Thus: always pass Nothing
                  do { (pats', pat_fvs) <- rnLHsTypes (FamPatCtx tycon) pats
                     ; (payload', rhs_fvs) <- rn_payload doc payload
 
diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst
index a07adf3..9b8df91 100644
--- a/docs/users_guide/glasgow_exts.rst
+++ b/docs/users_guide/glasgow_exts.rst
@@ -7577,9 +7577,9 @@ the left hand side can be explicitly bound. For example: ::
   
     data instance forall a (b :: Proxy a). F (Proxy b) = FProxy Bool
 
-When an explicit ``forall`` is present, all *type* variables mentioned must
-be bound by the ``forall``. Kind variables will be implicitly bound if
-necessary, for example: ::
+When an explicit ``forall`` is present, all *type* variables mentioned which
+are not already in scope must be bound by the ``forall``. Kind variables will
+be implicitly bound if necessary, for example: ::
   
     data instance forall (a :: k). F a = FOtherwise
 
diff --git a/testsuite/tests/rename/should_fail/T15828.hs b/testsuite/tests/rename/should_fail/T15828.hs
new file mode 100644
index 0000000..90c0621
--- /dev/null
+++ b/testsuite/tests/rename/should_fail/T15828.hs
@@ -0,0 +1,9 @@
+{-# LANGUAGE TypeFamilies, ExplicitForAll #-}
+
+module T15828 where
+
+class C a where
+  type T a b
+
+instance C (Maybe a) where
+  type forall a b. T (Maybe a) b = b
diff --git a/testsuite/tests/rename/should_fail/T15828.stderr b/testsuite/tests/rename/should_fail/T15828.stderr
new file mode 100644
index 0000000..aca2542
--- /dev/null
+++ b/testsuite/tests/rename/should_fail/T15828.stderr
@@ -0,0 +1,9 @@
+
+T15828.hs:9:20: error:
+    • Type indexes must match class instance head
+      Expected: T (Maybe a1) <tv>
+        Actual: T (Maybe a) b
+      where the `<tv>' arguments are type variables,
+      distinct from each other and from the instance variables
+    • In the type instance declaration for ‘T’
+      In the instance declaration for ‘C (Maybe a)’
\ No newline at end of file
diff --git a/testsuite/tests/rename/should_fail/all.T b/testsuite/tests/rename/should_fail/all.T
index 9ca330f..6fd0143 100644
--- a/testsuite/tests/rename/should_fail/all.T
+++ b/testsuite/tests/rename/should_fail/all.T
@@ -140,5 +140,6 @@ test('T15659', normal, compile_fail, [''])
 test('T15607', normal, compile_fail, [''])
 test('T15611a', normal, compile_fail, [''])
 test('T15611b', normal, ghci_script, ['T15611b.script'])
+test('T15828', normal, compile_fail, [''])
 
 test('ExplicitForAllRules2', normal, compile_fail, [''])



More information about the ghc-commits mailing list