[Git][ghc/ghc][wip/cusk-ext] Guard CUSKs behind a language pragma

Vladislav Zavialov gitlab at gitlab.haskell.org
Thu May 9 07:43:25 UTC 2019



Vladislav Zavialov pushed to branch wip/cusk-ext at Glasgow Haskell Compiler / GHC


Commits:
9a207a88 by Vladislav Zavialov at 2019-05-09T07:43:05Z
Guard CUSKs behind a language pragma

GHC Proposal #36 describes a transition plan away from CUSKs and to
top-level kind signatures:

1. Introduce a new extension, -XCUSKs, on by default, that detects CUSKs
   as they currently exist.
2. We turn off the -XCUSKs extension in a few releases and remove it
   sometime thereafter.

This patch implements phase 1 of this plan, introducing a new language
extension to control whether CUSKs are enabled. When top-level kind
signatures are implemented, we can transition to phase 2.

- - - - -


8 changed files:

- compiler/main/DynFlags.hs
- compiler/typecheck/TcTyClsDecls.hs
- docs/users_guide/glasgow_exts.rst
- libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs
- testsuite/tests/driver/T4437.hs
- testsuite/tests/typecheck/should_fail/all.T
- + testsuite/tests/typecheck/should_fail/tcfail225.hs
- + testsuite/tests/typecheck/should_fail/tcfail225.stderr


Changes:

=====================================
compiler/main/DynFlags.hs
=====================================
@@ -2260,6 +2260,7 @@ languageExtensions (Just Haskell98)
     = [LangExt.ImplicitPrelude,
        -- See Note [When is StarIsType enabled]
        LangExt.StarIsType,
+       LangExt.CUSKs,
        LangExt.MonomorphismRestriction,
        LangExt.NPlusKPatterns,
        LangExt.DatatypeContexts,
@@ -2276,6 +2277,7 @@ languageExtensions (Just Haskell2010)
     = [LangExt.ImplicitPrelude,
        -- See Note [When is StarIsType enabled]
        LangExt.StarIsType,
+       LangExt.CUSKs,
        LangExt.MonomorphismRestriction,
        LangExt.DatatypeContexts,
        LangExt.TraditionalRecordSyntax,
@@ -4358,6 +4360,7 @@ xFlagsDeps = [
   flagSpec "BinaryLiterals"                   LangExt.BinaryLiterals,
   flagSpec "CApiFFI"                          LangExt.CApiFFI,
   flagSpec "CPP"                              LangExt.Cpp,
+  flagSpec "CUSKs"                            LangExt.CUSKs,
   flagSpec "ConstrainedClassMethods"          LangExt.ConstrainedClassMethods,
   flagSpec "ConstraintKinds"                  LangExt.ConstraintKinds,
   flagSpec "DataKinds"                        LangExt.DataKinds,


=====================================
compiler/typecheck/TcTyClsDecls.hs
=====================================
@@ -510,8 +510,9 @@ kcTyClGroup decls
           --    3. Generalise the inferred kinds
           -- See Note [Kind checking for type and class decls]
 
+        ; cusks <- xoptM LangExt.CUSKs
         ; let (cusk_decls, no_cusk_decls)
-                 = partition (hsDeclHasCusk . unLoc) decls
+                 = partition (\d -> cusks && hsDeclHasCusk (unLoc d)) decls
 
         ; poly_cusk_tcs <- getInitialKinds True cusk_decls
 


=====================================
docs/users_guide/glasgow_exts.rst
=====================================
@@ -9012,6 +9012,9 @@ do so.
 Complete user-supplied kind signatures and polymorphic recursion
 ----------------------------------------------------------------
 
+.. extension:: CUSKs
+    :shortdesc: Enable detection of complete user-supplied kind signatures.
+
 Just as in type inference, kind inference for recursive types can only
 use *monomorphic* recursion. Consider this (contrived) example: ::
 


=====================================
libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs
=====================================
@@ -140,4 +140,5 @@ data Extension
    | QuantifiedConstraints
    | StarIsType
    | ImportQualifiedPost
+   | CUSKs
    deriving (Eq, Enum, Show, Generic, Bounded)


=====================================
testsuite/tests/driver/T4437.hs
=====================================
@@ -41,6 +41,7 @@ expectedGhcOnlyExtensions = ["RelaxedLayout",
                              "AlternativeLayoutRuleTransitional",
                              "EmptyDataDeriving",
                              "GeneralisedNewtypeDeriving",
+                             "CUSKs",
                              "ImportQualifiedPost"]
 
 expectedCabalOnlyExtensions :: [String]


=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -241,6 +241,7 @@ test('tcfail217', normal, compile_fail, [''])
 test('tcfail218', normal, compile_fail, [''])
 test('tcfail223', normal, compile_fail, [''])
 test('tcfail224', normal, compile_fail, [''])
+test('tcfail225', normal, compile_fail, [''])
 
 test('SilentParametersOverlapping', normal, compile, [''])
 test('FailDueToGivenOverlapping', normal, compile_fail, [''])


=====================================
testsuite/tests/typecheck/should_fail/tcfail225.hs
=====================================
@@ -0,0 +1,9 @@
+{-# LANGUAGE PolyKinds, GADTs #-}
+{-# LANGUAGE NoCUSKs #-}
+
+module TcFail225 where
+
+import Data.Kind (Type)
+
+data T (m :: k -> Type) :: k -> Type where
+  MkT :: m a -> T Maybe (m a) -> T m a


=====================================
testsuite/tests/typecheck/should_fail/tcfail225.stderr
=====================================
@@ -0,0 +1,6 @@
+
+tcfail225.hs:9:19: error:
+    • Expected kind ‘k -> *’, but ‘Maybe’ has kind ‘* -> *’
+    • In the first argument of ‘T’, namely ‘Maybe’
+      In the type ‘T Maybe (m a)’
+      In the definition of data constructor ‘MkT’



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/9a207a88df92c6c84c17f88d96a264fb3fd3e60f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/9a207a88df92c6c84c17f88d96a264fb3fd3e60f
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20190509/86b7af1a/attachment-0001.html>


More information about the ghc-commits mailing list