Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Thread-safe QPACK encoder/decoder.
Synopsis
- data QEncoderConfig = QEncoderConfig {}
- defaultQEncoderConfig :: QEncoderConfig
- type QEncoder = TokenHeaderList -> IO (EncodedFieldSection, EncodedEncoderInstruction)
- newQEncoder :: QEncoderConfig -> IO (QEncoder, DecoderInstructionHandler)
- data QDecoderConfig = QDecoderConfig {}
- defaultQDecoderConfig :: QDecoderConfig
- type QDecoder = EncodedFieldSection -> IO TokenHeaderTable
- newQDecoder :: QDecoderConfig -> IO (QDecoder, EncoderInstructionHandler)
- type QDecoderS = EncodedFieldSection -> IO [Header]
- newQDecoderS :: QDecoderConfig -> Bool -> IO (QDecoderS, EncoderInstructionHandlerS)
- type EncodedEncoderInstruction = ByteString
- type EncoderInstructionHandler = (Int -> IO EncodedEncoderInstruction) -> IO ()
- type EncoderInstructionHandlerS = EncodedEncoderInstruction -> IO ()
- type EncodedDecoderInstruction = ByteString
- type DecoderInstructionHandler = (Int -> IO EncodedDecoderInstruction) -> IO ()
- type InstructionHandler = (Int -> IO ByteString) -> IO ()
- type Size = Int
- data EncodeStrategy = EncodeStrategy {}
- data CompressionAlgo
- type TokenHeaderTable = (TokenHeaderList, ValueTable)
- type TokenHeaderList = [TokenHeader]
- type ValueTable = Array Int (Maybe FieldValue)
- type Header = (HeaderName, ByteString)
- getFieldValue :: Token -> ValueTable -> Maybe FieldValue
- toTokenHeaderTable :: [Header] -> IO TokenHeaderTable
- original :: CI s -> s
- foldedCase :: CI s -> s
- mk :: FoldCase s => s -> CI s
Encoder
data QEncoderConfig Source #
Configuration for QPACK encoder.
Instances
Show QEncoderConfig Source # | |
Defined in Network.QPACK showsPrec :: Int -> QEncoderConfig -> ShowS # show :: QEncoderConfig -> String # showList :: [QEncoderConfig] -> ShowS # |
defaultQEncoderConfig :: QEncoderConfig Source #
Default configuration for QPACK encoder.
>>>
defaultQEncoderConfig
QEncoderConfig {ecDynamicTableSize = 4096, ecHeaderBlockBufferSize = 4096, ecPrefixBufferSize = 128, ecInstructionBufferSize = 4096, encStrategy = EncodeStrategy {compressionAlgo = Static, useHuffman = True}}
type QEncoder = TokenHeaderList -> IO (EncodedFieldSection, EncodedEncoderInstruction) Source #
QPACK encoder.
newQEncoder :: QEncoderConfig -> IO (QEncoder, DecoderInstructionHandler) Source #
Creating a new QPACK encoder.
Decoder
data QDecoderConfig Source #
Configuration for QPACK decoder.
Instances
Show QDecoderConfig Source # | |
Defined in Network.QPACK showsPrec :: Int -> QDecoderConfig -> ShowS # show :: QDecoderConfig -> String # showList :: [QDecoderConfig] -> ShowS # |
defaultQDecoderConfig :: QDecoderConfig Source #
Default configuration for QPACK decoder.
>>>
defaultQDecoderConfig
QDecoderConfig {dcDynamicTableSize = 4096, dcHuffmanBufferSize = 4096}
type QDecoder = EncodedFieldSection -> IO TokenHeaderTable Source #
QPACK decoder.
newQDecoder :: QDecoderConfig -> IO (QDecoder, EncoderInstructionHandler) Source #
Creating a new QPACK decoder.
Decoder for debugging
newQDecoderS :: QDecoderConfig -> Bool -> IO (QDecoderS, EncoderInstructionHandlerS) Source #
Creating a new simple QPACK decoder.
Types
type EncodedEncoderInstruction = ByteString Source #
Encoded encoder instruction.
type EncoderInstructionHandler = (Int -> IO EncodedEncoderInstruction) -> IO () Source #
Encoder instruction handler.
type EncoderInstructionHandlerS = EncodedEncoderInstruction -> IO () Source #
Simple encoder instruction handler.
type EncodedDecoderInstruction = ByteString Source #
Encoded decoder instruction.
type DecoderInstructionHandler = (Int -> IO EncodedDecoderInstruction) -> IO () Source #
Decoder instruction handler.
type InstructionHandler = (Int -> IO ByteString) -> IO () Source #
A type to integrating handlers.
Strategy
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 # |
Re-exports
type TokenHeaderTable = (TokenHeaderList, ValueTable) #
A pair of token list and value table.
type TokenHeaderList = [TokenHeader] #
TokenBased header list.
type ValueTable = Array Int (Maybe FieldValue) #
An array to get FieldValue
quickly.
getHeaderValue
should be used.
Internally, the key is tokenIx
.
type Header = (HeaderName, ByteString) #
A full HTTP header field with the name and value separated.
E.g. "Content-Length: 28"
parsed into a Header
would turn into ("Content-Length", "28")
getFieldValue :: Token -> ValueTable -> Maybe FieldValue #
Accessing FieldValue
with Token
.
toTokenHeaderTable :: [Header] -> IO TokenHeaderTable #
Converting a header list of the http-types style to
TokenHeaderList
and ValueTable
.
foldedCase :: CI s -> s #
Retrieve the case folded string-like value.
(Also see foldCase
).