Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
HPACK(https://tools.ietf.org/html/rfc7541) encoding and decoding a header list.
Synopsis
- encodeHeader :: EncodeStrategy -> Size -> DynamicTable -> [Header] -> IO ByteString
- decodeHeader :: DynamicTable -> ByteString -> IO [Header]
- type Header = (HeaderName, ByteString)
- original :: CI s -> s
- foldedCase :: CI s -> s
- mk :: FoldCase s => s -> CI s
- encodeTokenHeader :: Buffer -> BufferSize -> EncodeStrategy -> Bool -> DynamicTable -> TokenHeaderList -> IO (TokenHeaderList, Int)
- decodeTokenHeader :: DynamicTable -> ByteString -> IO TokenHeaderTable
- data DynamicTable
- defaultDynamicTableSize :: Int
- newDynamicTableForEncoding :: Size -> IO DynamicTable
- newDynamicTableForDecoding :: Size -> Size -> IO DynamicTable
- withDynamicTableForEncoding :: Size -> (DynamicTable -> IO a) -> IO a
- withDynamicTableForDecoding :: Size -> Size -> (DynamicTable -> IO a) -> IO a
- setLimitForEncoding :: Size -> DynamicTable -> IO ()
- data CompressionAlgo
- data EncodeStrategy = EncodeStrategy {}
- defaultEncodeStrategy :: EncodeStrategy
- data DecodeError
- data BufferOverrun = BufferOverrun
- type FieldValue = ByteString
- type TokenHeader = (Token, FieldValue)
- type TokenHeaderList = [TokenHeader]
- toTokenHeaderTable :: [Header] -> IO TokenHeaderTable
- type ValueTable = Array Int (Maybe FieldValue)
- type TokenHeaderTable = (TokenHeaderList, ValueTable)
- getFieldValue :: Token -> ValueTable -> Maybe FieldValue
- getHeaderValue :: Token -> ValueTable -> Maybe FieldValue
- type Size = Int
- type Index = Int
- type Buffer = Ptr Word8
- type BufferSize = Int
Encoding and decoding
:: EncodeStrategy | |
-> Size | The size of a temporary buffer. |
-> DynamicTable | |
-> [Header] | |
-> IO ByteString | An HPACK format |
Converting '[Header]' to the HPACK format.
This function has overhead of allocating/freeing a temporary buffer.
BufferOverrun
will be thrown if the temporary buffer is too small.
:: DynamicTable | |
-> ByteString | An HPACK format |
-> IO [Header] |
Converting the HPACK format to '[Header]'.
- Headers are decoded as is.
DecodeError
would be thrown if the HPACK format is broken.BufferOverrun
will be thrown if the temporary buffer for Huffman decoding is too small.
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")
foldedCase :: CI s -> s #
Retrieve the case folded string-like value.
(Also see foldCase
).
Encoding and decoding with token
:: Buffer | |
-> BufferSize | |
-> EncodeStrategy | |
-> Bool | |
-> DynamicTable | |
-> TokenHeaderList | |
-> IO (TokenHeaderList, Int) | Leftover, filled length |
Converting TokenHeaderList
to the HPACK format directly in the buffer.
When calling this function for a new TokenHeaderList
,
4th argument must be True
.
The return value is a pair of leftover TokenHeaderList
and
how many bytes are filled in the buffer.
If the leftover is empty, the encoding is finished.
Otherwise, this function should be called with it again.
4th argument must be False
.
4th argument is relating to dynamic table size update.
If True
and the limit is set by setLimitForEncoding
,
dynamic table size update is generated at the beginning of
the HPACK format.
:: DynamicTable | |
-> ByteString | An HPACK format |
-> IO TokenHeaderTable |
Converting the HPACK format to TokenHeaderList
and ValueTable
.
- Multiple values of Cookie: are concatenated.
- If a pseudo header appears multiple times,
IllegalHeaderName
is thrown. - If unknown pseudo headers appear,
IllegalHeaderName
is thrown. - If pseudo headers are found after normal headers,
IllegalHeaderName
is thrown. - If a header key contains capital letters,
IllegalHeaderName
is thrown. DecodeError
would be thrown if the HPACK format is broken.BufferOverrun
will be thrown if the temporary buffer for Huffman decoding is too small.
DynamicTable
data DynamicTable Source #
Type for dynamic table.
defaultDynamicTableSize :: Int Source #
Default dynamic table size. The value is 4,096 bytes: an array has 128 entries.
>>>
defaultDynamicTableSize
4096
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.
withDynamicTableForEncoding Source #
:: Size | The dynamic table size |
-> (DynamicTable -> IO a) | |
-> IO a |
Creating DynamicTable
for encoding,
performing the action and
clearing the DynamicTable
.
withDynamicTableForDecoding Source #
:: Size | The dynamic table size |
-> Size | The size of temporary buffer for Huffman |
-> (DynamicTable -> IO a) | |
-> IO a |
Creating DynamicTable
for decoding,
performing the action and
clearing the DynamicTable
.
setLimitForEncoding :: Size -> DynamicTable -> IO () Source #
When SETTINGS_HEADER_TABLE_SIZE is received from a peer, its value should be set by this function.
Strategy for encoding
data CompressionAlgo Source #
Compression algorithms for HPACK encoding.
Instances
Show CompressionAlgo Source # | |
Defined in Network.HPACK.Types showsPrec :: Int -> CompressionAlgo -> ShowS # show :: CompressionAlgo -> String # showList :: [CompressionAlgo] -> ShowS # | |
Eq CompressionAlgo Source # | |
Defined in Network.HPACK.Types (==) :: CompressionAlgo -> CompressionAlgo -> Bool # (/=) :: CompressionAlgo -> CompressionAlgo -> Bool # |
data EncodeStrategy Source #
Strategy for HPACK encoding.
EncodeStrategy | |
|
Instances
Show EncodeStrategy Source # | |
Defined in Network.HPACK.Types showsPrec :: Int -> EncodeStrategy -> ShowS # show :: EncodeStrategy -> String # showList :: [EncodeStrategy] -> ShowS # | |
Eq EncodeStrategy Source # | |
Defined in Network.HPACK.Types (==) :: EncodeStrategy -> EncodeStrategy -> Bool # (/=) :: EncodeStrategy -> EncodeStrategy -> Bool # |
defaultEncodeStrategy :: EncodeStrategy Source #
Default EncodeStrategy
.
>>>
defaultEncodeStrategy
EncodeStrategy {compressionAlgo = Linear, useHuffman = False}
Errors
data DecodeError Source #
Errors for decoder.
IndexOverrun Index | Index is out of range |
EosInTheMiddle | Eos appears in the middle of huffman string |
IllegalEos | Non-eos appears in the end of huffman string |
TooLongEos | Eos of huffman string is more than 7 bits |
TooSmallTableSize | A peer set the dynamic table size less than 32 |
TooLargeTableSize | A peer tried to change the dynamic table size over the limit |
IllegalTableSizeUpdate | Table size update at the non-beginning |
HeaderBlockTruncated | |
IllegalHeaderName | |
TooLargeHeader |
Instances
Exception DecodeError Source # | |
Defined in Network.HPACK.Types | |
Show DecodeError Source # | |
Defined in Network.HPACK.Types showsPrec :: Int -> DecodeError -> ShowS # show :: DecodeError -> String # showList :: [DecodeError] -> ShowS # | |
Eq DecodeError Source # | |
Defined in Network.HPACK.Types (==) :: DecodeError -> DecodeError -> Bool # (/=) :: DecodeError -> DecodeError -> Bool # |
data BufferOverrun #
Buffer overrun exception.
BufferOverrun | The buffer size is not enough |
Instances
Exception BufferOverrun | |
Defined in Network.ByteOrder | |
Show BufferOverrun | |
Defined in Network.ByteOrder showsPrec :: Int -> BufferOverrun -> ShowS # show :: BufferOverrun -> String # showList :: [BufferOverrun] -> ShowS # | |
Eq BufferOverrun | |
Defined in Network.ByteOrder (==) :: BufferOverrun -> BufferOverrun -> Bool # (/=) :: BufferOverrun -> BufferOverrun -> Bool # |
Token header
type FieldValue = ByteString #
Field value.
type TokenHeader = (Token, FieldValue) #
TokenBased header.
type TokenHeaderList = [TokenHeader] #
TokenBased header list.
toTokenHeaderTable :: [Header] -> IO TokenHeaderTable Source #
Converting a header list of the http-types style to
TokenHeaderList
and ValueTable
.
Value table
type ValueTable = Array Int (Maybe FieldValue) #
An array to get FieldValue
quickly.
getHeaderValue
should be used.
Internally, the key is tokenIx
.
type TokenHeaderTable = (TokenHeaderList, ValueTable) #
A pair of token list and value table.
getFieldValue :: Token -> ValueTable -> Maybe FieldValue #
Accessing FieldValue
with Token
.
getHeaderValue :: Token -> ValueTable -> Maybe FieldValue #
Accessing FieldValue
with Token
.
Basic types
type BufferSize = Int #
Size of a buffer.