{-# LANGUAGE BinaryLiterals #-}
{-# LANGUAGE OverloadedStrings #-}
module Network.QUIC.Types.Frame where
import Network.QUIC.Imports
import Network.QUIC.Types.Ack
import Network.QUIC.Types.CID
import Network.QUIC.Types.Error
import Network.QUIC.Types.Time
type FrameType = Int
data Direction = Unidirectional | Bidirectional deriving (Direction -> Direction -> Bool
(Direction -> Direction -> Bool)
-> (Direction -> Direction -> Bool) -> Eq Direction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Direction -> Direction -> Bool
== :: Direction -> Direction -> Bool
$c/= :: Direction -> Direction -> Bool
/= :: Direction -> Direction -> Bool
Eq, StreamId -> Direction -> ShowS
[Direction] -> ShowS
Direction -> String
(StreamId -> Direction -> ShowS)
-> (Direction -> String)
-> ([Direction] -> ShowS)
-> Show Direction
forall a.
(StreamId -> a -> ShowS)
-> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: StreamId -> Direction -> ShowS
showsPrec :: StreamId -> Direction -> ShowS
$cshow :: Direction -> String
show :: Direction -> String
$cshowList :: [Direction] -> ShowS
showList :: [Direction] -> ShowS
Show)
type ReasonPhrase = ShortByteString
type SeqNum = Int
data Frame
= Padding Int
| Ping
| Ack AckInfo Delay
| ResetStream StreamId ApplicationProtocolError Int
| StopSending StreamId ApplicationProtocolError
| CryptoF Offset CryptoData
| NewToken Token
| StreamF StreamId Offset [StreamData] Fin
| MaxData Int
| MaxStreamData StreamId Int
| MaxStreams Direction Int
| DataBlocked Int
| StreamDataBlocked StreamId Int
| StreamsBlocked Direction Int
| NewConnectionID CIDInfo SeqNum
| RetireConnectionID SeqNum
| PathChallenge PathData
| PathResponse PathData
| ConnectionClose TransportError FrameType ReasonPhrase
| ConnectionCloseApp ApplicationProtocolError ReasonPhrase
| HandshakeDone
| UnknownFrame Int
deriving (Frame -> Frame -> Bool
(Frame -> Frame -> Bool) -> (Frame -> Frame -> Bool) -> Eq Frame
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Frame -> Frame -> Bool
== :: Frame -> Frame -> Bool
$c/= :: Frame -> Frame -> Bool
/= :: Frame -> Frame -> Bool
Eq, StreamId -> Frame -> ShowS
[Frame] -> ShowS
Frame -> String
(StreamId -> Frame -> ShowS)
-> (Frame -> String) -> ([Frame] -> ShowS) -> Show Frame
forall a.
(StreamId -> a -> ShowS)
-> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: StreamId -> Frame -> ShowS
showsPrec :: StreamId -> Frame -> ShowS
$cshow :: Frame -> String
show :: Frame -> String
$cshowList :: [Frame] -> ShowS
showList :: [Frame] -> ShowS
Show)
type StreamId = Int
isClientInitiatedBidirectional :: StreamId -> Bool
isClientInitiatedBidirectional :: StreamId -> Bool
isClientInitiatedBidirectional StreamId
sid = (StreamId
0b11 StreamId -> StreamId -> StreamId
forall a. Bits a => a -> a -> a
.&. StreamId
sid) StreamId -> StreamId -> Bool
forall a. Eq a => a -> a -> Bool
== StreamId
0
isServerInitiatedBidirectional :: StreamId -> Bool
isServerInitiatedBidirectional :: StreamId -> Bool
isServerInitiatedBidirectional StreamId
sid = (StreamId
0b11 StreamId -> StreamId -> StreamId
forall a. Bits a => a -> a -> a
.&. StreamId
sid) StreamId -> StreamId -> Bool
forall a. Eq a => a -> a -> Bool
== StreamId
1
isClientInitiatedUnidirectional :: StreamId -> Bool
isClientInitiatedUnidirectional :: StreamId -> Bool
isClientInitiatedUnidirectional StreamId
sid = (StreamId
0b11 StreamId -> StreamId -> StreamId
forall a. Bits a => a -> a -> a
.&. StreamId
sid) StreamId -> StreamId -> Bool
forall a. Eq a => a -> a -> Bool
== StreamId
2
isServerInitiatedUnidirectional :: StreamId -> Bool
isServerInitiatedUnidirectional :: StreamId -> Bool
isServerInitiatedUnidirectional StreamId
sid = (StreamId
0b11 StreamId -> StreamId -> StreamId
forall a. Bits a => a -> a -> a
.&. StreamId
sid) StreamId -> StreamId -> Bool
forall a. Eq a => a -> a -> Bool
== StreamId
3
isClientInitiated :: StreamId -> Bool
isClientInitiated :: StreamId -> Bool
isClientInitiated StreamId
sid = (StreamId
0b1 StreamId -> StreamId -> StreamId
forall a. Bits a => a -> a -> a
.&. StreamId
sid) StreamId -> StreamId -> Bool
forall a. Eq a => a -> a -> Bool
== StreamId
0
isServerInitiated :: StreamId -> Bool
isServerInitiated :: StreamId -> Bool
isServerInitiated StreamId
sid = (StreamId
0b1 StreamId -> StreamId -> StreamId
forall a. Bits a => a -> a -> a
.&. StreamId
sid) StreamId -> StreamId -> Bool
forall a. Eq a => a -> a -> Bool
== StreamId
1
isBidirectional :: StreamId -> Bool
isBidirectional :: StreamId -> Bool
isBidirectional StreamId
sid = (StreamId
0b10 StreamId -> StreamId -> StreamId
forall a. Bits a => a -> a -> a
.&. StreamId
sid) StreamId -> StreamId -> Bool
forall a. Eq a => a -> a -> Bool
== StreamId
0
isUnidirectional :: StreamId -> Bool
isUnidirectional :: StreamId -> Bool
isUnidirectional StreamId
sid = (StreamId
0b10 StreamId -> StreamId -> StreamId
forall a. Bits a => a -> a -> a
.&. StreamId
sid) StreamId -> StreamId -> Bool
forall a. Eq a => a -> a -> Bool
== StreamId
2
type Delay = Milliseconds
type Fin = Bool
type CryptoData = ByteString
type StreamData = ByteString
type Token = ByteString
emptyToken :: Token
emptyToken :: Token
emptyToken = Token
""
ackEliciting :: Frame -> Bool
ackEliciting :: Frame -> Bool
ackEliciting Padding{} = Bool
False
ackEliciting Ack{} = Bool
False
ackEliciting ConnectionClose{} = Bool
False
ackEliciting ConnectionCloseApp{} = Bool
False
ackEliciting Frame
_ = Bool
True
pathValidating :: Frame -> Bool
pathValidating :: Frame -> Bool
pathValidating PathChallenge{} = Bool
True
pathValidating PathResponse{} = Bool
True
pathValidating Frame
_ = Bool
False
inFlight :: Frame -> Bool
inFlight :: Frame -> Bool
inFlight Ack{} = Bool
False
inFlight ConnectionClose{} = Bool
False
inFlight ConnectionCloseApp{} = Bool
False
inFlight Frame
_ = Bool
True
rateControled :: Frame -> Bool
rateControled :: Frame -> Bool
rateControled ResetStream{} = Bool
True
rateControled StopSending{} = Bool
True
rateControled PathChallenge{} = Bool
True
rateControled PathResponse{} = Bool
True
rateControled NewConnectionID{} = Bool
True
rateControled RetireConnectionID{} = Bool
True
rateControled Frame
_ = Bool
False