module Network.QUIC.Info where
import Data.ByteString ()
import Network.QUIC.Connection
import Network.QUIC.Types
import Network.QUIC.Types.Info
import qualified Network.Socket as NS
getConnectionInfo :: Connection -> IO ConnectionInfo
getConnectionInfo :: Connection -> IO ConnectionInfo
getConnectionInfo Connection
conn = do
Socket
sock <- Connection -> IO Socket
getSocket Connection
conn
SockAddr
mysa <- Socket -> IO SockAddr
NS.getSocketName Socket
sock
PeerInfo SockAddr
peersa [Cmsg]
_ <- Connection -> IO PeerInfo
getPeerInfo Connection
conn
CID
mycid <- Connection -> IO CID
getMyCID Connection
conn
CID
peercid <- Connection -> IO CID
getPeerCID Connection
conn
Cipher
c <- Connection -> EncryptionLevel -> IO Cipher
getCipher Connection
conn EncryptionLevel
RTT1Level
Maybe NegotiatedProtocol
mproto <- Connection -> IO (Maybe NegotiatedProtocol)
getApplicationProtocol Connection
conn
HandshakeMode13
mode <- Connection -> IO HandshakeMode13
getTLSMode Connection
conn
Bool
r <- Connection -> IO Bool
getRetried Connection
conn
Version
v <- Connection -> IO Version
getVersion Connection
conn
ConnectionInfo -> IO ConnectionInfo
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
ConnectionInfo
{ version :: Version
version = Version
v
, cipher :: Cipher
cipher = Cipher
c
, alpn :: Maybe NegotiatedProtocol
alpn = Maybe NegotiatedProtocol
mproto
, handshakeMode :: HandshakeMode13
handshakeMode = HandshakeMode13
mode
, retry :: Bool
retry = Bool
r
, localSockAddr :: SockAddr
localSockAddr = SockAddr
mysa
, remoteSockAddr :: SockAddr
remoteSockAddr = SockAddr
peersa
, localCID :: CID
localCID = CID
mycid
, remoteCID :: CID
remoteCID = CID
peercid
}
data ConnectionStats = ConnectionStats
{ ConnectionStats -> Int
txBytes :: Int
, ConnectionStats -> Int
rxBytes :: Int
}
deriving (ConnectionStats -> ConnectionStats -> Bool
(ConnectionStats -> ConnectionStats -> Bool)
-> (ConnectionStats -> ConnectionStats -> Bool)
-> Eq ConnectionStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConnectionStats -> ConnectionStats -> Bool
== :: ConnectionStats -> ConnectionStats -> Bool
$c/= :: ConnectionStats -> ConnectionStats -> Bool
/= :: ConnectionStats -> ConnectionStats -> Bool
Eq, Int -> ConnectionStats -> ShowS
[ConnectionStats] -> ShowS
ConnectionStats -> String
(Int -> ConnectionStats -> ShowS)
-> (ConnectionStats -> String)
-> ([ConnectionStats] -> ShowS)
-> Show ConnectionStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConnectionStats -> ShowS
showsPrec :: Int -> ConnectionStats -> ShowS
$cshow :: ConnectionStats -> String
show :: ConnectionStats -> String
$cshowList :: [ConnectionStats] -> ShowS
showList :: [ConnectionStats] -> ShowS
Show)
getConnectionStats :: Connection -> IO ConnectionStats
getConnectionStats :: Connection -> IO ConnectionStats
getConnectionStats Connection
conn = do
Int
tx <- Connection -> IO Int
getTxBytes Connection
conn
Int
rx <- Connection -> IO Int
getRxBytes Connection
conn
ConnectionStats -> IO ConnectionStats
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (ConnectionStats -> IO ConnectionStats)
-> ConnectionStats -> IO ConnectionStats
forall a b. (a -> b) -> a -> b
$
ConnectionStats
{ txBytes :: Int
txBytes = Int
tx
, rxBytes :: Int
rxBytes = Int
rx
}