[GHC] #12068: RULE too complicated to desugar when using constraint synonyms

#12068: RULE too complicated to desugar when using constraint synonyms -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect Unknown/Multiple | warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- With the following minimal-as-I-could-get-it example, {{{ {-# LANGUAGE ConstraintKinds #-} class Qux a class (Num r) => Class1 r class (Num r) => Class2 r newtype Foo q z = Foo z type Qux' q z = (Qux q, Integral z) instance (Num z) => Num (Foo q z) instance (Qux' q z, Num z) => Class1 (Foo q z) instance (Qux' q z, Num z) => Class2 (Foo q z) newtype Bar r = Bar r {-# SPECIALIZE bar :: (Qux q) => Bar (Foo q Int) -> Bar (Foo q Int) #-} bar :: (Class1 r, Class2 r) => Bar r -> Bar r bar = undefined }}} I get the warning: {{{ RULE left-hand side too complicated to desugar Optimised lhs: let { $dNum_aGE :: Num (Foo q Int) [LclId, Str=DmdType] $dNum_aGE = Main.$fNumFoo @ q @ Int GHC.Num.$fNumInt } in bar @ (Foo q Int) (Main.$fClass1Foo @ q @ Int $dNum_aGE ($dQux_aFH, $dIntegral_aGI) GHC.Num.$fNumInt) (Main.$fClass2Foo @ q @ Int $dNum_aGE ($dQux_aFH, $dIntegral_aGI) GHC.Num.$fNumInt) Orig lhs: let { $dIntegral_aGI :: Integral Int [LclId, Str=DmdType] $dIntegral_aGI = GHC.Real.$fIntegralInt } in let { tup_aGJ :: Qux' q Int [LclId, Str=DmdType] tup_aGJ = ($dQux_aFH, $dIntegral_aGI) } in let { $dNum_aGH :: Num Int [LclId, Str=DmdType] $dNum_aGH = GHC.Num.$fNumInt } in let { $dNum_aGG :: Num Int [LclId, Str=DmdType] $dNum_aGG = $dNum_aGH } in let { tup_aGF :: Qux' q Int [LclId, Str=DmdType] tup_aGF = ($dQux_aFH, $dIntegral_aGI) } in let { $dNum_aGE :: Num (Foo q Int) [LclId, Str=DmdType] $dNum_aGE = Main.$fNumFoo @ q @ Int $dNum_aGH } in let { $dClass2_aFK :: Class2 (Foo q Int) [LclId, Str=DmdType] $dClass2_aFK = Main.$fClass2Foo @ q @ Int $dNum_aGE tup_aGJ $dNum_aGH } in let { $dClass1_aFJ :: Class1 (Foo q Int) [LclId, Str=DmdType] $dClass1_aFJ = Main.$fClass1Foo @ q @ Int $dNum_aGE tup_aGF $dNum_aGG } in bar @ (Foo q Int) $dClass1_aFJ $dClass2_aFK }}} This is apparently due to my use of a constraint synonym. In this code it would be quite simple to just replace the synonym with the constraints on its RHS, but in my real code my constraint synonym is an associated type, so that is not an option. It would be great o be able to specialize in the presence of constraint synonyms. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12068 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12068: RULE too complicated to desugar when using constraint synonyms -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): This is actually OK in HEAD. We get the RULE {{{ "SPEC bar" [ALWAYS] forall (@ q_a1SJ) ($dQux_a1SK :: Qux q_a1SJ) ($dIntegral_a1U3 :: Integral Int) ($dNum_a1U2 :: Num Int) ($dClass1_a1SM :: Class1 (Foo q_a1SJ Int)). bar @ (Foo q_a1SJ Int) $dClass1_a1SM (T12068.$fClass2Foo @ q_a1SJ @ Int ($dQux_a1SK, $dIntegral_a1U3) $dNum_a1U2) = T12068.bar_$sbar @ q_a1SJ $dQux_a1SK }}} (How likely that rule is to fire in practice isn't clear to me, but perhaps it will.) It works in HEAD because the "silent superclass" story, which adds extra parameters to dfuns, has gone away. c.ff #12074, which is defeated by a `let`. I'm not sure if it's worth adding a regression test. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12068#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12068: RULE too complicated to desugar when using constraint synonyms
-------------------------------------+-------------------------------------
Reporter: crockeea | Owner:
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.3
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect | Unknown/Multiple
warning at compile-time | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by thomie):
* status: new => closed
* resolution: => fixed
Comment:
commit a6f0f5ab45b2643b561e0a0a54a4f14745ab2152
{{{
Author: Simon Peyton Jones
It works in HEAD ... I'm not sure if it's worth adding a regression test.
Closing. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12068#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC