{-# 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
/= :: Direction -> Direction -> Bool
$c/= :: Direction -> Direction -> Bool
== :: Direction -> Direction -> Bool
$c== :: Direction -> Direction -> Bool
Eq, Int -> Direction -> ShowS
[Direction] -> ShowS
Direction -> String
(Int -> Direction -> ShowS)
-> (Direction -> String)
-> ([Direction] -> ShowS)
-> Show Direction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Direction] -> ShowS
$cshowList :: [Direction] -> ShowS
show :: Direction -> String
$cshow :: Direction -> String
showsPrec :: Int -> Direction -> ShowS
$cshowsPrec :: Int -> 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 -- retire prior to
           | 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
/= :: Frame -> Frame -> Bool
$c/= :: Frame -> Frame -> Bool
== :: Frame -> Frame -> Bool
$c== :: Frame -> Frame -> Bool
Eq,Int -> Frame -> ShowS
[Frame] -> ShowS
Frame -> String
(Int -> Frame -> ShowS)
-> (Frame -> String) -> ([Frame] -> ShowS) -> Show Frame
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Frame] -> ShowS
$cshowList :: [Frame] -> ShowS
show :: Frame -> String
$cshow :: Frame -> String
showsPrec :: Int -> Frame -> ShowS
$cshowsPrec :: Int -> Frame -> ShowS
Show)

-- | Stream identifier.
--   This should be 62-bit interger.
--   On 32-bit machines, the total number of stream identifiers is limited.
type StreamId = Int

-- | Checking if a stream is client-initiated bidirectional.
isClientInitiatedBidirectional :: StreamId -> Bool
isClientInitiatedBidirectional :: Int -> Bool
isClientInitiatedBidirectional  Int
sid = (Int
0b11 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
sid) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0

-- | Checking if a stream is server-initiated bidirectional.
isServerInitiatedBidirectional :: StreamId -> Bool
isServerInitiatedBidirectional :: Int -> Bool
isServerInitiatedBidirectional  Int
sid = (Int
0b11 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
sid) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1

-- | Checking if a stream is client-initiated unidirectional.
isClientInitiatedUnidirectional :: StreamId -> Bool
isClientInitiatedUnidirectional :: Int -> Bool
isClientInitiatedUnidirectional Int
sid = (Int
0b11 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
sid) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
2

-- | Checking if a stream is server-initiated unidirectional.
isServerInitiatedUnidirectional :: StreamId -> Bool
isServerInitiatedUnidirectional :: Int -> Bool
isServerInitiatedUnidirectional Int
sid = (Int
0b11 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
sid) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
3

isClientInitiated :: StreamId -> Bool
isClientInitiated :: Int -> Bool
isClientInitiated Int
sid = (Int
0b1 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
sid) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0

isServerInitiated :: StreamId -> Bool
isServerInitiated :: Int -> Bool
isServerInitiated Int
sid = (Int
0b1 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
sid) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1

type Delay = Milliseconds

type Fin = Bool

type CryptoData = ByteString
type StreamData = ByteString

type Token = ByteString -- to be decrypted
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