[GHC] #10056: Inconsistent precedence of ~

GHC ghc-devs at haskell.org
Tue Aug 4 14:27:43 UTC 2015


#10056: Inconsistent precedence of ~
-------------------------------------+-------------------------------------
        Reporter:  crockeea          |                   Owner:
            Type:  bug               |                  Status:  new
        Priority:  normal            |               Milestone:
       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            |  Differential Revisions:
-------------------------------------+-------------------------------------

Comment (by RyanGlScott):

 That leaves the remaining question of what fixity to give `(~)`. It seems
 pretty likely that no matter what is chosen, some code is going to break,
 so I suppose we should pick a fixity that is as consistent with existing
 uses of `(~)` as possible to minimize the fallout.

 Currently, it looks like `(~)` is neither `infixl` nor `infixr`, since the
 following code fails to parse:

 {{{#!hs
 f :: (Int ~ Char ~ Bool) => Int; f = 42
 }}}

 I can't think of any scenarios where chaining `(~)` applications like this
 would be useful (chime in if you think otherwise!), so that behavior seems
 alright.

 What about the actual precedence? Intuitively, one would imagine `(~)` to
 have a very low precedence, as motivated by the original example in this
 ticket:

 {{{#!hs
 {-# LANGUAGE TypeFamilies #-}
 type family a \\ b
 infixl 9 \\

 -- Currently parses like
 --
 -- a \\ (b ~ Int)
 --
 -- but probably ought to be
 --
 -- (a \\ b) ~ Int
 f :: (a \\ b ~ Int) => a -> b -> b
 f = error ""
 }}}

 If we declared `infix 0 ~`, that would give the desired behavior. In a
 couple of corner cases, you'd still have to use parentheses. For example,
 in order to make `Int -> Int ~ Int -> Int` parse, you'd need to add
 parentheses like so: `(Int -> Int) ~ (Int -> Int)`. (Since that example
 wouldn't have parsed before anyway, this isn't that bad.)

 Therefore, it looks like the only existing code that would break from this
 idea would be ones that abuse `(~)` parsing magic, as in the
 aforementioned example. These could easily be fixed by adding parentheses
 where needed, so this is a very backwards-amenable change.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10056#comment:13>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list