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

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

Moritz Angermann
Hi *,
while working on some related code. I came across a rather peculiar behavior with GHC built from the current master branch at b2c2e3e8.
Indeed this sounds like a real bug. Can you open a ticket? Also, it looks like the gist has projected out directory structure; do you think you could push the testcase as a proper git repository?
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?
The problem is that we don't have access to cabal-install. However, I think there is certainly room for this sort of testing as part of, for instance, the nightly test cycle. In this case we'd likely want to contain this infrastructure in a repository outside of ghc proper. Cheers, - Ben

Moritz Angermann
Hi *,
while working on some related code. I came across a rather peculiar behavior with GHC built from the current master branch at b2c2e3e8.
The issue was a bug indeed introduced by the commit you cite below. The problem was a mistake in a change in constant folding which, frighteningly, the testsuite did not catch. See D3904 for a fix and a test is forthcoming. Cheers, - Ben

Wow -- Fast work! Do add a test case
Simon
| -----Original Message-----
| From: ghc-devs [mailto:ghc-devs-bounces@haskell.org] On Behalf Of Ben
| Gamari
| Sent: 01 September 2017 14:53
| To: Moritz Angermann
participants (4)
-
Ben Gamari
-
Ben Gamari
-
Moritz Angermann
-
Simon Peyton Jones