#3049: STM with data invariants crashes GHC
-------------------------------+--------------------------------------------
  Reporter:  simonpj           |          Owner:                  
      Type:  bug               |         Status:  new             
  Priority:  normal            |      Milestone:                  
 Component:  Compiler          |        Version:  6.10.1          
  Severity:  normal            |       Keywords:                  
Difficulty:  Unknown           |       Testcase:                  
        Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
-------------------------------+--------------------------------------------
 Ben Franksen writes: 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:
 {{{
 b...@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... :-)

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3049>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to