Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data ApplicationProtocolError where
- pattern QpackDecompressionFailed :: ApplicationProtocolError
- pattern QpackEncoderStreamError :: ApplicationProtocolError
- pattern QpackDecoderStreamError :: ApplicationProtocolError
- data DecodeError
- data EncoderInstructionError = EncoderInstructionError
- data DecoderInstructionError = DecoderInstructionError
- data DynamicTable
- newDynamicTableForEncoding :: Size -> IO DynamicTable
- newDynamicTableForDecoding :: Size -> Size -> IO DynamicTable
- getMaxNumOfEntries :: DynamicTable -> IO Int
- setBasePointToInsersionPoint :: DynamicTable -> IO ()
- getBasePoint :: DynamicTable -> IO BasePoint
- getInsertionPoint :: DynamicTable -> IO InsertionPoint
- getInsertionPointSTM :: DynamicTable -> STM InsertionPoint
- checkInsertionPoint :: DynamicTable -> InsertionPoint -> IO ()
- getLargestReference :: DynamicTable -> IO InsertionPoint
- updateLargestReference :: DynamicTable -> AbsoluteIndex -> IO ()
- insertEntryToEncoder :: Entry -> DynamicTable -> IO AbsoluteIndex
- insertEntryToDecoder :: Entry -> DynamicTable -> STM ()
- toIndexedEntry :: DynamicTable -> HIndex -> STM Entry
- data RevIndex
- data RevResult
- getRevIndex :: DynamicTable -> RevIndex
- lookupRevIndex :: Token -> FieldValue -> RevIndex -> IO RevResult
- getHuffmanDecoder :: DynamicTable -> HuffmanDecoder
- setDebugQPACK :: DynamicTable -> IO ()
- getDebugQPACK :: DynamicTable -> IO Bool
- qpackDebug :: DynamicTable -> IO () -> IO ()
- data HIndex
- data EncoderInstruction
- type InsIndex = Either AbsoluteIndex InsRelativeIndex
- encodeEncoderInstructions :: [EncoderInstruction] -> Bool -> IO ByteString
- decodeEncoderInstructions :: HuffmanDecoder -> ByteString -> IO ([EncoderInstruction], ByteString)
- decodeEncoderInstructions' :: ByteString -> IO ([EncoderInstruction], ByteString)
- encodeEI :: WriteBuffer -> Bool -> EncoderInstruction -> IO ()
- decodeEI :: HuffmanDecoder -> ReadBuffer -> IO EncoderInstruction
- data DecoderInstruction
- encodeDecoderInstructions :: [DecoderInstruction] -> IO ByteString
- decodeDecoderInstructions :: ByteString -> IO ([DecoderInstruction], ByteString)
- encodeDI :: WriteBuffer -> DecoderInstruction -> IO ()
- decodeDI :: ReadBuffer -> IO DecoderInstruction
- encodeHeader :: EncodeStrategy -> DynamicTable -> [Header] -> IO (EncodedFieldSection, EncodedEncoderInstruction)
- encodeTokenHeader :: WriteBuffer -> WriteBuffer -> EncodeStrategy -> DynamicTable -> TokenHeaderList -> IO TokenHeaderList
- type EncodedFieldSection = ByteString
- type EncodedEncoderInstruction = ByteString
- data EncodeStrategy = EncodeStrategy {}
- data CompressionAlgo
- encodePrefix :: WriteBuffer -> DynamicTable -> IO ()
- decodeTokenHeader :: DynamicTable -> ReadBuffer -> IO TokenHeaderTable
- decodeTokenHeaderS :: DynamicTable -> ReadBuffer -> IO [Header]
- encodePrefix :: WriteBuffer -> DynamicTable -> IO ()
- decodePrefix :: ReadBuffer -> DynamicTable -> IO (InsertionPoint, BasePoint)
- encodeRequiredInsertCount :: Int -> InsertionPoint -> Int
- decodeRequiredInsertCount :: Int -> InsertionPoint -> Int -> InsertionPoint
- encodeBase :: InsertionPoint -> BasePoint -> (Bool, Int)
- decodeBase :: InsertionPoint -> Bool -> Int -> BasePoint
- newtype AbsoluteIndex = AbsoluteIndex Int
- newtype InsRelativeIndex = InsRelativeIndex Int
- newtype HBRelativeIndex = HBRelativeIndex Int
- newtype PostBaseIndex = PostBaseIndex Int
- newtype InsertionPoint = InsertionPoint Int
- newtype BasePoint = BasePoint Int
- data HIndex
- toInsRelativeIndex :: AbsoluteIndex -> InsertionPoint -> InsRelativeIndex
- fromInsRelativeIndex :: InsRelativeIndex -> InsertionPoint -> AbsoluteIndex
- toHBRelativeIndex :: AbsoluteIndex -> BasePoint -> HBRelativeIndex
- fromHBRelativeIndex :: HBRelativeIndex -> BasePoint -> AbsoluteIndex
- toPostBaseIndex :: AbsoluteIndex -> BasePoint -> PostBaseIndex
- fromPostBaseIndex :: PostBaseIndex -> BasePoint -> AbsoluteIndex
- type Setter = Word8 -> Word8
- set1 :: Setter
- set01 :: Setter
- set10 :: Setter
- set11 :: Setter
- set001 :: Setter
- set0001 :: Setter
- set0100 :: Setter
- set0101 :: Setter
- set0010 :: Setter
- set00001 :: Setter
- set0 :: Setter
- set00 :: Setter
- set000 :: Setter
- set0000 :: Setter
Errors
data ApplicationProtocolError where #
Application protocol errors of QUIC.
pattern QpackDecompressionFailed :: ApplicationProtocolError | |
pattern QpackEncoderStreamError :: ApplicationProtocolError | |
pattern QpackDecoderStreamError :: ApplicationProtocolError |
Instances
Show ApplicationProtocolError | |
Defined in Network.QUIC.Types.Error showsPrec :: Int -> ApplicationProtocolError -> ShowS # show :: ApplicationProtocolError -> String # showList :: [ApplicationProtocolError] -> ShowS # | |
Eq ApplicationProtocolError | |
Defined in Network.QUIC.Types.Error |
data DecodeError Source #
Instances
Exception DecodeError Source # | |
Defined in Network.QPACK.Error | |
Show DecodeError Source # | |
Defined in Network.QPACK.Error showsPrec :: Int -> DecodeError -> ShowS # show :: DecodeError -> String # showList :: [DecodeError] -> ShowS # | |
Eq DecodeError Source # | |
Defined in Network.QPACK.Error (==) :: DecodeError -> DecodeError -> Bool # (/=) :: DecodeError -> DecodeError -> Bool # |
data EncoderInstructionError Source #
Instances
Exception EncoderInstructionError Source # | |
Show EncoderInstructionError Source # | |
Defined in Network.QPACK.Error showsPrec :: Int -> EncoderInstructionError -> ShowS # show :: EncoderInstructionError -> String # showList :: [EncoderInstructionError] -> ShowS # | |
Eq EncoderInstructionError Source # | |
Defined in Network.QPACK.Error |
data DecoderInstructionError Source #
Instances
Exception DecoderInstructionError Source # | |
Show DecoderInstructionError Source # | |
Defined in Network.QPACK.Error showsPrec :: Int -> DecoderInstructionError -> ShowS # show :: DecoderInstructionError -> String # showList :: [DecoderInstructionError] -> ShowS # | |
Eq DecoderInstructionError Source # | |
Defined in Network.QPACK.Error |
Dynamic table
data DynamicTable Source #
Dynamic table for QPACK.
newDynamicTableForEncoding Source #
:: Size | The dynamic table size |
-> IO DynamicTable |
Creating DynamicTable
for encoding.
newDynamicTableForDecoding Source #
:: Size | The dynamic table size |
-> Size | The size of temporary buffer for Huffman decoding |
-> IO DynamicTable |
Creating DynamicTable
for decoding.
Getter and setter
getMaxNumOfEntries :: DynamicTable -> IO Int Source #
setBasePointToInsersionPoint :: DynamicTable -> IO () Source #
getBasePoint :: DynamicTable -> IO BasePoint Source #
checkInsertionPoint :: DynamicTable -> InsertionPoint -> IO () Source #
updateLargestReference :: DynamicTable -> AbsoluteIndex -> IO () Source #
Entry
insertEntryToEncoder :: Entry -> DynamicTable -> IO AbsoluteIndex Source #
insertEntryToDecoder :: Entry -> DynamicTable -> STM () Source #
toIndexedEntry :: DynamicTable -> HIndex -> STM Entry Source #
Reverse index
getRevIndex :: DynamicTable -> RevIndex Source #
lookupRevIndex :: Token -> FieldValue -> RevIndex -> IO RevResult Source #
Misc
setDebugQPACK :: DynamicTable -> IO () Source #
getDebugQPACK :: DynamicTable -> IO Bool Source #
qpackDebug :: DynamicTable -> IO () -> IO () Source #
Encoder instructions
data EncoderInstruction Source #
SetDynamicTableCapacity Int | |
InsertWithNameReference InsIndex FieldValue | |
InsertWithoutNameReference Token FieldValue | |
Duplicate InsRelativeIndex |
Instances
Show EncoderInstruction Source # | |
Defined in Network.QPACK.Instruction showsPrec :: Int -> EncoderInstruction -> ShowS # show :: EncoderInstruction -> String # showList :: [EncoderInstruction] -> ShowS # | |
Eq EncoderInstruction Source # | |
Defined in Network.QPACK.Instruction (==) :: EncoderInstruction -> EncoderInstruction -> Bool # (/=) :: EncoderInstruction -> EncoderInstruction -> Bool # |
encodeEncoderInstructions :: [EncoderInstruction] -> Bool -> IO ByteString Source #
decodeEncoderInstructions :: HuffmanDecoder -> ByteString -> IO ([EncoderInstruction], ByteString) Source #
encodeEI :: WriteBuffer -> Bool -> EncoderInstruction -> IO () Source #
decodeEI :: HuffmanDecoder -> ReadBuffer -> IO EncoderInstruction Source #
Decoder instructions
data DecoderInstruction Source #
Instances
Show DecoderInstruction Source # | |
Defined in Network.QPACK.Instruction showsPrec :: Int -> DecoderInstruction -> ShowS # show :: DecoderInstruction -> String # showList :: [DecoderInstruction] -> ShowS # | |
Eq DecoderInstruction Source # | |
Defined in Network.QPACK.Instruction (==) :: DecoderInstruction -> DecoderInstruction -> Bool # (/=) :: DecoderInstruction -> DecoderInstruction -> Bool # |
encodeDI :: WriteBuffer -> DecoderInstruction -> IO () Source #
Encoder
encodeHeader :: EncodeStrategy -> DynamicTable -> [Header] -> IO (EncodedFieldSection, EncodedEncoderInstruction) Source #
Encoding headers with QPACK. Header block with prefix and instructions are returned. 2048, 32, and 2048 bytes-buffers are temporally allocated for header block, prefix and encoder instructions.
:: WriteBuffer | Workspace for the body of header block |
-> WriteBuffer | Workspace for encoder instructions |
-> EncodeStrategy | |
-> DynamicTable | |
-> TokenHeaderList | |
-> IO TokenHeaderList | Leftover |
Converting TokenHeaderList
to the QPACK format.
type EncodedFieldSection = ByteString Source #
Encoded field section including prefix.
type EncodedEncoderInstruction = ByteString Source #
Encoded encoder instruction.
data EncodeStrategy #
Strategy for HPACK encoding.
EncodeStrategy | |
|
Instances
Show EncodeStrategy | |
Defined in Network.HPACK.Types showsPrec :: Int -> EncodeStrategy -> ShowS # show :: EncodeStrategy -> String # showList :: [EncodeStrategy] -> ShowS # | |
Eq EncodeStrategy | |
Defined in Network.HPACK.Types (==) :: EncodeStrategy -> EncodeStrategy -> Bool # (/=) :: EncodeStrategy -> EncodeStrategy -> Bool # |
data CompressionAlgo #
Compression algorithms for HPACK encoding.
Instances
Show CompressionAlgo | |
Defined in Network.HPACK.Types showsPrec :: Int -> CompressionAlgo -> ShowS # show :: CompressionAlgo -> String # showList :: [CompressionAlgo] -> ShowS # | |
Eq CompressionAlgo | |
Defined in Network.HPACK.Types (==) :: CompressionAlgo -> CompressionAlgo -> Bool # (/=) :: CompressionAlgo -> CompressionAlgo -> Bool # |
encodePrefix :: WriteBuffer -> DynamicTable -> IO () Source #
Encoding the prefix part of header block.
This should be used after encodeTokenHeader
.
Decoder
decodeTokenHeaderS :: DynamicTable -> ReadBuffer -> IO [Header] Source #
Prefix
encodePrefix :: WriteBuffer -> DynamicTable -> IO () Source #
Encoding the prefix part of header block.
This should be used after encodeTokenHeader
.
decodePrefix :: ReadBuffer -> DynamicTable -> IO (InsertionPoint, BasePoint) Source #
Decoding the prefix part of header block.
encodeRequiredInsertCount :: Int -> InsertionPoint -> Int Source #
>>>
encodeRequiredInsertCount 3 9
4>>>
encodeRequiredInsertCount 128 1000
233
decodeRequiredInsertCount :: Int -> InsertionPoint -> Int -> InsertionPoint Source #
for decoder
>>>
decodeRequiredInsertCount 3 10 4
InsertionPoint 9>>>
decodeRequiredInsertCount 128 990 233
InsertionPoint 1000
encodeBase :: InsertionPoint -> BasePoint -> (Bool, Int) Source #
>>>
encodeBase 6 9
(False,3)>>>
encodeBase 9 6
(True,2)
decodeBase :: InsertionPoint -> Bool -> Int -> BasePoint Source #
>>>
decodeBase 6 False 3
BasePoint 9>>>
decodeBase 9 True 2
BasePoint 6
Types
newtype AbsoluteIndex Source #
Instances
newtype InsRelativeIndex Source #
Instances
newtype HBRelativeIndex Source #
Instances
newtype PostBaseIndex Source #
Instances
newtype InsertionPoint Source #
Instances
toInsRelativeIndex :: AbsoluteIndex -> InsertionPoint -> InsRelativeIndex Source #
>>>
toInsRelativeIndex 99 100
InsRelativeIndex 0>>>
toInsRelativeIndex 98 100
InsRelativeIndex 1>>>
toInsRelativeIndex 97 100
InsRelativeIndex 2>>>
toInsRelativeIndex 96 100
InsRelativeIndex 3
fromInsRelativeIndex :: InsRelativeIndex -> InsertionPoint -> AbsoluteIndex Source #
>>>
fromInsRelativeIndex 0 100
AbsoluteIndex 99>>>
fromInsRelativeIndex 1 100
AbsoluteIndex 98>>>
fromInsRelativeIndex 2 100
AbsoluteIndex 97>>>
fromInsRelativeIndex 3 100
AbsoluteIndex 96
toHBRelativeIndex :: AbsoluteIndex -> BasePoint -> HBRelativeIndex Source #
>>>
toHBRelativeIndex 96 98
HBRelativeIndex 1>>>
toHBRelativeIndex 97 98
HBRelativeIndex 0
fromHBRelativeIndex :: HBRelativeIndex -> BasePoint -> AbsoluteIndex Source #
>>>
fromHBRelativeIndex 1 98
AbsoluteIndex 96>>>
fromHBRelativeIndex 0 98
AbsoluteIndex 97
toPostBaseIndex :: AbsoluteIndex -> BasePoint -> PostBaseIndex Source #
>>>
toPostBaseIndex 98 98
PostBaseIndex 0>>>
toPostBaseIndex 99 98
PostBaseIndex 1
fromPostBaseIndex :: PostBaseIndex -> BasePoint -> AbsoluteIndex Source #
>>>
fromPostBaseIndex 0 98
AbsoluteIndex 98>>>
fromPostBaseIndex 1 98
AbsoluteIndex 99