-- | Choose between the return value of an IO action and an STM
-- operation, depending on which is available first.
module Control.Concurrent.STM.OrElseIO(runOrElse, runOrElse',
                                       runOrTakeTMVar, runOrTakeTMVar',
                                       runOrRun) where

import Control.Applicative
import Control.Concurrent.STM
import Control.Concurrent.STM.TMVarIO

-- | @'runOrElse' io stm@ runs the IO action @io@. If its result is
-- available when @'runOrElse'@ itself returns, then that value is
-- used as the function's return value. If not, the STM operation
-- @stm@ is attempted. Then, whichever of @io@'s and @stm@'s return
-- value is then available first is returned from @'runOrElse'@, with
-- a preference to that of @io@ if both are available. @'runOrElse''@
-- reverses this priority.
--
-- It can happen that @stm@ is never attempted. If it is, however, its
-- result is used as return value /only/ if it is available before
-- that of @io@. Note that in that case, a long-running @io@ will keep
-- running until completed, even if @'runOrElse'@ has already returned
-- with the result of @stm@. A future version will probably kill off
-- the @io@ thread if its value is not needed (i.e. if that of @stm@
-- value is used), but that is /not/ currently the case.
runOrElse :: IO a -> STM b -> IO (Either a b)
runOrElse io stm = run io >>= \tm ->
                   atomically ((Left <$> takeTMVar tm) `orElse` (Right <$> stm))

-- | A version of 'runOrElse' that prefers the STM operation to the IO
-- action. In this case, the IO action is /always/ run, but its value
-- is only used if the return value of the STM operation is not
-- available when the function returns.
--
-- The same caveat regarding long-running IO operations as for
-- 'runOrElse' also applies here.
runOrElse' :: STM a -> IO b -> IO (Either a b)
runOrElse' stm io = run io >>= \tm ->
                    atomically ((Left <$> stm) `orElse` (Right <$> takeTMVar tm))

-- | @'runOrTakeTMVar' io tm = 'runOrElse' io ('takeTMVar' tm)@.
runOrTakeTMVar :: IO a -> TMVar b -> IO (Either a b)
runOrTakeTMVar io tm = runOrElse io (takeTMVar tm)

-- | @'runOrTakeTMVar'' tm io = 'runOrElse'' ('takeTMVar' tm) io@.
runOrTakeTMVar' :: TMVar a -> IO b -> IO (Either a b)
runOrTakeTMVar' tm io = runOrElse' (takeTMVar tm) io

-- | A version of @'runOrElse'@ where the STM operation is to
-- @'Control.Concurrent.STM.TMVarIO.run'@ another IO action and
-- @'Control.Concurrent.STM.takeTMVar'@ the associated 'TMVar' holding
-- its return value. The first is preferred to the second.
runOrRun :: IO a -> IO b -> IO (Either a b)
runOrRun io1 io2 = run io2 >>= runOrTakeTMVar io1