{-# LANGUAGE OverloadedStrings #-}

module Network.QUIC.Packet.Frame (
    encodeFrames
  , encodeFramesWithPadding
  , decodeFramesBS
  , decodeFramesBuffer
  , countZero -- testing
  ) where

import qualified Data.ByteString as BS
import qualified Data.ByteString.Short as Short
import Foreign.Ptr (Ptr, plusPtr, minusPtr, alignPtr, castPtr)
import Foreign.Storable (peek, alignment)
import Network.Socket.Internal (zeroMemory)

import Network.QUIC.Imports
import Network.QUIC.Types

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

encodeFrames :: [Frame] -> IO ByteString
encodeFrames :: [Frame] -> IO ByteString
encodeFrames [Frame]
frames = SeqNum -> (WriteBuffer -> IO ()) -> IO ByteString
withWriteBuffer SeqNum
2048 forall a b. (a -> b) -> a -> b
$ \WriteBuffer
wbuf ->
  forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (WriteBuffer -> Frame -> IO ()
encodeFrame WriteBuffer
wbuf) [Frame]
frames

encodeFramesWithPadding :: Buffer
                        -> BufferSize
                        -> [Frame]
                        -> IO Int   -- ^ payload size without paddings
encodeFramesWithPadding :: Ptr Word8 -> SeqNum -> [Frame] -> IO SeqNum
encodeFramesWithPadding Ptr Word8
buf SeqNum
siz [Frame]
frames = do
    forall a. Ptr a -> CSize -> IO ()
zeroMemory Ptr Word8
buf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
siz -- padding
    WriteBuffer
wbuf <- Ptr Word8 -> SeqNum -> IO WriteBuffer
newWriteBuffer Ptr Word8
buf SeqNum
siz
    forall a. Readable a => a -> IO ()
save WriteBuffer
wbuf
    forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (WriteBuffer -> Frame -> IO ()
encodeFrame WriteBuffer
wbuf) [Frame]
frames
    forall a. Readable a => a -> IO SeqNum
savingSize WriteBuffer
wbuf

encodeFrame :: WriteBuffer -> Frame -> IO ()
encodeFrame :: WriteBuffer -> Frame -> IO ()
encodeFrame WriteBuffer
wbuf (Padding SeqNum
n) = forall (m :: * -> *) a. Applicative m => SeqNum -> m a -> m ()
replicateM_ SeqNum
n forall a b. (a -> b) -> a -> b
$ WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x00
encodeFrame WriteBuffer
wbuf Frame
Ping = WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x01
encodeFrame WriteBuffer
wbuf (Ack (AckInfo SeqNum
largest SeqNum
range1 [(SeqNum, SeqNum)]
ranges) (Milliseconds Int64
delay)) = do
    WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x02
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
largest
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
delay
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> SeqNum
length [(SeqNum, SeqNum)]
ranges
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
range1
    forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ forall {a} {a}. (Integral a, Integral a) => (a, a) -> IO ()
putRanges [(SeqNum, SeqNum)]
ranges
  where
    putRanges :: (a, a) -> IO ()
putRanges (a
gap,a
rng) = do
        WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral a
gap
        WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral a
rng
encodeFrame WriteBuffer
wbuf (ResetStream SeqNum
sid (ApplicationProtocolError SeqNum
err) SeqNum
finalLen) = do
    WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x04
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
sid
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
err
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
finalLen
encodeFrame WriteBuffer
wbuf (StopSending SeqNum
sid (ApplicationProtocolError SeqNum
err)) = do
    WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x05
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
sid
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
err
encodeFrame WriteBuffer
wbuf (CryptoF SeqNum
off ByteString
cdata) = do
    WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x06
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
off
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ ByteString -> SeqNum
BS.length ByteString
cdata
    WriteBuffer -> ByteString -> IO ()
copyByteString WriteBuffer
wbuf ByteString
cdata
encodeFrame WriteBuffer
wbuf (NewToken ByteString
token) = do
    WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x07
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ ByteString -> SeqNum
BS.length ByteString
token
    WriteBuffer -> ByteString -> IO ()
copyByteString WriteBuffer
wbuf ByteString
token
encodeFrame WriteBuffer
wbuf (StreamF SeqNum
sid SeqNum
off [ByteString]
dats Fin
fin) = do
    let flag0 :: Word8
flag0 = Word8
0x08 forall a. Bits a => a -> a -> a
.|. Word8
0x02 -- len
        flag1 :: Word8
flag1 | SeqNum
off forall a. Eq a => a -> a -> Fin
/= SeqNum
0  = Word8
flag0 forall a. Bits a => a -> a -> a
.|. Word8
0x04 -- off
              | Fin
otherwise = Word8
flag0
        flag2 :: Word8
flag2 | Fin
fin       = Word8
flag1 forall a. Bits a => a -> a -> a
.|. Word8
0x01 -- fin
              | Fin
otherwise = Word8
flag1
    WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
flag2
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
sid
    forall (f :: * -> *). Applicative f => Fin -> f () -> f ()
when (SeqNum
off forall a. Eq a => a -> a -> Fin
/= SeqNum
0) forall a b. (a -> b) -> a -> b
$ WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
off
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ [ByteString] -> SeqNum
totalLen [ByteString]
dats
    forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (WriteBuffer -> ByteString -> IO ()
copyByteString WriteBuffer
wbuf) [ByteString]
dats
encodeFrame WriteBuffer
wbuf (MaxData SeqNum
n) = do
    WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x10
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
n
encodeFrame WriteBuffer
wbuf (MaxStreamData SeqNum
sid SeqNum
n) = do
    WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x11
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
sid
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
n
encodeFrame WriteBuffer
wbuf (MaxStreams Direction
dir SeqNum
ms) = do
    case Direction
dir of
      Direction
Bidirectional  -> WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x12
      Direction
Unidirectional -> WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x13
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
ms
encodeFrame WriteBuffer
wbuf (DataBlocked SeqNum
n) = do
    WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x14
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
n
encodeFrame WriteBuffer
wbuf (StreamDataBlocked SeqNum
sid SeqNum
n) = do
    WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x15
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
sid
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
n
encodeFrame WriteBuffer
wbuf (StreamsBlocked Direction
dir SeqNum
ms) = do
    case Direction
dir of
      Direction
Bidirectional  -> WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x16
      Direction
Unidirectional -> WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x17
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
ms
encodeFrame WriteBuffer
wbuf (NewConnectionID CIDInfo
cidInfo SeqNum
rpt) = do
    WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x18
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ CIDInfo -> SeqNum
cidInfoSeq CIDInfo
cidInfo
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
rpt
    let (ShortByteString
cid, Word8
len) = CID -> (ShortByteString, Word8)
unpackCID forall a b. (a -> b) -> a -> b
$ CIDInfo -> CID
cidInfoCID CIDInfo
cidInfo
    WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
len
    WriteBuffer -> ShortByteString -> IO ()
copyShortByteString WriteBuffer
wbuf ShortByteString
cid
    let StatelessResetToken ShortByteString
token = CIDInfo -> StatelessResetToken
cidInfoSRT CIDInfo
cidInfo
    WriteBuffer -> ShortByteString -> IO ()
copyShortByteString WriteBuffer
wbuf ShortByteString
token
encodeFrame WriteBuffer
wbuf (RetireConnectionID SeqNum
seqNum) = do
    WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x19
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
seqNum
encodeFrame WriteBuffer
wbuf (PathChallenge (PathData ShortByteString
pdata)) = do
    WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x1a
    WriteBuffer -> ByteString -> IO ()
copyByteString WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ ShortByteString -> ByteString
Short.fromShort ShortByteString
pdata
encodeFrame WriteBuffer
wbuf (PathResponse (PathData ShortByteString
pdata)) = do
    WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x1b
    WriteBuffer -> ByteString -> IO ()
copyByteString WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ ShortByteString -> ByteString
Short.fromShort ShortByteString
pdata
encodeFrame WriteBuffer
wbuf (ConnectionClose (TransportError SeqNum
err) SeqNum
ftyp ShortByteString
reason) = do
    WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x1c
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
err
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
ftyp
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ ShortByteString -> SeqNum
Short.length ShortByteString
reason
    WriteBuffer -> ShortByteString -> IO ()
copyShortByteString WriteBuffer
wbuf ShortByteString
reason
encodeFrame WriteBuffer
wbuf (ConnectionCloseApp (ApplicationProtocolError SeqNum
err) ShortByteString
reason) = do
    WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x1d
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
err
    WriteBuffer -> Int64 -> IO ()
encodeInt' WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ ShortByteString -> SeqNum
Short.length ShortByteString
reason
    WriteBuffer -> ShortByteString -> IO ()
copyShortByteString WriteBuffer
wbuf ShortByteString
reason
encodeFrame WriteBuffer
wbuf Frame
HandshakeDone =
    WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf Word8
0x1e
encodeFrame WriteBuffer
wbuf (UnknownFrame SeqNum
typ) =
    WriteBuffer -> Word8 -> IO ()
write8 WriteBuffer
wbuf forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral SeqNum
typ

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

decodeFramesBS :: ByteString -> IO (Maybe [Frame])
decodeFramesBS :: ByteString -> IO (Maybe [Frame])
decodeFramesBS ByteString
bs = forall a. ByteString -> (ReadBuffer -> IO a) -> IO a
withReadBuffer ByteString
bs ReadBuffer -> IO (Maybe [Frame])
decodeFrames

decodeFramesBuffer :: Buffer -> BufferSize -> IO (Maybe [Frame])
decodeFramesBuffer :: Ptr Word8 -> SeqNum -> IO (Maybe [Frame])
decodeFramesBuffer Ptr Word8
buf SeqNum
bufsiz = Ptr Word8 -> SeqNum -> IO ReadBuffer
newReadBuffer Ptr Word8
buf SeqNum
bufsiz forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ReadBuffer -> IO (Maybe [Frame])
decodeFrames

decodeFrames :: ReadBuffer -> IO (Maybe [Frame])
decodeFrames :: ReadBuffer -> IO (Maybe [Frame])
decodeFrames ReadBuffer
rbuf = forall {a}. ([Frame] -> a) -> IO (Maybe a)
loop forall a. a -> a
id
  where
    loop :: ([Frame] -> a) -> IO (Maybe a)
loop [Frame] -> a
frames = do
        Fin
ok <- (forall a. Ord a => a -> a -> Fin
>= SeqNum
1) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Readable a => a -> IO SeqNum
remainingSize ReadBuffer
rbuf
        if Fin
ok then do
            Frame
frame <- ReadBuffer -> IO Frame
decodeFrame ReadBuffer
rbuf
            case Frame
frame of
              UnknownFrame SeqNum
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
              Frame
_              -> ([Frame] -> a) -> IO (Maybe a)
loop ([Frame] -> a
frames forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Frame
frameforall a. a -> [a] -> [a]
:))
          else
            forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ [Frame] -> a
frames []

decodeFrame :: ReadBuffer -> IO Frame
decodeFrame :: ReadBuffer -> IO Frame
decodeFrame ReadBuffer
rbuf = do
    SeqNum
ftyp <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    case SeqNum
ftyp :: FrameType of
      SeqNum
0x00 -> ReadBuffer -> IO Frame
decodePadding ReadBuffer
rbuf
      SeqNum
0x01 -> forall (m :: * -> *) a. Monad m => a -> m a
return Frame
Ping
      SeqNum
0x02 -> ReadBuffer -> IO Frame
decodeAck ReadBuffer
rbuf
   -- 0x03 -> Ack with ECN Counts
      SeqNum
0x04 -> ReadBuffer -> IO Frame
decodeResetStream ReadBuffer
rbuf
      SeqNum
0x05 -> ReadBuffer -> IO Frame
decodeStopSending ReadBuffer
rbuf
      SeqNum
0x06 -> ReadBuffer -> IO Frame
decodeCrypto ReadBuffer
rbuf
      SeqNum
0x07 -> ReadBuffer -> IO Frame
decodeNewToken ReadBuffer
rbuf
      SeqNum
x | SeqNum
0x08 forall a. Ord a => a -> a -> Fin
<= SeqNum
x Fin -> Fin -> Fin
&& SeqNum
x forall a. Ord a => a -> a -> Fin
<= SeqNum
0x0f -> do
              let off :: Fin
