[GHC] #14171: STM causes program to suddenly exit
GHC
ghc-devs at haskell.org
Thu Aug 31 02:29:09 UTC 2017
#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
More information about the ghc-tickets
mailing list