[broken HEAD] In which the strict state monad fails at basic arithmetic

Moritz Angermann moritz.angermann at gmail.com
Fri Sep 1 08:44:21 UTC 2017


Hi *,

while working on some related code.  I came across a rather peculiar behavior
with GHC built from the current master branch at b2c2e3e8.

After condensing the application quite a bit[1], the test case now produces

   8 with ghc 8.2.1 and
  -6 with ghc 8.3 @ b2c2e3e8

The sample application is essentially a strict `State Int a` monad, that is being 
advanced by 1 and then by another 7.

```
module Lib where

import Control.Monad.Trans.State.Strict

eval :: Int -> State Int a -> a
eval p = fst . flip runState p

advance :: Int -> State Int ()
advance = modify' . (+)

loc :: State Int Int
loc = get

emit1 :: State Int ()
emit1 = advance 1

emitN :: Int -> State Int ()
-- adding in the 0 case, breaks with HEAD. 8.2.1 is fine with it.
-- emitN 0 = advance 0
emitN 0 = pure ()
emitN n = advance n

align8 :: State Int ()
align8 = do
  bits <- (`mod` 8) <$> loc
  emitN (8 - bits)
```

with the test driver

```

module Main where

import Lib
import System.Exit

main :: IO ()
main = do
  let p = eval 0 (emit1 >> align8 >> loc)
  putStrLn $ show p
  if p == 8
    then putStrLn "OK" >> exitSuccess
    else putStrLn "FAIL" >> exitFailure
```

Compiling both with ghc, will *NOT* exhibit the issue. Only when the `Lib` module
is packed, and `Main` is linked against the package is the issue visible. A 
cabal file for this is contained in [1].

Using the following git bisect script (where [1] is in `../break` relative to ghc)

```
#!/bin/bash
git submodule update --init --recursive
make -s clean
make -s distclean
./boot > /dev/null

if  ./configure --silent --disable-large-address-space &&
        make -s -j9
then
    (cd ../break &&
         rm -fR dist-newstyle &&
         cabal new-run test -w ../ghc/inplace/bin/ghc-stage2)
    status=$?
else
    status=125
fi

exit $status
```

$ git bisect $PWD/bisect.sh

yields:

```
193664d42dbceadaa1e4689dfa17ff1cf5a405a0 is the first bad commit
commit 193664d42dbceadaa1e4689dfa17ff1cf5a405a0
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Wed Mar 8 10:26:47 2017 +0000

    Re-engineer caseRules to add tagToEnum/dataToTag

    See Note [Scrutinee Constant Folding] in SimplUtils

    * Add cases for tagToEnum and dataToTag. This is the main new
      bit.  It allows the simplifier to remove the pervasive uses
      of     case tagToEnum (a > b) of
                False -> e1
                True  -> e2
      and replace it by the simpler
             case a > b of
                DEFAULT -> e1
                1#      -> e2
      See Note [caseRules for tagToEnum]
      and Note [caseRules for dataToTag] in PrelRules.

    * This required some changes to the API of caseRules, and hence
      to code in SimplUtils.  See Note [Scrutinee Constant Folding]
      in SimplUtils.

    * Avoid duplication of work in the (unusual) case of
         case BIG + 3# of b
           DEFAULT -> e1
           6#      -> e2

      Previously we got
         case BIG of
           DEFAULT -> let b = BIG + 3# in e1
           3#      -> let b = 6#       in e2

      Now we get
         case BIG of b#
           DEFAULT -> let b = b' + 3# in e1
           3#      -> let b = 6#      in e2

    * Avoid duplicated code in caseRules

    A knock-on refactoring:

    * Move Note [Word/Int underflow/overflow] to Literal, as
      documentation to accompany mkMachIntWrap etc; and get
      rid of PrelRuls.intResult' in favour of mkMachIntWrap
```

I do not yet understand exactly where this goes wrong. But I hope
someone else will be able to help out? I do find it curious though
that this bug seems to have gone unnoticed (assuming the commit
git bisect found is indeed the underlying issue) for almost half
a year. And please, if my analysis is faulty at some point don’t
hesitate to point that out!

Cheers,
 Moritz

PS: can we have a folder in ghc, which contains cabal packages,
    and part of the validation is just iterating over all those
    packages with `cabal new-test -w /path/to/inplace/bin/ghc-stage2`?
    In that case, one could simply change the executable target in
    [1] into a testsuite, and drop the package into that folder?

—
[1]: https://gist.github.com/angerman/c6ee51e4892ce6efdbcabb8c5ab990fa


More information about the ghc-devs mailing list