Unexpected variable untouchable inside constraint since GHC 9.8
Summary
With GHC 9.2.4 and GHC 9.6.2, this compiles:
{-# LANGUAGE GHC2021 #-}
{-# LANGUAGE QuantifiedConstraints #-}
module Main where
import Data.Coerce
satisfyConstraint :: (forall x y. Coercible x y => Coercible (m x) (m y)) => ((forall x y. Coercible x y => Coercible (m x) (m y)) => m a) -> m a
satisfyConstraint go = go
main :: IO ()
main = do
satisfyConstraint $ pure ()
pure ()
However, with 9.8.1, I get:
Test.hs:12:28: error: [GHC-83865]
• Couldn't match expected type ‘a0’ with actual type ‘()’
‘a0’ is untouchable
inside the constraints: forall x y.
Coercible x y =>
Coercible (IO x) (IO y)
bound by a type expected by the context:
(forall x y. Coercible x y => Coercible (IO x) (IO y)) => IO a0
at Test.hs:12:23-29
• In the first argument of ‘pure’, namely ‘()’
In the second argument of ‘($)’, namely ‘pure ()’
In a stmt of a 'do' block: satisfyConstraint $ pure ()
|
12 | satisfyConstraint $ pure ()
| ^^
Environment
- GHC version used: 9.2.4, 9.6.2, 9.8.1
Edited by Shea Levy