module Async ( Async, async, withAsync, cancel, waitCatch, waitCatchSTM, waitSTM, wait, waitEither, waitAny, waitBoth, concurrently ) where import Control.Concurrent.STM import Control.Exception import Control.Concurrent (ThreadId, forkIO) -- <> forkFinally :: IO a -> (Either SomeException a -> IO ()) -> IO ThreadId forkFinally action fun = mask $ \restore -> forkIO (do r <- try (restore action); fun r) -- < IO (Async a) async action = do var <- newEmptyTMVarIO t <- forkFinally action (atomically . putTMVar var) return (Async t (readTMVar var)) -- >> -- < return (Left e) Right a -> return (Right (f a)) -- >> --- < IO (Either SomeException a) waitCatch = atomically . waitCatchSTM -- >> -- < STM (Either SomeException a) waitCatchSTM (Async _ stm) = stm -- >> -- < STM a waitSTM a = do r <- waitCatchSTM a case r of Left e -> throwSTM e Right a -> return a -- >> -- < IO a wait = atomically . waitSTM -- >> -- < IO () cancel (Async t _) = throwTo t ThreadKilled -- >> -- < Async b -> IO (Either a b) waitEither a b = atomically $ fmap Left (waitSTM a) `orElse` fmap Right (waitSTM b) -- >> -- < IO a waitAny asyncs = atomically $ foldr orElse retry $ map waitSTM asyncs -- >> -- < (Async a -> IO b) -> IO b withAsync io operation = bracket (async io) cancel operation -- >> -- < Async b -> IO (a,b) waitBoth a1 a2 = atomically $ do r1 <- waitSTM a1 `orElse` (do waitSTM a2; retry) -- <1> r2 <- waitSTM a2 return (r1,r2) -- >> -- < IO b -> IO (a,b) concurrently ioa iob = withAsync ioa $ \a -> withAsync iob $ \b -> waitBoth a b -- >> -- < IO b -> IO (Either a b) race ioa iob = withAsync ioa $ \a -> withAsync iob $ \b -> waitEither a b -- >>