http2-5.1.0: HTTP/2 library
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.HTTP2.Frame

Description

Synopsis

Frame

data Frame Source #

The data type for HTTP/2 frames.

Instances

Instances details
Read Frame Source # 
Instance details

Defined in Network.HTTP2.Frame.Types

Show Frame Source # 
Instance details

Defined in Network.HTTP2.Frame.Types

Methods

showsPrec :: Int -> Frame -> ShowS #

show :: Frame -> String #

showList :: [Frame] -> ShowS #

Eq Frame Source # 
Instance details

Defined in Network.HTTP2.Frame.Types

Methods

(==) :: Frame -> Frame -> Bool #

(/=) :: Frame -> Frame -> Bool #

data FrameHeader Source #

The data type for HTTP/2 frame headers.

type HeaderBlockFragment = ByteString Source #

The type for fragments of a header encoded with HPACK.

type Padding = ByteString Source #

The type for padding in payloads.

isPaddingDefined :: FramePayload -> Bool Source #

Checking if padding is defined in this frame type.

>>> isPaddingDefined $ DataFrame ""
True
>>> isPaddingDefined $ PingFrame ""
False

Encoding

encodeFrame :: EncodeInfo -> FramePayload -> ByteString Source #

Encoding an HTTP/2 frame to ByteString. This function is not efficient enough for high performace program because of the concatenation of ByteString.

>>> encodeFrame (encodeInfo id 1) (DataFrame "body")
"\NUL\NUL\EOT\NUL\NUL\NUL\NUL\NUL\SOHbody"

encodeFrameChunks :: EncodeInfo -> FramePayload -> [ByteString] Source #

Encoding an HTTP/2 frame to [ByteString]. This is suitable for sendMany.

encodeFrameHeader :: FrameType -> FrameHeader -> ByteString Source #

Encoding an HTTP/2 frame header. The frame header must be completed.

encodeFrameHeaderBuf :: FrameType -> FrameHeader -> Ptr Word8 -> IO () Source #

Writing an encoded HTTP/2 frame header to the buffer. The length of the buffer must be larger than or equal to 9 bytes.

encodeFramePayload :: EncodeInfo -> FramePayload -> (FrameHeader, [ByteString]) Source #

Encoding an HTTP/2 frame payload. This returns a complete frame header and chunks of payload.

data EncodeInfo Source #

Auxiliary information for frame encoding.

Constructors

EncodeInfo 

Fields

  • encodeFlags :: FrameFlags

    Flags to be set in a frame header

  • encodeStreamId :: StreamId

    Stream id to be set in a frame header

  • encodePadding :: Maybe Padding

    Padding if any. In the case where this value is set but the priority flag is not set, this value gets preference over the priority flag. So, if this value is set, the priority flag is also set.

encodeInfo Source #

Arguments

:: (FrameFlags -> FrameFlags) 
-> Int

stream identifier

-> EncodeInfo 

A smart builder of EncodeInfo.

>>> encodeInfo setAck 0
EncodeInfo {encodeFlags = 1, encodeStreamId = 0, encodePadding = Nothing}

Decoding

decodeFrame Source #

Arguments

:: ByteString

Input byte-stream

-> Either FrameDecodeError Frame

Decoded frame

Decoding an HTTP/2 frame to ByteString. The second argument must be include the entire of frame. So, this function is not useful for real applications but useful for testing.

decodeFrameHeader :: ByteString -> (FrameType, FrameHeader) Source #

Decoding an HTTP/2 frame header. Must supply 9 bytes.

checkFrameHeader :: (FrameType, FrameHeader) -> Either FrameDecodeError (FrameType, FrameHeader) Source #

Checking a frame header and reporting an error if any.

>>> checkFrameHeader (FrameData,(FrameHeader 100 0 0))
Left (FrameDecodeError ProtocolError 0 "cannot used in control stream")

Decoding payload

decodeFramePayload :: FrameType -> FramePayloadDecoder Source #

Decoding an HTTP/2 frame payload. This function is considered to return a frame payload decoder according to a frame type.

type FramePayloadDecoder = FrameHeader -> ByteString -> Either FrameDecodeError FramePayload Source #

The type for frame payload decoder.

decodeDataFrame :: FramePayloadDecoder Source #

Frame payload decoder for DATA frame.

decodeHeadersFrame :: FramePayloadDecoder Source #

Frame payload decoder for HEADERS frame.

decodePriorityFrame :: FramePayloadDecoder Source #

Frame payload decoder for PRIORITY frame.

decodeRSTStreamFrame :: FramePayloadDecoder Source #

Frame payload decoder for RST_STREAM frame.

decodeSettingsFrame :: FramePayloadDecoder Source #

Frame payload decoder for SETTINGS frame.

decodePushPromiseFrame :: FramePayloadDecoder Source #

Frame payload decoder for PUSH_PROMISE frame.

decodePingFrame :: FramePayloadDecoder Source #

Frame payload decoder for PING frame.

decodeGoAwayFrame :: FramePayloadDecoder Source #

Frame payload decoder for GOAWAY frame.

decodeWindowUpdateFrame :: FramePayloadDecoder Source #

Frame payload decoder for WINDOW_UPDATE frame.

decodeContinuationFrame :: FramePayloadDecoder Source #

Frame payload decoder for CONTINUATION frame.

Frame type

newtype FrameType Source #

The type for raw frame type.

Constructors

FrameType Word8 

Bundled Patterns

pattern FrameData :: FrameType 
pattern FrameHeaders :: FrameType 
pattern FramePriority :: FrameType 
pattern FrameRSTStream :: FrameType 
pattern FrameSettings :: FrameType 
pattern FramePushPromise :: FrameType 
pattern FramePing :: FrameType 
pattern FrameGoAway :: FrameType 
pattern FrameWindowUpdate :: FrameType 
pattern FrameContinuation :: FrameType 

fromFrameType :: FrameType -> Word8 Source #

Converting FrameType to Word8.

>>> fromFrameType FrameData
0
>>> fromFrameType FrameContinuation
9

framePayloadToFrameType :: FramePayload -> FrameType Source #

Getting FrameType from FramePayload.

>>> framePayloadToFrameType (DataFrame "body")
FrameData

Priority

data Priority Source #

Type for stream priority. Deprecated in RFC 9113 but provided for FrameHeaders.

Constructors

Priority 

Instances

Instances details
Read Priority Source # 
Instance details

Defined in Network.HTTP2.Frame.Types

Show Priority Source # 
Instance details

Defined in Network.HTTP2.Frame.Types

Eq Priority Source # 
Instance details

Defined in Network.HTTP2.Frame.Types

type Weight = Int Source #

The type for weight in priority. Its values are from 1 to 256. Deprecated in RFC 9113.

Stream identifier

type StreamId = Int Source #

The type for stream identifier

isControl :: StreamId -> Bool Source #

Checking if the stream identifier for control.

>>> isControl 0
True
>>> isControl 1
False

isClientInitiated :: StreamId -> Bool Source #

Checking if the stream identifier is from a client.

>>> isClientInitiated 0
False
>>> isClientInitiated 1
True

isServerInitiated :: StreamId -> Bool Source #

Checking if the stream identifier is from a server.

>>> isServerInitiated 0
False
>>> isServerInitiated 2
True

Stream identifier related

testExclusive :: StreamId -> Bool Source #

Checking if the exclusive flag is set.

setExclusive :: StreamId -> StreamId Source #

Setting the exclusive flag.

clearExclusive :: StreamId -> StreamId Source #

Clearing the exclusive flag.

Flags

type FrameFlags = Word8 Source #

The type for flags.

defaultFlags :: FrameFlags Source #

The initial value of flags. No flags are set.

>>> defaultFlags
0

testEndStream :: FrameFlags -> Bool Source #

Checking if the END_STREAM flag is set. >>> testEndStream 0x1 True

testAck :: FrameFlags -> Bool Source #

Checking if the ACK flag is set. >>> testAck 0x1 True

testEndHeader :: FrameFlags -> Bool Source #

Checking if the END_HEADERS flag is set.

>>> testEndHeader 0x4
True

testPadded :: FrameFlags -> Bool Source #

Checking if the PADDED flag is set.

>>> testPadded 0x8
True

testPriority :: FrameFlags -> Bool Source #

Checking if the PRIORITY flag is set.

>>> testPriority 0x20
True

setEndStream :: FrameFlags -> FrameFlags Source #

Setting the END_STREAM flag.

>>> setEndStream 0
1

setAck :: FrameFlags -> FrameFlags Source #

Setting the ACK flag.

>>> setAck 0
1

setEndHeader :: FrameFlags -> FrameFlags Source #

Setting the END_HEADERS flag.

>>> setEndHeader 0
4

setPadded :: FrameFlags -> FrameFlags Source #

Setting the PADDED flag.

>>> setPadded 0
8

setPriority :: FrameFlags -> FrameFlags Source #

Setting the PRIORITY flag.

>>> setPriority 0
32

SettingsList

type SettingsList = [(SettingsKey, SettingsValue)] Source #

Association list of SETTINGS.

type SettingsValue = Int Source #

The type for raw SETTINGS value.

Payload length

defaultPayloadLength :: Int Source #

The default payload length of HTTP/2 payload.

>>> defaultPayloadLength
16384

maxPayloadLength :: Int Source #

The maximum payload length of HTTP/2 payload.

>>> maxPayloadLength
16777215

Window

type WindowSize = Int #

Window size.

defaultWindowSize :: WindowSize Source #

The default initial window size.

>>> defaultWindowSize
65535

maxWindowSize :: WindowSize Source #

The maximum window size.

>>> maxWindowSize
2147483647

isWindowOverflow :: WindowSize -> Bool Source #

Checking if a window size exceeds the maximum window size.

>>> isWindowOverflow 10
False
>>> isWindowOverflow maxWindowSize
False
>>> isWindowOverflow (maxWindowSize + 1)
True

Error code

newtype ErrorCode Source #

The type for raw error code.

Constructors

ErrorCode Word32 

Bundled Patterns

pattern NoError :: ErrorCode

The type for error code. See https://www.rfc-editor.org/rfc/rfc9113#ErrorCodes.

pattern ProtocolError :: ErrorCode 
pattern InternalError :: ErrorCode 
pattern FlowControlError :: ErrorCode 
pattern SettingsTimeout :: ErrorCode 
pattern StreamClosed :: ErrorCode 
pattern FrameSizeError :: ErrorCode 
pattern RefusedStream :: ErrorCode 
pattern Cancel :: ErrorCode 
pattern CompressionError :: ErrorCode 
pattern ConnectError :: ErrorCode 
pattern EnhanceYourCalm :: ErrorCode 
pattern InadequateSecurity :: ErrorCode 
pattern HTTP11Required :: ErrorCode 

Predefined values

connectionPreface :: ByteString Source #

The preface of HTTP/2.

>>> connectionPreface
"PRI * HTTP/2.0\r\n\r\nSM\r\n\r\n"

connectionPrefaceLength :: Int Source #

Length of the preface.

>>> connectionPrefaceLength
24

frameHeaderLength :: Int Source #

The length of HTTP/2 frame header.

>>> frameHeaderLength
9

recommendedConcurrency :: Int Source #

Default concurrency.

>>> recommendedConcurrency
100

Deprecated