{-# LANGUAGE BinaryLiterals #-}

module Network.QUIC.Packet.Header (
    isLong
  , isShort
  , protectFlags
  , unprotectFlags
  , encodeLongHeaderFlags
  , encodeShortHeaderFlags
  , decodeLongHeaderPacketType
  , encodePktNumLength
  , decodePktNumLength
  , versionNegotiationPacketType
  , retryPacketType
  ) where

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

{-# INLINE isLong #-}
isLong :: Word8 -> Bool
isLong :: Word8 -> Bool
isLong Word8
flags = forall a. Bits a => a -> Int -> Bool
testBit Word8
flags Int
7

{-# INLINE isShort #-}
isShort :: Flags Protected -> Bool
isShort :: Flags Protected -> Bool
isShort (Flags Word8
flags) = Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall a. Bits a => a -> Int -> Bool
testBit Word8
flags Int
7

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

unprotectFlags :: Flags Protected -> Word8 -> Flags Raw
unprotectFlags :: Flags Protected -> Word8 -> Flags Raw
unprotectFlags (Flags Word8
proFlags) Word8
mask1 = forall a. Word8 -> Flags a
Flags Word8
flags
  where
    mask :: Word8
mask = Word8
mask1 forall a. Bits a => a -> a -> a
.&. Word8 -> Word8
flagBits Word8
proFlags
    flags :: Word8
flags = Word8
proFlags forall a. Bits a => a -> a -> a
`xor` Word8
mask

protectFlags :: Flags Raw -> Word8 -> Flags Protected
protectFlags :: Flags Raw -> Word8 -> Flags Protected
protectFlags (Flags Word8
flags) Word8
mask1 = forall a. Word8 -> Flags a
Flags Word8
proFlags
  where
    mask :: Word8
mask = Word8
mask1 forall a. Bits a => a -> a -> a
.&. Word8 -> Word8
flagBits Word8
flags
    proFlags :: Word8
proFlags = Word8
flags forall a. Bits a => a -> a -> a
`xor` Word8
mask


{-# INLINE flagBits #-}
flagBits :: Word8 -> Word8
flagBits :: Word8 -> Word8
flagBits Word8
flags
  | Word8 -> Bool
isLong Word8
flags = Word8
0b00001111 -- long header
  | Bool
otherwise    = Word8
0b00011111 -- short header

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

randomizeQuicBit :: Word8 -> Bool -> IO Word8
randomizeQuicBit :: Word8 -> Bool -> IO Word8
randomizeQuicBit Word8
flags Bool
quicBit
  | Bool
quicBit = do
        Word8
r <- IO Word8
getRandomOneByte
        forall (m :: * -> *) a. Monad m => a -> m a
return ((Word8
flags forall a. Bits a => a -> a -> a
.&. Word8
0b10111111) forall a. Bits a => a -> a -> a
.|. (Word8
r forall a. Bits a => a -> a -> a
.&. Word8
0b01000000))
  | Bool
otherwise = forall (m :: * -> *) a. Monad m => a -> m a
return Word8
flags

{-# INLINE encodeShortHeaderFlags #-}
encodeShortHeaderFlags :: Flags Raw -> Flags Raw -> Bool -> Bool -> IO (Flags Raw)
encodeShortHeaderFlags :: Flags Raw -> Flags Raw -> Bool -> Bool -> IO (Flags Raw)
encodeShortHeaderFlags (Flags Word8
fg) (Flags Word8
pp) Bool
quicBit Bool
keyPhase =
    forall a. Word8 -> Flags a
Flags forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Word8 -> Bool -> IO Word8
randomizeQuicBit Word8
flags Bool
quicBit
  where
    flags :: Word8
flags =          Word8
0b01000000
         forall a. Bits a => a -> a -> a
.|. (Word8
fg forall a. Bits a => a -> a -> a
.&. Word8
0b00111100)
         forall a. Bits a => a -> a -> a
.|. (Word8
pp forall a. Bits a => a -> a -> a
.&. Word8
0b00000011)
         forall a. Bits a => a -> a -> a
.|. (if Bool
keyPhase then Word8
0b00000100 else Word8
0b00000000)

{-# INLINE encodeLongHeaderFlags #-}
encodeLongHeaderFlags :: Version -> LongHeaderPacketType -> Flags Raw -> Flags Raw -> Bool -> IO (Flags Raw)
encodeLongHeaderFlags :: Version
-> LongHeaderPacketType
-> Flags Raw
-> Flags Raw
-> Bool
-> IO (Flags Raw)
encodeLongHeaderFlags Version
ver LongHeaderPacketType
typ (Flags Word8
fg) (Flags Word8
pp) Bool
quicBit =
    forall a. Word8 -> Flags a
Flags forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Word8 -> Bool -> IO Word8
randomizeQuicBit Word8
flags Bool
quicBit
  where
    Flags Word8
tp = Version -> LongHeaderPacketType -> Flags Raw
longHeaderPacketType Version
ver LongHeaderPacketType
typ
    flags :: Word8
flags =   Word8
tp
         forall a. Bits a => a -> a -> a
.|. (Word8
fg forall a. Bits a => a -> a -> a
.&. Word8
0b00001100)
         forall a. Bits a => a -> a -> a
.|. (Word8
pp forall a. Bits a => a -> a -> a
.&. Word8
0b00000011)

{-# INLINE longHeaderPacketType #-}
longHeaderPacketType :: Version -> LongHeaderPacketType -> Flags Raw
longHeaderPacketType :: Version -> LongHeaderPacketType -> Flags Raw
longHeaderPacketType Version
Version2 LongHeaderPacketType
InitialPacketType   = forall a. Word8 -> Flags a
Flags Word8
0b11010000
longHeaderPacketType Version
Version2 LongHeaderPacketType
RTT0PacketType      = forall a. Word8 -> Flags a
Flags Word8
0b11100000
longHeaderPacketType Version
Version2 LongHeaderPacketType
HandshakePacketType = forall a. Word8 -> Flags a
Flags Word8
0b11110000
longHeaderPacketType Version
Version2 LongHeaderPacketType
RetryPacketType     = forall a. Word8 -> Flags a
Flags Word8
0b11000000
longHeaderPacketType Version
_        LongHeaderPacketType
InitialPacketType   = forall a. Word8 -> Flags a
Flags Word8
0b11000000
longHeaderPacketType Version
_        LongHeaderPacketType
RTT0PacketType      = forall a. Word8 -> Flags a
Flags Word8
0b11010000
longHeaderPacketType Version
_        LongHeaderPacketType
HandshakePacketType = forall a. Word8 -> Flags a
Flags Word8
0b11100000
longHeaderPacketType Version
_        LongHeaderPacketType
RetryPacketType     = forall a. Word8 -> Flags a
Flags Word8
0b11110000

retryPacketType :: Version -> IO (Flags Raw)
retryPacketType :: Version -> IO (Flags Raw)
retryPacketType Version
Version2 = do
    Word8
r <- IO Word8
getRandomOneByte
    let flags :: Word8
flags = Word8
0b11000000 forall a. Bits a => a -> a -> a
.|. (Word8
r forall a. Bits a => a -> a -> a
.&. Word8
0b00001111)
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. Word8 -> Flags a
Flags Word8
flags
retryPacketType Version
_ = do
    Word8
r <- IO Word8
getRandomOneByte
    let flags :: Word8
flags = Word8
0b11110000 forall a. Bits a => a -> a -> a
.|. (Word8
r forall a. Bits a => a -> a -> a
.&. Word8
0b00001111)
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. Word8 -> Flags a
Flags Word8
flags

versionNegotiationPacketType :: IO (Flags Raw)
versionNegotiationPacketType :: IO (Flags Raw)
versionNegotiationPacketType = do
    Word8
r <- IO Word8
getRandomOneByte
    let flags :: Word8
flags = Word8
0b10000000 forall a. Bits a => a -> a -> a
.|. (Word8
r forall a. Bits a => a -> a -> a
.&. Word8
0b01111111)
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. Word8 -> Flags a
Flags Word8
flags

{-# INLINE decodeLongHeaderPacketType #-}
decodeLongHeaderPacketType :: Version -> Flags Protected -> LongHeaderPacketType
decodeLongHeaderPacketType :: Version -> Flags Protected -> LongHeaderPacketType
decodeLongHeaderPacketType Version
Version2 (Flags Word8
flags) = case Word8
flags forall a. Bits a => a -> a -> a
.&. Word8
0b00110000 of
    Word8
0b00010000 -> LongHeaderPacketType
InitialPacketType
    Word8
0b00100000 -> LongHeaderPacketType
RTT0PacketType
    Word8
0b00110000 -> LongHeaderPacketType
HandshakePacketType
    Word8
_          -> LongHeaderPacketType
RetryPacketType
decodeLongHeaderPacketType Version
_ (Flags Word8
flags) = case Word8
flags forall a. Bits a => a -> a -> a
.&. Word8
0b00110000 of
    Word8
0b00000000 -> LongHeaderPacketType
InitialPacketType
    Word8
0b00010000 -> LongHeaderPacketType
RTT0PacketType
    Word8
0b00100000 -> LongHeaderPacketType
HandshakePacketType
    Word8
_          -> LongHeaderPacketType
RetryPacketType

{-# INLINE encodePktNumLength #-}
encodePktNumLength :: Int -> Flags Raw
encodePktNumLength :: Int -> Flags Raw
encodePktNumLength Int
epnLen = forall a. Word8 -> Flags a
Flags forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
epnLen forall a. Num a => a -> a -> a
- Int
1)

{-# INLINE decodePktNumLength #-}
decodePktNumLength :: Flags Raw -> Int
decodePktNumLength :: Flags Raw -> Int
decodePktNumLength (Flags Word8
flags) = forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8
flags forall a. Bits a => a -> a -> a
.&. Word8
0b11) forall a. Num a => a -> a -> a
+ Int
1