[Git][ghc/ghc][wip/T23923-mikolaj-take-2] Fix the 3 plugin tests that fail
Mikolaj Konarski (@Mikolaj)
gitlab at gitlab.haskell.org
Thu Feb 8 09:28:00 UTC 2024
Mikolaj Konarski pushed to branch wip/T23923-mikolaj-take-2 at Glasgow Haskell Compiler / GHC
Commits:
b6454d5e by Mikolaj Konarski at 2024-02-08T10:25:20+01:00
Fix the 3 plugin tests that fail
- - - - -
3 changed files:
- testsuite/tests/tcplugins/CtIdPlugin.hs
- testsuite/tests/tcplugins/RewritePlugin.hs
- testsuite/tests/tcplugins/TyFamPlugin.hs
Changes:
=====================================
testsuite/tests/tcplugins/CtIdPlugin.hs
=====================================
@@ -21,6 +21,7 @@ import GHC.Tc.Plugin
import GHC.Tc.Types
import GHC.Tc.Types.Constraint
import GHC.Tc.Types.Evidence
+import GHC.Types.Unique.DSet
-- common
import Common
@@ -41,7 +42,7 @@ solver :: [String]
-> PluginDefs -> EvBindsVar -> [Ct] -> [Ct]
-> TcPluginM TcPluginSolveResult
solver _args defs ev givens wanteds = do
- let pluginCo = mkUnivCo (PluginProv "CtIdPlugin") Representational
+ let pluginCo = mkUnivCo (PluginProv "CtIdPlugin" emptyUniqDSet) Representational
let substEvidence ct ct' =
evCast (ctEvExpr $ ctEvidence ct') $ pluginCo (ctPred ct') (ctPred ct)
=====================================
testsuite/tests/tcplugins/RewritePlugin.hs
=====================================
@@ -45,6 +45,8 @@ import GHC.Tc.Types.Constraint
)
import GHC.Tc.Types.Evidence
( EvTerm(EvExpr), Role(Nominal) )
+import GHC.Types.Unique.DSet
+ ( emptyUniqDSet )
import GHC.Types.Unique.FM
( UniqFM, listToUFM )
@@ -85,5 +87,5 @@ mkTyFamReduction :: TyCon -> [ Type ] -> Type -> Reduction
mkTyFamReduction tyCon args res = Reduction co res
where
co :: Coercion
- co = mkUnivCo ( PluginProv "RewritePlugin" ) Nominal
+ co = mkUnivCo ( PluginProv "RewritePlugin" emptyUniqDSet) Nominal
( mkTyConApp tyCon args ) res
=====================================
testsuite/tests/tcplugins/TyFamPlugin.hs
=====================================
@@ -39,6 +39,8 @@ import GHC.Tc.Types.Constraint
)
import GHC.Tc.Types.Evidence
( EvBindsVar, EvTerm(EvExpr), Role(Nominal) )
+import GHC.Types.Unique.DSet
+ ( emptyUniqDSet )
-- common
import Common
@@ -78,6 +80,6 @@ solveCt ( PluginDefs {..} ) ct@( classifyPredType . ctPred -> EqPred NomEq lhs r
, let
evTerm :: EvTerm
evTerm = EvExpr . Coercion
- $ mkUnivCo ( PluginProv "TyFamPlugin" ) Nominal lhs rhs
+ $ mkUnivCo ( PluginProv "TyFamPlugin" emptyUniqDSet) Nominal lhs rhs -- !!! how do I take the free variables at this point? should we provide a smart constructor that computes the free variables? how about another that sets the empty set? would some plugins work fine with that?
= pure $ Just ( evTerm, ct )
solveCt _ ct = pure Nothing
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b6454d5ecfc99e15e10e7f681d94d89988d22270
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b6454d5ecfc99e15e10e7f681d94d89988d22270
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240208/50c29f98/attachment-0001.html>
More information about the ghc-commits
mailing list