Bug in STM with data invariants

Ben Franksen ben.franksen at online.de
Tue Feb 24 14:49:54 EST 2009


My ghc(i) crashes when using STM data invariants. This little piece of code
demonstrates the problem:

module Bug where

import Control.Concurrent.STM

test = do
  x <- atomically $ do
    v <- newTVar 0
    always $ return True -- remove this line and all is fine
    return v
  atomically (readTVar x) >>= print

This is what ghci makes of it:

ben at sarun> ghci Bug.hs
GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Bug              ( Bug.hs, interpreted )
Ok, modules loaded: Bug.
*Bug> test
Loading package syb ... linking ... done.
Loading package array-0.2.0.0 ... linking ... done.
Loading package stm-2.1.1.2 ... linking ... done.
zsh: segmentation fault  ghci Bug.hs

I am using ghc-6.10.1 freshly installed from source with just a 'cabal
install stm' thrown after it.

BTW, the documentation for Control.Concurrent.STM.TVar lists... nothing.
Similar with Control.Monad.STM. Well, at least the source link works, so
one isn't completely lost... :-)

Cheers
Ben



More information about the Glasgow-haskell-users mailing list