Coercions are not properly threaded through arrow notation desugaring, resulting in Core Lint errors
This program results in a Core Lint error on HEAD:
{-# LANGUAGE Arrows, GADTs #-}
module ArrowPanic where
data D a where
D :: D ()
get :: (D a, a) -> ()
get = proc (D, x) -> id -< x
$ ghc -c -dcore-lint ArrowPanic.hs
*** Core Lint errors : in result of Desugar (before optimization) ***
ArrowPanic.hs:8:16: warning:
The coercion variable co_aGT :: a_aCY ~# ()
[LclId[CoVarId]]
is out of scope
After desugaring, the RHS of get
ends up looking roughly like this (simplified and abbreviated for clarity):
arr (\(D co, x) -> x)
-- ^ coercion bound here
>>> arr (\x -> x `cast` co)
-- ^ coercion used here (out of scope!)
>>> id
The root issue appears to be that GHC.Hs.Utils.add_ev_bndr
does not collect coercion variable binders. Indeed, a comment below its definition already notes that very issue:
-- A worry: what about coercion variable binders??
Fixing this is awkward, as the coercions would need to be boxed in order to thread them through arrow notation, but it seems perfectly possible (unlike #20470, which seems trickier). That said, it would mean that such coercions would necessarily have a runtime cost unless they can be eliminated by the optimizer, which could be somewhat surprising.
Edited by Alexis King