[GHC] #14171: STM causes program to suddenly exit

#14171: STM causes program to suddenly exit ----------------------------------------+---------------------------------- Reporter: MichaelBurge | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: libraries/stm | Version: 8.2.1 Keywords: | Operating System: Linux Architecture: Unknown/Multiple | Type of failure: Runtime crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: ----------------------------------------+---------------------------------- Observed behavior: * The below program exits with return code 0 between the call to 'error "derp2"' and the call to 'error "derp"' * If the statement 'error "derp2"' is uncommented, the program will terminate with an exception. * The program only exits without output with -O. And in particular, with no-ignore-interface-pragmas. Expected behavior: * The program should terminate with an exception regardless of whether 'error "derp2"' is commented out or not. {{{#!hs module Main where import Control.Concurrent.STM import Control.Concurrent.STM.TVar data A = A String deriving (Eq, Show) data E = E { a :: TVar [Int], b :: TVar A, c :: TVar [Int] } consistency_1 :: E -> STM Bool consistency_1 = \e -> do _ <- readTVar $ c e return True installSanityChecks :: E -> IO () installSanityChecks e = do x e error "derp" x e = do atomically $ mapM_ installCheck [ consistency_1 ] -- error "derp2" where installCheck check = always $ check e main :: IO () main = do state <- initialize installSanityChecks state initialize :: IO E initialize = E <$> newTVarIO [] <*> newTVarIO (A "USD") <*> newTVarIO [] }}} Build options: (Remove -O and it will show the error) {{{ /home/mburge/tmp/ghc/ghc-8.2.1/build/bin/ghc \ -O \ -package-id base-4.10.0.0 \ -package-id stm-2.4.4.1-2iQ3ZIiQ6vc4AnCVcs8oMd \ app/Main.hs \ -package-db /home/mburge/.stack/snapshots/x86_64-linux/nightly-2017-08-24/8.2.1/pkgdb }}} I used a fresh copy of GHC installed from here: https://www.haskell.org/ghc/download.html -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14171 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14171: STM causes program to suddenly exit
----------------------------------+----------------------------------------
Reporter: MichaelBurge | Owner: bgamari
Type: bug | Status: new
Priority: highest | Milestone:
Component: libraries/stm | Version: 8.2.1
Resolution: | Keywords:
Operating System: Linux | Architecture: Unknown/Multiple
Type of failure: Runtime crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
----------------------------------+----------------------------------------
Changes (by bgamari):
* owner: (none) => bgamari
* priority: normal => highest
Comment:
This sounds quite bad. Furthermore, it seems that `check#` has absolutely
no test coverage.
I suspect this is due to our treatment of STM in the demand analyser; `x`
in the above program ends up looking like this after strictness analysis,
{{{#!hs
x_s2KO :: E -> State# RealWorld -> (# State# RealWorld, () #)
x_s2KO
= \ (e_a2hN [Dmd=], ipv1_a2Kk [Dmd=] :: State# RealWorld) ->
case e_a2hN of
{ E ds_d2EV [Dmd=] ->
case ds_d2EX of { GHC.Conc.Sync.TVar tvar#_a2JR
[Dmd=] ->
case readTVar#
@ RealWorld @ [Int] tvar#_a2JR s_a2Ki
of
{ (# ipv_a2JG [Dmd=], ipv1_a2JH [Dmd=]
{ __DEFAULT -> (# s'_a2Kv, GHC.Tuple.() #) }
})
eta_B1
}}}
Which then leads us to conclude that the failure in `installSanityChecks`
is redundant. Concerningly, this doesn't seem to be caught by the
`-fcatch-bottoms` flag introduced in #13916.
I'll try to come back to this tomorrow or after ICFP.
--
Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14171#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

#14171: STM causes program to suddenly exit
----------------------------------+----------------------------------------
Reporter: MichaelBurge | Owner: bgamari
Type: bug | Status: new
Priority: highest | Milestone:
Component: libraries/stm | Version: 8.2.1
Resolution: | Keywords:
Operating System: Linux | Architecture: Unknown/Multiple
Type of failure: Runtime crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
----------------------------------+----------------------------------------
Comment (by Ben Gamari

#14171: STM causes program to suddenly exit
----------------------------------+----------------------------------------
Reporter: MichaelBurge | Owner: bgamari
Type: bug | Status: new
Priority: highest | Milestone:
Component: libraries/stm | Version: 8.2.1
Resolution: | Keywords:
Operating System: Linux | Architecture: Unknown/Multiple
Type of failure: Runtime crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
----------------------------------+----------------------------------------
Comment (by bgamari):
I had another quick look at this and believe that the critical mistake is
this,
{{{
dmdAnal:app
dmd =

#14171: STM causes program to suddenly exit ----------------------------------+---------------------------------------- Reporter: MichaelBurge | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: Component: libraries/stm | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------+---------------------------------------- Comment (by bgamari): I think I see what is going on here: `postProcessDmdResult` looks only for `ThrowsExn` `DmdResult` when computing termination, {{{#!hs postProcessDmdResult :: Str () -> DmdResult -> DmdResult postProcessDmdResult Lazy _ = topRes postProcessDmdResult (Str ExnStr _) ThrowsExn = topRes -- Key point! postProcessDmdResult _ res = res }}} However, the demand being analysed here is `Diverges`, not `ThrowsExn` (again, due to the use of `retry#`). One "solution" here is, {{{#!patch diff --git a/compiler/basicTypes/Demand.hs b/compiler/basicTypes/Demand.hs index dfff0a2c92..f56d28c4a9 100644 --- a/compiler/basicTypes/Demand.hs +++ b/compiler/basicTypes/Demand.hs @@ -1440,6 +1441,7 @@ postProcessDmdType du@(JD { sd = ss }) (DmdType fv _ res_ty) postProcessDmdResult :: Str () -> DmdResult -> DmdResult postProcessDmdResult Lazy _ = topRes postProcessDmdResult (Str ExnStr _) ThrowsExn = topRes -- Key point! +postProcessDmdResult (Str ExnStr _) Diverges = topRes -- Key point! postProcessDmdResult _ res = res }}} This allows the program malfunctioning in this ticket to run as expected. However, it's not clear to me that this is correct: the `ThrowsExn`/`Diverges` distinction isn't defined in the original demand analysis paper nor any of the later papers that I have found. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14171#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14171: STM causes program to suddenly exit ----------------------------------+---------------------------------------- Reporter: MichaelBurge | Owner: bgamari Type: bug | Status: patch Priority: highest | Milestone: 8.4.1 Component: libraries/stm | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3919 Wiki Page: | ----------------------------------+---------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D3919 * milestone: => 8.4.1 Comment: I think the correct fix is Phab:D3919. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14171#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14171: STM causes program to suddenly exit ----------------------------------+---------------------------------------- Reporter: MichaelBurge | Owner: bgamari Type: bug | Status: patch Priority: highest | Milestone: 8.4.1 Component: libraries/stm | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #8091 | Differential Rev(s): Phab:D3919 Wiki Page: | ----------------------------------+---------------------------------------- Changes (by bgamari): * related: => #8091 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14171#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14171: STM causes program to suddenly exit
----------------------------------+----------------------------------------
Reporter: MichaelBurge | Owner: bgamari
Type: bug | Status: patch
Priority: highest | Milestone: 8.4.1
Component: libraries/stm | Version: 8.2.1
Resolution: | Keywords:
Operating System: Linux | Architecture: Unknown/Multiple
Type of failure: Runtime crash | Test Case:
Blocked By: | Blocking:
Related Tickets: #8091 | Differential Rev(s): Phab:D3919
Wiki Page: |
----------------------------------+----------------------------------------
Comment (by Ben Gamari

#14171: STM causes program to suddenly exit ----------------------------------+---------------------------------------- Reporter: MichaelBurge | Owner: bgamari Type: bug | Status: closed Priority: highest | Milestone: 8.4.1 Component: libraries/stm | Version: 8.2.1 Resolution: fixed | Keywords: Operating System: Linux | Architecture: Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #8091 | Differential Rev(s): Phab:D3919 Wiki Page: | ----------------------------------+---------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14171#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC