| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Network.HPACK
Description
HPACK(https://tools.ietf.org/html/rfc7541) encoding and decoding a header list.
Synopsis
- encodeHeader :: EncodeStrategy -> Size -> DynamicTable -> HeaderList -> IO ByteString
- decodeHeader :: DynamicTable -> ByteString -> IO HeaderList
- encodeTokenHeader :: Buffer -> BufferSize -> EncodeStrategy -> Bool -> DynamicTable -> TokenHeaderList -> IO (TokenHeaderList, Int)
- decodeTokenHeader :: DynamicTable -> ByteString -> IO HeaderTable
- 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 HeaderList = [Header]
- type Header = (HeaderName, HeaderValue)
- type HeaderName = ByteString
- type HeaderValue = ByteString
- type TokenHeaderList = [TokenHeader]
- type TokenHeader = (Token, HeaderValue)
- type ValueTable = Array Int (Maybe HeaderValue)
- type HeaderTable = (TokenHeaderList, ValueTable)
- getHeaderValue :: Token -> ValueTable -> Maybe HeaderValue
- toHeaderTable :: [(CI HeaderName, HeaderValue)] -> IO HeaderTable
- type Size = Int
- type Index = Int
- type Buffer = Ptr Word8
- type BufferSize = Int
- original :: CI s -> s
- foldedCase :: CI s -> s
- mk :: FoldCase s => s -> CI s
Encoding and decoding
Arguments
| :: EncodeStrategy | |
| -> Size | The size of a temporary buffer. | 
| -> DynamicTable | |
| -> HeaderList | |
| -> IO ByteString | An HPACK format | 
Converting HeaderList 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.
Arguments
| :: DynamicTable | |
| -> ByteString | An HPACK format | 
| -> IO HeaderList | 
Converting the HPACK format to HeaderList.
- Headers are decoded as is.
- DecodeErrorwould be thrown if the HPACK format is broken.
- BufferOverrunwill be thrown if the temporary buffer for Huffman decoding is too small.
Encoding and decoding with token
Arguments
| :: 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.
Arguments
| :: DynamicTable | |
| -> ByteString | An HPACK format | 
| -> IO HeaderTable | 
Converting the HPACK format to TokenHeaderList
   and ValueTable.
- Multiple values of Cookie: are concatenated.
- If a pseudo header appears multiple times,
     IllegalHeaderNameis thrown.
- If unknown pseudo headers appear,
     IllegalHeaderNameis thrown.
- If pseudo headers are found after normal headers,
     IllegalHeaderNameis thrown.
- If a header key contains capital letters,
     IllegalHeaderNameis thrown.
- DecodeErrorwould be thrown if the HPACK format is broken.
- BufferOverrunwill 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.
>>>defaultDynamicTableSize4096
newDynamicTableForEncoding Source #
Arguments
| :: Size | The dynamic table size | 
| -> IO DynamicTable | 
Creating DynamicTable for encoding.
newDynamicTableForDecoding Source #
Arguments
| :: Size | The dynamic table size | 
| -> Size | The size of temporary buffer for Huffman decoding | 
| -> IO DynamicTable | 
Creating DynamicTable for decoding.
withDynamicTableForEncoding Source #
Arguments
| :: Size | The dynamic table size | 
| -> (DynamicTable -> IO a) | |
| -> IO a | 
Creating DynamicTable for encoding,
   performing the action and
   clearing the DynamicTable.
withDynamicTableForDecoding Source #
Arguments
| :: 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
| Eq CompressionAlgo Source # | |
| Defined in Network.HPACK.Types Methods (==) :: CompressionAlgo -> CompressionAlgo -> Bool # (/=) :: CompressionAlgo -> CompressionAlgo -> Bool # | |
| Show CompressionAlgo Source # | |
| Defined in Network.HPACK.Types Methods showsPrec :: Int -> CompressionAlgo -> ShowS # show :: CompressionAlgo -> String # showList :: [CompressionAlgo] -> ShowS # | |
data EncodeStrategy Source #
Strategy for HPACK encoding.
Constructors
| EncodeStrategy | |
| Fields 
 | |
Instances
| Eq EncodeStrategy Source # | |
| Defined in Network.HPACK.Types Methods (==) :: EncodeStrategy -> EncodeStrategy -> Bool # (/=) :: EncodeStrategy -> EncodeStrategy -> Bool # | |
| Show EncodeStrategy Source # | |
| Defined in Network.HPACK.Types Methods showsPrec :: Int -> EncodeStrategy -> ShowS # show :: EncodeStrategy -> String # showList :: [EncodeStrategy] -> ShowS # | |
defaultEncodeStrategy :: EncodeStrategy Source #
Default EncodeStrategy.
>>>defaultEncodeStrategyEncodeStrategy {compressionAlgo = Linear, useHuffman = False}
Errors
data DecodeError Source #
Errors for decoder.
Constructors
| 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
| Eq DecodeError Source # | |
| Defined in Network.HPACK.Types | |
| Show DecodeError Source # | |
| Defined in Network.HPACK.Types Methods showsPrec :: Int -> DecodeError -> ShowS # show :: DecodeError -> String # showList :: [DecodeError] -> ShowS # | |
| Exception DecodeError Source # | |
| Defined in Network.HPACK.Types Methods toException :: DecodeError -> SomeException # fromException :: SomeException -> Maybe DecodeError # displayException :: DecodeError -> String # | |
data BufferOverrun #
Buffer overrun exception.
Constructors
| BufferOverrun | The buffer size is not enough | 
Instances
| Eq BufferOverrun | |
| Defined in Network.ByteOrder Methods (==) :: BufferOverrun -> BufferOverrun -> Bool # (/=) :: BufferOverrun -> BufferOverrun -> Bool # | |
| Show BufferOverrun | |
| Defined in Network.ByteOrder Methods showsPrec :: Int -> BufferOverrun -> ShowS # show :: BufferOverrun -> String # showList :: [BufferOverrun] -> ShowS # | |
| Exception BufferOverrun | |
| Defined in Network.ByteOrder Methods toException :: BufferOverrun -> SomeException # fromException :: SomeException -> Maybe BufferOverrun # displayException :: BufferOverrun -> String # | |
Headers
type HeaderList = [Header] Source #
Header list.
type Header = (HeaderName, HeaderValue) Source #
Header.
type HeaderName = ByteString Source #
Header name.
type HeaderValue = ByteString Source #
Header value.
type TokenHeaderList = [TokenHeader] Source #
TokenBased header list.
type TokenHeader = (Token, HeaderValue) Source #
TokenBased header.
Value table
type ValueTable = Array Int (Maybe HeaderValue) Source #
An array to get HeaderValue quickly.
   getHeaderValue should be used.
   Internally, the key is Token ix.
type HeaderTable = (TokenHeaderList, ValueTable) Source #
A pair of token list and value table.
getHeaderValue :: Token -> ValueTable -> Maybe HeaderValue Source #
Accessing HeaderValue with Token.
toHeaderTable :: [(CI HeaderName, HeaderValue)] -> IO HeaderTable Source #
Converting a header list of the http-types style to
   TokenHeaderList and ValueTable.
Basic types
type BufferSize = Int #
Size of a buffer.
Re-exports
foldedCase :: CI s -> s #
Retrieve the case folded string-like value.
   (Also see foldCase).