{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE OverloadedStrings #-}
module Network.HTTP2.Frame.Types (
  
    frameHeaderLength
  , maxPayloadLength
  
  , SettingsKeyId(..)
  , checkSettingsList
  , fromSettingsKeyId
  , SettingsValue
  , SettingsList
  , toSettingsKeyId
  
  , Settings(..)
  , defaultSettings
  , updateSettings
  
  , HTTP2Error(..)
  , errorCodeId
  
  , ErrorCode
  , ErrorCodeId(..)
  , fromErrorCodeId
  , toErrorCodeId
  
  , FrameType
  , minFrameType
  , maxFrameType
  , FrameTypeId(..)
  , fromFrameTypeId
  , toFrameTypeId
  
  , Frame(..)
  , FrameHeader(..)
  , FramePayload(..)
  , framePayloadToFrameTypeId
  , isPaddingDefined
  
  , StreamId
  , isControl
  , isClientInitiated
  , isServerInitiated
  , isRequest
  , isResponse
  , testExclusive
  , setExclusive
  , clearExclusive
  
  , FrameFlags
  , defaultFlags
  , testEndStream
  , testAck
  , testEndHeader
  , testPadded
  , testPriority
  , setEndStream
  , setAck
  , setEndHeader
  , setPadded
  , setPriority
  
  , WindowSize
  , defaultInitialWindowSize
  , maxWindowSize
  , isWindowOverflow
  
  , recommendedConcurrency
  
  , HeaderBlockFragment
  , Weight
  , defaultWeight
  , Priority(..)
  , defaultPriority
  , highestPriority
  , Padding
  ) where
import qualified Control.Exception as E
import Data.Typeable
import Imports
frameHeaderLength :: Int
 = Int
9
type ErrorCode = Word32
data ErrorCodeId = NoError
                 | ProtocolError
                 | InternalError
                 | FlowControlError
                 | SettingsTimeout
                 | StreamClosed
                 | FrameSizeError
                 | RefusedStream
                 | Cancel
                 | CompressionError
                 | ConnectError
                 | EnhanceYourCalm
                 | InadequateSecurity
                 | HTTP11Required
                   
                 | UnknownErrorCode ErrorCode
                 deriving (Int -> ErrorCodeId -> ShowS
[ErrorCodeId] -> ShowS
ErrorCodeId -> String
(Int -> ErrorCodeId -> ShowS)
-> (ErrorCodeId -> String)
-> ([ErrorCodeId] -> ShowS)
-> Show ErrorCodeId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ErrorCodeId] -> ShowS
$cshowList :: [ErrorCodeId] -> ShowS
show :: ErrorCodeId -> String
$cshow :: ErrorCodeId -> String
showsPrec :: Int -> ErrorCodeId -> ShowS
$cshowsPrec :: Int -> ErrorCodeId -> ShowS
Show, ReadPrec [ErrorCodeId]
ReadPrec ErrorCodeId
Int -> ReadS ErrorCodeId
ReadS [ErrorCodeId]
(Int -> ReadS ErrorCodeId)
-> ReadS [ErrorCodeId]
-> ReadPrec ErrorCodeId
-> ReadPrec [ErrorCodeId]
-> Read ErrorCodeId
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ErrorCodeId]
$creadListPrec :: ReadPrec [ErrorCodeId]
readPrec :: ReadPrec ErrorCodeId
$creadPrec :: ReadPrec ErrorCodeId
readList :: ReadS [ErrorCodeId]
$creadList :: ReadS [ErrorCodeId]
readsPrec :: Int -> ReadS ErrorCodeId
$creadsPrec :: Int -> ReadS ErrorCodeId
Read, ErrorCodeId -> ErrorCodeId -> Bool
(ErrorCodeId -> ErrorCodeId -> Bool)
-> (ErrorCodeId -> ErrorCodeId -> Bool) -> Eq ErrorCodeId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ErrorCodeId -> ErrorCodeId -> Bool
$c/= :: ErrorCodeId -> ErrorCodeId -> Bool
== :: ErrorCodeId -> ErrorCodeId -> Bool
$c== :: ErrorCodeId -> ErrorCodeId -> Bool
Eq, Eq ErrorCodeId
Eq ErrorCodeId
-> (ErrorCodeId -> ErrorCodeId -> Ordering)
-> (ErrorCodeId -> ErrorCodeId -> Bool)
-> (ErrorCodeId -> ErrorCodeId -> Bool)
-> (ErrorCodeId -> ErrorCodeId -> Bool)
-> (ErrorCodeId -> ErrorCodeId -> Bool)
-> (ErrorCodeId -> ErrorCodeId -> ErrorCodeId)
-> (ErrorCodeId -> ErrorCodeId -> ErrorCodeId)
-> Ord ErrorCodeId
ErrorCodeId -> ErrorCodeId -> Bool
ErrorCodeId -> ErrorCodeId -> Ordering
ErrorCodeId -> ErrorCodeId -> ErrorCodeId
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ErrorCodeId -> ErrorCodeId -> ErrorCodeId
$cmin :: ErrorCodeId -> ErrorCodeId -> ErrorCodeId
max :: ErrorCodeId -> ErrorCodeId -> ErrorCodeId
$cmax :: ErrorCodeId -> ErrorCodeId -> ErrorCodeId
>= :: ErrorCodeId -> ErrorCodeId -> Bool
$c>= :: ErrorCodeId -> ErrorCodeId -> Bool
> :: ErrorCodeId -> ErrorCodeId -> Bool
$c> :: ErrorCodeId -> ErrorCodeId -> Bool
<= :: ErrorCodeId -> ErrorCodeId -> Bool
$c<= :: ErrorCodeId -> ErrorCodeId -> Bool
< :: ErrorCodeId -> ErrorCodeId -> Bool
$c< :: ErrorCodeId -> ErrorCodeId -> Bool
compare :: ErrorCodeId -> ErrorCodeId -> Ordering
$ccompare :: ErrorCodeId -> ErrorCodeId -> Ordering
$cp1Ord :: Eq ErrorCodeId
Ord)
fromErrorCodeId :: ErrorCodeId -> ErrorCode
fromErrorCodeId :: ErrorCodeId -> ErrorCode
fromErrorCodeId ErrorCodeId
NoError              = ErrorCode
0x0
fromErrorCodeId ErrorCodeId
ProtocolError        = ErrorCode
0x1
fromErrorCodeId ErrorCodeId
InternalError        = ErrorCode
0x2
fromErrorCodeId ErrorCodeId
FlowControlError     = ErrorCode
0x3
fromErrorCodeId ErrorCodeId
SettingsTimeout      = ErrorCode
0x4
fromErrorCodeId ErrorCodeId
StreamClosed         = ErrorCode
0x5
fromErrorCodeId ErrorCodeId
FrameSizeError       = ErrorCode
0x6
fromErrorCodeId ErrorCodeId
RefusedStream        = ErrorCode
0x7
fromErrorCodeId ErrorCodeId
Cancel               = ErrorCode
0x8
fromErrorCodeId ErrorCodeId
CompressionError     = ErrorCode
0x9
fromErrorCodeId ErrorCodeId
ConnectError         = ErrorCode
0xa
fromErrorCodeId ErrorCodeId
EnhanceYourCalm      = ErrorCode
0xb
fromErrorCodeId ErrorCodeId
InadequateSecurity   = ErrorCode
0xc
fromErrorCodeId ErrorCodeId
HTTP11Required       = ErrorCode
0xd
fromErrorCodeId (UnknownErrorCode ErrorCode
w) = ErrorCode
w
toErrorCodeId :: ErrorCode -> ErrorCodeId
toErrorCodeId :: ErrorCode -> ErrorCodeId
toErrorCodeId ErrorCode
0x0 = ErrorCodeId
NoError
toErrorCodeId ErrorCode
0x1 = ErrorCodeId
ProtocolError
toErrorCodeId ErrorCode
0x2 = ErrorCodeId
InternalError
toErrorCodeId ErrorCode
0x3 = ErrorCodeId
FlowControlError
toErrorCodeId ErrorCode
0x4 = ErrorCodeId
SettingsTimeout
toErrorCodeId ErrorCode
0x5 = ErrorCodeId
StreamClosed
toErrorCodeId ErrorCode
0x6 = ErrorCodeId
FrameSizeError
toErrorCodeId ErrorCode
0x7 = ErrorCodeId
RefusedStream
toErrorCodeId ErrorCode
0x8 = ErrorCodeId
Cancel
toErrorCodeId ErrorCode
0x9 = ErrorCodeId
CompressionError
toErrorCodeId ErrorCode
0xa = ErrorCodeId
ConnectError
toErrorCodeId ErrorCode
0xb = ErrorCodeId
EnhanceYourCalm
toErrorCodeId ErrorCode
0xc = ErrorCodeId
InadequateSecurity
toErrorCodeId ErrorCode
0xd = ErrorCodeId
HTTP11Required
toErrorCodeId ErrorCode
w   = ErrorCode -> ErrorCodeId
UnknownErrorCode ErrorCode
w
data HTTP2Error = ConnectionError ErrorCodeId ByteString
                | StreamError ErrorCodeId StreamId
                deriving (HTTP2Error -> HTTP2Error -> Bool
(HTTP2Error -> HTTP2Error -> Bool)
-> (HTTP2Error -> HTTP2Error -> Bool) -> Eq HTTP2Error
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HTTP2Error -> HTTP2Error -> Bool
$c/= :: HTTP2Error -> HTTP2Error -> Bool
== :: HTTP2Error -> HTTP2Error -> Bool
$c== :: HTTP2Error -> HTTP2Error -> Bool
Eq, Int -> HTTP2Error -> ShowS
[HTTP2Error] -> ShowS
HTTP2Error -> String
(Int -> HTTP2Error -> ShowS)
-> (HTTP2Error -> String)
-> ([HTTP2Error] -> ShowS)
-> Show HTTP2Error
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HTTP2Error] -> ShowS
$cshowList :: [HTTP2Error] -> ShowS
show :: HTTP2Error -> String
$cshow :: HTTP2Error -> String
showsPrec :: Int -> HTTP2Error -> ShowS
$cshowsPrec :: Int -> HTTP2Error -> ShowS
Show, Typeable, ReadPrec [HTTP2Error]
ReadPrec HTTP2Error
Int -> ReadS HTTP2Error
ReadS [HTTP2Error]
(Int -> ReadS HTTP2Error)
-> ReadS [HTTP2Error]
-> ReadPrec HTTP2Error
-> ReadPrec [HTTP2Error]
-> Read HTTP2Error
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HTTP2Error]
$creadListPrec :: ReadPrec [HTTP2Error]
readPrec :: ReadPrec HTTP2Error
$creadPrec :: ReadPrec HTTP2Error
readList :: ReadS [HTTP2Error]
$creadList :: ReadS [HTTP2Error]
readsPrec :: Int -> ReadS HTTP2Error
$creadsPrec :: Int -> ReadS HTTP2Error
Read)
instance E.Exception HTTP2Error
errorCodeId :: HTTP2Error -> ErrorCodeId
errorCodeId :: HTTP2Error -> ErrorCodeId
errorCodeId (ConnectionError ErrorCodeId
err ByteString
_) = ErrorCodeId
err
errorCodeId (StreamError     ErrorCodeId
err Int
_) = ErrorCodeId
err
data SettingsKeyId = 
                   | SettingsEnablePush
                   | SettingsMaxConcurrentStreams
                   | SettingsInitialWindowSize
                   | SettingsMaxFrameSize 
                   | 
                   deriving (Int -> SettingsKeyId -> ShowS
[SettingsKeyId] -> ShowS
SettingsKeyId -> String
(Int -> SettingsKeyId -> ShowS)
-> (SettingsKeyId -> String)
-> ([SettingsKeyId] -> ShowS)
-> Show SettingsKeyId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SettingsKeyId] -> ShowS
$cshowList :: [SettingsKeyId] -> ShowS
show :: SettingsKeyId -> String
$cshow :: SettingsKeyId -> String
showsPrec :: Int -> SettingsKeyId -> ShowS
$cshowsPrec :: Int -> SettingsKeyId -> ShowS
Show, ReadPrec [SettingsKeyId]
ReadPrec SettingsKeyId
Int -> ReadS SettingsKeyId
ReadS [SettingsKeyId]
(Int -> ReadS SettingsKeyId)
-> ReadS [SettingsKeyId]
-> ReadPrec SettingsKeyId
-> ReadPrec [SettingsKeyId]
-> Read SettingsKeyId
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SettingsKeyId]
$creadListPrec :: ReadPrec [SettingsKeyId]
readPrec :: ReadPrec SettingsKeyId
$creadPrec :: ReadPrec SettingsKeyId
readList :: ReadS [SettingsKeyId]
$creadList :: ReadS [SettingsKeyId]
readsPrec :: Int -> ReadS SettingsKeyId
$creadsPrec :: Int -> ReadS SettingsKeyId
Read, SettingsKeyId -> SettingsKeyId -> Bool
(SettingsKeyId -> SettingsKeyId -> Bool)
-> (SettingsKeyId -> SettingsKeyId -> Bool) -> Eq SettingsKeyId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SettingsKeyId -> SettingsKeyId -> Bool
$c/= :: SettingsKeyId -> SettingsKeyId -> Bool
== :: SettingsKeyId -> SettingsKeyId -> Bool
$c== :: SettingsKeyId -> SettingsKeyId -> Bool
Eq, Eq SettingsKeyId
Eq SettingsKeyId
-> (SettingsKeyId -> SettingsKeyId -> Ordering)
-> (SettingsKeyId -> SettingsKeyId -> Bool)
-> (SettingsKeyId -> SettingsKeyId -> Bool)
-> (SettingsKeyId -> SettingsKeyId -> Bool)
-> (SettingsKeyId -> SettingsKeyId -> Bool)
-> (SettingsKeyId -> SettingsKeyId -> SettingsKeyId)
-> (SettingsKeyId -> SettingsKeyId -> SettingsKeyId)
-> Ord SettingsKeyId
SettingsKeyId -> SettingsKeyId -> Bool
SettingsKeyId -> SettingsKeyId -> Ordering
SettingsKeyId -> SettingsKeyId -> SettingsKeyId
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SettingsKeyId -> SettingsKeyId -> SettingsKeyId
$cmin :: SettingsKeyId -> SettingsKeyId -> SettingsKeyId
max :: SettingsKeyId -> SettingsKeyId -> SettingsKeyId
$cmax :: SettingsKeyId -> SettingsKeyId -> SettingsKeyId
>= :: SettingsKeyId -> SettingsKeyId -> Bool
$c>= :: SettingsKeyId -> SettingsKeyId -> Bool
> :: SettingsKeyId -> SettingsKeyId -> Bool
$c> :: SettingsKeyId -> SettingsKeyId -> Bool
<= :: SettingsKeyId -> SettingsKeyId -> Bool
$c<= :: SettingsKeyId -> SettingsKeyId -> Bool
< :: SettingsKeyId -> SettingsKeyId -> Bool
$c< :: SettingsKeyId -> SettingsKeyId -> Bool
compare :: SettingsKeyId -> SettingsKeyId -> Ordering
$ccompare :: SettingsKeyId -> SettingsKeyId -> Ordering
$cp1Ord :: Eq SettingsKeyId
Ord, Int -> SettingsKeyId
SettingsKeyId -> Int
SettingsKeyId -> [SettingsKeyId]
SettingsKeyId -> SettingsKeyId
SettingsKeyId -> SettingsKeyId -> [SettingsKeyId]
SettingsKeyId -> SettingsKeyId -> SettingsKeyId -> [SettingsKeyId]
(SettingsKeyId -> SettingsKeyId)
-> (SettingsKeyId -> SettingsKeyId)
-> (Int -> SettingsKeyId)
-> (SettingsKeyId -> Int)
-> (SettingsKeyId -> [SettingsKeyId])
-> (SettingsKeyId -> SettingsKeyId -> [SettingsKeyId])
-> (SettingsKeyId -> SettingsKeyId -> [SettingsKeyId])
-> (SettingsKeyId
    -> SettingsKeyId -> SettingsKeyId -> [SettingsKeyId])
