STM and unsafePerformIO/bracket

I’ve run into a difficulty I’d appreciate some advice to solve. I am trying to make a call to C (through the FFI) within an STM transaction to compute what is effectively a pure result. By itself this doesn’t seem to be a problem, except that the C function depends on some global state in a way that compromises thread safety, and so I would like to serialize the process of setting up that state and calling the FFI. I have tried wrapping my call up with:
unsafePerformIO $ bracket (takeMVar lock) (putMVar lock) $ \_ -> do setupFFIGlobalState callFFI
This seems to work as intended, with one significant exception. If the surrounding STM transaction is aborted (i.e. because of a TVar conflict detected by another thread) while inside the bracket, then apparently the second argument to ‘bracket’ may never be evaluated, leaving my ‘lock’ mutex forever empty, and eventually causing deadlock. Here is a working example of the problem: http://lpaste.net/99399 When I run that, I get: taking lock... lock acquired taking lock... stm-test: thread blocked indefinitely in an MVar operation Is this expected behavior? I realize performing any IO within an STM transaction is inherently unsafe, but I am a little surprised that ‘bracket’ fails here. Is there a better way to do what I’m trying to accomplish? How can I provide a pure interface to my foreign function that will work within an STM transaction? Thanks, -- Rob Leslie rob@mars.org

Rob Leslie
writes:
Is this expected behavior? I realize performing any IO within an STM transaction is inherently unsafe, but I am a little surprised that ‘bracket’ fails here.
Is there a better way to do what I’m trying to accomplish? How can I provide a pure interface to my foreign function that will work within an STM transaction?
If your foreign function "depends on some global state in a way that compromises thread safety", I would hestitate to simply tell the FFI that it is pure. Instead, you can break up your STM transaction into two pieces: A first part that sets up the transaction and sets a guard variable so other transactions cannot proceed until the second part is completed, then perform the FFI call, then the second part of the transaction. For example: atomically $ do m <- readTVar mutex check (not m) writeTVar m True ... do whatever STM setup work is needed here ... ffiCall atomically $ do ... do whatever STM cleanup work is needed here ... writeTVar m False This way your ffiCall is conceptually within a larger transactional block. John

John's approach is the right one, but note that the "STM setup work" will
be visible to other transactions. Any work done there must be considered
consistent as it will be committed. For instance if we have the following:
atomically $ do
m <- readTVar mutex
check (not m)
writeTVar m True
writeTVar a True
ffiCall
atomically $ do
writeTVar b True
writeTVar m False
If it should be the case that `a` is true only if `b` is true then we could
run into problems with some other transaction that is not concerned with
the `ffiCall` but is concerned about `a` and `b`.
Another approach that might be viable is to just fix your foreign call's
interface by putting a lock in the foreign code. If it really is a pure
call, then there is no danger of deadlocking there. This will then be as
safe as any foreign call inside STM. There are dangers here of course.
One particular danger is if your call takes multiple arguments that need
to be consistent, you can see inconsistency inside a failed transaction
before the runtime system has determined that it is a failed transaction.
For instance:
atomically $ do
x <- readTVar a
y <- readTVar b
return $ unsafePerformIO $ ffiCall x y
Say `x` is an array and `y` is an index into that array. Even if your
transactions keep these consistent, you could send inconsistent data to the
foreign call. You can fix this by checking (at the value level)
the integrity of the data or changing the granularity of the data and
putting values `x` and `y` into the same `TVar`.
Beyond this problem I don't know what other issues foreign calls inside STM
face, but I would love to hear what others know.
Ryan
On Mon, Feb 3, 2014 at 6:17 AM, John Wiegley
Rob Leslie
writes: Is this expected behavior? I realize performing any IO within an STM transaction is inherently unsafe, but I am a little surprised that 'bracket' fails here.
Is there a better way to do what I'm trying to accomplish? How can I provide a pure interface to my foreign function that will work within an STM transaction?
If your foreign function "depends on some global state in a way that compromises thread safety", I would hestitate to simply tell the FFI that it is pure.
Instead, you can break up your STM transaction into two pieces: A first part that sets up the transaction and sets a guard variable so other transactions cannot proceed until the second part is completed, then perform the FFI call, then the second part of the transaction. For example:
atomically $ do m <- readTVar mutex check (not m) writeTVar m True ... do whatever STM setup work is needed here ... ffiCall atomically $ do ... do whatever STM cleanup work is needed here ... writeTVar m False
This way your ffiCall is conceptually within a larger transactional block.
John _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mon, Feb 3, 2014 at 5:50 AM, Rob Leslie
I’ve run into a difficulty I’d appreciate some advice to solve.
I am trying to make a call to C (through the FFI) within an STM transaction to compute what is effectively a pure result. By itself this doesn’t seem to be a problem, except that the C function depends on some global state in a way that compromises thread safety, and so I would like to
This does not sound particularly pure to me, from a Haskell standpoint.
unsafePerformIO $ bracket (takeMVar lock) (putMVar lock) $ \_ -> do
And this looks to me like completely undefined behavior. I suspect bracket *can't* work in unsafePerformIO. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Rob Leslie wrote:
I’ve run into a difficulty I’d appreciate some advice to solve. [unsafePerformIO and bracket, within an STM transaction]
There's a long-standing bug report for this issue, https://ghc.haskell.org/trac/ghc/ticket/2401 So the current situation is that bracket within unsafePerformIO (and unsafeIOToSTM) and STM transactions don't mix. I'm a bit surprised that this doesn't bite more people. Cheers, Bertram

I use this trick, that unlike the previous workarounds permits concurrency
and does handle the IO computation in a civilized way, that is, it permits
brackets and so on:
notReallySafeButNotAsUnsafeAsUnsafeIOToSTM= safeIOToSTM
safeIOToSTM ∷ IO a → STM a
safeIOToSTM req= unsafeIOToSTM $ do
tv ← newEmptyMVar
forkIO $ (req ↠ putMVar tv . Right)
`Control.Exception.catch`
(λ(e ∷ SomeException) → putMVar tv $ Left e )
r ← takeMVar tv
case r of
Right x → return x
Left e → throw e
Here the IO computation is run in another thread. Even If the STM
transaction is aborted, the IO computation finalizes. If the STM
transaction is retried, the IO computation is re-executed, so it is up to
you to take this into account depending on what you intend to do.
If the IO computation throws an exception the STM transaction throws it. As
far as I remember, this trick was used in a package time ago to do solve
the problem.
2014-02-04 Bertram Felgenhauer
Rob Leslie wrote:
I’ve run into a difficulty I’d appreciate some advice to solve. [unsafePerformIO and bracket, within an STM transaction]
There's a long-standing bug report for this issue,
https://ghc.haskell.org/trac/ghc/ticket/2401
So the current situation is that bracket within unsafePerformIO (and unsafeIOToSTM) and STM transactions don't mix. I'm a bit surprised that this doesn't bite more people.
Cheers,
Bertram _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Alberto.
participants (6)
-
Alberto G. Corona
-
Bertram Felgenhauer
-
Brandon Allbery
-
John Wiegley
-
Rob Leslie
-
Ryan Yates