
#10083: ghc: panic! (the 'impossible' happened) -------------------------------------+------------------------------------- Reporter: hedayaty | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): OK, good. With your reduced test case I can reproduce the bug. I've produced a much smaller version, in two variants {{{ ---------- RSR.hs-boot ------------ module RSR where data RSR instance Eq RSR ---------- SR.hs ------------ module SR where import {-# SOURCE #-} RSR data SR = MkSR RSR deriving( Eq ) ---------- SR.hs ------------ module RSR where import SR data RSR = MkRSR SR deriving( Eq ) }}} Now compile like this {{{ ghc -c -O RSR.hs-boot ghc -c -O SR.hs ghc -c -O RSR.hs }}} Indeed, compiling `RSR` causes infinite inlining. Here's a version that doesn't use instances and so is a bit clearer {{{ ---------- RSR.hs-boot ------------ module RSR where data RSR eqRSR :: RSR -> RSR -> Bool ---------- SR.hs ------------ module SR where import {-# SOURCE #-} RSR data SR = MkSR RSR eqSR (MkSR r1) (MkSR r2) = eqRSR r1 r2 ---------- SR.hs ------------ module RSR where import SR data RSR = MkRSR SR -- deriving( Eq ) eqRSR (MkRSR s1) (MkRSR s2) = (eqSR s1 s2) foo x y = not (eqRSR x y) }}} This fails in the same way. The problem is this. When compiling `RSR` we get this code {{{ RSR.eqRSR :: RSR.RSR -> RSR.RSR -> GHC.Types.Bool RSR.eqRSR = \ (ds_dkA [Occ=Once!] :: RSR.RSR) (ds_dkB [Occ=Once!] :: RSR.RSR) -> case ds_dkA of _ { RSR.MkRSR s1_aeO [Occ=Once] -> case ds_dkB of _ { RSR.MkRSR s2_aeP [Occ=Once] -> SR.eqSR s1_aeO s2_aeP } } RSR.foo :: RSR.RSR -> RSR.RSR -> GHC.Types.Bool RSR.foo = \ (x_aeQ [Occ=Once] :: RSR.RSR) (y_aeR [Occ=Once] :: RSR.RSR) -> GHC.Classes.not (RSR.eqRSR x_aeQ y_aeR) }}} Notice that neither are (apprently) recursive, and neither is a loop breaker. Now, when optimising `foo`: * Inline `eqRSR` * Inline `eqSR` but the result of inlining `eqSR` from `SR` is another call to `eqRSR`, so everything repeats. It's pretty simple, so I'm quite surprised that this hasn't bitten us before now! Next: figure out a solution. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10083#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler