[GHC] #15431: Coercible and Existential types don't play nicely
GHC
ghc-devs at haskell.org
Mon Jul 23 12:51:39 UTC 2018
#15431: Coercible and Existential types don't play nicely
-------------------------------------+-------------------------------------
Reporter: NioBium | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.4.3
Resolution: | Keywords: Roles
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #14333 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):
* keywords: => Roles
* related: => #14333
Comment:
Hm, this is interesting. This can be minimized to the following examples,
which are slight variations of each other:
{{{#!hs
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
module Bug where
import Data.Coerce
import Data.Functor.Identity
g1 :: Coercible (t a) Int => t a -> Int
g1 = coerce
g2 :: Coercible Int (t a) => t a -> Int
g2 = coerce
}}}
`g1` typechecks, but `g2` doesn't!
{{{
$ /opt/ghc/8.4.3/bin/ghc Bug.hs
[1 of 1] Compiling Bug ( Bug.hs, Bug.o )
Bug.hs:12:6: error:
• Couldn't match representation of type ‘t a’ with that of ‘Int’
arising from a use of ‘coerce’
• In the expression: coerce
In an equation for ‘g2’: g2 = coerce
• Relevant bindings include g2 :: t a -> Int (bound at Bug.hs:12:1)
|
12 | g2 = coerce
| ^^^^^^
}}}
I'm not sure if this is related to #14333 or not.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15431#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list