{-# LANGUAGE CPP #-} -- STM Async API used in \secref{stm-async} module Main where import GetURL #if __GLASGOW_HASKELL__ < 706 import ConcurrentUtils (forkFinally) #endif import Control.Concurrent import Control.Exception import Control.Concurrent.STM import Text.Printf import qualified Data.ByteString as B -- ----------------------------------------------------------------------------- -- STM Async API -- <> -- < IO (Async a) async action = do var <- newEmptyTMVarIO t <- forkFinally action (atomically . putTMVar var) return (Async t var) -- >> --- < IO (Either SomeException a) waitCatch = atomically . waitCatchSTM -- >> -- < STM (Either SomeException a) waitCatchSTM (Async _ var) = readTMVar var -- >> -- < 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 -- >> ----------------------------------------------------------------------------- sites = ["http://www.google.com", "http://www.bing.com", "http://www.yahoo.com", "http://www.wikipedia.com/wiki/Spade", "http://www.wikipedia.com/wiki/Shovel"] -- <
>