{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
module Network.HTTP2.H2.Settings where
import Network.Control
import Imports
import Network.HTTP2.Frame
import Network.HTTP2.H2.EncodeFrame
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 (Settings -> Settings -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Settings -> Settings -> Bool
$c/= :: Settings -> Settings -> Bool
== :: Settings -> Settings -> Bool
$c== :: Settings -> Settings -> Bool
Eq, Int -> Settings -> ShowS
[Settings] -> ShowS
Settings -> String
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)
baseSettings :: Settings
baseSettings :: Settings
baseSettings =
Settings
{ headerTableSize :: Int
headerTableSize = Int
4096
, enablePush :: Bool
enablePush = Bool
True
, maxConcurrentStreams :: Maybe Int
maxConcurrentStreams = forall a. Maybe a
Nothing
, initialWindowSize :: Int
initialWindowSize = Int
defaultWindowSize
, maxFrameSize :: Int
maxFrameSize = Int
defaultPayloadLength
, maxHeaderListSize :: Maybe Int
maxHeaderListSize = forall a. Maybe a
Nothing
}
defaultSettings :: Settings
defaultSettings :: Settings
defaultSettings =
Settings
baseSettings
{ maxConcurrentStreams :: Maybe Int
maxConcurrentStreams = forall a. a -> Maybe a
Just Int
defaultMaxStreams
, initialWindowSize :: Int
initialWindowSize = Int
defaultMaxStreamData
}
fromSettingsList :: Settings -> SettingsList -> Settings
fromSettingsList :: Settings -> SettingsList -> Settings
fromSettingsList Settings
settings SettingsList
kvs = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Settings -> (SettingsKey, Int) -> Settings
update Settings
settings SettingsList
kvs
where
update :: Settings -> (SettingsKey, Int) -> Settings
update Settings
def (SettingsKey
SettingsHeaderTableSize,Int
x) = Settings
def { headerTableSize :: Int
headerTableSize = Int
x }
update Settings
def (SettingsKey
SettingsEnablePush,Int
x) = Settings
def { enablePush :: Bool
enablePush = Int
x forall a. Ord a => a -> a -> Bool
> Int
0 }
update Settings
def (SettingsKey
SettingsMaxConcurrentStreams,Int
x) = Settings
def { maxConcurrentStreams :: Maybe Int
maxConcurrentStreams = forall a. a -> Maybe a
Just Int
x }
update Settings
def (SettingsKey
SettingsInitialWindowSize,Int
x) = Settings
def { initialWindowSize :: Int
initialWindowSize = Int
x }
update Settings
def (SettingsKey
SettingsMaxFrameSize,Int
x) = Settings
def { maxFrameSize :: Int
maxFrameSize = Int
x }
update Settings
def (SettingsKey
SettingsMaxHeaderListSize,Int
x) = Settings
def { maxHeaderListSize :: Maybe Int
maxHeaderListSize = forall a. a -> Maybe a
Just Int
x }
update Settings
def (SettingsKey, Int)
_ = Settings
def
diff
:: Eq a
=> Settings
-> Settings
-> (Settings -> a)
-> SettingsKey
-> (a -> SettingsValue)
-> Maybe (SettingsKey, SettingsValue)
diff :: forall a.
Eq a =>
Settings
-> Settings
-> (Settings -> a)
-> SettingsKey
-> (a -> Int)
-> Maybe (SettingsKey, Int)
diff Settings
settings Settings
settings0 Settings -> a
label SettingsKey
key a -> Int
enc
| a
val forall a. Eq a => a -> a -> Bool
== a
val0 = forall a. Maybe a
Nothing
| Bool
otherwise = forall a. a -> Maybe a
Just (SettingsKey
key, a -> Int
enc a
val)
where
val :: a
val = Settings -> a
label Settings
settings
val0 :: a
val0 = Settings -> a
label Settings
settings0
toSettingsList :: Settings -> Settings -> SettingsList
toSettingsList :: Settings -> Settings -> SettingsList
toSettingsList Settings
s Settings
s0 =
forall a. [Maybe a] -> [a]
catMaybes
[ forall a.
Eq a =>
Settings
-> Settings
-> (Settings -> a)
-> SettingsKey
-> (a -> Int)
-> Maybe (SettingsKey, Int)
diff
Settings
s
Settings
s0
Settings -> Int
headerTableSize
SettingsKey
SettingsHeaderTableSize
forall a. a -> a
id
, forall a.
Eq a =>
Settings
-> Settings
-> (Settings -> a)
-> SettingsKey
-> (a -> Int)
-> Maybe (SettingsKey, Int)
diff
Settings
s
Settings
s0
Settings -> Bool
enablePush
SettingsKey
SettingsEnablePush
(forall a b. a -> b -> a
const Int
0)
, forall a.
Eq a =>
Settings
-> Settings
-> (Settings -> a)
-> SettingsKey
-> (a -> Int)
-> Maybe (SettingsKey, Int)
diff
Settings
s
Settings
s0
Settings -> Maybe Int
maxConcurrentStreams
SettingsKey
SettingsMaxConcurrentStreams
forall a. HasCallStack => Maybe a -> a
fromJust
, forall a.
Eq a =>
Settings
-> Settings
-> (Settings -> a)
-> SettingsKey
-> (a -> Int)
-> Maybe (SettingsKey, Int)
diff
Settings
s
Settings
s0
Settings -> Int
initialWindowSize
SettingsKey
SettingsInitialWindowSize
forall a. a -> a
id
, forall a.
Eq a =>
Settings
-> Settings
-> (Settings -> a)
-> SettingsKey
-> (a -> Int)
-> Maybe (SettingsKey, Int)
diff
Settings
s
Settings
s0
Settings -> Int
maxFrameSize
SettingsKey
SettingsMaxFrameSize
forall a. a -> a
id
, forall a.
Eq a =>
Settings
-> Settings
-> (Settings -> a)
-> SettingsKey
-> (a -> Int)
-> Maybe (SettingsKey, Int)
diff
Settings
s
Settings
s0
Settings -> Maybe Int
maxHeaderListSize
SettingsKey
SettingsMaxHeaderListSize
forall a. HasCallStack => Maybe a -> a
fromJust
]
makeNegotiationFrames :: Settings -> WindowSize -> [ByteString]
makeNegotiationFrames :: Settings -> Int -> [ByteString]
makeNegotiationFrames Settings
settings Int
connWindowSize = ByteString
frame1 forall a. a -> [a] -> [a]
: [ByteString]
frames
where
alist :: SettingsList
alist = Settings -> Settings -> SettingsList
toSettingsList Settings
settings Settings
baseSettings
frame1 :: ByteString
frame1 = (FrameFlags -> FrameFlags) -> SettingsList -> ByteString
settingsFrame forall a. a -> a
id SettingsList
alist
frames :: [ByteString]
frames =
if Int
connWindowSize forall a. Eq a => a -> a -> Bool
/= Int
defaultWindowSize
then [Int -> Int -> ByteString
windowUpdateFrame Int
0 (Int
connWindowSize forall a. Num a => a -> a -> a
- Int
defaultWindowSize)]
else []