[commit: ghc] master: Fix #12102/#15872 by removing outdated users' guide prose (73cce63)

git at git.haskell.org git at git.haskell.org
Fri Dec 7 15:13:19 UTC 2018


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

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

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

commit 73cce63f33ee80f5095085141df9313ac70d1cfa
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date:   Fri Dec 7 09:35:53 2018 -0500

    Fix #12102/#15872 by removing outdated users' guide prose
    
    Summary:
    In the beginning, #12102 (and #15872, which is of a similar
    ilk) were caused by a poor, confused user trying to use code that
    looks like this (with a constraint in the kind of a data type):
    
    ```lang=haskell
    type family IsTypeLit a where
      IsTypeLit Nat    = 'True
      IsTypeLit Symbol = 'True
      IsTypeLit a      = 'False
    
    data T :: forall a. (IsTypeLit a ~ 'True) => a -> * where
      MkNat    :: T 42
      MkSymbol :: T "Don't panic!"
    ```
    
    Many bizarre GHC quirks (documented in those tickets) arose from
    this sort of construction. Ultimately, the use of constraints in
    data type kinds like this has made a lot of people very confused and
    been widely regarded as a bad move.
    
    Commit 2257a86daa72db382eb927df12a718669d5491f8 finally put this
    feature out of its misery, so now the code above simply errors with
    `Illegal constraint in a kind`. As a result, the aforementioned
    tickets are moot, so this patch wraps a bow on the whole thing by:
    
    1. Removing the (now outdated) section on constraints in data type
       kinds from the users' guide, and
    2. Adding a test case to test this code path.
    
    Test Plan: make test TEST=T12102
    
    Reviewers: goldfire, simonpj, bgamari, tdammers
    
    Reviewed By: tdammers
    
    Subscribers: tdammers, rwbarton, carter
    
    GHC Trac Issues: #12102, #15872
    
    Differential Revision: https://phabricator.haskell.org/D5397


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

73cce63f33ee80f5095085141df9313ac70d1cfa
 docs/users_guide/glasgow_exts.rst                  | 23 ----------------------
 testsuite/tests/typecheck/should_fail/T12102.hs    | 17 ++++++++++++++++
 .../tests/typecheck/should_fail/T12102.stderr      |  6 ++++++
 testsuite/tests/typecheck/should_fail/all.T        |  1 +
 4 files changed, 24 insertions(+), 23 deletions(-)

diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst
index 9b8df91..402262e 100644
--- a/docs/users_guide/glasgow_exts.rst
+++ b/docs/users_guide/glasgow_exts.rst
@@ -9274,29 +9274,6 @@ distinction). GHC does not consider ``forall k. k -> Type`` and
 ``forall {k}. k -> Type`` to be equal at the kind level, and thus rejects
 ``Foo Proxy`` as ill-kinded.
 
-Constraints in kinds
---------------------
-
-As kinds and types are the same, kinds can (with :extension:`PolyKinds`)
-contain type constraints. Only equality constraints are currently supported,
-however. We expect this to extend to other constraints in the future.
-
-Here is an example of a constrained kind: ::
-
-  type family IsTypeLit a where
-    IsTypeLit Nat    = 'True
-    IsTypeLit Symbol = 'True
-    IsTypeLit a      = 'False
-
-  data T :: forall a. (IsTypeLit a ~ 'True) => a -> Type where
-    MkNat    :: T 42
-    MkSymbol :: T "Don't panic!"
-
-The declarations above are accepted. However, if we add ``MkOther :: T Int``,
-we get an error that the equality constraint is not satisfied; ``Int`` is
-not a type literal. Note that explicitly quantifying with ``forall a`` is
-not necessary here.
-
 The kind ``Type``
 -----------------
 
diff --git a/testsuite/tests/typecheck/should_fail/T12102.hs b/testsuite/tests/typecheck/should_fail/T12102.hs
new file mode 100644
index 0000000..6d21fef
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T12102.hs
@@ -0,0 +1,17 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeFamilies #-}
+module T12102 where
+
+import Data.Kind
+import GHC.TypeLits
+
+type family IsTypeLit a where
+  IsTypeLit Nat    = 'True
+  IsTypeLit Symbol = 'True
+  IsTypeLit a      = 'False
+
+data T :: forall a. (IsTypeLit a ~ 'True) => a -> Type where
+  MkNat    :: T 42
+  MkSymbol :: T "Don't panic!"
diff --git a/testsuite/tests/typecheck/should_fail/T12102.stderr b/testsuite/tests/typecheck/should_fail/T12102.stderr
new file mode 100644
index 0000000..ea3016b
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T12102.stderr
@@ -0,0 +1,6 @@
+
+T12102.hs:15:1: error:
+    • Illegal constraint in a kind: forall a.
+                                    (IsTypeLit a ~ 'True) =>
+                                    a -> *
+    • In the data type declaration for ‘T’
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index 7ca05e6..777d1b9 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -408,6 +408,7 @@ test('T12063', [expect_broken(12063)], multimod_compile_fail, ['T12063', '-v0'])
 test('T12083a', normal, compile_fail, [''])
 test('T12083b', normal, compile_fail, [''])
 test('T11974b', normal, compile_fail, [''])
+test('T12102', normal, compile_fail, [''])
 test('T12151', normal, compile_fail, [''])
 test('T7437', normal, compile_fail, [''])
 test('T12177', normal, compile_fail, [''])



More information about the ghc-commits mailing list