-> Enum SettingsKeyId
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: SettingsKeyId -> SettingsKeyId -> SettingsKeyId -> [SettingsKeyId]
$cenumFromThenTo :: SettingsKeyId -> SettingsKeyId -> SettingsKeyId -> [SettingsKeyId]
enumFromTo :: SettingsKeyId -> SettingsKeyId -> [SettingsKeyId]
$cenumFromTo :: SettingsKeyId -> SettingsKeyId -> [SettingsKeyId]
enumFromThen :: SettingsKeyId -> SettingsKeyId -> [SettingsKeyId]
$cenumFromThen :: SettingsKeyId -> SettingsKeyId -> [SettingsKeyId]
enumFrom :: SettingsKeyId -> [SettingsKeyId]
$cenumFrom :: SettingsKeyId -> [SettingsKeyId]
fromEnum :: SettingsKeyId -> Int
$cfromEnum :: SettingsKeyId -> Int
toEnum :: Int -> SettingsKeyId
$ctoEnum :: Int -> SettingsKeyId
pred :: SettingsKeyId -> SettingsKeyId
$cpred :: SettingsKeyId -> SettingsKeyId
succ :: SettingsKeyId -> SettingsKeyId
$csucc :: SettingsKeyId -> SettingsKeyId
Enum, SettingsKeyId
SettingsKeyId -> SettingsKeyId -> Bounded SettingsKeyId
forall a. a -> a -> Bounded a
maxBound :: SettingsKeyId
$cmaxBound :: SettingsKeyId
minBound :: SettingsKeyId
$cminBound :: SettingsKeyId
Bounded)
type SettingsValue = Int 
fromSettingsKeyId :: SettingsKeyId -> Word16
fromSettingsKeyId :: SettingsKeyId -> Word16
fromSettingsKeyId SettingsKeyId
x = Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (SettingsKeyId -> Int
forall a. Enum a => a -> Int
fromEnum SettingsKeyId
x) Word16 -> Word16 -> Word16
forall a. Num a => a -> a -> a
+ Word16
1
minSettingsKeyId :: Word16
minSettingsKeyId :: Word16
minSettingsKeyId = Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word16) -> Int -> Word16
forall a b. (a -> b) -> a -> b
$ SettingsKeyId -> Int
forall a. Enum a => a -> Int
fromEnum (SettingsKeyId
forall a. Bounded a => a
minBound :: SettingsKeyId)
maxSettingsKeyId :: Word16
maxSettingsKeyId :: Word16
maxSettingsKeyId = Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word16) -> Int -> Word16
forall a b. (a -> b) -> a -> b
$ SettingsKeyId -> Int
forall a. Enum a => a -> Int
fromEnum (SettingsKeyId
forall a. Bounded a => a
maxBound :: SettingsKeyId)
toSettingsKeyId :: Word16 -> Maybe SettingsKeyId
toSettingsKeyId :: Word16 -> Maybe SettingsKeyId
toSettingsKeyId Word16
x
  | Word16
