[GHC] #10056: Inconsistent precedence of ~

GHC ghc-devs at haskell.org
Sun Feb 1 14:39:53 UTC 2015


#10056: Inconsistent precedence of ~
-------------------------------------+-------------------------------------
              Reporter:  crockeea    |             Owner:
                  Type:  bug         |            Status:  new
              Priority:  normal      |         Milestone:
             Component:  Compiler    |           Version:  7.8.4
  (Parser)                           |  Operating System:  Unknown/Multiple
              Keywords:              |   Type of failure:  GHC rejects
          Architecture:              |  valid program
  Unknown/Multiple                   |        Blocked By:
             Test Case:              |   Related Tickets:
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------
 The following compiles as expected:

 {{{#!hs
 {-# LANGUAGE TypeFamilies #-}
 type family Foo a b

 f :: (Foo a b ~ Int) => a -> b -> b
 f = error ""
 }}}

 but this fails:
 {{{#!hs
 {-# LANGUAGE TypeFamilies #-}
 type family a \\ b

 f :: (a \\ b ~ Int) => a -> b -> b
 f = error ""
 }}}

 with the error
 > "The second argument of `(\\)` should have kind `*`, but `b ~ Int` has
 kind `Constraint`."

 Thus the first example is being parsed as `(Foo a b) ~ Int`, while the
 second is parsed as `a \\ (b ~ Int)`. I believe the second example should
 compile, i.e. `(\\)` and `Foo` should have the same precedence, both of
 which are higher than `(~)`.

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


More information about the ghc-tickets mailing list