{-# LANGUAGE OverloadedStrings #-}
module Network.Wai.Handler.Warp.WithApplication (
withApplication,
withApplicationSettings,
testWithApplication,
testWithApplicationSettings,
openFreePort,
withFreePort,
) where
import Control.Concurrent
import Control.Concurrent.Async
import Control.Exception
import Control.Monad (when)
import Data.Streaming.Network (bindRandomPortTCP)
import Network.Socket
import Network.Wai
import Network.Wai.Handler.Warp.Run
import Network.Wai.Handler.Warp.Settings
import Network.Wai.Handler.Warp.Types
withApplication :: IO Application -> (Port -> IO a) -> IO a
withApplication = withApplicationSettings defaultSettings
withApplicationSettings :: Settings -> IO Application -> (Port -> IO a) -> IO a
withApplicationSettings settings' mkApp action = do
app <- mkApp
withFreePort $ \ (port, sock) -> do
started <- mkWaiter
let settings =
settings' {
settingsBeforeMainLoop
= notify started () >> settingsBeforeMainLoop settings'
}
result <- race
(runSettingsSocket settings sock app)
(waitFor started >> action port)
case result of
Left () -> throwIO $ ErrorCall "Unexpected: runSettingsSocket exited"
Right x -> return x
testWithApplication :: IO Application -> (Port -> IO a) -> IO a
testWithApplication = testWithApplicationSettings defaultSettings
testWithApplicationSettings :: Settings -> IO Application -> (Port -> IO a) -> IO a
testWithApplicationSettings settings mkApp action = do
callingThread <- myThreadId
app <- mkApp
let wrappedApp request respond =
app request respond `catch` \ e -> do
when
(defaultShouldDisplayException e)
(throwTo callingThread e)
throwIO e
withApplicationSettings settings (return wrappedApp) action
data Waiter a
= Waiter {
notify :: a -> IO (),
waitFor :: IO a
}
mkWaiter :: IO (Waiter a)
mkWaiter = do
mvar <- newEmptyMVar
return Waiter {
notify = putMVar mvar,
waitFor = readMVar mvar
}
openFreePort :: IO (Port, Socket)
openFreePort = bindRandomPortTCP "127.0.0.1"
withFreePort :: ((Port, Socket) -> IO a) -> IO a
withFreePort = bracket openFreePort (close . snd)