Re: Simplifier bug fixed in GHC 8.8.1?

2019-10-28 Thread Alexis King
Wonderful, thank you for the investigation! (Well, maybe not so wonderful if it 
isn’t actually fixed yet, but your followup comment in the issue gives me hope 
it is.) I’ll take the discussion over there, then.

> On Oct 28, 2019, at 05:06, Sebastian Graf  wrote:
> 
> Hi Alexis,
> 
> I think the fact that it looks like it's fixed is only a coincidence. See 
> https://gitlab.haskell.org/ghc/ghc/issues/17409 
> , where I go into a bit more 
> detail.
> 
> Cheers
> Sebastian
> 
> Am Mo., 28. Okt. 2019 um 07:16 Uhr schrieb Alexis King  >:
> Hi all,
> 
> I have an odd question: I’ve bumped into a clear simplifier bug, and although 
> it only happens on GHC 8.6.5, not 8.8.1, I’d like to locate the change that 
> fixed it. My library’s test suite currently fails on GHC 8.6.5 due to the 
> bug, and I’d rather not force all my users to upgrade to 8.8 if I can help 
> it, so I’m hoping to find a workaround.
> 
> The minimal test case I’ve found for the bug is this program:
> 
> {-# LANGUAGE GeneralizedNewtypeDeriving, StandaloneDeriving, TypeFamilies 
> #-}
> 
> import Control.Exception
> import Control.Monad.IO.Class
> import Control.Monad.Trans.Identity
> import Control.Monad.Trans.Reader
> 
> class Monad m => MonadFoo m where
>   foo :: m a -> m a
> instance MonadFoo IO where
>   foo m = onException m (pure ())
> instance MonadFoo m => MonadFoo (ReaderT r m) where
>   foo m = ReaderT $ \r -> foo (runReaderT m r)
> deriving instance MonadFoo m => MonadFoo (IdentityT m)
> 
> type family F m where
>   F m = IdentityT m
> 
> newtype FT m a = FT { runFT :: F m a }
>   deriving (Functor, Applicative, Monad, MonadIO, MonadFoo)
> 
> main :: IO ()
> main = run (foo (liftIO (throwIO (IndexOutOfBounds "bang"
>   where
> run :: ReaderT () (FT (ReaderT () IO)) a -> IO a
> run = flip runReaderT () . runIdentityT . runFT . flip runReaderT ()
> 
> Using GHC 8.6.5 on macOS 10.14.5, compiling this program with optimizations 
> reliably triggers the -fcatch-bottoms sanitization:
> 
> $ ghc -O -fcatch-bottoms weird.hs && ./weird
> [1 of 1] Compiling Main ( weird.hs, weird.o )
> Linking weird ...
> weird: Bottoming expression returned
> 
> What goes wrong? Somehow the generated core for this program includes the 
> following:
> 
> lvl_s47B :: SomeException
> lvl_s47B = $fExceptionArrayException_$ctoException lvl_s483
> 
> m_s47r :: () -> State# RealWorld -> (# State# RealWorld, () #)
> m_s47r
>   = \ _ (eta_B1 :: State# RealWorld) -> raiseIO# lvl_s47B eta_B1
> 
> main_s2Ww :: State# RealWorld -> (# State# RealWorld, () #)
> main_s2Ww
>   = \ (eta_a2wK :: State# RealWorld) ->
>   catch# (case m_s47r `cast`  of { }) raiseIO# eta_a2wK
> 
> This core is completely bogus: it assumes that m_s47r is bottom, but m_s47r 
> is a top-level function! The program still passes -dcore-lint, unfortunately, 
> as it is still well-typed. (Also, in case it helps: 
> -ddump-simplifier-iterations shows that the buggy transformation occurs in 
> the first iteration of the very first simplifier pass.)
> 
> I’ve been trying to figure out what change might have fixed this so that I 
> can assess if it’s possible to work around, but I haven’t found anything 
> obvious. I’ve been slowly `git bisect`ing to look for the commit that 
> introduced the fix, but many of the commits I’ve tested cause unrelated 
> panics on my machine, which has been exacerbating the problem of the slow 
> recompilation times. I’m a little at wits’ end, but opening a bug report 
> hasn’t felt right, since the bug does appear to already be fixed.
> 
> Does this issue ring any bells to anyone on this list? Is there a particular 
> patch that landed between GHC 8.6.5 and GHC 8.8.1 that might have fixed this 
> problem? If not, I’ll keep trying with `git bisect`, but I’d appreciate any 
> pointers.
> 
> Thanks,
> Alexis
> 
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org 
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs 
> 

___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Simplifier bug fixed in GHC 8.8.1?

2019-10-28 Thread Sebastian Graf
Hi Alexis,

I think the fact that it looks like it's fixed is only a coincidence. See
https://gitlab.haskell.org/ghc/ghc/issues/17409, where I go into a bit more
detail.

Cheers
Sebastian

Am Mo., 28. Okt. 2019 um 07:16 Uhr schrieb Alexis King <
lexi.lam...@gmail.com>:

> Hi all,
>
> I have an odd question: I’ve bumped into a clear simplifier bug, and
> although it only happens on GHC 8.6.5, not 8.8.1, I’d like to locate the
> change that fixed it. My library’s test suite currently fails on GHC 8.6.5
> due to the bug, and I’d rather not force all my users to upgrade to 8.8 if
> I can help it, so I’m hoping to find a workaround.
>
> The minimal test case I’ve found for the bug is this program:
>
> {-# LANGUAGE GeneralizedNewtypeDeriving, StandaloneDeriving,
> TypeFamilies #-}
>
> import Control.Exception
> import Control.Monad.IO.Class
> import Control.Monad.Trans.Identity
> import Control.Monad.Trans.Reader
>
> class Monad m => MonadFoo m where
>   foo :: m a -> m a
> instance MonadFoo IO where
>   foo m = onException m (pure ())
> instance MonadFoo m => MonadFoo (ReaderT r m) where
>   foo m = ReaderT $ \r -> foo (runReaderT m r)
> deriving instance MonadFoo m => MonadFoo (IdentityT m)
>
> type family F m where
>   F m = IdentityT m
>
> newtype FT m a = FT { runFT :: F m a }
>   deriving (Functor, Applicative, Monad, MonadIO, MonadFoo)
>
> main :: IO ()
> main = run (foo (liftIO (throwIO (IndexOutOfBounds "bang"
>   where
> run :: ReaderT () (FT (ReaderT () IO)) a -> IO a
> run = flip runReaderT () . runIdentityT . runFT . flip runReaderT
> ()
>
> Using GHC 8.6.5 on macOS 10.14.5, compiling this program with
> optimizations reliably triggers the -fcatch-bottoms sanitization:
>
> $ ghc -O -fcatch-bottoms weird.hs && ./weird
> [1 of 1] Compiling Main ( weird.hs, weird.o )
> Linking weird ...
> weird: Bottoming expression returned
>
> What goes wrong? Somehow the generated core for this program includes the
> following:
>
> lvl_s47B :: SomeException
> lvl_s47B = $fExceptionArrayException_$ctoException lvl_s483
>
> m_s47r :: () -> State# RealWorld -> (# State# RealWorld, () #)
> m_s47r
>   = \ _ (eta_B1 :: State# RealWorld) -> raiseIO# lvl_s47B eta_B1
>
> main_s2Ww :: State# RealWorld -> (# State# RealWorld, () #)
> main_s2Ww
>   = \ (eta_a2wK :: State# RealWorld) ->
>   catch# (case m_s47r `cast`  of { }) raiseIO# eta_a2wK
>
> This core is completely bogus: it assumes that m_s47r is bottom, but
> m_s47r is a top-level function! The program still passes -dcore-lint,
> unfortunately, as it is still well-typed. (Also, in case it helps:
> -ddump-simplifier-iterations shows that the buggy transformation occurs in
> the first iteration of the very first simplifier pass.)
>
> I’ve been trying to figure out what change might have fixed this so that I
> can assess if it’s possible to work around, but I haven’t found anything
> obvious. I’ve been slowly `git bisect`ing to look for the commit that
> introduced the fix, but many of the commits I’ve tested cause unrelated
> panics on my machine, which has been exacerbating the problem of the slow
> recompilation times. I’m a little at wits’ end, but opening a bug report
> hasn’t felt right, since the bug does appear to already be fixed.
>
> Does this issue ring any bells to anyone on this list? Is there a
> particular patch that landed between GHC 8.6.5 and GHC 8.8.1 that might
> have fixed this problem? If not, I’ll keep trying with `git bisect`, but
> I’d appreciate any pointers.
>
> Thanks,
> Alexis
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Simplifier bug fixed in GHC 8.8.1?

2019-10-27 Thread Alexis King
Hi all,

I have an odd question: I’ve bumped into a clear simplifier bug, and although 
it only happens on GHC 8.6.5, not 8.8.1, I’d like to locate the change that 
fixed it. My library’s test suite currently fails on GHC 8.6.5 due to the bug, 
and I’d rather not force all my users to upgrade to 8.8 if I can help it, so 
I’m hoping to find a workaround.

The minimal test case I’ve found for the bug is this program:

{-# LANGUAGE GeneralizedNewtypeDeriving, StandaloneDeriving, TypeFamilies 
#-}

import Control.Exception
import Control.Monad.IO.Class
import Control.Monad.Trans.Identity
import Control.Monad.Trans.Reader

class Monad m => MonadFoo m where
  foo :: m a -> m a
instance MonadFoo IO where
  foo m = onException m (pure ())
instance MonadFoo m => MonadFoo (ReaderT r m) where
  foo m = ReaderT $ \r -> foo (runReaderT m r)
deriving instance MonadFoo m => MonadFoo (IdentityT m)

type family F m where
  F m = IdentityT m

newtype FT m a = FT { runFT :: F m a }
  deriving (Functor, Applicative, Monad, MonadIO, MonadFoo)

main :: IO ()
main = run (foo (liftIO (throwIO (IndexOutOfBounds "bang"
  where
run :: ReaderT () (FT (ReaderT () IO)) a -> IO a
run = flip runReaderT () . runIdentityT . runFT . flip runReaderT ()

Using GHC 8.6.5 on macOS 10.14.5, compiling this program with optimizations 
reliably triggers the -fcatch-bottoms sanitization:

$ ghc -O -fcatch-bottoms weird.hs && ./weird
[1 of 1] Compiling Main ( weird.hs, weird.o )
Linking weird ...
weird: Bottoming expression returned

What goes wrong? Somehow the generated core for this program includes the 
following:

lvl_s47B :: SomeException
lvl_s47B = $fExceptionArrayException_$ctoException lvl_s483

m_s47r :: () -> State# RealWorld -> (# State# RealWorld, () #)
m_s47r
  = \ _ (eta_B1 :: State# RealWorld) -> raiseIO# lvl_s47B eta_B1

main_s2Ww :: State# RealWorld -> (# State# RealWorld, () #)
main_s2Ww
  = \ (eta_a2wK :: State# RealWorld) ->
  catch# (case m_s47r `cast`  of { }) raiseIO# eta_a2wK

This core is completely bogus: it assumes that m_s47r is bottom, but m_s47r is 
a top-level function! The program still passes -dcore-lint, unfortunately, as 
it is still well-typed. (Also, in case it helps: -ddump-simplifier-iterations 
shows that the buggy transformation occurs in the first iteration of the very 
first simplifier pass.)

I’ve been trying to figure out what change might have fixed this so that I can 
assess if it’s possible to work around, but I haven’t found anything obvious. 
I’ve been slowly `git bisect`ing to look for the commit that introduced the 
fix, but many of the commits I’ve tested cause unrelated panics on my machine, 
which has been exacerbating the problem of the slow recompilation times. I’m a 
little at wits’ end, but opening a bug report hasn’t felt right, since the bug 
does appear to already be fixed.

Does this issue ring any bells to anyone on this list? Is there a particular 
patch that landed between GHC 8.6.5 and GHC 8.8.1 that might have fixed this 
problem? If not, I’ll keep trying with `git bisect`, but I’d appreciate any 
pointers.

Thanks,
Alexis

___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs