[GHC] #14317: Solve Coercible constraints over type constructors
GHC
ghc-devs at haskell.org
Wed Oct 4 20:54:09 UTC 2017
#14317: Solve Coercible constraints over type constructors
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: feature request | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.1
Resolution: | Keywords: Roles,
| QuantifiedContexts
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 adamse):
Slightly on a tangent but:
This program typechecks in 8.0.2 but fails in 8.2.1
{{{#!haskell
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE GADTs #-}
import Data.Coerce
newtype (f ... g) a = C (f (g a))
newtype I a = I a
data F f a b where
MkF :: Coercible (f b) (f' b) => (a -> f' b) -> F f a b
id1 :: a -> I a
id1 = I
id1F :: Coercible b (f b) => F f b b
id1F = MkF I
}}}
{{{
/Users/adam/src/doodles/co.hs:17:8: error:
• Could not deduce: Coercible b (f b) arising from a use of ‘MkF’
from the context: Coercible b (f b)
bound by the type signature for:
id1F :: forall b (f :: * -> *). Coercible b (f b) => F
f b b
at /Users/adam/src/doodles/co.hs:16:1-36
‘b’ is a rigid type variable bound by
the type signature for:
id1F :: forall b (f :: * -> *). Coercible b (f b) => F f b b
at /Users/adam/src/doodles/co.hs:16:1-36
• In the expression: MkF I
In an equation for ‘id1F’: id1F = MkF I
• Relevant bindings include
id1F :: F f b b (bound at /Users/adam/src/doodles/co.hs:17:1)
|
17 | id1F = MkF I
| ^^^^^
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14317#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list