off = forall a. Bits a => a -> SeqNum -> Fin
testBit SeqNum
x SeqNum
2
                  len :: Fin
len = forall a. Bits a => a -> SeqNum -> Fin
testBit SeqNum
x SeqNum
1
                  fin :: Fin
fin = forall a. Bits a => a -> SeqNum -> Fin
testBit SeqNum
x SeqNum
0
              ReadBuffer -> Fin -> Fin -> Fin -> IO Frame
decodeStream ReadBuffer
rbuf Fin
off Fin
len Fin
fin
      SeqNum
0x10 -> ReadBuffer -> IO Frame
decodeMaxData ReadBuffer
rbuf
      SeqNum
0x11 -> ReadBuffer -> IO Frame
decodeMaxStreamData ReadBuffer
rbuf
      SeqNum
0x12 -> ReadBuffer -> Direction -> IO Frame
decodeMaxStreams ReadBuffer
rbuf Direction
Bidirectional
      SeqNum
0x13 -> ReadBuffer -> Direction -> IO Frame
decodeMaxStreams ReadBuffer
rbuf Direction
Unidirectional
      SeqNum
0x14 -> ReadBuffer -> IO Frame
decodeDataBlocked ReadBuffer
rbuf
      SeqNum
0x15 -> ReadBuffer -> IO Frame
decodeStreamDataBlocked ReadBuffer
rbuf
      SeqNum
0x16 -> ReadBuffer -> Direction -> IO Frame
decodeStreamsBlocked ReadBuffer
rbuf Direction
Bidirectional
      SeqNum
0x17 -> ReadBuffer -> Direction -> IO Frame
decodeStreamsBlocked ReadBuffer
rbuf Direction
Unidirectional
      SeqNum
0x18 -> ReadBuffer -> IO Frame
decodeNewConnectionID ReadBuffer
rbuf
      SeqNum
0x19 -> ReadBuffer -> IO Frame
decodeRetireConnectionID ReadBuffer
rbuf
      SeqNum
0x1a -> ReadBuffer -> IO Frame
decodePathChallenge ReadBuffer
rbuf
      SeqNum
0x1b -> ReadBuffer -> IO Frame
decodePathResponse ReadBuffer
rbuf
      SeqNum
0x1c -> ReadBuffer -> IO Frame
decodeConnectionClose ReadBuffer
rbuf
      SeqNum
0x1d -> ReadBuffer -> IO Frame
decodeConnectionCloseApp ReadBuffer
rbuf
      SeqNum
0x1e -> forall (m :: * -> *) a. Monad m => a -> m a
return Frame
HandshakeDone
      SeqNum
x    -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ SeqNum -> Frame
UnknownFrame SeqNum
x

decodePadding :: ReadBuffer -> IO Frame
decodePadding :: ReadBuffer -> IO Frame
decodePadding ReadBuffer
rbuf = do
    SeqNum
n <- forall a b. Readable a => a -> (Ptr Word8 -> IO b) -> IO b
withCurrentOffSet ReadBuffer
rbuf forall a b. (a -> b) -> a -> b
$ \Ptr Word8
beg -> do
        SeqNum
rest <- forall a. Readable a => a -> IO SeqNum
remainingSize ReadBuffer
rbuf
        let end :: Ptr b
end = Ptr Word8
beg forall a b. Ptr a -> SeqNum -> Ptr b
`plusPtr` SeqNum
rest
        Ptr Word8 -> Ptr Word8 -> IO SeqNum
countZero Ptr Word8
beg forall {b}. Ptr b
end
    forall a. Readable a => a -> SeqNum -> IO ()
ff ReadBuffer
rbuf SeqNum
n
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ SeqNum -> Frame
Padding (SeqNum
n forall a. Num a => a -> a -> a
+ SeqNum
1)

countZero :: Ptr Word8 -> Ptr Word8 -> IO Int
countZero :: Ptr Word8 -> Ptr Word8 -> IO SeqNum
countZero Ptr Word8
beg0 Ptr Word8
end0
  | (Ptr Word8
end0 forall a b. Ptr a -> Ptr b -> SeqNum
`minusPtr` Ptr Word8
beg0) forall a. Ord a => a -> a -> Fin
<= SeqNum
ali = forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word8 -> Ptr Word8 -> SeqNum -> IO (SeqNum, Fin)
countBy1 Ptr Word8
beg0 Ptr Word8
end0 SeqNum
0
  | Fin
otherwise = do
    let beg1 :: Ptr Word8
beg1 = forall a. Ptr a -> SeqNum -> Ptr a
alignPtr Ptr Word8
beg0 SeqNum
ali
        end1' :: Ptr Word8
end1' = forall a. Ptr a -> SeqNum -> Ptr a
alignPtr Ptr Word8
end0 SeqNum
ali
        end1 :: Ptr Word8
end1 | Ptr Word8
end0 forall a. Eq a => a -> a -> Fin
== Ptr Word8
end1' = Ptr Word8
end1'
             | Fin
otherwise     = Ptr Word8
end1' forall a b. Ptr a -> SeqNum -> Ptr b
`plusPtr` forall a. Num a => a -> a
negate SeqNum
ali
    (SeqNum
n1,Fin
cont1) <- Ptr Word8 -> Ptr Word8 -> SeqNum -> IO (SeqNum, Fin)
countBy1 Ptr Word8
beg0 Ptr Word8
beg1 SeqNum
0
    if Fin -> Fin
not Fin
cont1 then
        forall (m :: * -> *) a. Monad m => a -> m a
return SeqNum
n1
      else do
        (SeqNum
n2,Ptr Word64
beg2) <- Ptr Word64 -> Ptr Word64 -> SeqNum -> IO (SeqNum, Ptr Word64)
countBy8 (forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
beg1) (forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
end1) SeqNum
0
        (SeqNum
n3,Fin
_) <- Ptr Word8 -> Ptr Word8 -> SeqNum -> IO (SeqNum, Fin)
countBy1 (forall a b. Ptr a -> Ptr b
castPtr Ptr Word64
beg2) Ptr Word8
end0 SeqNum
0
        forall (m :: * -> *) a. Monad m => a -> m a
return (SeqNum
n1 forall a. Num a => a -> a -> a
+ SeqNum
n2 forall a. Num a => a -> a -> a
+ SeqNum
n3)
  where
    ali :: SeqNum
ali = forall a. Storable a => a -> SeqNum
alignment (Word64
0 :: Word64)
    countBy1 :: Ptr Word8 -> Ptr Word8 -> Int -> IO (Int,Bool)
    countBy1 :: Ptr Word8 -> Ptr Word8 -> SeqNum -> IO (SeqNum, Fin)
countBy1 Ptr Word8
beg Ptr Word8
end SeqNum
n
      | Ptr Word8
beg forall a. Ord a => a -> a -> Fin
< Ptr Word8
end = do
            Word8
ftyp <- forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
beg
            if Word8
