[GHC] #10018: Cannot define custom fixity for infix data constructors in GHCi

#10018: Cannot define custom fixity for infix data constructors in GHCi -------------------------------------+------------------------------------- Reporter: | Owner: RyanGlScott | Status: new Type: bug | Milestone: Priority: normal | Version: 7.8.4 Component: GHCi | Operating System: Unknown/Multiple Keywords: | Type of failure: Incorrect result Architecture: | at runtime Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- When compiling from a module, declaring a custom fixity for an infix data constructor is valid: {{{#!hs module DataFixity where data Infix a b = a :@: b infixl 4 :@: }}} And GHCi recognizes this: {{{ $ ghci DataFixity.hs GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. [1 of 1] Compiling DataFixity ( DataFixity.hs, interpreted ) Ok, modules loaded: DataFixity. λ> :i :@: data Infix a b = a :@: b -- Defined at DataFixity.hs:3:18 infixl 4 :@: }}} However, one cannot do this entirely in GHCi: {{{ $ ghci GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. λ> data Infix a b = a :@: b; infixl 4 :@: λ> :i (:@:) data Infix a b = a :@: b -- Defined at <interactive>:2:18 }}} GHCi simply assumes {{{:@:}}} has the default infix precedence. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10018 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10018: Cannot define custom fixity for infix data constructors in GHCi -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: GHCi | Version: 7.8.4 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => fixed Comment: Whoops. I originally thought this was a separate issue from [https://ghc.haskell.org/trac/ghc/ticket/9830 9830], but I can't duplicate this issue on GHC 7.10-rc2, so it appears that this issue was also fixed as a result. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10018#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10018: Cannot define custom fixity for infix data constructors in GHCi -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: closed => new * version: 7.8.4 => 7.10.1-rc2 * resolution: fixed => Comment: Sorry, it turns out that the bug is more nuanced than I thought. I prematurely closed this ticket when I discovered that a {{{deriving Show}}} clause does in fact pick up on a custom fixity: {{{ $ ghci GHCi, version 7.10.0.20150123: http://www.haskell.org/ghc/ :? for help λ> data Infix a b = a :@: b deriving Show; infix 4 :@: λ> showsPrec 4 ('a' :@: 'b') "" "'a' :@: 'b'" λ> showsPrec 5 ('a' :@: 'b') "" "('a' :@: 'b')" }}} So as far as {{{Show}}} is concerned, {{{:@:}}} is {{{infix 4}}}. However, it behaves as {{{infixl 11}}} when it is actually used: {{{ λ> 'a' :@: 'b' :@: 'c' ('a' :@: 'b') :@: 'c' }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10018#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10018: Cannot define custom fixity for infix data constructors in GHCi -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #9830 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #9830 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10018#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10018: Cannot define custom fixity for infix data constructors in GHCi -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #9830 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by RyanGlScott): I'm not sure if this is related, but when I tried declaring the above data type with {{{infixr 5 :@:}}} first, GHCi fails to parse it: {{{ $ ghci GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help λ> infixr 5 :@:; data Infix a b = a :@: b deriving Show <interactive>:2:1: parse error on input ‘infixr’ }}} It's possible that this bug wouldn't manifest itself if the {{{infixr}}} declaration appeared first, but GHCi won't allow this in the first place, so it's impossible to tell. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10018#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10018: Cannot define custom fixity for infix data constructors in GHCi -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: GHCi | Version: 7.10.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | ghci/scripts/T10018 Related Tickets: #9830, #2947, | Blocking: #4929 | Differential Revisions: Phab:D1028 -------------------------------------+------------------------------------- Changes (by thomie): * testcase: => ghci/scripts/T10018 * differential: => Phab:D1028 * related: #9830 => #9830, #2947, #4929 * milestone: => 7.12.1 Comment: I'm not sure why it partially worked when you added `deriving Show` in comment:2, but I have a patch up for review in Phab:D1028 that enables custom fixity declarations for infix data constructors. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10018#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10018: Cannot define custom fixity for infix data constructors in GHCi -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: GHCi | Version: 7.10.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | ghci/scripts/T10018 Related Tickets: #9830, #2947, | Blocking: #4929 | Differential Revisions: Phab:D1028 -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:5 thomie]:
I'm not sure why it partially worked when you added `deriving Show` in comment:2, but I have a patch up for review in Phab:D1028 that enables custom fixity declarations for infix data constructors.
I'm guessing that the fixity info that derived `Read`/`Show` instances see must be distinct from the fixity info that's used when parenthesizing expressions (I'm not a GHC developer, this is just my speculation). I added #9830 since it addresses a similar issue, so maybe there's a clue in simonpj's fix for it. In any case, it looks like your patch will fix this discrepancy, so all is good. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10018#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10018: Cannot define custom fixity for infix data constructors in GHCi
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 7.12.1
Component: GHCi | Version: 7.10.1-rc2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: Incorrect result | Test Case:
at runtime | ghci/scripts/T10018
Blocked By: | Blocking:
Related Tickets: #9830, #2947, | Differential Revisions: Phab:D1028
#4929 |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#10018: Cannot define custom fixity for infix data constructors in GHCi -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: GHCi | Version: 7.10.1-rc2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect result | Test Case: at runtime | ghci/scripts/T10018 Blocked By: | Blocking: Related Tickets: #9830, #2947, | Differential Revisions: Phab:D1028 #4929 | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10018#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC