[Git][ghc/ghc][wip/postfix-operators] 2 commits: Remove "Operator sections" from docs/users_guide/bugs.rst
Vladislav Zavialov
gitlab at gitlab.haskell.org
Tue Oct 13 17:38:32 UTC 2020
Vladislav Zavialov pushed to branch wip/postfix-operators at Glasgow Haskell Compiler / GHC
Commits:
2ca1f851 by Vladislav Zavialov at 2020-10-13T20:37:30+03:00
Remove "Operator sections" from docs/users_guide/bugs.rst
The issue described in that section was fixed by
2b89ca5b850b4097447cc4908cbb0631011ce979
- - - - -
db665fd6 by Vladislav Zavialov at 2020-10-13T20:37:30+03:00
Fix PostfixOperators (#18151)
This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979
See the new T18151x test case.
- - - - -
5 changed files:
- compiler/GHC/HsToCore/Expr.hs
- docs/users_guide/bugs.rst
- + testsuite/tests/deSugar/should_run/T18151x.hs
- + testsuite/tests/deSugar/should_run/T18151x.stdout
- testsuite/tests/deSugar/should_run/all.T
Changes:
=====================================
compiler/GHC/HsToCore/Expr.hs
=====================================
@@ -70,6 +70,8 @@ import GHC.Utils.Panic
import GHC.Core.PatSyn
import Control.Monad
+import qualified GHC.LanguageExtensions as LangExt
+
{-
************************************************************************
* *
@@ -347,7 +349,11 @@ converting to core it must become a CO.
Note [Desugaring operator sections]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-At first it looks as if we can convert
+Desugaring left sections with -XPostfixOperators is straightforward: convert
+(expr `op`) to (op expr).
+
+Without -XPostfixOperators it's a bit more tricky. At first it looks as if we
+can convert
(expr `op`)
@@ -398,6 +404,13 @@ dsExpr e@(OpApp _ e1 op e2)
-- See Note [Desugaring operator sections].
-- N.B. this also must handle postfix operator sections due to -XPostfixOperators.
dsExpr e@(SectionL _ expr op) = do
+ postfix_operators <- xoptM LangExt.PostfixOperators
+ if postfix_operators then
+ -- Desugar (e !) to ((!) e)
+ do { op' <- dsLExpr op
+ ; dsWhenNoErrs (dsLExprNoLP expr) $ \expr' ->
+ mkCoreAppDs (text "sectionl" <+> ppr expr) op' expr' }
+ else do
core_op <- dsLExpr op
x_core <- dsLExpr expr
case splitFunTys (exprType core_op) of
=====================================
docs/users_guide/bugs.rst
=====================================
@@ -438,31 +438,6 @@ The Foreign Function Interface
single: hs_init
single: hs_exit
-.. _infelicities-operator-sections:
-
-Operator sections
-^^^^^^^^^^^^^^^^^
-
-The Haskell Report demands that, for infix operators ``%``, the following
-identities hold:
-
-::
-
- (% expr) = \x -> x % expr
- (expr %) = \x -> expr % x
-
-However, the second law is violated in the presence of undefined operators,
-
-::
-
- (%) = error "urk"
- (() %) `seq` () -- urk
- (\x -> () % x) `seq` () -- OK, result ()
-
-The operator section is treated like function application of an undefined
-function, while the lambda form is in WHNF that contains an application of an
-undefined function.
-
.. _haskell-98-2010-undefined:
GHC's interpretation of undefined behaviour in HaskellĀ 98 and HaskellĀ 2010
=====================================
testsuite/tests/deSugar/should_run/T18151x.hs
=====================================
@@ -0,0 +1,17 @@
+{-# LANGUAGE PostfixOperators #-}
+
+import Control.Exception
+
+data MyException = MyE
+ deriving (Show)
+
+instance Exception MyException
+
+(#) :: Bool -> Bool -> Bool
+(#) = throw MyE
+
+main = do
+ r <- try (evaluate (seq (True #) ()))
+ case r of
+ Left MyE -> putStrLn "PostfixOperators ok"
+ Right () -> putStrLn "PostfixOperators broken"
=====================================
testsuite/tests/deSugar/should_run/T18151x.stdout
=====================================
@@ -0,0 +1 @@
+PostfixOperators ok
=====================================
testsuite/tests/deSugar/should_run/all.T
=====================================
@@ -65,6 +65,7 @@ test('T11747', normal, compile_and_run, ['-dcore-lint'])
test('T12595', normal, compile_and_run, [''])
test('T13285', normal, compile_and_run, [''])
test('T18151', normal, compile_and_run, [''])
+test('T18151x', normal, compile_and_run, [''])
test('T18172', [], ghci_script, ['T18172.script'])
test('DsDoExprFailMsg', exit_code(1), compile_and_run, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ac67a2a6dc56e95fdb93448e1f4c05873ebc65fd...db665fd671c23fb79b35f4a902d792dbb32f3531
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ac67a2a6dc56e95fdb93448e1f4c05873ebc65fd...db665fd671c23fb79b35f4a902d792dbb32f3531
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/20201013/3438e6a4/attachment-0001.html>
More information about the ghc-commits
mailing list