ftyp forall a. Eq a => a -> a -> Fin
== Word8
0 then
                Ptr Word8 -> Ptr Word8 -> SeqNum -> IO (SeqNum, Fin)
countBy1 (Ptr Word8
beg forall a b. Ptr a -> SeqNum -> Ptr b
`plusPtr` SeqNum
1) Ptr Word8
end (SeqNum
n forall a. Num a => a -> a -> a
+ SeqNum
1)
              else
                forall (m :: * -> *) a. Monad m => a -> m a
return (SeqNum
n, Fin
False)
      | Fin
otherwise = forall (m :: * -> *) a. Monad m => a -> m a
return (SeqNum
n, Fin
True)
    countBy8 :: Ptr Word64 -> Ptr Word64 -> Int -> IO (Int, Ptr Word64)
    countBy8 :: Ptr Word64 -> Ptr Word64 -> SeqNum -> IO (SeqNum, Ptr Word64)
countBy8 Ptr Word64
beg Ptr Word64
end SeqNum
n
      | Ptr Word64
beg forall a. Ord a => a -> a -> Fin
< Ptr Word64
end = do
            Word64
ftyp <- forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
beg
            if Word64
ftyp forall a. Eq a => a -> a -> Fin
== Word64
0 then
                Ptr Word64 -> Ptr Word64 -> SeqNum -> IO (SeqNum, Ptr Word64)
countBy8 (Ptr Word64
beg forall a b. Ptr a -> SeqNum -> Ptr b
`plusPtr` SeqNum
ali) Ptr Word64
end (SeqNum
n forall a. Num a => a -> a -> a
+ SeqNum
ali)
              else
                forall (m :: * -> *) a. Monad m => a -> m a
return (SeqNum
n, Ptr Word64
beg)
      | Fin
otherwise = forall (m :: * -> *) a. Monad m => a -> m a
return (SeqNum
n, Ptr Word64
beg)

decodeCrypto :: ReadBuffer -> IO Frame
decodeCrypto :: ReadBuffer -> IO Frame
decodeCrypto ReadBuffer
rbuf = do
    SeqNum
off <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    SeqNum
len <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    ByteString
cdata <- forall a. Readable a => a -> SeqNum -> IO ByteString
extractByteString ReadBuffer
rbuf SeqNum
len
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ SeqNum -> ByteString -> Frame
CryptoF SeqNum
off ByteString
cdata

decodeAck :: ReadBuffer -> IO Frame
decodeAck :: ReadBuffer -> IO Frame
decodeAck ReadBuffer
rbuf = do
    SeqNum
largest <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    Int64
delay   <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    SeqNum
count   <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    SeqNum
range1  <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    [(SeqNum, SeqNum)]
ranges  <- forall {a} {b} {c}.
(Num a, Num b) =>
SeqNum -> ([(a, b)] -> c) -> IO c
getRanges SeqNum
count forall a. a -> a
id
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ AckInfo -> Milliseconds -> Frame
Ack (SeqNum -> SeqNum -> [(SeqNum, SeqNum)] -> AckInfo
AckInfo SeqNum
largest SeqNum
range1 [(SeqNum, SeqNum)]
ranges) forall a b. (a -> b) -> a -> b
$ Int64 -> Milliseconds
Milliseconds Int64
delay
  where
    getRanges :: SeqNum -> ([(a, b)] -> c) -> IO c
getRanges SeqNum
0 [(a, b)] -> c
build = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [(a, b)] -> c
build []
    getRanges SeqNum
n [(a, b)] -> c
build = do
        a
gap <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
        b
rng <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
        let n' :: SeqNum
n' = SeqNum
n forall a. Num a => a -> a -> a
- SeqNum
1 :: Int
        SeqNum -> ([(a, b)] -> c) -> IO c
getRanges SeqNum
n' ([(a, b)] -> c
build forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a
gap, b
rng) forall a. a -> [a] -> [a]
:))

decodeResetStream :: ReadBuffer -> IO Frame
decodeResetStream :: ReadBuffer -> IO Frame
decodeResetStream ReadBuffer
rbuf = do
    SeqNum
sID <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    ApplicationProtocolError
err <- SeqNum -> ApplicationProtocolError
ApplicationProtocolError forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    SeqNum
finalLen <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ SeqNum -> ApplicationProtocolError -> SeqNum -> Frame
ResetStream SeqNum
sID ApplicationProtocolError
err SeqNum
finalLen

decodeStopSending :: ReadBuffer -> IO Frame
decodeStopSending :: ReadBuffer -> IO Frame
decodeStopSending ReadBuffer
rbuf = do
    SeqNum
sID <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    ApplicationProtocolError
err <- SeqNum -> ApplicationProtocolError
ApplicationProtocolError forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ SeqNum -> ApplicationProtocolError -> Frame
StopSending SeqNum
sID ApplicationProtocolError
err

decodeNewToken :: ReadBuffer -> IO Frame
decodeNewToken :: ReadBuffer -> IO Frame
decodeNewToken ReadBuffer
rbuf = do
    SeqNum
len <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    ByteString -> Frame
NewToken forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Readable a => a -> SeqNum -> IO ByteString
extractByteString ReadBuffer
rbuf SeqNum
len

decodeStream :: ReadBuffer -> Bool -> Bool -> Bool -> IO Frame
decodeStream :: ReadBuffer -> Fin -> Fin -> Fin -> IO Frame
decodeStream ReadBuffer
rbuf Fin
hasOff Fin
hasLen Fin
fin = do
    SeqNum
sID <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    SeqNum
off <- if Fin
hasOff then
             forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
           else
             forall (m :: * -> *) a. Monad m => a -> m a
return SeqNum
0
    ByteString
dat <- if Fin
hasLen then do
             SeqNum
len <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
             forall a. Readable a => a -> SeqNum -> IO ByteString
extractByteString ReadBuffer
rbuf SeqNum
len
           else do
             SeqNum
len <- forall a. Readable a => a -> IO SeqNum
remainingSize ReadBuffer
rbuf
             forall a. Readable a => a -> SeqNum -> IO ByteString
extractByteString ReadBuffer
rbuf SeqNum
len
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ SeqNum -> SeqNum -> [ByteString] -> Fin -> Frame
StreamF SeqNum
sID SeqNum
off [ByteString
dat] Fin
fin

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

decodeMaxData :: ReadBuffer -> IO Frame
decodeMaxData :: ReadBuffer -> IO Frame
decodeMaxData ReadBuffer
rbuf = SeqNum -> Frame
MaxData forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf

decodeMaxStreamData :: ReadBuffer -> IO Frame
decodeMaxStreamData :: ReadBuffer -> IO Frame
decodeMaxStreamData ReadBuffer
rbuf = do
    SeqNum
sID <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    SeqNum
maxstrdata <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ SeqNum -> SeqNum -> Frame
MaxStreamData SeqNum
sID SeqNum
maxstrdata

decodeMaxStreams :: ReadBuffer -> Direction -> IO Frame
decodeMaxStreams :: ReadBuffer -> Direction -> IO Frame
decodeMaxStreams ReadBuffer
rbuf Direction
dir = Direction -> SeqNum -> Frame
MaxStreams Direction
dir forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf

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

decodeDataBlocked :: ReadBuffer -> IO Frame
decodeDataBlocked :: ReadBuffer -> IO Frame
decodeDataBlocked ReadBuffer
rbuf = SeqNum -> Frame
DataBlocked forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf

decodeStreamDataBlocked :: ReadBuffer -> IO Frame
decodeStreamDataBlocked :: ReadBuffer -> IO Frame
decodeStreamDataBlocked ReadBuffer
rbuf = do
    SeqNum
sID <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    SeqNum
msd <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ SeqNum -> SeqNum -> Frame
StreamDataBlocked SeqNum
sID SeqNum
msd

