[GHC] #13429: Optimizer produces Core with an infinite <<loop>>
GHC
ghc-devs at haskell.org
Tue May 2 00:23:00 UTC 2017
#13429: Optimizer produces Core with an infinite <<loop>>
-------------------------------------+-------------------------------------
Reporter: lehins | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone: 7.10.4
Component: Compiler | Version: 8.0.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: Runtime crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by bgamari):
So David and I discussed this a bit and I suspect that the loop arises as
early as typechecking. David summarized quite well above, but I thought I
might try to recap to make sure I also understand.
Recall that the minimized example has the following,
{{{#!hs
module Loop where
data X
class Num e => Array cs e where ...
instance Num e => Array X e where ...
module Main where
import Loop
{- some bindings requiring an Array X Word8 instance -}
}}}
The output from the desugarer is nothing special, containing a local
dictionary binding for `Array X Word8`,
{{{#!hs
-- main.dump-ds
$dArray_a1zv :: Array X Word8
$dArray_a1zv = Loop.$fArrayXe @Word8 GHC.Word.$fNumWord8
}}}
The specialiser then takes this and sees the `Loop.$fArrayXe` DFun from
the `Array X e` instance and tries to specialise it. This results in,
{{{#!hs
$dArray_s1BE :: Array X Word8
$dArray_s1BE = Loop.$fArrayXe @Word8 GHC.Word.$fNumWord8
$s$fArrayXe_s1BU [InlPrag=[ALWAYS] CONLIKE] :: Array X Word8
$s$fArrayXe_s1BU =
Loop.C:Array
@ X
@ Word8
(Loop.$fArrayXe_$cp1Array @Word8 $dNum_s1BJ)
(Loop.$fArrayXe_$cpromote @Word8 $dNum_s1BJ)
(Loop.$fArrayXe_$cmakeImage @Word8 $dNum_s1BJ)
$dNum_s1BJ :: Num Word8
$dNum_s1BJ = Loop.$p1Array @X @Word8 $dArray_s1BE
-- N.B. $p1Array is a selector for Array's Num superclass
{- Rules:
"SPEC/Main $fArrayXe @Word8" [ALWAYS]
forall ($dNum_s1BL :: Num Word8).
Loop.$fArrayXe @Word8 $dNum_s1BL
= $s$fArrayXe_s1BU
-}
}}}
As David pointed out above, this introduces a rather problematic rule.
It's problematic because it will rewrite `$dArray_s1BE`, which introduces
the concrete `fNumWord8` dictionary into our local `Array X Word8`
dictionary. It will rewrite `$dArray_s1BE` in terms of `$s$fArrayXe_s1BU`,
which has no mention of any concrete `Num` dictionary, instead pulling it
out of `$dArray_s1BE` via a superclass selector.
This is clearly a bad situation: the specialiser has introduced a loop
where there was none previously. It's not entirely obvious how to pin down
what is "bad" about this rule, but the fact that it throws away a
dictionary argument is certainly relevant.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13429#comment:15>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list