{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Network.QUIC.Server.Run (
    run
  , stop
  ) where

import qualified Network.Socket as NS
import Network.UDP (UDPSocket(..), ListenSocket(..))
import qualified Network.UDP as UDP
import System.Log.FastLogger
import UnliftIO.Async
import UnliftIO.Concurrent
import qualified UnliftIO.Exception as E

import Network.QUIC.Closer
import Network.QUIC.Common
import Network.QUIC.Config
import Network.QUIC.Connection
import Network.QUIC.Crypto
import Network.QUIC.Exception
import Network.QUIC.Handshake
import Network.QUIC.Imports
import Network.QUIC.Logger
import Network.QUIC.Packet
import Network.QUIC.Parameters
import Network.QUIC.QLogger
import Network.QUIC.Qlog
import Network.QUIC.Receiver
import Network.QUIC.Recovery
import Network.QUIC.Sender
import Network.QUIC.Server.Reader
import Network.QUIC.Types

----------------------------------------------------------------

-- | Running a QUIC server.
--   The action is executed with a new connection
--   in a new lightweight thread.
run :: ServerConfig -> (Connection -> IO ()) -> IO ()
run :: ServerConfig -> (Connection -> IO ()) -> IO ()
run ServerConfig
conf Connection -> IO ()
server = IO () -> IO ()
forall a. IO a -> IO a
NS.withSocketsDo (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ DebugLogger -> IO () -> IO ()
handleLogUnit DebugLogger
debugLog (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    ThreadId
baseThreadId <- IO ThreadId
forall (m :: * -> *). MonadIO m => m ThreadId
myThreadId
    IO (Dispatch, [ThreadId])
-> ((Dispatch, [ThreadId]) -> IO ())
-> ((Dispatch, [ThreadId]) -> IO ())
-> IO ()
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
E.bracket IO (Dispatch, [ThreadId])
setup (Dispatch, [ThreadId]) -> IO ()
forall {t :: * -> *}. Foldable t => (Dispatch, t ThreadId) -> IO ()
teardown (((Dispatch, [ThreadId]) -> IO ()) -> IO ())
-> ((Dispatch, [ThreadId]) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(Dispatch
dispatch,[ThreadId]
_) -> do
        Hooks -> IO ()
onServerReady (Hooks -> IO ()) -> Hooks -> IO ()
forall a b. (a -> b) -> a -> b
$ ServerConfig -> Hooks
scHooks ServerConfig
conf
        IO () -> IO ()
forall (f :: * -> *) a b. Applicative f => f a -> f b
forever (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
            Accept
acc <- Dispatch -> IO Accept
accept Dispatch
dispatch
            IO ThreadId -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO ThreadId -> IO ()) -> IO ThreadId -> IO ()
forall a b. (a -> b) -> a -> b
$ IO () -> IO ThreadId
forall (m :: * -> *). MonadUnliftIO m => m () -> m ThreadId
forkIO (ServerConfig
-> (Connection -> IO ()) -> Dispatch -> ThreadId -> Accept -> IO ()
runServer ServerConfig
conf Connection -> IO ()
server Dispatch
dispatch ThreadId
baseThreadId Accept
acc)
  where
    doDebug :: Bool
doDebug = Maybe FilePath -> Bool
forall a. Maybe a -> Bool
isJust (Maybe FilePath -> Bool) -> Maybe FilePath -> Bool
forall a b. (a -> b) -> a -> b
$ ServerConfig -> Maybe FilePath
scDebugLog ServerConfig
conf
    debugLog :: DebugLogger
debugLog Builder
msg | Bool
doDebug   = DebugLogger
stdoutLogger (Builder
"run: " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
msg)
                 | Bool
otherwise = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    setup :: IO (Dispatch, [ThreadId])
setup = do
        Dispatch
dispatch <- ServerConfig -> IO Dispatch
newDispatch ServerConfig
conf
        -- fixme: the case where sockets cannot be created.
        [ListenSocket]
ssas <- ((IP, PortNumber) -> IO ListenSocket)
-> [(IP, PortNumber)] -> IO [ListenSocket]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (IP, PortNumber) -> IO ListenSocket
UDP.serverSocket ([(IP, PortNumber)] -> IO [ListenSocket])
-> [(IP, PortNumber)] -> IO [ListenSocket]
forall a b. (a -> b) -> a -> b
$ ServerConfig -> [(IP, PortNumber)]
scAddresses ServerConfig
conf
        [ThreadId]
tids <- (ListenSocket -> IO ThreadId) -> [ListenSocket] -> IO [ThreadId]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Dispatch -> ServerConfig -> ListenSocket -> IO ThreadId
runDispatcher Dispatch
dispatch ServerConfig
conf) [ListenSocket]
ssas
        (Dispatch, [ThreadId]) -> IO (Dispatch, [ThreadId])
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Dispatch
dispatch, [ThreadId]
tids)
    teardown :: (Dispatch, t ThreadId) -> IO ()
teardown (Dispatch
dispatch, t ThreadId
tids) = do
        Dispatch -> IO ()
clearDispatch Dispatch
dispatch
        (ThreadId -> IO ()) -> t ThreadId -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ThreadId -> IO ()
forall (m :: * -> *). MonadIO m => ThreadId -> m ()
killThread t ThreadId
tids

-- Typically, ConnectionIsClosed breaks acceptStream.
-- And the exception should be ignored.
runServer :: ServerConfig -> (Connection -> IO ()) -> Dispatch -> ThreadId -> Accept -> IO ()
runServer :: ServerConfig
-> (Connection -> IO ()) -> Dispatch -> ThreadId -> Accept -> IO ()
runServer ServerConfig
conf Connection -> IO ()
server0 Dispatch
dispatch ThreadId
baseThreadId Accept
acc =
    IO ConnRes -> (ConnRes -> IO ()) -> (ConnRes -> IO ()) -> IO ()
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
E.bracket IO ConnRes
open ConnRes -> IO ()
clse ((ConnRes -> IO ()) -> IO ()) -> (ConnRes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(ConnRes Connection
conn AuthCIDs
myAuthCIDs IO ()
_reader) ->
        DebugLogger -> IO () -> IO ()
handleLogUnit (Connection -> DebugLogger
debugLog Connection
conn) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
#if !defined(mingw32_HOST_OS)
            IO () -> IO ThreadId
forall (m :: * -> *). MonadUnliftIO m => m () -> m ThreadId
forkIO IO ()
_reader IO ThreadId -> (ThreadId -> IO ()) -> IO ()
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Connection -> ThreadId -> IO ()
addReader Connection
conn
#endif
            let conf' :: ServerConfig
conf' = ServerConfig
conf {
                    scParameters = (scParameters conf) {
                          versionInformation = Just $ accVersionInfo acc
                        }
                  }
            IO ()
handshaker <- ServerConfig -> Connection -> AuthCIDs -> IO (IO ())
handshakeServer ServerConfig
conf' Connection
conn AuthCIDs
myAuthCIDs
            let server :: IO ()
server = do
                    Connection -> IO ()
wait1RTTReady Connection
conn
                    ServerConfig -> Connection -> IO ()
afterHandshakeServer ServerConfig
conf Connection
conn
                    Connection -> IO ()
server0 Connection
conn
                ldcc :: LDCC
ldcc = Connection -> LDCC
connLDCC Connection
conn
                supporters :: IO ()
supporters = (IO () -> IO () -> IO ()) -> [IO ()] -> IO ()
forall a. (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldr1 IO () -> IO () -> IO ()
forall (m :: * -> *) a b. MonadUnliftIO m => m a -> m b -> m ()
concurrently_ [IO ()
handshaker
                                                  ,Connection -> IO ()
sender   Connection
conn
                                                  ,Connection -> IO ()
receiver Connection
conn
                                                  ,LDCC -> IO ()
resender  LDCC
ldcc
                                                  ,LDCC -> IO ()
ldccTimer LDCC
ldcc
                                                  ]
                runThreads :: IO ()
runThreads = do
                    Either () ()
er <- IO () -> IO () -> IO (Either () ())
forall (m :: * -> *) a b.
MonadUnliftIO m =>
m a -> m b -> m (Either a b)
race IO ()
supporters IO ()
server
                    case Either () ()
er of
                      Left () -> InternalControl -> IO ()
forall (m :: * -> *) e a. (MonadIO m, Exception e) => e -> m a
E.throwIO InternalControl
MustNotReached
                      Right ()
r -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
r
            Either SomeException ()
ex <- IO () -> IO (Either SomeException ())
forall (m :: * -> *) e a.
(MonadUnliftIO m, Exception e) =>
m a -> m (Either e a)
E.trySyncOrAsync IO ()
runThreads
            Connection -> IO ()
sendFinal Connection
conn
            Connection -> LDCC -> Either SomeException () -> IO ()
forall a. Connection -> LDCC -> Either SomeException a -> IO a
closure Connection
conn LDCC
ldcc Either SomeException ()
ex
  where
    open :: IO ConnRes
open = ServerConfig -> Dispatch -> Accept -> ThreadId -> IO ConnRes
createServerConnection ServerConfig
conf Dispatch
dispatch Accept
acc ThreadId
baseThreadId
    clse :: ConnRes -> IO ()
clse ConnRes
connRes = do
        let conn :: Connection
conn = ConnRes -> Connection
connResConnection ConnRes
connRes
        Connection -> IO ()
setDead Connection
conn
        Connection -> IO ()
freeResources Connection
conn
#if !defined(mingw32_HOST_OS)
        Connection -> IO ()
killReaders Connection
conn
#endif
    debugLog :: Connection -> DebugLogger
debugLog Connection
conn Builder
msg = do
        Connection -> DebugLogger
connDebugLog Connection
conn (Builder
"runServer: " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
msg)
        Connection -> Debug -> IO ()
forall q. KeepQlog q => q -> Debug -> IO ()
qlogDebug Connection
conn (Debug -> IO ()) -> Debug -> IO ()
forall a b. (a -> b) -> a -> b
$ LogStr -> Debug
Debug (LogStr -> Debug) -> LogStr -> Debug
forall a b. (a -> b) -> a -> b
$ Builder -> LogStr
forall msg. ToLogStr msg => msg -> LogStr
toLogStr Builder
msg

createServerConnection :: ServerConfig -> Dispatch -> Accept -> ThreadId
                       -> IO ConnRes
createServerConnection :: ServerConfig -> Dispatch -> Accept -> ThreadId -> IO ConnRes
createServerConnection conf :: ServerConfig
conf@ServerConfig{Bool
Int
[(IP, PortNumber)]
[Group]
[Cipher]
[Version]
Maybe FilePath
Maybe (Version -> [ByteString] -> IO ByteString)
SessionManager
Credentials
ServerHooks
Parameters
Hooks
FilePath -> IO ()
scHooks :: ServerConfig -> Hooks
scDebugLog :: ServerConfig -> Maybe FilePath
scAddresses :: ServerConfig -> [(IP, PortNumber)]
scParameters :: ServerConfig -> Parameters
scVersions :: [Version]
scCiphers :: [Cipher]
scGroups :: [Group]
scParameters :: Parameters
scKeyLog :: FilePath -> IO ()
scQLog :: Maybe FilePath
scCredentials :: Credentials
scHooks :: Hooks
scTlsHooks :: ServerHooks
scUse0RTT :: Bool
scAddresses :: [(IP, PortNumber)]
scALPN :: Maybe (Version -> [ByteString] -> IO ByteString)
scRequireRetry :: Bool
scSessionManager :: SessionManager
scDebugLog :: Maybe FilePath
scTicketLifetime :: Int
scVersions :: ServerConfig -> [Version]
scCiphers :: ServerConfig -> [Cipher]
scGroups :: ServerConfig -> [Group]
scKeyLog :: ServerConfig -> FilePath -> IO ()
scQLog :: ServerConfig -> Maybe FilePath
scCredentials :: ServerConfig -> Credentials
scTlsHooks :: ServerConfig -> ServerHooks
scUse0RTT :: ServerConfig -> Bool
scALPN :: ServerConfig -> Maybe (Version -> [ByteString] -> IO ByteString)
scRequireRetry :: ServerConfig -> Bool
scSessionManager :: ServerConfig -> SessionManager
scTicketLifetime :: ServerConfig -> Int
..} Dispatch
dispatch Accept{Bool
Int
ClientSockAddr
ListenSocket
TimeMicrosecond
VersionInfo
RecvQ
AuthCIDs
CID -> IO ()
CID -> Connection -> IO ()
accVersionInfo :: Accept -> VersionInfo
accVersionInfo :: VersionInfo
accMyAuthCIDs :: AuthCIDs
accPeerAuthCIDs :: AuthCIDs
accMySocket :: ListenSocket
accPeerSockAddr :: ClientSockAddr
accRecvQ :: RecvQ
accPacketSize :: Int
accRegister :: CID -> Connection -> IO ()
accUnregister :: CID -> IO ()
accAddressValidated :: Bool
accTime :: TimeMicrosecond
accMyAuthCIDs :: Accept -> AuthCIDs
accPeerAuthCIDs :: Accept -> AuthCIDs
accMySocket :: Accept -> ListenSocket
accPeerSockAddr :: Accept -> ClientSockAddr
accRecvQ :: Accept -> RecvQ
accPacketSize :: Accept -> Int
accRegister :: Accept -> CID -> Connection -> IO ()
accUnregister :: Accept -> CID -> IO ()
accAddressValidated :: Accept -> Bool
accTime :: Accept -> TimeMicrosecond
..} ThreadId
baseThreadId = do
    UDPSocket
us <- ListenSocket -> ClientSockAddr -> IO UDPSocket
UDP.accept ListenSocket
accMySocket ClientSockAddr
accPeerSockAddr
    let ListenSocket Socket
_ SockAddr
mysa Bool
_ = ListenSocket
accMySocket
    IORef UDPSocket
sref <- UDPSocket -> IO (IORef UDPSocket)
forall a. a -> IO (IORef a)
newIORef UDPSocket
us
    let send :: Ptr Word8 -> Int -> IO ()
send Ptr Word8
buf Int
siz = IO Int -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO Int -> IO ()) -> IO Int -> IO ()
forall a b. (a -> b) -> a -> b
$ do
            UDPSocket{Bool
SockAddr
Socket
udpSocket :: Socket
peerSockAddr :: SockAddr
connected :: Bool
udpSocket :: UDPSocket -> Socket
peerSockAddr :: UDPSocket -> SockAddr
connected :: UDPSocket -> Bool
..} <- IORef UDPSocket -> IO UDPSocket
forall a. IORef a -> IO a
readIORef IORef UDPSocket
sref
            Socket -> Ptr Word8 -> Int -> IO Int
NS.sendBuf Socket
udpSocket Ptr Word8
buf Int
siz
        recv :: IO ReceivedPacket
recv = RecvQ -> IO ReceivedPacket
recvServer RecvQ
accRecvQ
    let myCID :: CID
myCID = Maybe CID -> CID
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe CID -> CID) -> Maybe CID -> CID
forall a b. (a -> b) -> a -> b
$ AuthCIDs -> Maybe CID
initSrcCID AuthCIDs
accMyAuthCIDs
        ocid :: CID
ocid  = Maybe CID -> CID
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe CID -> CID) -> Maybe CID -> CID
forall a b. (a -> b) -> a -> b
$ AuthCIDs -> Maybe CID
origDstCID AuthCIDs
accMyAuthCIDs
    (QLogger
qLog, IO ()
qclean)     <- Maybe FilePath
-> TimeMicrosecond -> CID -> ByteString -> IO (QLogger, IO ())
dirQLogger Maybe FilePath
scQLog TimeMicrosecond
accTime CID
ocid ByteString
"server"
    (DebugLogger
debugLog, IO ()
dclean) <- Maybe FilePath -> CID -> IO (DebugLogger, IO ())
dirDebugLogger Maybe FilePath
scDebugLog CID
ocid
    DebugLogger
debugLog DebugLogger -> DebugLogger
forall a b. (a -> b) -> a -> b
$ Builder
"Original CID: " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> CID -> Builder
forall a. Show a => a -> Builder
bhow CID
ocid
    Connection
conn <- ServerConfig
-> VersionInfo
-> AuthCIDs
-> AuthCIDs
-> DebugLogger
-> QLogger
-> Hooks
-> IORef UDPSocket
-> RecvQ
-> (Ptr Word8 -> Int -> IO ())
-> IO ReceivedPacket
-> IO Connection
serverConnection ServerConfig
conf VersionInfo
accVersionInfo AuthCIDs
accMyAuthCIDs AuthCIDs
accPeerAuthCIDs DebugLogger
debugLog QLogger
qLog Hooks
scHooks IORef UDPSocket
sref RecvQ
accRecvQ Ptr Word8 -> Int -> IO ()
send IO ReceivedPacket
recv
    Connection -> IO () -> IO ()
addResource Connection
conn IO ()
qclean
    Connection -> IO () -> IO ()
addResource Connection
conn IO ()
dclean
    let cid :: CID
cid = CID -> Maybe CID -> CID
forall a. a -> Maybe a -> a
fromMaybe CID
ocid (Maybe CID -> CID) -> Maybe CID -> CID
forall a b. (a -> b) -> a -> b
$ AuthCIDs -> Maybe CID
retrySrcCID AuthCIDs
accMyAuthCIDs
        ver :: Version
ver = VersionInfo -> Version
chosenVersion VersionInfo
accVersionInfo
    Connection
-> EncryptionLevel -> TrafficSecrets InitialSecret -> IO ()
forall a.
Connection -> EncryptionLevel -> TrafficSecrets a -> IO ()
initializeCoder Connection
conn EncryptionLevel
InitialLevel (TrafficSecrets InitialSecret -> IO ())
-> TrafficSecrets InitialSecret -> IO ()
forall a b. (a -> b) -> a -> b
$ Version -> CID -> TrafficSecrets InitialSecret
initialSecrets Version
ver CID
cid
    Connection -> IO ()
setupCryptoStreams Connection
conn -- fixme: cleanup
    let pktSiz :: Int
pktSiz = (SockAddr -> Int
defaultPacketSize SockAddr
mysa Int -> Int -> Int
forall a. Ord a => a -> a -> a
`max` Int
accPacketSize) Int -> Int -> Int
forall a. Ord a => a -> a -> a
`min` SockAddr -> Int
maximumPacketSize SockAddr
mysa
    Connection -> Int -> IO ()
setMaxPacketSize Connection
conn Int
pktSiz
    LDCC -> Int -> IO ()
setInitialCongestionWindow (Connection -> LDCC
connLDCC Connection
conn) Int
pktSiz
    DebugLogger
debugLog DebugLogger -> DebugLogger
forall a b. (a -> b) -> a -> b
$ Builder
"Packet size: " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Int -> Builder
forall a. Show a => a -> Builder
bhow Int
pktSiz Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
" (" Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Int -> Builder
forall a. Show a => a -> Builder
bhow Int
accPacketSize Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
")"
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
accAddressValidated (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Connection -> IO ()
setAddressValidated Connection
conn
    --
    let retried :: Bool
retried = Maybe CID -> Bool
forall a. Maybe a -> Bool
isJust (Maybe CID -> Bool) -> Maybe CID -> Bool
forall a b. (a -> b) -> a -> b
$ AuthCIDs -> Maybe CID
retrySrcCID AuthCIDs
accMyAuthCIDs
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
retried (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
        Connection -> IO ()
forall q. KeepQlog q => q -> IO ()
qlogRecvInitial Connection
conn
        Connection -> IO ()
forall q. KeepQlog q => q -> IO ()
qlogSentRetry Connection
conn
    --
    let mgr :: TokenManager
mgr = Dispatch -> TokenManager
tokenMgr Dispatch
dispatch
    Connection -> TokenManager -> IO ()
setTokenManager Connection
conn TokenManager
mgr
    --
    Connection -> ThreadId -> IO ()
setBaseThreadId Connection
conn ThreadId
baseThreadId
    --
    Connection
-> (CID -> Connection -> IO ()) -> (CID -> IO ()) -> IO ()
setRegister Connection
conn CID -> Connection -> IO ()
accRegister CID -> IO ()
accUnregister
    CID -> Connection -> IO ()
accRegister CID
myCID Connection
conn
    Connection -> IO () -> IO ()
addResource Connection
conn (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
        [CID]
myCIDs <- Connection -> IO [CID]
getMyCIDs Connection
conn
        (CID -> IO ()) -> [CID] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ CID -> IO ()
accUnregister [CID]
myCIDs
    --
#if defined(mingw32_HOST_OS)
    return $ ConnRes conn accMyAuthCIDs undefined
#else
    let reader :: IO ()
reader = UDPSocket -> Connection -> IO ()
readerServer UDPSocket
us Connection
conn -- dies when us is closed.
    ConnRes -> IO ConnRes
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (ConnRes -> IO ConnRes) -> ConnRes -> IO ConnRes
forall a b. (a -> b) -> a -> b
$ Connection -> AuthCIDs -> IO () -> ConnRes
ConnRes Connection
conn AuthCIDs
accMyAuthCIDs IO ()
reader
#endif

afterHandshakeServer :: ServerConfig -> Connection -> IO ()
afterHandshakeServer :: ServerConfig -> Connection -> IO ()
afterHandshakeServer ServerConfig{Bool
Int
[(IP, PortNumber)]
[Group]
[Cipher]
[Version]
Maybe FilePath
Maybe (Version -> [ByteString] -> IO ByteString)
SessionManager
Credentials
ServerHooks
Parameters
Hooks
FilePath -> IO ()
scHooks :: ServerConfig -> Hooks
scDebugLog :: ServerConfig -> Maybe FilePath
scAddresses :: ServerConfig -> [(IP, PortNumber)]
scParameters :: ServerConfig -> Parameters
scVersions :: ServerConfig -> [Version]
scCiphers :: ServerConfig -> [Cipher]
scGroups :: ServerConfig -> [Group]
scKeyLog :: ServerConfig -> FilePath -> IO ()
scQLog :: ServerConfig -> Maybe FilePath
scCredentials :: ServerConfig -> Credentials
scTlsHooks :: ServerConfig -> ServerHooks
scUse0RTT :: ServerConfig -> Bool
scALPN :: ServerConfig -> Maybe (Version -> [ByteString] -> IO ByteString)
scRequireRetry :: ServerConfig -> Bool
scSessionManager :: ServerConfig -> SessionManager
scTicketLifetime :: ServerConfig -> Int
scVersions :: [Version]
scCiphers :: [Cipher]
scGroups :: [Group]
scParameters :: Parameters
scKeyLog :: FilePath -> IO ()
scQLog :: Maybe FilePath
scCredentials :: Credentials
scHooks :: Hooks
scTlsHooks :: ServerHooks
scUse0RTT :: Bool
scAddresses :: [(IP, PortNumber)]
scALPN :: Maybe (Version -> [ByteString] -> IO ByteString)
scRequireRetry :: Bool
scSessionManager :: SessionManager
scDebugLog :: Maybe FilePath
scTicketLifetime :: Int
..} Connection
conn = DebugLogger -> IO () -> IO ()
forall a. DebugLogger -> IO a -> IO a
handleLogT DebugLogger
logAction (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    --
    CIDInfo
cidInfo <- Connection -> IO CIDInfo
getNewMyCID Connection
conn
    CID -> Connection -> IO ()
register <- Connection -> IO (CID -> Connection -> IO ())
getRegister Connection
conn
    CID -> Connection -> IO ()
register (CIDInfo -> CID
cidInfoCID CIDInfo
cidInfo) Connection
conn
    --
    Version
ver <- Connection -> IO Version
getVersion Connection
conn
    CryptoToken
cryptoToken <- Version -> Int -> IO CryptoToken
generateToken Version
ver Int
scTicketLifetime
    TokenManager
mgr <- Connection -> IO TokenManager
getTokenManager Connection
conn
    ByteString
token <- TokenManager -> CryptoToken -> IO ByteString
encryptToken TokenManager
mgr CryptoToken
cryptoToken
    let ncid :: Frame
ncid = CIDInfo -> Int -> Frame
NewConnectionID CIDInfo
cidInfo Int
0
    Connection -> EncryptionLevel -> [Frame] -> IO ()
sendFrames Connection
conn EncryptionLevel
RTT1Level [ByteString -> Frame
NewToken ByteString
token,Frame
ncid,Frame
HandshakeDone]
  where
    logAction :: DebugLogger
logAction Builder
msg = Connection -> DebugLogger
connDebugLog Connection
conn DebugLogger -> DebugLogger
forall a b. (a -> b) -> a -> b
$ Builder
"afterHandshakeServer: " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
msg

-- | Stopping the base thread of the server.
stop :: Connection -> IO ()
stop :: Connection -> IO ()
stop Connection
conn = Connection -> IO ThreadId
getBaseThreadId Connection
conn IO ThreadId -> (ThreadId -> IO ()) -> IO ()
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ThreadId -> IO ()
forall (m :: * -> *). MonadIO m => ThreadId -> m ()
killThread