[Git][ghc/ghc][wip/T18888] Restrict Linear arrow %1 to exactly literal 1 only

Alan Zimmerman gitlab at gitlab.haskell.org
Mon Nov 2 08:24:08 UTC 2020



Alan Zimmerman pushed to branch wip/T18888 at Glasgow Haskell Compiler / GHC


Commits:
791cb337 by Alan Zimmerman at 2020-11-02T08:23:42+00:00
Restrict Linear arrow %1 to exactly literal 1 only

This disallows `a %001 -> b`, and makes sure the type literal is
printed from its SourceText so it is clear why.

Closes #18888

- - - - -


7 changed files:

- compiler/GHC/Hs/Type.hs
- compiler/GHC/Parser/PostProcess.hs
- + testsuite/tests/linear/should_fail/T18888.hs
- + testsuite/tests/linear/should_fail/T18888.stderr
- + testsuite/tests/linear/should_fail/T18888_datakinds.hs
- + testsuite/tests/linear/should_fail/T18888_datakinds.stderr
- testsuite/tests/linear/should_fail/all.T


Changes:

=====================================
compiler/GHC/Hs/Type.hs
=====================================
@@ -1982,8 +1982,8 @@ ppr_fun_ty mult ty1 ty2
 
 --------------------------
 ppr_tylit :: HsTyLit -> SDoc
-ppr_tylit (HsNumTy _ i) = integer i
-ppr_tylit (HsStrTy _ s) = text (show s)
+ppr_tylit (HsNumTy source i) = pprWithSourceText source (integer i)
+ppr_tylit (HsStrTy source s) = pprWithSourceText source (text (show s))
 
 
 -- | @'hsTypeNeedsParens' p t@ returns 'True' if the type @t@ needs parentheses


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -2620,7 +2620,8 @@ mkLHsOpTy x op y =
   in L loc (mkHsOpTy x op y)
 
 mkMultTy :: IsUnicodeSyntax -> Located Token -> LHsType GhcPs -> (HsArrow GhcPs, AddAnn)
-mkMultTy u tok t@(L _ (HsTyLit _ (HsNumTy _ 1)))
+mkMultTy u tok t@(L _ (HsTyLit _ (HsNumTy (SourceText "1") 1)))
+  -- See #18888 for the use of (SourceText "1") above
   = (HsLinearArrow u, AddAnn AnnPercentOne (combineLocs tok t))
 mkMultTy u tok t = (HsExplicitMult u t, AddAnn AnnPercent (getLoc tok))
 


=====================================
testsuite/tests/linear/should_fail/T18888.hs
=====================================
@@ -0,0 +1,5 @@
+{-# LANGUAGE LinearTypes #-}
+module T18888 where
+
+f :: a %001 -> b
+f x = undefined x


=====================================
testsuite/tests/linear/should_fail/T18888.stderr
=====================================
@@ -0,0 +1,3 @@
+
+T18888.hs:4:9:
+    Illegal type: ‘001’ Perhaps you intended to use DataKinds


=====================================
testsuite/tests/linear/should_fail/T18888_datakinds.hs
=====================================
@@ -0,0 +1,6 @@
+{-# LANGUAGE LinearTypes #-}
+{-# LANGUAGE DataKinds #-}
+module T18888 where
+
+f :: a %001 -> b
+f x = undefined x


=====================================
testsuite/tests/linear/should_fail/T18888_datakinds.stderr
=====================================
@@ -0,0 +1,5 @@
+
+T18888_datakinds.hs:5:9:
+     Expected kind ‘GHC.Types.Multiplicity’,
+        but ‘001’ has kind ‘GHC.Num.Natural.Natural’
+     In the type signature: f :: a %001 -> b


=====================================
testsuite/tests/linear/should_fail/all.T
=====================================
@@ -32,3 +32,5 @@ test('LinearIf', normal, compile_fail, [''])
 test('LinearPatternGuardWildcard', normal, compile_fail, [''])
 test('LinearFFI', normal, compile_fail, [''])
 test('LinearTHFail', normal, compile_fail, [''])
+test('T18888', normal, compile_fail, [''])
+test('T18888_datakinds', normal, compile_fail, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/791cb337549df002ff4323299e6baf825fe994f4

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/791cb337549df002ff4323299e6baf825fe994f4
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/20201102/e5818b6a/attachment-0001.html>


More information about the ghc-commits mailing list