On this page:
16.1 Supplementary files
16.2 Overview
8.7

16 An API for asynchronous programming

16.1 Supplementary files

In order for you to complete the exercises in this file, you’ll need this cabal file. When you have both files in your directory, you can start a repl session with cabal repl.

16.2 Overview

../code/async/Async.hs

-- For the example to work you need to have the `bytestring` and the `download`
-- haskell packages installed
import Control.Concurrent
import Data.ByteString as B
import Network.Download

import Control.Exception

-- Get a URL and keep the server's response as a bytestring
getURL :: String -> IO ByteString
getURL uri = do
  res <- openURI uri
  case res of
    Left _ -> error "Oh no..."
    Right bs -> return bs

--------------------------------------------------------------------------------
--- The concept of "Doing things asynchronously"
--------------------------------------------------------------------------------

-- If we wanted to get more than one URL at a time, we could easily 'spawn off'
-- one thread for each URL we want to download, however we have a problem:
--
-- * How do we know when one has finished?
--
-- We can solve this by using an `MVar` as a single-message channel between the
-- spawned off thread and our primary thread of computation, as follows:
main = do
  -- New MVars for coordinating downloads
  m1 <- newEmptyMVar
  m2 <- newEmptyMVar

  -- Actually getting the URLs
  forkIO $ do
    r <- getURL "http://www.facebook.com"
    putMVar m1 r

  forkIO $ do
    r <- getURL "http://www.wikipedia.org/wiki/"
    putMVar m2 r

  -- Getting back the bytestrings from the spawned off threads
  r1 <- takeMVar m1
  r2 <- takeMVar m2

  print (B.length r1, B.length r2)


-- The above works pretty well, except at the end, where we have the two
-- calls to `takeMVar`.
--
-- But there are two issues:
--
-- First issue relates to viewing this as an API:
--
--  * Why does a programmer wanting to download a few things at once need to
--    know about `MVar`s?! That sort of managing of resources seems like a
--    'lower'-level concern than what the programmer is trying to accomplish.
--
-- Another issue is that we _wanted_ to do things independently, but with
-- `takeMVar` we block on one! It doesn't matter if the second download is
-- faster... we have to wait for the first one. That's unfortunate. We'll
-- come back to this one a bit later.

-- Let's solve the first problem

--------------------------------------------------------------------------------
--- An API for Asynchronous programming
--------------------------------------------------------------------------------

---------------------------------------
--- The API we want:
--
--  - data Async a
--         ^---- `Async a`s are asynchonous values, things we want to
--               do independently of the primary thread of computation
--
--  - async :: IO a -> IO (Async a)
--    ^---- the `async` function is given an IO action that we'd like to do
--          independently of the primary thread of computation.
--
--          The thing we get back is the `Async a` value that is being computed
--          in another thread.
--   
--  - wait :: Async a -> IO (Either ErrorCall a)
--    ^---- the `wait` function is given an `Async a` value, and we _block_ until
--          we get the value from the asynchronous computation. The result is an
--          IO action that can either be an exception (something went wrong) or
--          the resulting value itself.

---------------------------------------
--- How to get there
--
--
-- The key insight here is that we want to separate the _implementation_ detail
-- of `MVar`s from the user-facing API, which hopefully doesn't require any
-- knowledge of `MVar`s at all!
--
-- So let's define a type, the user will _consume_ this type, but they can
-- (and should) treat it as an abstract type.
--
-- Inside of the type we can hold an `MVar`, which we need for implementing
-- the type. But if we've done our job correctly the user will never need
-- to know this.

data Async a = Async (MVar (Either ErrorCall a))

-- for `async` we basically do what we did for each URL download in `main`,
-- except we also deal with exceptions appropriately.
async :: IO a -> IO (Async a)
async act = do
  m <- newEmptyMVar
  forkIO (try act >>= putMVar m)
  return (Async m)

-- `wait` is just reading the MVar, which gives us the blocking behavior that
-- we want.
wait :: Async a -> IO (Either ErrorCall a)
wait (Async m) = readMVar m

-- This is a useful internal function, it should not be exposed to the consumer
-- of our API without them knowing that exceptions are not caught here!
waitUnsafe :: Async a -> IO a
waitUnsafe a = do
  r <- wait a
  case r of
    Left e  -> throwIO e
    Right v -> return v

---------------------------------------
--- Solving the second problem
--
-- Earlier we didn't like that we had to wait for each computation to finish,
-- it doesn't allow us to say "give me the first thing that finishes".
--
-- Here, we solve that problem in the simplest case: We have two independent
-- computations, and we want to know which one finished first.
--
-- Make sure you understand this definition before attempting the exercise.
waitEither :: Async a -> Async b -> IO (Either a b)
waitEither a1 a2 = do
  m <- newEmptyMVar
  
  forkIO (do r <- try (fmap Left  (waitUnsafe a1)); putMVar m r)
  forkIO (do r <- try (fmap Right (waitUnsafe a2)); putMVar m r)

  waitUnsafe (Async m)


---------------------------------------
--- Exercises

-- Write the following function:
first :: [Async a] -> IO (Either ErrorCall a)
first = undefined


-- Write a function similar to `main` above, but with our new API.
newMain :: IO ()
newMain = undefined