minSettingsKeyId Word16 -> Word16 -> Bool
forall a. Ord a => a -> a -> Bool
<= Word16
n Bool -> Bool -> Bool
&& Word16
n Word16 -> Word16 -> Bool
forall a. Ord a => a -> a -> Bool
<= Word16
maxSettingsKeyId = SettingsKeyId -> Maybe SettingsKeyId
forall a. a -> Maybe a
Just (SettingsKeyId -> Maybe SettingsKeyId)
-> (Word16 -> SettingsKeyId) -> Word16 -> Maybe SettingsKeyId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> SettingsKeyId
forall a. Enum a => Int -> a
toEnum (Int -> SettingsKeyId)
-> (Word16 -> Int) -> Word16 -> SettingsKeyId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Maybe SettingsKeyId) -> Word16 -> Maybe SettingsKeyId
forall a b. (a -> b) -> a -> b
$ Word16
n
  | Bool
otherwise                                = Maybe SettingsKeyId
forall a. Maybe a
Nothing
  where
    n :: Word16
n = Word16
x Word16 -> Word16 -> Word16
forall a. Num a => a -> a -> a
- Word16
1
type SettingsList = [(SettingsKeyId,SettingsValue)]
checkSettingsList :: SettingsList -> Maybe HTTP2Error
checkSettingsList :: SettingsList -> Maybe HTTP2Error
checkSettingsList SettingsList
settings = case ((SettingsKeyId, Int) -> Maybe HTTP2Error)
-> SettingsList -> [HTTP2Error]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (SettingsKeyId, Int) -> Maybe HTTP2Error
checkSettingsValue SettingsList
settings of
    []    -> Maybe HTTP2Error
forall a. Maybe a
Nothing
    (HTTP2Error
x:[HTTP2Error]
_) -> HTTP2Error -> Maybe HTTP2Error
forall a. a -> Maybe a
Just HTTP2Error
x
checkSettingsValue :: (SettingsKeyId,SettingsValue) -> Maybe HTTP2Error
checkSettingsValue :: (SettingsKeyId, Int) -> Maybe HTTP2Error
checkSettingsValue (SettingsKeyId
SettingsEnablePush,Int
v)
  | Int
v Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0 Bool -> Bool -> Bool
&& Int
v Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
1 = HTTP2Error -> Maybe HTTP2Error
forall a. a -> Maybe a
Just (HTTP2Error -> Maybe HTTP2Error) -> HTTP2Error -> Maybe HTTP2Error
forall a b. (a -> b) -> a -> b
$ ErrorCodeId -> ByteString -> HTTP2Error
ConnectionError ErrorCodeId
ProtocolError ByteString
"enable push must be 0 or 1"
checkSettingsValue (SettingsKeyId
SettingsInitialWindowSize,Int
v)
  | Int
v Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
2147483647   = HTTP2Error -> Maybe HTTP2Error
forall a. a -> Maybe a
Just (HTTP2Error -> Maybe HTTP2Error) -> HTTP2Error -> Maybe HTTP2Error
forall a b. (a -> b) -> a -> b
$ ErrorCodeId -> ByteString -> HTTP2Error
ConnectionError ErrorCodeId
FlowControlError ByteString
"Window size must be less than or equal to 65535"
checkSettingsValue (SettingsKeyId
SettingsMaxFrameSize,Int
v)
  | Int
v Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
16384 Bool -> Bool -> Bool
|| Int
v Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
16777215 = HTTP2Error -> Maybe HTTP2Error
forall a. a -> Maybe a
Just (HTTP2Error -> Maybe HTTP2Error) -> HTTP2Error -> Maybe HTTP2Error
forall a b. (a -> b) -> a -> b
$ ErrorCodeId -> ByteString -> HTTP2Error
ConnectionError ErrorCodeId
ProtocolError ByteString
"Max frame size must be in between 16384 and 16777215"
checkSettingsValue (SettingsKeyId, Int)
_ = Maybe HTTP2Error
forall a. Maybe a
Nothing
data Settings = Settings {
     :: Int
  , Settings -> Bool
enablePush :: Bool
  , Settings -> Maybe Int
maxConcurrentStreams :: Maybe Int
  , Settings -> Int
initialWindowSize :: WindowSize
  , Settings -> Int
maxFrameSize :: Int
  ,  :: Maybe Int
  } deriving (Int -> Settings -> ShowS
[Settings] -> ShowS
Settings -> String
(Int -> Settings -> ShowS)
-> (Settings -> String) -> ([Settings] -> ShowS) -> Show Settings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Settings] -> ShowS
$cshowList :: [Settings] -> ShowS
show :: Settings -> String
$cshow :: Settings -> String
showsPrec :: Int -> Settings -> ShowS
$cshowsPrec :: Int -> Settings -> ShowS
Show)
defaultSettings :: Settings
defaultSettings :: Settings
defaultSettings = Settings :: Int -> Bool -> Maybe Int -> Int -> Int -> Maybe Int -> Settings
Settings {
    headerTableSize :: Int
headerTableSize = Int
4096
  , enablePush :: Bool
enablePush = Bool
True
  , maxConcurrentStreams :: Maybe Int
maxConcurrentStreams = Maybe Int
forall a. Maybe a
Nothing
  , initialWindowSize :: Int
initialWindowSize = Int
defaultInitialWindowSize
  , maxFrameSize :: Int
maxFrameSize = Int
16384
  , maxHeaderBlockSize :: Maybe Int
maxHeaderBlockSize = Maybe Int
forall a. Maybe a
Nothing
  }
updateSettings :: Settings -> SettingsList -> Settings
updateSettings :: Settings -> SettingsList -> Settings
updateSettings Settings
settings SettingsList
kvs = (Settings -> (SettingsKeyId, Int) -> Settings)
-> Settings -> SettingsList -> Settings
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Settings -> (SettingsKeyId, Int) -> Settings
update Settings
settings SettingsList
kvs
  where
    update :: Settings -> (SettingsKeyId, Int) -> Settings
update Settings
def (SettingsKeyId
SettingsHeaderTableSize,Int
x)      = Settings
def { headerTableSize :: Int
headerTableSize = Int
x }
    
    update Settings
def (SettingsKeyId
SettingsEnablePush,Int
x)           = Settings
def { enablePush :: Bool
enablePush = Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 }
    update Settings
def (SettingsKeyId
SettingsMaxConcurrentStreams,Int
x) = Settings
def { maxConcurrentStreams :: Maybe Int
maxConcurrentStreams = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
x }
    update Settings
def (SettingsKeyId
SettingsInitialWindowSize,Int
x)    = Settings
def { initialWindowSize :: Int
initialWindowSize = Int
x }
    update Settings
def (SettingsKeyId
SettingsMaxFrameSize,Int
x)         = Settings
def { maxFrameSize :: Int
maxFrameSize = Int
x }
    update Settings
