{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Network.HTTP2.Server.Run where
import UnliftIO.Async (concurrently_)
import Imports
import Network.HTTP2.Arch
import Network.HTTP2.Frame
import Network.HTTP2.Server.Types
import Network.HTTP2.Server.Worker
import Control.Exception
run :: Config -> Server -> IO ()
run :: Config -> Server -> IO ()
run conf :: Config
conf@Config{BufferSize
Buffer
Manager
SockAddr
BufferSize -> IO ByteString
PositionReadMaker
ByteString -> IO ()
confPeerSockAddr :: Config -> SockAddr
confMySockAddr :: Config -> SockAddr
confTimeoutManager :: Config -> Manager
confPositionReadMaker :: Config -> PositionReadMaker
confReadN :: Config -> BufferSize -> IO ByteString
confSendAll :: Config -> ByteString -> IO ()
confBufferSize :: Config -> BufferSize
confWriteBuffer :: Config -> Buffer
confPeerSockAddr :: SockAddr
confMySockAddr :: SockAddr
confTimeoutManager :: Manager
confPositionReadMaker :: PositionReadMaker
confReadN :: BufferSize -> IO ByteString
confSendAll :: ByteString -> IO ()
confBufferSize :: BufferSize
confWriteBuffer :: Buffer
..} Server
server = do
Bool
ok <- IO Bool
checkPreface
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
ok forall a b. (a -> b) -> a -> b
$ do
RoleInfo
serverInfo <- IO RoleInfo
newServerInfo
Context
ctx <- RoleInfo -> BufferSize -> SockAddr -> SockAddr -> IO Context
newContext RoleInfo
serverInfo BufferSize
confBufferSize SockAddr
confMySockAddr SockAddr
confPeerSockAddr
Manager
mgr <- Manager -> IO Manager
start Manager
confTimeoutManager
let wc :: WorkerConf Stream
wc = Context -> WorkerConf Stream
fromContext Context
ctx
Manager -> IO () -> IO ()
setAction Manager
mgr forall a b. (a -> b) -> a -> b
$ forall a. WorkerConf a -> Manager -> Server -> IO ()
worker WorkerConf Stream
wc Manager
mgr Server
server
forall (m :: * -> *) a. Applicative m => BufferSize -> m a -> m ()
replicateM_ BufferSize
3 forall a b. (a -> b) -> a -> b
$ Manager -> IO ()
spawnAction Manager
mgr
let runReceiver :: IO ()
runReceiver = Context -> Config -> IO ()
frameReceiver Context
ctx Config
conf
runSender :: IO ()
runSender = Context -> Config -> Manager -> IO ()
frameSender Context
ctx Config
conf Manager
mgr
forall a b.
Manager -> IO a -> (Either SomeException a -> IO b) -> IO b
stopAfter Manager
mgr (forall (m :: * -> *) a b. MonadUnliftIO m => m a -> m b -> m ()
concurrently_ IO ()
runReceiver IO ()
runSender) forall a b. (a -> b) -> a -> b
$ \Either SomeException ()
res -> do
StreamTable -> Maybe SomeException -> IO ()
closeAllStreams (Context -> StreamTable
streamTable Context
ctx) forall a b. (a -> b) -> a -> b
$ forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall a. a -> Maybe a
Just (forall a b. a -> b -> a
const forall a. Maybe a
Nothing) Either SomeException ()
res
case Either SomeException ()
res of
Left SomeException
err ->
forall e a. Exception e => e -> IO a
throwIO SomeException
err
Right ()
x ->
forall (m :: * -> *) a. Monad m => a -> m a
return ()
x
where
checkPreface :: IO Bool
checkPreface = do
ByteString
preface <- BufferSize -> IO ByteString
confReadN BufferSize
connectionPrefaceLength
if ByteString
connectionPreface forall a. Eq a => a -> a -> Bool
/= ByteString
preface then do
Config -> ErrorCode -> ByteString -> IO ()
goaway Config
conf ErrorCode
ProtocolError ByteString
"Preface mismatch"
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
else
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
goaway :: Config -> ErrorCode -> ByteString -> IO ()
goaway :: Config -> ErrorCode -> ByteString -> IO ()
goaway Config{BufferSize
Buffer
Manager
SockAddr
BufferSize -> IO ByteString
PositionReadMaker
ByteString -> IO ()
confPeerSockAddr :: SockAddr
confMySockAddr :: SockAddr
confTimeoutManager :: Manager
confPositionReadMaker :: PositionReadMaker
confReadN :: BufferSize -> IO ByteString
confSendAll :: ByteString -> IO ()
confBufferSize :: BufferSize
confWriteBuffer :: Buffer
confPeerSockAddr :: Config -> SockAddr
confMySockAddr :: Config -> SockAddr
confTimeoutManager :: Config -> Manager
confPositionReadMaker :: Config -> PositionReadMaker
confReadN :: Config -> BufferSize -> IO ByteString
confSendAll :: Config -> ByteString -> IO ()
confBufferSize :: Config -> BufferSize
confWriteBuffer :: Config -> Buffer
..} ErrorCode
etype ByteString
debugmsg = ByteString -> IO ()
confSendAll ByteString
bytestream
where
bytestream :: ByteString
bytestream = BufferSize -> ErrorCode -> ByteString -> ByteString
goawayFrame BufferSize
0 ErrorCode
etype ByteString
debugmsg