SPECIALISE rule desugaring fails unnecessarily
Consider this strange program (which is a minimised version of this bug report):
{-# LANGUAGE QuantifiedConstraints, UndecidableInstances #-}
module Foo where
f :: (Eq a, Eq a) => a -> b -> Int
f = error "urk"
{-# SPECIALISE f :: T Maybe -> b -> Int #-}
instance (forall a. Eq a => Eq (f a)) => Eq (T f) where {}
data T f = MkT (f Int)
It involves
- A repeated constraint in
f
's type - A quantified constraint in an instance declaration.
When compiled with -O we get
Foo.hs:8:1: warning: [GHC-69441]
RULE left-hand side too complicated to desugar
Optimised lhs: let {
$dEq_aN2 :: Eq (T Maybe)
[LclId,
Unf=Unf{Src=<vanilla>, TopLvl=False,
Value=False, ConLike=True, WorkFree=False, Expandable=True,
Guidance=IF_ARGS [] 20 0}]
$dEq_aN2 = Foo.$fEqT @Maybe GHC.Maybe.$fEqMaybe } in
f @(T Maybe) @b $dEq_aN2 $dEq_aN2
Orig lhs: let {
df_aNY :: forall a. Eq a => Eq (Maybe a)
[LclId]
df_aNY
= \ (@a) ($dEq_aO1 :: Eq a) ->
let {
$dEq_aO2 :: Eq (Maybe a)
[LclId]
$dEq_aO2 = GHC.Maybe.$fEqMaybe @a $dEq_aO1 } in
$dEq_aO2 } in
let {
$dEq_aN2 :: Eq (T Maybe)
[LclId]
$dEq_aN2 = Foo.$fEqT @Maybe df_aNY } in
let {
$dEq_aN3 :: Eq (T Maybe)
[LclId]
$dEq_aN3 = $dEq_aN2 } in
f @(T Maybe) @b $dEq_aN2 $dEq_aN3
|
8 | {-# SPECIALISE f :: T Maybe -> b -> Int #-}
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Diagnosis
In GHC.HsToCore.Binds.decomposeRuleLhs we have
split_lets (Let (NonRec d r) body)
| isDictId d
= ((d,r):bs, body')
where (bs, body') = split_lets body
But that isDictId
triggers only on dictionaries not dictionary functions created by solving quantified constraints. Boo.
Cure
I think this is easy to fix by making isDictTy
say True for dictionary functions.
Edited by sheaf