[GHC] #13083: Constraint solving failure with Coercible + type family + newtype

#13083: Constraint solving failure with Coercible + type family + newtype -------------------------------------+------------------------------------- Reporter: conal | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: Coercible | Operating System: MacOS X Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I'm getting a type error using `coerce` to remove the wrapper of a `newtype` specialization involving a the following. See below for the smallest example I was able to construct. {{{#!hs {-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} {-# OPTIONS_GHC -Wall #-} -- | Bug(?) in Coercible constraint solving -- module B2 where import GHC.Generics (Par1(..),(:*:)(..)) import GHC.Exts (coerce) -- Representation as free vector space type family V (a :: *) :: * -> * type instance V Float = Par1 type instance V (a,b) = V a :*: V b type instance V (Par1 a) = V a type instance V ((f :*: g) a) = V (f a, g a) -- • Variable ‘a’ occurs more often -- in the type family application ‘V (f a, g a)’ -- than in the instance head -- (Use UndecidableInstances to permit this) type R = Float -- Linear map in row-major order newtype L a b = L (V b (V a R)) -- Use coerce to drop newtype wrapper bar :: L a b -> V b (V a R) bar = coerce {-------------------------------------------------------------------- Bug demo --------------------------------------------------------------------} -- A rejected type specialization of bar with a ~ (R,R), b ~ (Par1 R,R) foo :: L (R,R) (Par1 R,R) -> V (Par1 R,R) (V (R,R) R) foo = coerce -- • Couldn't match representation of type ‘V Par1’ -- with that of ‘Par1’ -- arising from a use of ‘coerce’ -- Note that Par1 has the wrong kind (* -> *) for V Par1 -- Same error: -- -- foo :: (a ~ (R,R), b ~ (Par1 R,R)) => L a b -> V b (V a R) -- The following similar signatures work: -- foo :: L (R,R) (R,Par1 R) -> V (R,Par1 R) (V (R,R) R) -- foo :: L (Par1 R,R) (R,R) -> V (R,R) (V (Par1 R,R) R) -- Same error: -- -- Linear map in column-major order -- newtype L a b = L (V a (V b s)) -- foo :: L (R,R) (Par1 R,R) -> V (R,R) (V (Par1 R,R) R) -- foo = coerce }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13083 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13083: Constraint solving failure with Coercible + type family + newtype -------------------------------------+------------------------------------- Reporter: conal | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Coercible Operating System: MacOS X | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: goldfire (added) Comment: I believe this is expected behavior. You can only coerce from `V Par1` to `Par` if the [https://ghc.haskell.org/trac/ghc/wiki/Roles role] of `V1`'s argument is permissive enough (that is, it must have a representational or phantom role, not a nominal role). But currently, all arguments to a type family (such as `V`) are always assigned nominal roles. This solves problems like the [https://ghc.haskell.org/trac/ghc/wiki/Roles#Theproblemwewishtosolve original motivation for roles], but it does rule out scenarios like yours. FWIW, I've been advocating for role inference/the ability to give type families role annotations in #8177. I think a type family like: {{{#!hs type family Id a where Id a = a }}} should definitely be able to have a representational role for its argument. Not sure about `V`, though. I'll cc goldfire for his thoughts as well. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13083#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13083: Constraint solving failure with Coercible + type family + newtype -------------------------------------+------------------------------------- Reporter: conal | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Coercible Operating System: MacOS X | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I'm afraid I don't see how comment:1 applies. The type of `foo` seems to be a straightforward specialization of the type of `bar`. So it seems this should work. Confirmed reproducible in a fairly recent HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13083#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13083: Constraint solving failure with Coercible + type family + newtype -------------------------------------+------------------------------------- Reporter: conal | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Coercible Operating System: MacOS X | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Derp, I didn't read the source closely enough. In particular, I missed this more glaring issue: {{{#!hs -- Note that Par1 has the wrong kind (* -> *) for V Par1 }}} So please ignore everything I said in comment:1 :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13083#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13083: Constraint solving failure with Coercible + type family + newtype -------------------------------------+------------------------------------- Reporter: conal | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Coercible Operating System: MacOS X | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => goldfire Comment: Richard, `TcCanonical.zonk_eq_types` is completely broken. I don't quite know why it's there but it's utterly wrong. Consider the call `zonkEqTypes (T Par1) (S (Par1 b))`. Even though the head type constructors are utterly different you still use `tcRepSplitAppTy_maybe` to make recursive calls to {{{ go T S and go Par1 (Par1 b) }}} Notice these two arguments have different kinds. Incidentally it seems terribly inefficient to break into binary applications when both types are manifestly `TyConApp`s. Now the `tc1 == tc2` case of `go` kicks in, and we call `tycon`. Alas this calls `zipWithM` which simply discards the `b` argument to `Par1`. Eek. This mis-match kind stuff could occur, I guess, if you had {{{ go (T k1 t1) (T k2 t2) }}} where `T` is polykinded and `k1` differs from `k2`. So fixing the efficiency bug would not be enough to fix the mis-matched kind bug. I have a fix validating Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13083#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13083: Constraint solving failure with Coercible + type family + newtype
-------------------------------------+-------------------------------------
Reporter: conal | Owner: goldfire
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.0.1
checker) |
Resolution: | Keywords: Coercible
Operating System: MacOS X | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#13083: Constraint solving failure with Coercible + type family + newtype -------------------------------------+------------------------------------- Reporter: conal | Owner: goldfire Type: bug | Status: merge Priority: normal | Milestone: 8.0.3 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Coercible Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T13083 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge * testcase: => typecheck/should_compile/T13083 * milestone: => 8.0.3 Comment: Richard: pls check. Merge to 8.0 branch -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13083#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13083: Constraint solving failure with Coercible + type family + newtype -------------------------------------+------------------------------------- Reporter: conal | Owner: goldfire Type: bug | Status: merge Priority: normal | Milestone: 8.0.3 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Coercible Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T13083 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Yes, looks good to me. Previous version was just wrong, as you discovered. Thanks! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13083#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC