[GHC] #15639: Surprising failure combining QuantifiedConstraints with Coercible
GHC
ghc-devs at haskell.org
Tue Dec 4 20:00:02 UTC 2018
#15639: Surprising failure combining QuantifiedConstraints with Coercible
-------------------------------------+-------------------------------------
Reporter: dfeuer | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler (Type | Version: 8.5
checker) | Keywords:
Resolution: | QuantifiedConstraints
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by malo):
I'm having a similar issue using GHC 8.6.2. Posting as a comment on this
ticket since I expect it's related. Here's a minimal example:
{{{
-- test.hs
{-# LANGUAGE RankNTypes, QuantifiedConstraints #-}
import Data.Coerce
data Foo i = Foo i
data Bar f i = Bar (f i)
-- When I ask that we can lift coercions through the functor...
class (forall i j. Coercible i j => Coercible (f i) (f j)) => MyFunctor f
where
-- ...
-- ... this works fine.
instance MyFunctor Foo
-- When I try to ask that we can lift coercions through a higher
functor...
class (forall f g. (forall i. Coercible (f i) (g i)) => (forall i.
Coercible (x f i) (x g i))) => MyHigherFunctor x where
-- ...
-- ...this fails
instance MyHigherFunctor Bar
-- Output from ghci:
--
-- Prelude> :l test.hs
-- [1 of 1] Compiling Main ( test.hs, interpreted )
--
-- test.hs:21:10: error:
-- • Couldn't match representation of type ‘f’ with that of ‘g’
-- arising from the superclasses of an instance declaration
-- ‘f’ is a rigid type variable bound by
-- a quantified context
-- at test.hs:1:1
-- ‘g’ is a rigid type variable bound by
-- a quantified context
-- at test.hs:1:1
-- • In the instance declaration for ‘MyHigherFunctor Bar’
-- |
-- 21 | instance MyHigherFunctor Bar
-- | ^^^^^^^^^^^^^^^^^^^
-- Failed, no modules loaded.
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15639#comment:6>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list