[Haskell-cafe] STM/Data Invariant related Segfault with GHC 6.10.3

Jan Schaumlöffel jsch at informatik.uni-kiel.de
Mon Jun 22 07:25:36 EDT 2009


Hello,

I just discovered that programs compiled with GHC 6.10.3 segfault when
accessing a TVar created under certain conditions.  This happens when
the TVar is created and a data invariant is added (using
alwaysSucceeds) in the same atomic block.  The invariant does not
necessarily have to read the TVar in question, a mere
"alwaysSucceeds (return ())" is enough.

It looks like by adding the invariant the TVar allocation is not kept
after the block.  The appended code snippets show how to reproduce
this behaviour.  IMHO the first version should work, too.

Is there anything one can do to (reliably) work around this problem?
Is there maybe an underlying problem that causes this?

Regards,
Jan



module Main where
import GHC.Conc

-- this segfaults:
main = do { t <- atomically
                   (do { t1 <- newTVar 0
                       ; alwaysSucceeds (readTVar t1)
                       ; return t1 })
          ; atomically $ readTVar t }

-- it works if written like this:
main2 = do { t <- newTVarIO 0
           ; atomically $ alwaysSucceeds (readTVar t)
           ; atomically $ readTVar t }

-- works also if no invariant is added:             
main3 = do { t <- atomically
                    (do { t1 <- newTVar 0
                        ; return t1 })
           ; atomically $ readTVar t }

-- works also if invariant is added later:
main4 = do { t <- atomically
                    (do { t1 <- newTVar 0
                        ; return t1 })
           ; atomically $ alwaysSucceeds (readTVar t)
           ; atomically $ readTVar t }

-- 
If you're happy and you know it, syntax error!


More information about the Haskell-Cafe mailing list