[GHC] #10218: GHC creates incorrect code which throws <<loop>>

GHC ghc-devs at haskell.org
Fri Apr 10 16:46:21 UTC 2015


#10218: GHC creates incorrect code which throws <<loop>>
-------------------------------------+-------------------------------------
        Reporter:  yongqli           |                   Owner:
            Type:  bug               |                  Status:  new
        Priority:  normal            |               Milestone:
       Component:  Compiler          |                 Version:  7.10.1
      Resolution:                    |                Keywords:
Operating System:  Unknown/Multiple  |            Architecture:
 Type of failure:  None/Unknown      |  Unknown/Multiple
      Blocked By:                    |               Test Case:  yes
 Related Tickets:                    |                Blocking:
                                     |  Differential Revisions:
-------------------------------------+-------------------------------------

Comment (by simonpj):

 OK here is a nice small test case, which does not (unlike the test above)
 depend on `lens`!
 {{{
 module Main where

 {-# NOINLINE foo #-}
 foo :: Bool -> Int -> Int -> Int
 foo True  _ x = 1
 foo False _ x = x+1

 {-# NOINLINE bar #-}
 bar :: Int -> (Int,Int)
 bar x = let y1 = x * 2
             y2 = x * 2
         in (foo False y1 y2,foo False y2 y1)

 main = print (fst p + snd p)
   where
     p = bar 3
 }}}
 Compile with `-O -feager-blackholing` and you get `<<loop>`.  Add `-fno-
 cse` or `-flate-dmd-anal` restores correct behaviour.

 Points to note
  * `foo` uses its second argument zero times, and its third argument
 exactly once.
  * So the two calls to `foo` in `bar` use `y1` exactly once and `y2`
 exactly once.
  * But when `y1` and `y2` are CSE'd, the usage goes up to twice; and that
 is the problem.

 I'm validating a simple fix in CSE, which zaps the demand-info on binders
 which are potentially shared.  It's a bit brutal.  But another run of the
 demand analyser (which has other advantages) restores everything again.
 I'm validating now; will commit next week.

 Really sorry to have taken two weeks of your time to find this bug.  But
 at least your efforts will be rewarded by a real fix.

 Simon

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


More information about the ghc-tickets mailing list