TH silently drops quantification in instance heads
Summary
Here's a program I was writing, the exact program doesn't matter except that it uses a forall
in the instance head to bind a variable (and give it an explicit kind, which is what I care about).
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -ddump-splices -ddump-to-file -dsuppress-uniques -dsuppress-coercions -dsuppress-type-applications -dsuppress-unfoldings -dsuppress-idinfo -dppr-cols=200 -dumpdir /tmp/dumps #-}
module Repro where
import Data.Kind
$([d|
data P = L | R
data T (a :: P) where
A :: T a
B :: T R
type TConstraint = forall a . T a -> Constraint
type ForAllA :: TConstraint -> Constraint
class (forall a . constr @a A) => ForAllA constr
instance forall (constr :: TConstraint) . (forall a . constr @a A) => ForAllA constr
|])
The splice output is this:
Repro.hs:(17,2)-(27,6): Splicing declarations
[d| type ForAllA :: TConstraint -> Constraint
data P = L | R
data T (a :: P)
where
A :: T a
B :: T R
type TConstraint = forall a. T a -> Constraint
class (forall a. constr @a A) => ForAllA constr
instance forall (constr :: TConstraint). (forall a. constr @a A) => ForAllA constr |]
======>
data P = L | R
data T (a :: P)
where
A :: T a
B :: T 'R
type TConstraint = forall a. T a -> Constraint
type ForAllA :: TConstraint -> Constraint
class (forall a. constr @a 'A) => ForAllA constr
instance (forall a. constr @a 'A) => ForAllA constr
Note the absence of the forall. And indeed, the program fails to compile in exactly the way it would if the forall was missing (which happens to be #21793).
Steps to reproduce
The above file should compile standalone and show the problem.
Expected behavior
Actually include all the syntax!
Environment
- GHC version used: 9.2.3
Edited by sheaf