[Haskell-cafe] threads + IORefs = Segmentation fault?

Lennart Augustsson lennart at augustsson.net
Sat Jan 19 08:46:38 EST 2008


You should use an MVar if you want it to be thread safe.

On Jan 19, 2008 1:36 PM, David Roundy <droundy at darcs.net> wrote:

> Using ghc 6.6, but I've since isolated the bug as being unrelated to the
> IORefs and threading, it was in an FFI binding that somehow never died
> until I was testing this new code.
>
> David
>
> On Sat, Jan 19, 2008 at 01:27:47PM +0100, Peter Verswyvelen wrote:
> > Hi David,
> >
> > Which version of GHC are you using?
> >
> > I tried to recompile some GHC 6.6.1 progs using GHC 6.8.2 and I also got
> > segfaults. I haven't figured out yet if this is because my changes to
> > make it work with GHC 6.8.2 are incorrect, or if this is an issue with
> > 6.8.2.
> >
> > Cheers,
> > Peter
> >
> >
> > On Fri, 2008-01-18 at 18:22 -0500, David Roundy wrote:
> > > Hi all,
> > >
> > > I'm working on some new progress-reporting code for darcs, and am
> getting
> > > segmentation faults!  :( The code uses threads + an IORef global
> variable
> > > to do this (with lots of unsafePerformIO).  So my question for the
> gurus
> > > who know more about this than I do:  is this safe? I thought it would
> be,
> > > because only one thread ever modifies the IORef, and the others only
> read
> > > it.  I don't really care if they read a correct value, as long as they
> > > don't segfault.
> > >
> > > The code (to summarize) looks like:
> > >
> > > {-# NOINLINE _progressData #-}
> > > _progressData :: IORef (Map String ProgressData)
> > > _progressData = unsafePerformIO $ newIORef empty
> > >
> > > updateProgressData :: String -> (ProgressData -> ProgressData) -> IO
> ()
> > > updateProgressData k f = when (progressMode) $ modifyIORef
> _progressData (adjust f k)
> > >
> > > setProgressData :: String -> ProgressData -> IO ()
> > > setProgressData k p = when (progressMode) $ modifyIORef _progressData
> (insert k p)
> > >
> > > getProgressData :: String -> IO (Maybe ProgressData)
> > > getProgressData k = if progressMode then lookup k `fmap` readIORef
> _progressData
> > >                                     else return Nothing
> > >
> > > The key function is
> > >
> > > beginTedious :: String -> IO ()
> > > beginTedious k = do tid <- forkIO $ handleProgress k
> > >                     debugMessage $ "Beginning " ++ k
> > >                     setProgressData k $ ProgressData { sofar = 0,
> > >                                                        latest =
> Nothing,
> > >                                                        total =
> Nothing,
> > >                                                        handler = Just
> tid }
> > >
> > > which is called before an action that may be so tedious for our users
> that
> > > they need their day brightened by messages such as "Applying patch
> > > 137/1436".  The handleProgress function alternates between threadDelay
> and
> > > reading the progress data to see whether any progress has been made
> and
> > > printing messages.  Meanwhile the main thread calls functions that
> update
> > > _progressData.
> > >
> > > Anyhow, the point is that I'm getting segfaults, even after
> recompiling
> > > everything from scratch! Is this in fact that unsafe? Do I really need
> to
> > > switch to MVars, even though no locking is required?
> >
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
>
> --
> David Roundy
> Department of Physics
> Oregon State University
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20080119/7e6b75ac/attachment.htm


More information about the Haskell-Cafe mailing list