[GHC] #15235: GHCi's claim of infixr 0 (->) is a lie
GHC
ghc-devs at haskell.org
Wed Jun 6 11:47:17 UTC 2018
#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
More information about the ghc-tickets
mailing list