[GHC] #10056: Inconsistent precedence of ~

#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

#10056: Inconsistent precedence of ~ -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 (Parser) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: | Differential Revisions: Related Tickets: | -------------------------------------+------------------------------------- Comment (by htebalaka): I was tempted to say precedence rules are the same on the type level. Prefix `Foo` should have higher precedence then any infix expression, and I ''thought'' that infix type operators took the same precedence as their value level versions, though when I tried to construct a quick example to illustrate in GHCi I didn't get that behaviour: {{{ type family a + b type instance a + b = a type family a * b type instance a * b = b :kind! Int + Bool * Char Int + Bool * Char :: * = Char :kind! Int + (Bool * Char) Int + (Bool * Char) :: * = Int }}} :/ -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

I ''thought'' that infix type operators took the same precedence as
#10056: Inconsistent precedence of ~ -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 (Parser) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: | Differential Revisions: Related Tickets: | -------------------------------------+------------------------------------- Comment (by crockeea): Replying to [comment:1 htebalaka]: their value level versions I'm not sure what you mean by "value level versions". Surely you wouldn't expect the precedence of your type family `(+) :: * -> * -> *` be related in any way to the function `(+) :: (Num a) :: a -> a -> a`. If I set up two type families {{{!#hs type family Foo a b type family a \\ b infixr 9 \\ }}} we can ask GHCi
`:kind 'Int \\ Int 'Foo' Int` (can't figure out how to put backticks on Foo here)
and it will complain that I can't mix an `infixr 9 \\` with `infixl 9 'Foo`, so this indicates that the infix version of `Foo` has the same precedence as the prefix version. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Replying to [comment:1 htebalaka]:
I ''thought'' that infix type operators took the same precedence as
#10056: Inconsistent precedence of ~ -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 (Parser) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: | Differential Revisions: Related Tickets: | -------------------------------------+------------------------------------- Comment (by dfeuer): Replying to [comment:2 crockeea]: their value level versions
I'm not sure what you mean by "value level versions". Surely you
wouldn't expect the precedence of your type family `(+) :: * -> * -> *` be related in any way to the function `(+) :: (Num a) :: a -> a -> a`. I certainly ''would'' expect the fixity of the type operator `+` to be the same as that of the function `+`, because the parser doesn't know about kinds. It seems the complaint is that `~` has too high a precedence for its purpose. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10056: Inconsistent precedence of ~ -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 (Parser) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: | Differential Revisions: Related Tickets: | -------------------------------------+------------------------------------- Comment (by goldfire): Here's what I know about all of this, to the best of my knowledge: - Types do ''not'' "inherit" fixity from terms. The type family `(+) :: * -> * -> *` (or whatever kinds) is completely and totally unrelated to the term-level variable `(+) :: Num a => a -> a -> a`. - There is no way in a fixity declaration to specify what namespace you want the declaration to operate over. So, in (what I consider to be) a terrible hack, a fixity declaration will affect either or both of local term-level and type-level definitions. So, if you have {{{ (//) :: a -> a -> a (//) = ... type family (//) a b infixl 5 // }}} then ''both'' the term `(//)` and the type `(//)` get the given fixity. This isn't a case of one inheriting the fixity from the other or being at all related -- it's just a peculiar meaning given to a fixity declaration. - While the parser doesn't know what type a term has, it ''does'' know whether you're writing a term, a type, or a kind. So it can behave differently in each of these cases -- they're all syntactically distinct in Haskell source. - Traditional fixity declarations don't affect the parser. And, upon some thought, we realize they can't: a fixity declaration can't be acted upon until after (or in) the renamer, when we know where a symbol is declared. - `(~)` is parsed separately from the normal infix operators. Recall that `TypeOperators` used to require type-level operators to begin with `:`. `(~)` does not, and so it must be special. Now that `TypeOperators` has been changed, there actually doesn't seem to be a good reason to keep `(~)` special. It's declared (in `ghc-prim:GHC.Types`). It has magic in the solver, but there needs to be no magic dealing with naming or parsing. However, simply removing the magic causes several minor conundrums: - Do we require `TypeOperators` when `~` appears in source code? Currently, we don't. - Do we require `TypeFamilies` or `GADTs` when `~` appears in source code? Currently, we do, but if we drop the magic, this decision is suspect, especially if `~` isn't ever really acted on in the module (because it appears only on the RHS of a type synonym, say). - Should `(~)` be imported as part of the Prelude? If no, then a lot of code breaks. If yes, that implies that hiding the Prelude also hides `(~)`, breaking less code, but still breaking code. These issues are surmountable, perhaps, but when I looked at making `~` non-magical, I discovered both that it's technically quite straightforward and socially rather annoying for little benefit. I suppose there's a middle road where it's non-magical in the parser but magical in the renamer. When I realized how tangled this all was, I gave up, as I was just doing some cleaning. Now that bugs are actually appearing, there might be more incentive to come up with a consistent response. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10056: Inconsistent precedence of ~ -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 (Parser) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: | Differential Revisions: Related Tickets: #10059 | -------------------------------------+------------------------------------- Changes (by goldfire): * related: => #10059 Comment: See also #10059 for another place where the magic behind `(~)` causes weird behavior. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10056: Inconsistent precedence of ~ -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 (Parser) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: | Differential Revisions: Related Tickets: #10059 | -------------------------------------+------------------------------------- Comment (by simonpj): I would love someone to take this on. It's detail work, but treating `(~)` more systematically would be a jolly good thing, and a public service. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10056: Inconsistent precedence of ~ -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 (Parser) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: | Differential Revisions: Related Tickets: #10059 | -------------------------------------+------------------------------------- Comment (by goldfire): See also brief commentary on #9194, which is a dup of this ticket. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 goldfire): See also comment:10:ticket:10704, which points out that `:i (~)` fails. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): What exactly ''should'' the precedence of `(~)` be, anyway? It definitely seems like it should be lower than most things, but how low? For example, should this: {{{#!hs f :: (Int -> Int ~ Int -> Int) => String }}} parse as this? {{{#!hs f :: ((Int -> Int) ~ (Int -> Int)) => String }}} Also, I'm not sure that I understand this concern:
Should `(~)` be imported as part of the Prelude? If no, then a lot of code breaks. If yes, that implies that hiding the `Prelude` also hides `(~)`, breaking less code, but still breaking code.
Does hiding `Prelude` necessarily mean that `(~)` won't be visible? I was under the impression that certain types would still be visible even if `Prelude` was hidden, e.g., `(->)`. Couldn't we make `(~)` another such type and sidestep that issue? As for the `LANGUAGE` pragma question, I think it would make sense for `TypeOperators` to enable use of `(~)`. I would keep `TypeFamilies` and `GADTs`' ability to enable use of `(~)` to avoid breaking code unnecessarily—perhaps a warning can be emitted if `(~)` is used in the presence of `TypeFamilies` or `GADTs` but not `TypeOperators`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonpj): Yes I think we should probably treat `(~)` as "built-in syntax", like `(->)` and `[]`. You can't override, import, or hide these things. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 goldfire): Agreed that `~` should be built-in. Using `TypeOperators`, `GADTs` or `TypeFamilies` to enable `~` also makes sense, given the history. It sounds like you're moving toward the "non-magical in the parser but magical in the renamer" route, which I generally support. Thanks for pushing this along! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#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 dfeuer): I would think we'd want it to have even lower precedence than `->` to support easy use in contexts. This would require parentheses for some constraint kind applications, but I conjecture that's less common in practice. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonpj): Sounds good to me. Needs examples in the user manual to show what is and is not ok. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): Replying to [comment:14 dfeuer]:
I would think we'd want it to have even lower precedence than `->` to support easy use in contexts.
Is that even possible at the moment? I thought that `(->)` had the lowest possible precedence: {{{#!hs $ inplace/bin/ghc-stage2 --interactive GHCi, version 7.11.20150727: http://www.haskell.org/ghc/ :? for help λ> :i (->) data (->) a b -- Defined in ‘GHC.Prim’ infixr 0 `(->)` }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 dfeuer): Replying to [comment:16 RyanGlScott]:
Replying to [comment:14 dfeuer]:
I would think we'd want it to have even lower precedence than `->` to support easy use in contexts.
Is that even possible at the moment? I thought that `(->)` had the lowest possible precedence:
{{{#!hs $ inplace/bin/ghc-stage2 --interactive GHCi, version 7.11.20150727: http://www.haskell.org/ghc/ :? for help λ> :i (->) data (->) a b -- Defined in ‘GHC.Prim’ infixr 0 `(->)` }}}
Ze who writes the parser makes the rules. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 rwbarton): I would expect `~` to have lower precedence than everything except `=>`. This isn't a totally solid conviction, I could imagine changing my mind if I saw a suitable example, but I can't think of what such an example would look like. By the way, why can't ghci tell me about `:i (=>)`? :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): How exactly would this work? In order to make `(~)` have lower precedence than `(->)`, it seems to me we'd have to do one of the following [1]: 1. Give `(~)` a negative precedence. 2. Declare `infix 0 ~` and give `(->)` a higher precedence. Option 1 sounds particularly scary, since we'd be changing the lower bound of precedences. Option 2 allows users to define their own type operators that have lower precedence than `(->)`, and may cause some existing code to break. [1] That is, assuming that we're still committed to the idea of non- magically parsing `(~)` like any other type operator. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 rwbarton): I was guessing that your option 1 would in fact be easy, though I haven't looked at any of the code involved. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): One potential hiccup is that the [https://www.haskell.org/onlinereport/decls.html#sect4.4.2 Haskell 98 Report] requires all operators to have an integer precedence from 0 to 9, so we'd have to deviate from that to achieve option 1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 dfeuer): Replying to [comment:21 RyanGlScott]:
One potential hiccup is that the [https://www.haskell.org/onlinereport/decls.html#sect4.4.2 Haskell 98 Report] requires all operators to have an integer precedence from 0 to 9, so we'd have to deviate from that to achieve option 1.
Operator precedence is just syntax. There is no way to write a function `f :: OPERATOR -> Int` to get the precedence, nor could there be. This just isn't an issue. Allowing users to set arbitrary rational precedence values, or use some sort of general precedence DAG, would require a syntactic extension, but this does not, as it does not allow any new fixity declarations. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): OK, so the idea is to still require that user-defined fixity declarations have precedence 0–9, but grant exceptions for certain types (e.g., `(~)`). I think this would technically meet the Haskell 2010 Report, so that's good. As far as implementation details go, it looks like `(->)`'s fixity is currently hardwired in [http://git.haskell.org/ghc.git/blob/f063bd5413edf40f1b48e0f958410dcb6bf20b68... BasicTypes.hs], so we could stick in {{{tildeFixity = Fixity (-1) Infix}}} there. I'm not aware of any bounds-checking code that would be tripped up by having a precedence lower than {{{minPrecedence = 0}}}, so I don't think that would be too invasive of a change. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): There hasn't been any movement on this in a while, and I'd really like to see it changed. Are there people who disagree with the idea, or is it just a matter of getting it done? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I'm not aware of anyone disagreeing, so I don't think that's an obstacle. I attempted to fix this at one point, but I wasn't experienced enough in GHC to come up with a solution. One huge obstacle (for me, anyway) is that GHC co-opts the tilde symbol for [http://git.haskell.org/ghc.git/blob/1e041b7382b6aa329e4ad9625439f811e0f27232... laziness annotations], which means that all occurrences of `~` as type equalities are converted via a [http://git.haskell.org/ghc.git/blob/5f1e42f22cf29bc1b7150e06b2711fa7c43c6e5b... special parser function]. This makes it much harder to remove `~` as a special parser case, and when I tried removing it, it ended up introducing an enormous number of shift-reduce conflicts. I would also like to see this fixed at some point, but I don't think I'm going to be the one to fix it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Oh, I really wasn't talking about removing it as a special case; I was talking about giving it (effectively) a negative precedence. Its current behavior in that regard is very annoying. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:26 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I few comments as I'm catching up on this thread: * We don't need to conform to any standards here. We're talking about type-level operators, so we're already beyond the Haskell reports. Thinking about standards is a Good Thing, but I just want to note that we're already quite off the map. * I think that, given the laziness annotation wrinkle, `~` will have to stay somewhat magical in the parser. (That may not have been true when this ticket started, as I think allowing laziness annotations in types came about only with `-XStrictData`.) * However, I think we ''can'' eliminate `HsEqTy` from `HsType`. Instead, just use `HsOpTy` with `eqTyCon_RDR` as the operator. Once we get rid of `HsEqTy`, I think we'll be well on our way to solving this ticket. Indeed, that's probably a good approach: get rid of `HsEqTy` and get everything to work again. * Parsing `->` is magical. And it has to be: we can write `forall a. a -> forall b. b -> (a,b)`, for example. `forall` can't appear to the right of other operators. And `->` has various other special things about it (like being able to appear in record GADT syntax). So we have to keep this in mind. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:27 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Edward Kmett notes [https://mail.haskell.org/pipermail/ghc- devs/2016-August/012537.html on the ghc-devs mailing list] that making `-XTypeOperators` allow the use of `(~)` is not a good idea, since it means that other compilers who wish to implement `-XTypeOperators` must now implement all of the ideas in the OutsideIn(X) paper, which is a big ask. It might be better to introduce a new pragma (`-XTypeEqualities`?) for this purpose. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:28 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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, #10431 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: #10059 => #10059, #10431 Comment: And as it turns out, `-XEqualityConstraints` has been proposed before. See #10431. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:29 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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, #10431 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Replying to [comment:29 RyanGlScott]:
And as it turns out, `-XEqualityConstraints` has been proposed before. See #10431.
I'm compelled to ask whether there is more than one equality constraints in light of [https://youtu.be/hIZxTQP1ifo?t=2764 these] [https://www.reddit.com/r/haskell/comments/4w1jcr/using_typelevel_naturals_ov... comments] by Edward and if `EqualityConstraint` were more apt (unless `~~`, `~#`, `~R#`, `~P#`, `Coercible` count) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:30 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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, #10431 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'm all for `-XTypeEqualities`, if someone wants to specify the details, and implement it. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:31 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10056: Inconsistent precedence of ~ -------------------------------------+------------------------------------- Reporter: crockeea | Owner: (none) 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, #10431, | Differential Rev(s): #14316 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: #10059, #10431 => #10059, #10431, #14316 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:32 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10056: Inconsistent precedence of ~ -------------------------------------+------------------------------------- Reporter: crockeea | Owner: (none) 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, #10431, | Differential Rev(s): Phab:D4876 #14316 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * differential: => Phab:D4876 Comment: Post-d650729f9a0f3b6aa5e6ef2d5fba337f6f70fa60, it's quite easy to remove `HsEqTy`, at the very least. I've done so in Phab:D4876. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:33 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10056: Inconsistent precedence of ~
-------------------------------------+-------------------------------------
Reporter: crockeea | Owner: (none)
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, #10431, | Differential Rev(s): Phab:D4876
#14316 |
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#10056: Inconsistent precedence of ~ -------------------------------------+------------------------------------- Reporter: crockeea | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 7.8.4 (Parser) | Resolution: fixed | 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: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: => 8.6.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:35 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10056: Inconsistent precedence of ~ -------------------------------------+------------------------------------- Reporter: crockeea | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.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: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: closed => new * resolution: fixed => -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:36 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => 8.8.1 Comment: I believe there is more to do here, but it won't happen for 8.6. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:37 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#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 simonpj): Can someone just summarise why we can't treat `(~)`, from a parsing point of view, as just an ordinary type operator with a specific fixity? With no special treatment in the parser? Why doe we need a "post-parsing pass" for `(~)`? And if it's just an ordinary operator, why does it even need to be built- in syntax? Maybe this all explained above, but a standalone summary would help make sure this ticket is well focused. Thanks! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:39 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): When talking about `(~)`, it's important to distinguish between two different uses of it: 1. As the equality type operator. 2. As a laziness annotation in `-XStrict` (e.g., `data Foo a = MkFoo ~a`). If it weren't for usage (2), `(~)` would not need any special treatment at all in the parser. But alas, because of (2), we initially parse all uses of `(~)` as laziness annotations, and perform an additional pass right after parsing to determine which uses of `(~)` are for actually for (1), and which are for actually for (2). (Note that the problems I describe about `(->)` in comment:38 would still be relevant even if `(~)` had no special treatment in the parser. In other words, if we decided in the future to have some other type operator with a precedence of -2 or lower, than we'd have to figure out how to answer The `(->)` Question.) Once that's taken care of, the fixity of `(~)` is handled like any other type operator. I only opted to wire in the fixity of `(~)` in comment:38 since it's negative, and you can't assign a negative fixity through an `infix -2 ~` declaration. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:40 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonpj): Ah! I'd forgotten about `-XStrict`. So the special treatment in `Parsery.y` is (only) here {{{ strictness :: { Located ([AddAnn], SrcStrictness) } : '!' { sL1 $1 ([mj AnnBang $1], SrcStrict) } | '~' { sL1 $1 ([mj AnnTilde $1], SrcLazy) } }}} So is `(~)` (in types) handled uniformly with `(!)`? It seems not. Perhaps that's because we don't want to give up `(~)` as an infix operator, but we are willing to give up `(!)`? I got as far as reading `splitTilde` but got lost in its invocations in `RdrHsSyn` and `Parser.y`. Anyway, it'd be good to summarise how the moving parts fit together, in a Note. There are some e.g. `Note [Parsing ~]`, but they are too brief to do justice to the question. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:41 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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, #15457 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: #10059, #10431, #14316 => #10059, #10431, #14316, #15457 Comment: Replying to [comment:41 simonpj]:
So is `(~)` (in types) handled uniformly with `(!)`? It seems not. Perhaps that's because we don't want to give up `(~)` as an infix operator, but we are willing to give up `(!)`?
Ugh, that's a very good point. We //should// be able to use `!` as a type operator, but because of this lack of uniformity, we can't. We should fix this.
Anyway, it'd be good to summarise how the moving parts fit together, in a Note. There are some e.g. `Note [Parsing ~]`, but they are too brief to do justice to the question.
Indeed, `Note [Parsing ~]` could stand to be a bit longer. I've opened #15457 for both of these issues. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10056#comment:42 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC