What's different about quantified constraints since GHC 9.2?

Dear Café, There's a trick [1] involving quantified constraints (and usually type families) where a function has a quantified constraint (forall a. CF a) and which is explicitly instantiated with a well-placed type annotation (_ :: CF x => ...). Since GHC 9.2, this trick works without that type annotation. How did GHC get smarter at instantiating this quantified constraint? Below is a minimized example which compiles on GHC 9.2.1 but not 9.0.1 (haven't tested 9.0.2), unless you uncomment the last line. Cheers, Li-yao [1]: an Iceland_jack trick https://gitlab.haskell.org/ghc/ghc/-/issues/14860#note_151394 {-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, QuantifiedConstraints, ScopedTypeVariables #-} module A where type family F a class C a class C (F a) => CF a f :: C (F a) => a f = undefined g :: (forall a. CF a) => a g = f -- :: forall a. CF a => a -- needed until GHC 9.0.1 but not GHC 9.2.1 (and later)

If I remember correctly, we added more aggressive expansion of superclasses in quantified-constraint givens. But it's all a bit surprising that it works, given that the superclass given will have a type family in an instance head, which is supposed to not happen (because inference would be fragile, not because there's anything unsound). Richard
On Sep 20, 2022, at 5:07 PM, Li-yao Xia
wrote: Dear Café,
There's a trick [1] involving quantified constraints (and usually type families) where a function has a quantified constraint (forall a. CF a) and which is explicitly instantiated with a well-placed type annotation (_ :: CF x => ...). Since GHC 9.2, this trick works without that type annotation. How did GHC get smarter at instantiating this quantified constraint? Below is a minimized example which compiles on GHC 9.2.1 but not 9.0.1 (haven't tested 9.0.2), unless you uncomment the last line.
Cheers, Li-yao
[1]: an Iceland_jack trick https://gitlab.haskell.org/ghc/ghc/-/issues/14860#note_151394
{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts, QuantifiedConstraints, ScopedTypeVariables #-} module A where
type family F a class C a class C (F a) => CF a
f :: C (F a) => a f = undefined
g :: (forall a. CF a) => a g = f -- :: forall a. CF a => a -- needed until GHC 9.0.1 but not GHC 9.2.1 (and later)
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
participants (2)
-
Li-yao Xia
-
Richard Eisenberg