[GHC] #12074: RULE too complicated to desugar
GHC
ghc-devs at haskell.org
Mon May 16 18:50:36 UTC 2016
#12074: RULE too complicated to desugar
-------------------------------------+-------------------------------------
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:
-------------------------------------+-------------------------------------
Another example of specialization failing. Unlike #12068, this example
doesn't use constraint/type synonyms.
{{{
{-# LANGUAGE FlexibleContexts #-}
data Bar a
instance (Num a) => Num (Bar a)
data Foo q
instance (C1 q) => Num (Foo q)
class C1 a
class (Num r, Num (Bar r)) => C2 r
instance (C1 q) => C2 (Foo q)
instance (C2 r) => C2 (Bar r)
{-# SPECIALIZE f :: (C1 q) => Foo q -> Foo q #-}
f :: (C2 r, C2 (Bar r)) => r -> r
f = undefined
}}}
Warning:
{{{
RULE left-hand side too complicated to desugar
Optimised lhs: let {
$dNum_aFp :: Num (Foo q)
[LclId, Str=DmdType]
$dNum_aFp = Main.$fNumFoo @ q $dC1_aEj } in
let {
$dNum_aFq :: Num (Bar (Foo q))
[LclId, Str=DmdType]
$dNum_aFq = Main.$fNumBar @ (Foo q) $dNum_aFp } in
f @ (Foo q)
$dC2_aEl
(Main.$fC2Bar
@ (Foo q)
$dNum_aFq
(Main.$fNumBar @ (Bar (Foo q)) $dNum_aFq)
$dC2_aEl)
Orig lhs: let {
$dNum_aFp :: Num (Foo q)
[LclId, Str=DmdType]
$dNum_aFp = Main.$fNumFoo @ q $dC1_aEj } in
let {
$dNum_aFq :: Num (Bar (Foo q))
[LclId, Str=DmdType]
$dNum_aFq = Main.$fNumBar @ (Foo q) $dNum_aFp } in
let {
$dNum_aFr :: Num (Bar (Bar (Foo q)))
[LclId, Str=DmdType]
$dNum_aFr = Main.$fNumBar @ (Bar (Foo q)) $dNum_aFq } in
let {
$dC2_aEl :: C2 (Foo q)
[LclId, Str=DmdType]
$dC2_aEl = Main.$fC2Foo @ q $dNum_aFp $dNum_aFq $dC1_aEj
} in
let {
$dC2_aEm :: C2 (Bar (Foo q))
[LclId, Str=DmdType]
$dC2_aEm = Main.$fC2Bar @ (Foo q) $dNum_aFq $dNum_aFr
$dC2_aEl } in
f @ (Foo q) $dC2_aEl $dC2_aEm
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12074>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list