Defaulting plugin's proposed solution can interfere with built-in defauilting mechanism by writing into the same metavars
The following defaulting plugin trys to default everything to Int
:
module GHC.Defaulting.INTerference (plugin) where
import GHC.Driver.Plugins
import GHC.Tc.Plugin
import GHC.Tc.Types
import GHC.Types.Var
import GHC.Tc.Utils.TcType
import GHC.Tc.Types.Constraint
import GHC.Core.Predicate
import GHC.Tc.Solver
import GHC.Core.Type
import GHC.Core.Class
import GHC.Data.Bag
import GHC.Builtin.Types (intTy)
plugin :: Plugin
plugin = defaultPlugin
{ defaultingPlugin = \_ -> Just DefaultingPlugin
{ dePluginInit = pure ()
, dePluginRun = \ _ -> fill
, dePluginStop = \ _ -> pure ()
}
}
fill :: WantedConstraints -> TcPluginM [DefaultingProposal]
fill wanteds = pure
[ DefaultingProposal tv [intTy] [ct]
| ct <- bagToList $ approximateWC True wanteds
, Just (cls, tys) <- pure $ getClassPredTys_maybe (ctPred ct)
, [ty] <- pure $ filterOutInvisibleTypes (classTyCon cls) tys
, Just tv <- pure $ getTyVar_maybe ty
, isMetaTyVar tv
]
We can try it out with a small example program:
{-# OPTIONS_GHC -fplugin GHC.Defaulting.INTerference #-}
{-# LANGUAGE ExtendedDefaultRules #-}
class IsColor a where
op :: a -> ()
instance IsColor (Int, Int, Int) where
op _ = ()
main :: IO ()
main = pure $ op (1, 2, 3)
What happens here is that the plugin is called on Num a, Num b, Num c => (a, b, c)
(the so-far inferred type of (1, 2, 3)
) and it proposes a ~ Int, b ~ Int, c ~ Int
(with the appropriate Num
constraints). Since the Num
constraints are trivally fulfillable, GHC then accepts these proposals, and thus writes a := Int, b := Int, c := Int
. However, it then still tries to run the built-in defaulting mechanism, which proposes a ~ Integer
, resulting in the double-write a := Integer
.
We can see this by building a -DDEBUG
version of GHC (e.g. --flavour=devel2
) and looking at the relevant parts of the -ddump-tc-trace
output:
defaultingPlugins {
WC {wc_simple =
[W] $dIsColor_aGj {0}:: IsColor
(a_aGl[tau:0], b_aGm[tau:0], c_aGn[tau:0]) (CDictCan)
[W] $dNum_aJL {0}:: Num a_aGl[tau:0] (CDictCan)
[W] $dNum_aJO {0}:: Num b_aGm[tau:0] (CDictCan)
[W] $dNum_aJR {0}:: Num c_aGn[tau:0] (CDictCan)}
...
writeMetaTyVar a_aGl[tau:0] := Int
...
writeMetaTyVar b_aGm[tau:0] := Int
...
writeMetaTyVar c_aGn[tau:0] := Int
...
defaultingPlugin
[DefaultingProposal a_aGl[tau:0] [Int] [[W] $dNum_aJL {0}:: Num
a_aGl[tau:0] (CDictCan)],
DefaultingProposal b_aGm[tau:0] [Int] [[W] $dNum_aJO {0}:: Num
b_aGm[tau:0] (CDictCan)],
DefaultingProposal c_aGn[tau:0] [Int] [[W] $dNum_aJR {0}:: Num
c_aGn[tau:0] (CDictCan)]]
defaultingPlugins } [True]
applyDefaultingRules {
wanteds = WC {wc_simple =
[W] $dIsColor_aGj {0}:: IsColor
(a_aGl[tau:0], b_aGm[tau:0], c_aGn[tau:0]) (CDictCan)
[W] $dNum_aJL {0}:: Num a_aGl[tau:0] (CDictCan)
[W] $dNum_aJO {0}:: Num b_aGm[tau:0] (CDictCan)
[W] $dNum_aJR {0}:: Num c_aGn[tau:0] (CDictCan)}
groups = [(a_aGl[tau:0],
[[W] $dNum_aJL {0}:: Num a_aGl[tau:0] (CDictCan)]),
(b_aGm[tau:0], [[W] $dNum_aJO {0}:: Num b_aGm[tau:0] (CDictCan)]),
(c_aGn[tau:0], [[W] $dNum_aJR {0}:: Num c_aGn[tau:0] (CDictCan)])]
info = ([(), [], Integer, Double], (False, True))
...
unifyTyVar a_aGl[tau:0] := Integer
writeMetaTyVar a_aGl[tau:0] := Integer
<no location info>: error:
panic! (the 'impossible' happened)
GHC version 9.7.20230620:
ASSERT failed!
Double update of meta tyvar
a_aGl[tau:0]
Indirect Int
Call stack:
CallStack (from HasCallStack):
massertPpr, called at compiler/GHC/Tc/Zonk/TcType.hs:156:10 in ghc-9.7-inplace:GHC.Tc.Zonk.TcType
writeMetaTyVarRef, called at compiler/GHC/Tc/Zonk/TcType.hs:115:5 in ghc-9.7-inplace:GHC.Tc.Zonk.TcType
writeMetaTyVar, called at compiler/GHC/Tc/Solver/Monad.hs:1306:26 in ghc-9.7-inplace:GHC.Tc.Solver.Monad
CallStack (from HasCallStack):
panic, called at compiler/GHC/Utils/Error.hs:503:29 in ghc-9.7-inplace:GHC.Utils.Error
Please report this as a GHC bug: https://www.haskell.org/ghc/reportabug
Edited by sheaf