def (SettingsKeyId
SettingsMaxHeaderBlockSize,Int
x)   = Settings
def { maxHeaderBlockSize :: Maybe Int
maxHeaderBlockSize = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
x }
type WindowSize = Int
defaultInitialWindowSize :: WindowSize
defaultInitialWindowSize :: Int
defaultInitialWindowSize = Int
65535
maxWindowSize :: WindowSize
maxWindowSize :: Int
maxWindowSize = Int
2147483647
isWindowOverflow :: WindowSize -> Bool
isWindowOverflow :: Int -> Bool
isWindowOverflow Int
w = Int -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Int
w Int
31
recommendedConcurrency :: Int
recommendedConcurrency :: Int
recommendedConcurrency = Int
100
type Weight = Int
defaultWeight :: Weight
defaultWeight :: Int
defaultWeight = Int
16
{-# DEPRECATED defaultWeight "Don't use this" #-}
data Priority = Priority {
    Priority -> Bool
exclusive :: Bool
  , Priority -> Int
streamDependency :: StreamId
  , Priority -> Int
weight :: Weight
  } deriving (Int -> Priority -> ShowS
[Priority] -> ShowS
Priority -> String
(Int -> Priority -> ShowS)
-> (Priority -> String) -> ([Priority] -> ShowS) -> Show Priority
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Priority] -> ShowS
$cshowList :: [Priority] -> ShowS
show :: Priority -> String
$cshow :: Priority -> String
showsPrec :: Int -> Priority -> ShowS
$cshowsPrec :: Int -> Priority -> ShowS
Show, ReadPrec [Priority]
ReadPrec Priority
Int -> ReadS Priority
ReadS [Priority]
(Int -> ReadS Priority)
-> ReadS [Priority]
-> ReadPrec Priority
-> ReadPrec [Priority]
-> Read Priority
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Priority]
$creadListPrec :: ReadPrec [Priority]
readPrec :: ReadPrec Priority
$creadPrec :: ReadPrec Priority
readList :: ReadS [Priority]
$creadList :: ReadS [Priority]
readsPrec :: Int -> ReadS Priority
$creadsPrec :: Int -> ReadS Priority
Read, Priority -> Priority -> Bool
(Priority -> Priority -> Bool)
-> (Priority -> Priority -> Bool) -> Eq Priority
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Priority -> Priority -> Bool
$c/= :: Priority -> Priority -> Bool
== :: Priority -> Priority -> Bool
$c== :: Priority -> Priority -> Bool
Eq)
defaultPriority :: Priority
defaultPriority :: Priority
defaultPriority = Bool -> Int -> Int -> Priority
Priority Bool
False Int
0 Int
defaultWeight
highestPriority :: Priority
highestPriority :: Priority
highestPriority = Bool -> Int -> Int -> Priority
Priority Bool
False Int
0 Int
256
type FrameType = Word8
minFrameType :: FrameType
minFrameType :: FrameType
minFrameType = FrameType
0
maxFrameType :: FrameType
maxFrameType :: FrameType
maxFrameType = FrameType
9
data FrameTypeId = FrameData
                 | 
                 | FramePriority
                 | FrameRSTStream
                 | FrameSettings
                 | FramePushPromise
                 | FramePing
                 | FrameGoAway
                 | FrameWindowUpdate
                 | FrameContinuation
                 | FrameUnknown FrameType
                 deriving (Int -> FrameTypeId -> ShowS
[FrameTypeId] -> ShowS
FrameTypeId -> String
(Int -> FrameTypeId -> ShowS)
-> (FrameTypeId -> String)
-> ([FrameTypeId] -> ShowS)
-> Show FrameTypeId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FrameTypeId] -> ShowS
$cshowList :: [FrameTypeId] -> ShowS
show :: FrameTypeId -> String
$cshow :: FrameTypeId -> String
showsPrec :: Int -> FrameTypeId -> ShowS
$cshowsPrec :: Int -> FrameTypeId -> ShowS
Show, FrameTypeId -> FrameTypeId -> Bool
(FrameTypeId -> FrameTypeId -> Bool)
-> (FrameTypeId -> FrameTypeId -> Bool) -> Eq FrameTypeId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FrameTypeId -> FrameTypeId -> Bool
$c/= :: FrameTypeId -> FrameTypeId -> Bool
== :: FrameTypeId -> FrameTypeId -> Bool
$c== :: FrameTypeId -> FrameTypeId -> Bool
Eq, Eq FrameTypeId
Eq FrameTypeId
-> (FrameTypeId -> FrameTypeId -> Ordering)
-> (FrameTypeId -> FrameTypeId -> Bool)
-> (FrameTypeId -> FrameTypeId -> Bool)
-> (FrameTypeId -> FrameTypeId -> Bool)
-> (FrameTypeId -> FrameTypeId -> Bool)
-> (FrameTypeId -> FrameTypeId -> FrameTypeId)
-> (FrameTypeId -> FrameTypeId -> FrameTypeId)
-> Ord FrameTypeId
FrameTypeId -> FrameTypeId -> Bool
FrameTypeId -> FrameTypeId -> Ordering
FrameTypeId -> FrameTypeId -> FrameTypeId
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FrameTypeId -> FrameTypeId -> FrameTypeId
$cmin :: FrameTypeId -> FrameTypeId -> FrameTypeId
max :: FrameTypeId -> FrameTypeId -> FrameTypeId
$cmax :: FrameTypeId -> FrameTypeId -> FrameTypeId
>= :: FrameTypeId -> FrameTypeId -> Bool
$c>= :: FrameTypeId -> FrameTypeId -> Bool
> :: FrameTypeId -> FrameTypeId -> Bool
$c> :: FrameTypeId -> FrameTypeId -> Bool
<= :: FrameTypeId -> FrameTypeId -> Bool
$c<= :: FrameTypeId -> FrameTypeId -> Bool
< :: FrameTypeId -> FrameTypeId -> Bool
$c< :: FrameTypeId -> FrameTypeId -> Bool
compare :: FrameTypeId -> FrameTypeId -> Ordering
$ccompare :: FrameTypeId -> FrameTypeId -> Ordering
$cp1Ord :: Eq FrameTypeId
Ord)
fromFrameTypeId :: FrameTypeId -> FrameType
fromFrameTypeId :: FrameTypeId -> FrameType
fromFrameTypeId FrameTypeId
FrameData         = FrameType
0
fromFrameTypeId FrameTypeId
FrameHeaders      = FrameType
1
fromFrameTypeId FrameTypeId
FramePriority     = FrameType
2
fromFrameTypeId FrameTypeId
FrameRSTStream    = FrameType
3
fromFrameTypeId FrameTypeId
FrameSettings     = FrameType
4
fromFrameTypeId FrameTypeId
FramePushPromise  = FrameType
5
fromFrameTypeId FrameTypeId
FramePing         = FrameType
6
fromFrameTypeId FrameTypeId
FrameGoAway       = FrameType
7
fromFrameTypeId FrameTypeId
FrameWindowUpdate = FrameType
8
fromFrameTypeId FrameTypeId
FrameContinuation = FrameType
9
fromFrameTypeId (FrameUnknown FrameType
x)  = FrameType
x
toFrameTypeId :: FrameType -> FrameTypeId
toFrameTypeId :: FrameType -> FrameTypeId
toFrameTypeId  FrameType
0 = FrameTypeId
FrameData
toFrameTypeId  FrameType
1 = FrameTypeId
FrameHeaders
toFrameTypeId  FrameType
2 = FrameTypeId
FramePriority
toFrameTypeId  FrameType
3 = FrameTypeId
FrameRSTStream
toFrameTypeId  FrameType
4 = FrameTypeId
FrameSettings
toFrameTypeId  FrameType
5 = FrameTypeId
FramePushPromise
toFrameTypeId  FrameType
6 = FrameTypeId
FramePing
toFrameTypeId  FrameType
7 = FrameTypeId
FrameGoAway
toFrameTypeId  FrameType
8 = FrameTypeId
FrameWindowUpdate
toFrameTypeId  FrameType
9 = FrameTypeId
FrameContinuation
toFrameTypeId  FrameType
x = FrameType -> FrameTypeId
FrameUnknown FrameType
x
maxPayloadLength :: Int
maxPayloadLength :: Int
maxPayloadLength = Int
2Int -> Int -> Int
forall a b. (Num a, Integral b) => a -> b -> a
^(Int
14::Int)
type FrameFlags = Word8
defaultFlags :: FrameFlags
defaultFlags :: FrameType
defaultFlags = FrameType
0
testEndStream :: FrameFlags -> Bool
testEndStream :: FrameType -> Bool
testEndStream FrameType
x = FrameType
x FrameType -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
`testBit` Int
0
testAck :: FrameFlags -> Bool
testAck :: FrameType -> Bool
testAck FrameType
x = FrameType
x FrameType -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
`testBit` Int
0 
testEndHeader :: FrameFlags -> Bool
 FrameType
x = FrameType
x FrameType -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
`testBit` Int
2
testPadded :: FrameFlags -> Bool
testPadded :: FrameType -> Bool
testPadded FrameType
x = FrameType
x FrameType -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
`testBit` Int
3
testPriority :: FrameFlags -> Bool
testPriority :: FrameType -> Bool
testPriority FrameType
x = FrameType
x FrameType -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
`testBit` Int
5
setEndStream :: FrameFlags -> FrameFlags
setEndStream :: FrameType -> FrameType
setEndStream FrameType
x = FrameType
x FrameType -> Int -> FrameType
forall a. Bits a => a -> Int -> a
`setBit` Int
0
setAck :: FrameFlags -> FrameFlags
setAck :: FrameType -> FrameType
setAck FrameType
x = FrameType
x FrameType -> Int -> FrameType
forall a. Bits a => a -> Int -> a
`setBit` Int
0 
setEndHeader :: FrameFlags -> FrameFlags
 FrameType
x = FrameType
x FrameType -> Int -> FrameType
forall a. Bits a => a -> Int -> a
`setBit` Int
2
setPadded :: FrameFlags -> FrameFlags
setPadded :: FrameType -> FrameType
setPadded FrameType
x = FrameType
x FrameType -> Int -> FrameType
forall a. Bits a => a -> Int -> a
`setBit` Int
3
setPriority :: FrameFlags -> FrameFlags
setPriority :: FrameType -> FrameType
setPriority FrameType
x = FrameType
x FrameType -> Int -> FrameType
forall a. Bits a => a -> Int -> a
`setBit` Int
5
type StreamId = Int
isControl :: StreamId -> Bool
isControl :: Int -> Bool
isControl Int
0 = Bool
True
isControl Int
_ = Bool
False
isClientInitiated :: StreamId -> Bool
isClientInitiated :: Int -> Bool
isClientInitiated = Int -> Bool
forall a. Integral a => a -> Bool
odd
isServerInitiated :: StreamId -> Bool
isServerInitiated :: Int -> Bool
isServerInitiated Int
0 = Bool
False
isServerInitiated Int
n = Int -> Bool
forall a. Integral a => a -> Bool
even Int
n
isRequest :: StreamId -> Bool
isRequest :: Int -> Bool
isRequest = Int -> Bool
forall a. Integral a => a -> Bool
odd
{-# DEPRECATED isRequest "Use isClientInitiated instead" #-}
isResponse :: StreamId -> Bool
isResponse :: Int -> Bool
isResponse Int
0 = Bool
False
isResponse Int
n = Int -> Bool
forall a. Integral a => a -> Bool
even Int
n
{-# DEPRECATED isResponse "Use isServerInitiated instead" #-}
testExclusive :: StreamId -> Bool
testExclusive :: Int -> Bool
testExclusive Int
n = Int
n Int -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
`testBit` Int
31
setExclusive :: StreamId -> StreamId
setExclusive :: Int -> Int
setExclusive Int
n = Int
n Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`setBit` Int
31
clearExclusive :: StreamId -> StreamId
clearExclusive :: Int -> Int
clearExclusive Int
n = Int
n Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`clearBit` Int
31
type  = ByteString
type Padding = ByteString
data Frame = Frame
    {   :: FrameHeader
    , Frame -> FramePayload
framePayload :: FramePayload
    } deriving (Int -> Frame -> ShowS
[Frame] -> ShowS
Frame -> String
(Int -> Frame -> ShowS)
-> (Frame -> String) -> ([Frame] -> ShowS) -> Show Frame
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Frame] -> ShowS
$cshowList :: [Frame] -> ShowS
show :: Frame -> String
$cshow :: Frame -> String
showsPrec :: Int -> Frame -> ShowS
$cshowsPrec :: Int -> Frame -> ShowS
Show, ReadPrec [Frame]
ReadPrec Frame
Int -> ReadS Frame
ReadS [Frame]
(Int -> ReadS Frame)
-> ReadS [Frame]
-> ReadPrec Frame
-> ReadPrec [Frame]
-> Read Frame
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Frame]
$creadListPrec :: ReadPrec [Frame]
readPrec :: ReadPrec Frame
$creadPrec :: ReadPrec Frame
readList :: ReadS [Frame]
$creadList :: ReadS [Frame]
readsPrec :: Int -> ReadS Frame
$creadsPrec :: Int -> ReadS Frame
Read, Frame -> Frame -> Bool
(Frame -> Frame -> Bool) -> (Frame -> Frame -> Bool) -> Eq Frame
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Frame -> Frame -> Bool
$c/= :: Frame -> Frame -> Bool
== :: Frame -> Frame -> Bool
$c== :: Frame -> Frame -> Bool
Eq)
data  = 
    { FrameHeader -> Int
payloadLength :: Int
    , FrameHeader -> FrameType
flags         :: FrameFlags
    , FrameHeader -> Int
streamId      :: StreamId
    } deriving (Int -> FrameHeader -> ShowS
[FrameHeader] -> ShowS
FrameHeader -> String
(Int -> FrameHeader -> ShowS)
-> (FrameHeader -> String)
-> ([FrameHeader] -> ShowS)
-> Show FrameHeader
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FrameHeader] -> ShowS
$cshowList :: [FrameHeader] -> ShowS
show :: FrameHeader -> String
$cshow :: FrameHeader -> String
showsPrec :: Int -> FrameHeader -> ShowS
$cshowsPrec :: Int -> FrameHeader -> ShowS
Show, ReadPrec [FrameHeader]
ReadPrec FrameHeader
Int -> ReadS FrameHeader
ReadS [FrameHeader]
(Int -> ReadS FrameHeader)
-> ReadS [FrameHeader]
-> ReadPrec FrameHeader
-> ReadPrec [FrameHeader]
-> Read FrameHeader
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FrameHeader]
$creadListPrec :: ReadPrec [FrameHeader]
readPrec :: ReadPrec FrameHeader
$creadPrec :: ReadPrec FrameHeader
readList :: ReadS [FrameHeader]
$creadList :: ReadS [FrameHeader]
readsPrec :: Int -> ReadS FrameHeader
$creadsPrec :: Int -> ReadS FrameHeader
Read, FrameHeader -> FrameHeader -> Bool
(FrameHeader -> FrameHeader -> Bool)
-> (FrameHeader -> FrameHeader -> Bool) -> Eq FrameHeader
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FrameHeader -> FrameHeader -> Bool
$c/= :: FrameHeader -> FrameHeader -> Bool
== :: FrameHeader -> FrameHeader -> Bool
$c== :: FrameHeader -> FrameHeader -> Bool
Eq)
data FramePayload =
    DataFrame ByteString
  |  (Maybe Priority) HeaderBlockFragment
  | PriorityFrame Priority
  | RSTStreamFrame ErrorCodeId
  | SettingsFrame SettingsList
  | PushPromiseFrame StreamId HeaderBlockFragment
  | PingFrame ByteString
  | GoAwayFrame StreamId ErrorCodeId ByteString
  | WindowUpdateFrame WindowSize
  | ContinuationFrame HeaderBlockFragment
  | UnknownFrame FrameType ByteString
  deriving (Int -> FramePayload -> ShowS
[FramePayload] -> ShowS
FramePayload -> String
(Int -> FramePayload -> ShowS)
-> (FramePayload -> String)
-> ([FramePayload] -> ShowS)
-> Show FramePayload
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FramePayload] -> ShowS
$cshowList :: [FramePayload] -> ShowS
show :: FramePayload -> String
$cshow :: FramePayload -> String
showsPrec :: Int -> FramePayload -> ShowS
$cshowsPrec :: Int -> FramePayload -> ShowS
Show, ReadPrec [FramePayload]
ReadPrec FramePayload
Int -> ReadS FramePayload
ReadS [FramePayload]
(Int -> ReadS FramePayload)
-> ReadS [FramePayload]
-> ReadPrec FramePayload
-> ReadPrec [FramePayload]
-> Read FramePayload
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FramePayload]
$creadListPrec :: ReadPrec [FramePayload]
readPrec :: ReadPrec FramePayload
$creadPrec :: ReadPrec FramePayload
readList :: ReadS [FramePayload]
$creadList :: ReadS [FramePayload]
readsPrec :: Int -> ReadS FramePayload
$creadsPrec :: Int -> ReadS FramePayload
Read, FramePayload -> FramePayload -> Bool
(FramePayload -> FramePayload -> Bool)
-> (FramePayload -> FramePayload -> Bool) -> Eq FramePayload
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FramePayload -> FramePayload -> Bool
$c/= :: FramePayload -> FramePayload -> Bool
== :: FramePayload -> FramePayload -> Bool
$c== :: FramePayload -> FramePayload -> Bool
Eq)
framePayloadToFrameTypeId :: FramePayload -> FrameTypeId
framePayloadToFrameTypeId :: FramePayload -> FrameTypeId
framePayloadToFrameTypeId DataFrame{}          = FrameTypeId
FrameData
framePayloadToFrameTypeId HeadersFrame{}       = FrameTypeId
FrameHeaders
framePayloadToFrameTypeId PriorityFrame{}      = FrameTypeId
FramePriority
framePayloadToFrameTypeId RSTStreamFrame{}     = FrameTypeId
FrameRSTStream
framePayloadToFrameTypeId SettingsFrame{}      = FrameTypeId
FrameSettings
framePayloadToFrameTypeId PushPromiseFrame{}   = FrameTypeId
FramePushPromise
framePayloadToFrameTypeId PingFrame{}          = FrameTypeId
FramePing
framePayloadToFrameTypeId GoAwayFrame{}        = FrameTypeId
FrameGoAway
framePayloadToFrameTypeId WindowUpdateFrame{}  = FrameTypeId
FrameWindowUpdate
framePayloadToFrameTypeId ContinuationFrame{}  = FrameTypeId
FrameContinuation
framePayloadToFrameTypeId (UnknownFrame FrameType
w8 ByteString
_)  = FrameType -> FrameTypeId
FrameUnknown FrameType
w8
isPaddingDefined :: FramePayload -> Bool
isPaddingDefined :: FramePayload -> Bool
isPaddingDefined DataFrame{}         = Bool
True
isPaddingDefined HeadersFrame{}      = Bool
True
isPaddingDefined PriorityFrame{}     = Bool
False
isPaddingDefined RSTStreamFrame{}    = Bool
False
isPaddingDefined SettingsFrame{}     = Bool
False
isPaddingDefined PushPromiseFrame{}  = Bool
True
isPaddingDefined PingFrame{}         = Bool
False
isPaddingDefined GoAwayFrame{}       = Bool
False
isPaddingDefined WindowUpdateFrame{} = Bool
False
isPaddingDefined ContinuationFrame{} = Bool
False
isPaddingDefined UnknownFrame{}      = Bool
False