[GHC] #11702: Constant folding on 'mod/Word' - incorrect result

GHC ghc-devs at haskell.org
Sat Mar 12 19:44:28 UTC 2016


#11702: Constant folding on 'mod/Word' - incorrect result
-------------------------------------+-------------------------------------
           Reporter:  ondrap         |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Prelude        |           Version:  7.10.3
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Incorrect result
  Unknown/Multiple                   |  at runtime
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Compiling this with GHC 7.10.3 on both MacOS and Linux with '-O' producess
 results '5 0'.

 {{{#!hs
 module Main where

 testfn :: Word -> IO ()
 testfn wseq = do
   print $ wseq `mod` 1

 main = do
   testfn 5
   print $ (5 :: Word) `mod` 1
 }}}

 Changing type to Int produces correct result. It has probably something to
 do with compiler/prelude/PrelRules.hs - the rules for Int and Word differ.
 It seems to me that it should be optimized the same way, but the culprit
 seems to be the 'rightIdentityDynFlags onew' - that seems to be a clear
 bug (if it does what I think it does).

 {{{#!hs
 primOpRules nm IntRemOp    = mkPrimOpRule nm 2 [ nonZeroLit 1 >> binaryLit
 (intOp2 rem)
                                                , leftZero zeroi
                                                , do l <- getLiteral 1
                                                     dflags <- getDynFlags
                                                     guard (l == onei
 dflags)
                                                     retLit zeroi
                                                , equalArgs >> retLit zeroi
                                                , equalArgs >> retLit zeroi
 ]
 primOpRules nm WordRemOp   = mkPrimOpRule nm 2 [ nonZeroLit 1 >> binaryLit
 (wordOp2 rem)
                                                , rightIdentityDynFlags
 onew ]
 }}}

 I found it in different code where lots of inlining reduced some branch of
 code into this and produced wrong result.

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


More information about the ghc-tickets mailing list