[GHC] #15235: GHCi's claim of infixr 0 (->) is a lie

#15235: GHCi's claim of infixr 0 (->) is a lie -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Currently, if you query the `:info` for `(->)` in GHCi, it will give you: {{{ $ ghci GHCi, version 8.4.3: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/ryanglscott/.ghci λ> :i (->) data (->) (a :: TYPE q) (b :: TYPE r) -- Defined in ‘GHC.Prim’ infixr 0 `(->)` <instances elided> }}} This fixity information appears to be plain wrong, as the following program demonstrates: {{{#!hs {-# LANGUAGE TypeOperators #-} module Bug where import Data.Type.Equality type (~>) = (->) infixr 0 ~> f :: (a ~> b -> c) :~: (a ~> (b -> c)) f = Refl }}} Since `(~>)` and `(->)` are both `infixr 0`, I would expect `a ~> b -> c` to associate as `a ~> (b -> c)`, like the type signature for `f` wants to prove. However, GHC believes otherwise: {{{ $ ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:10:5: error: • Occurs check: cannot construct the infinite type: a ~ a ~> b Expected type: ((a ~> b) -> c) :~: (a ~> (b -> c)) Actual type: ((a ~> b) -> c) :~: ((a ~> b) -> c) • In the expression: Refl In an equation for ‘f’: f = Refl • Relevant bindings include f :: ((a ~> b) -> c) :~: (a ~> (b -> c)) (bound at Bug.hs:10:1) | 10 | f = Refl | ^^^^ }}} Reading the error message above, it appears that GHC gives `(->)` an even //lower// precedence than 0, since it associates `a ~> b -> c` as `(a ~> b) -> c`. I'm not sure how to reconcile these two facts. There are at least a couple of options I can think of: 1. Claim `(->)` has a negative fixity. 2. Try to change GHC so that `(->)` really is `infixr 0`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15235 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15235: GHCi's claim of infixr 0 (->) is a lie -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I've been bitten by this before. I'm worried about breakage with option (2), so I favor option (1), even if negative fixities are not available to users. While we're in town, it should be `infixr (-1) ->`, without parentheses/backticks around the arrow. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15235#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15235: GHCi's claim of infixr 0 (->) is a lie -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #15236 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #15236 Comment: Replying to [comment:1 goldfire]:
I'm worried about breakage with option (2), so I favor option (1), even if negative fixities are not available to users.
While we're in town, it should be `infixr (-1) ->`, without
Sounds good to me. parentheses/backticks around the arrow. This was done separately in #15236. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15235#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15235: GHCi's claim of infixr 0 (->) is a lie -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #15236 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Changing GHCi's fixity information for `(->)` is a simple matter of applying this change: {{{#!diff diff --git a/compiler/basicTypes/BasicTypes.hs b/compiler/basicTypes/BasicTypes.hs index 93010b7..e9d32f6 100644 --- a/compiler/basicTypes/BasicTypes.hs +++ b/compiler/basicTypes/BasicTypes.hs @@ -409,7 +409,7 @@ defaultFixity = Fixity NoSourceText maxPrecedence InfixL negateFixity, funTyFixity :: Fixity -- Wired-in fixities negateFixity = Fixity NoSourceText 6 InfixL -- Fixity of unary negate -funTyFixity = Fixity NoSourceText 0 InfixR -- Fixity of '->' +funTyFixity = Fixity NoSourceText (-1) InfixR -- Fixity of '->' {- Consider }}} However, there's one more question we should answer before applying this change: do we want the displayed `:info` output to be this: {{{ infixr -1 -> }}} Or this? {{{ infixr (-1) -> }}} With only the above change, `:info` will display the former. If we want the latter, we'd have to make additional changes to the pretty-printer output for fixity information to add parentheses. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15235#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15235: GHCi's claim of infixr 0 (->) is a lie -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #15236 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I don't think it matters much, so I'd be inclined to do whatever is least work. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15235#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15235: GHCi's claim of infixr 0 (->) is a lie -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #15236 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => newcomer Comment: Sounds good to me. This would be a good task for someone wanting to get involved with GHC development, so I'll mark this as a newcomer ticket. All you'd need to do is apply the change in comment:4, and include a comment explaining why this negative fixity is used. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15235#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15235: GHCi's claim of infixr 0 (->) is a lie -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #15236 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch Comment: See https://github.com/ghc/ghc/pull/158 for a patch. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15235#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15235: GHCi's claim of infixr 0 (->) is a lie -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #15236 | Differential Rev(s): Phab:D5199 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * differential: => Phab:D5199 Comment: The patch in comment:7 has been superseded by Phab:D5199. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15235#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15235: GHCi's claim of infixr 0 (->) is a lie
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone: 8.8.1
Component: Compiler | Version: 8.4.3
Resolution: | Keywords: newcomer
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #15236 | Differential Rev(s): Phab:D5199
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#15235: GHCi's claim of infixr 0 (->) is a lie -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.3 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | ghci/scripts/T8535 Blocked By: | Blocking: Related Tickets: #15236 | Differential Rev(s): Phab:D5199 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * testcase: => ghci/scripts/T8535 * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15235#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC