Re: [GHC] #15005: GHC fails with “StgCmmEnv: variable not found” when trying to compile order-maintenance-0.2.1.0

GHC ghc-devs at haskell.org
Fri Apr 6 08:33:37 UTC 2018


#15005: GHC fails with “StgCmmEnv: variable not found” when trying to compile
order-maintenance-0.2.1.0
-------------------------------------+-------------------------------------
        Reporter:  jeltsch           |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:  8.4.3
       Component:  Compiler          |              Version:  8.4.2-rc1
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  Compile-time      |  Unknown/Multiple
  crash or panic                     |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by simonpj):

 The bug is in this line of `Exitify`
 {{{
         -- The possible arguments of this exit join point
         args = filter (`elemVarSet` fvs) captured
 }}}
 You have to do at least `map zapStableUnfolding` over args.

 Consider
 {{{
 joinrec j x
   = let {-# INLINE foo #-}
         foo y = blah
     in
     case x of
        True -> j2 foo (h x)
        False -> ...j....
 }}}
 We are going to exitify the True branch of the 'case x'.  But 'foo' is
 captured, so we get
 {{{
 join exit foo x = jump j2 foo (h x) in
 joinrec j x
   = let {-# INLINE foo #-}
         foo y = blah
     in
     case x of
        True -> jump exit foo x
        False -> ...j....
 }}}
 But we must zap `foo`'s unfolding when we lambda-abstract it!  In effect,
 the lambda-bound `foo` is an entirely new `foo`, unrelated to the
 original.

 Actually, arguably we should give the lambda-bound foo `vanillaIdInfo`.
 We do this in `SetLevels.abstractVars`.  I think that'd be safer.  We
 don't seem to have a function `zapAllIdInfo` but we probably should.

 Over to you.  Please include some version of this explanation, of course.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15005#comment:6>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list