GHCi's claim of infixr 0 (->) is a lie
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:
{-# 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:
- Claim
(->)
has a negative fixity. - Try to change GHC so that
(->)
really isinfixr 0
.
Trac metadata
Trac field | Value |
---|---|
Version | 8.4.3 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |