[reactive] Is the code in makeTVal free of race conditions?

Peter Verswyvelen bugfact at gmail.com
Sat Nov 29 18:02:54 EST 2008


I'm looking at the makeTVal code:

data TVal t a = TVal { timeVal :: (t,a), definedAt :: t -> Bool }
makeTVal :: Clock TimeT -> MkFed (TVal TimeT a) amakeTVal (Clock getT
_) = f <$> newEmptyIVar
  where
    f v = (TVal (readIVar v) (unsafePerformIO . undefAt), sink)
     where
      undefAt t =
        -- Read v after time t.  If it's undefined, then it wasn't defined
        -- at t.  If it is defined, then see whether it was defined before t.
        do -- ser $ putStrLn $ "sleepPast " ++ show t
           sleepPast getT t--            maybe True ((> t) . fst) <$>
tryReadIVar v
           value <- tryReadIVar v
           case value of
             -- We're past t, if it's not defined now, it wasn't at t.
             Nothing     -> return False
             -- If it became defined before t, then it's defined now.
             Just (t',_) -> return (t' < t)

      sink a = do t <- getT
                  writeIVar v (t,a)

I assume the sink function is called from a different thread than the
one on which undefAt is called.

Suppose a thread switch happens just before the (t,a) value is written
to the IVar in

      sink a = do t <- getT
                  writeIVar v (t,a)

Lets call the t above t1.

Now sleepPast getT t is evaluated on the other thread.

           sleepPast getT t

Assume the parameter t passed to sleepPast is really close to t1 but larger
than t1. Call it t2. So t1 < t2.

Call t3 the time as evaluated by getT in the sleepPast function. So t1 < t2
< t3 (since t3 is read a after t1, and since the clock is serialized, this
is the case I guess)
Since t3 > t2, sleepPast will not call threadDelay, so it is not unlikely
that a thread switch happens. But then

  value <- tryReadIVar v

evaluates to Nothing, since the IVar is not written to yet. So undefAt
will return False, although clearly t1 < t2 and so it should have
returned True.

I'm not sure if my reasoning is correct. But if it is, it would be
solvable my making sure that getting the time from clock and writing
it to the IVar is an atomic operation.

Does any of the above make sense?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/reactive/attachments/20081130/3aa34e52/attachment-0001.htm


More information about the Reactive mailing list