{-# LANGUAGE Arrows #-}
{-# LANGUAGE RecordWildCards #-}
module LiveCoding.Cell.NonBlocking
( nonBlocking
)
where
import Control.Concurrent
import Control.Monad ((>=>), void, when)
import Data.Data
import LiveCoding.Cell
import LiveCoding.Handle
import LiveCoding.Handle.Examples
threadVarHandle :: Handle IO (MVar ThreadId)
threadVarHandle = Handle
{ create = newEmptyMVar
, destroy = tryTakeMVar >=> mapM_ killThread
}
nonBlocking
:: Typeable b
=> Bool
-> Cell IO a b
-> Cell (HandlingStateT IO) (Maybe a) (Maybe b)
nonBlocking abort Cell { .. } = proc aMaybe -> do
threadVar <- handling threadVarHandle -< ()
resultVar <- handling emptyMVarHandle -< ()
liftCell Cell { cellStep = nonBlockingStep, .. } -< (aMaybe, threadVar, resultVar)
where
nonBlockingStep s (Nothing, threadVar, resultVar) = do
bsMaybe <- tryTakeMVar resultVar
case bsMaybe of
Just (b, s') -> do
threadId <- takeMVar threadVar
killThread threadId
return (Just b, s')
Nothing -> return (Nothing, s)
nonBlockingStep s (Just a, threadVar, resultVar) = do
noThreadRunning <- if abort
then do
maybeThreadId <- tryTakeMVar threadVar
mapM_ killThread maybeThreadId
return True
else isEmptyMVar threadVar
when noThreadRunning $ do
threadId <- forkIO $ putMVar resultVar =<< cellStep s a
putMVar threadVar threadId
nonBlockingStep s (Nothing, threadVar, resultVar)
nonBlocking abort noCell = nonBlocking abort $ toCell noCell