decodeStreamsBlocked :: ReadBuffer -> Direction -> IO Frame
decodeStreamsBlocked :: ReadBuffer -> Direction -> IO Frame
decodeStreamsBlocked ReadBuffer
rbuf Direction
dir = Direction -> SeqNum -> Frame
StreamsBlocked Direction
dir forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf

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

decodeConnectionClose :: ReadBuffer -> IO Frame
decodeConnectionClose :: ReadBuffer -> IO Frame
decodeConnectionClose ReadBuffer
rbuf = do
    TransportError
err    <- SeqNum -> TransportError
TransportError forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    SeqNum
ftyp   <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    SeqNum
len    <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    ShortByteString
reason <- forall a. Readable a => a -> SeqNum -> IO ShortByteString
extractShortByteString ReadBuffer
rbuf SeqNum
len
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ TransportError -> SeqNum -> ShortByteString -> Frame
ConnectionClose TransportError
err SeqNum
ftyp ShortByteString
reason

decodeConnectionCloseApp  :: ReadBuffer -> IO Frame
decodeConnectionCloseApp :: ReadBuffer -> IO Frame
decodeConnectionCloseApp ReadBuffer
rbuf = do
    ApplicationProtocolError
err    <- SeqNum -> ApplicationProtocolError
ApplicationProtocolError forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    SeqNum
len    <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    ShortByteString
reason <- forall a. Readable a => a -> SeqNum -> IO ShortByteString
extractShortByteString ReadBuffer
rbuf SeqNum
len
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ApplicationProtocolError -> ShortByteString -> Frame
ConnectionCloseApp ApplicationProtocolError
err ShortByteString
reason

decodeNewConnectionID :: ReadBuffer -> IO Frame
decodeNewConnectionID :: ReadBuffer -> IO Frame
decodeNewConnectionID ReadBuffer
rbuf = do
    SeqNum
seqNum <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    SeqNum
rpt <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    SeqNum
cidLen <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Readable a => a -> IO Word8
read8 ReadBuffer
rbuf
    CID
cID <- ShortByteString -> CID
makeCID forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Readable a => a -> SeqNum -> IO ShortByteString
extractShortByteString ReadBuffer
rbuf SeqNum
cidLen
    StatelessResetToken
token <- ShortByteString -> StatelessResetToken
StatelessResetToken forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Readable a => a -> SeqNum -> IO ShortByteString
extractShortByteString ReadBuffer
rbuf SeqNum
16
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ CIDInfo -> SeqNum -> Frame
NewConnectionID (SeqNum -> CID -> StatelessResetToken -> CIDInfo
CIDInfo SeqNum
seqNum CID
cID StatelessResetToken
token) SeqNum
rpt

decodeRetireConnectionID :: ReadBuffer -> IO Frame
decodeRetireConnectionID :: ReadBuffer -> IO Frame
decodeRetireConnectionID ReadBuffer
rbuf = do
    SeqNum
seqNum <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBuffer -> IO Int64
decodeInt' ReadBuffer
rbuf
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ SeqNum -> Frame
RetireConnectionID SeqNum
seqNum

decodePathChallenge :: ReadBuffer -> IO Frame
decodePathChallenge :: ReadBuffer -> IO Frame
decodePathChallenge ReadBuffer
rbuf =
    PathData -> Frame
PathChallenge forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> PathData
PathData forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Readable a => a -> SeqNum -> IO ShortByteString
extractShortByteString ReadBuffer
rbuf SeqNum
8

decodePathResponse :: ReadBuffer -> IO Frame
decodePathResponse :: ReadBuffer -> IO Frame
decodePathResponse ReadBuffer
rbuf =
    PathData -> Frame
PathResponse forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> PathData
PathData forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Readable a => a -> SeqNum -> IO ShortByteString
extractShortByteString ReadBuffer
rbuf SeqNum
8