[GHC] #10056: Inconsistent precedence of ~
GHC
ghc-devs at haskell.org
Sat Jul 28 13:08:31 UTC 2018
#10056: Inconsistent precedence of ~
-------------------------------------+-------------------------------------
Reporter: crockeea | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.8.1
Component: Compiler | Version: 7.8.4
(Parser) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: #10059, #10431, | Differential Rev(s): Phab:D4876
#14316 |
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
An update on this ticket. It seems that the only remaining thing here is
to wire in an appropriately low fixity for `(~)` (and `(~~)`, which GHC
introduced after the creation of this ticket). As it turns out, this part
is way, way easier than I originally thought. This patch suffices, in
fact:
{{{#!diff
diff --git a/compiler/rename/RnFixity.hs b/compiler/rename/RnFixity.hs
index f1bfb38..05d1b89 100644
--- a/compiler/rename/RnFixity.hs
+++ b/compiler/rename/RnFixity.hs
@@ -27,6 +27,8 @@ import Maybes
import Data.List
import Data.Function ( on )
import RnUnbound
+import PrelNames ( eqTyConKey, heqTyConKey )
+import Unique
{-
*********************************************************
@@ -124,6 +126,9 @@ lookupFixityRn_help' name occ
-- a>0 `foo` b>0
-- where 'foo' is not in scope, should not give an error (Trac #7937)
+ | name `hasKey` eqTyConKey || name `hasKey` heqTyConKey
+ = pure (True, Fixity NoSourceText (-2) InfixN)
+
| otherwise
= do { local_fix_env <- getFixityEnv
; case lookupNameEnv local_fix_env name of {
diff --git a/testsuite/tests/ghci/scripts/T10059.stdout
b/testsuite/tests/ghci/scripts/T10059.stdo
index 92fbb45..854f52a 100644
--- a/testsuite/tests/ghci/scripts/T10059.stdout
+++ b/testsuite/tests/ghci/scripts/T10059.stdout
@@ -1,4 +1,6 @@
class (a ~ b) => (~) (a :: k0) (b :: k0) -- Defined in ‘GHC.Types’
+infix -2 ~
(~) :: k0 -> k0 -> Constraint
class (a GHC.Prim.~# b) => (~) (a :: k0) (b :: k0)
-- Defined in ‘GHC.Types’
+infix -2 ~
}}}
I'm giving this a precedence of -2, since in #15235, we decided to give
`(->)` a precedence of -1, and the consensus in this ticket is that
`(~)`/`(~~)` should have a lower precedence than everything else.
Unfortunately, things are never as simple as they appear. Even with this
patch, `(->)` will //still// have a lower precedence than `(~)` in
practice. Why? Because saying that `(->)` has a precedence of -1 is a bit
of a lie; in reality, it has a precedence closer to -∞, since `(->)` has
special treatment in the parser, which causes it to bind more tightly than
it ought to.
Note that `(~)` is also treated specially in the parser, but there is a
post-parsing pass which flattens uses of `(~)` to appear as ordinary type
operators. Perhaps we should extend this treatment to `(->)` as well?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10056#comment:38>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list