Skip to content

Commit

Permalink
passing Config to newConfig
Browse files Browse the repository at this point in the history
  • Loading branch information
kazu-yamamoto committed Nov 17, 2023
1 parent 6aa842d commit 38e5bca
Show file tree
Hide file tree
Showing 8 changed files with 48 additions and 57 deletions.
6 changes: 1 addition & 5 deletions Network/HTTP2/Client/Run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -102,15 +102,11 @@ getResponse strm = do
setup :: ClientConfig -> Config -> IO (Context, Manager)
setup ClientConfig{..} conf@Config{..} = do
let clientInfo = newClientInfo scheme authority
myAlist = makeMySettingsList conf concurrentStreams windowSize
ctx <-
newContext
clientInfo
conf
cacheLimit
confBufferSize
confMySockAddr
confPeerSockAddr
myAlist
concurrentStreams
windowSize
mgr <- start confTimeoutManager
Expand Down
22 changes: 1 addition & 21 deletions Network/HTTP2/H2/Config.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
module Network.HTTP2.H2.Config where

import Data.ByteString (ByteString)
import Data.IORef
import Foreign.Marshal.Alloc (free, mallocBytes)
import Network.Socket
Expand All @@ -10,26 +9,7 @@ import qualified System.TimeManager as T
import Network.HPACK
import Network.HTTP2.H2.File
import Network.HTTP2.H2.ReadN

-- | HTTP/2 configuration.
data Config = Config
{ confWriteBuffer :: Buffer
-- ^ This is used only by frameSender.
-- This MUST be freed after frameSender is terminated.
, confBufferSize :: BufferSize
-- ^ The size of the write buffer.
-- We assume that the read buffer is the same size.
-- So, this value is announced via SETTINGS_MAX_FRAME_SIZE
-- to the peer.
, confSendAll :: ByteString -> IO ()
, confReadN :: Int -> IO ByteString
, confPositionReadMaker :: PositionReadMaker
, confTimeoutManager :: T.Manager
, confMySockAddr :: SockAddr
-- ^ This is copied into 'Aux', if exist, on server.
, confPeerSockAddr :: SockAddr
-- ^ This is copied into 'Aux', if exist, on server.
}
import Network.HTTP2.H2.Types

-- | Making simple configuration whose IO is not efficient.
-- A write buffer is allocated internally.
Expand Down
30 changes: 21 additions & 9 deletions Network/HTTP2/H2/Context.hs
Original file line number Diff line number Diff line change
Expand Up @@ -92,15 +92,12 @@ data Context = Context

newContext
:: RoleInfo
-> Config
-> Int
-> BufferSize
-> SockAddr
-> SockAddr
-> SettingsList
-> Int
-> WindowSize
-> IO Context
newContext rinfo cacheSiz siz mysa peersa settingAlist maxConc rxws =
newContext rinfo conf@Config{..} cacheSiz maxConc rxws =
Context rl rinfo settingAlist
<$> newIORef False
<*> newIORef Nothing
Expand Down Expand Up @@ -128,8 +125,8 @@ newContext rinfo cacheSiz siz mysa peersa settingAlist maxConc rxws =
<*> newRate
<*> newRate
<*> newRate
<*> return mysa
<*> return peersa
<*> return confMySockAddr
<*> return confPeerSockAddr
where
rl = case rinfo of
RIC{} -> Client
Expand All @@ -139,8 +136,23 @@ newContext rinfo cacheSiz siz mysa peersa settingAlist maxConc rxws =
| otherwise = 2
dlim = defaultPayloadLength + frameHeaderLength
buflim
| siz >= dlim = dlim
| otherwise = siz
| confBufferSize >= dlim = dlim
| otherwise = confBufferSize
settingAlist = makeMySettingsList conf maxConc rxws

makeMySettingsList :: Config -> Int -> WindowSize -> [(SettingsKey, Int)]
makeMySettingsList Config{..} maxConc winSiz = myInitialAlist
where
-- confBufferSize is the size of the write buffer.
-- But we assume that the size of the read buffer is the same size.
-- So, the size is announced to via SETTINGS_MAX_FRAME_SIZE.
len = confBufferSize - frameHeaderLength
payloadLen = max defaultPayloadLength len
myInitialAlist =
[ (SettingsMaxFrameSize, payloadLen)
, (SettingsMaxConcurrentStreams, maxConc)
, (SettingsInitialWindowSize, winSiz)
]

----------------------------------------------------------------

Expand Down
1 change: 0 additions & 1 deletion Network/HTTP2/H2/Receiver.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,6 @@ import Imports hiding (delete, insert)
import Network.HPACK
import Network.HPACK.Token
import Network.HTTP2.Frame
import Network.HTTP2.H2.Config
import Network.HTTP2.H2.Context
import Network.HTTP2.H2.EncodeFrame
import Network.HTTP2.H2.HPACK
Expand Down
1 change: 0 additions & 1 deletion Network/HTTP2/H2/Sender.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,6 @@ import UnliftIO.STM
import Imports
import Network.HPACK (TokenHeaderList, setLimitForEncoding, toHeaderTable)
import Network.HTTP2.Frame
import Network.HTTP2.H2.Config
import Network.HTTP2.H2.Context
import Network.HTTP2.H2.EncodeFrame
import Network.HTTP2.H2.File
Expand Down
15 changes: 0 additions & 15 deletions Network/HTTP2/H2/Settings.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,6 @@ import Data.IntMap.Strict (IntMap)

import Imports
import Network.HTTP2.Frame
import Network.HTTP2.H2.Config
import Network.HTTP2.H2.Context
import Network.HTTP2.H2.EncodeFrame
import Network.HTTP2.H2.StreamTable
Expand All @@ -24,20 +23,6 @@ properWindowSize = 1048575
properConcurrentStreams :: Int
properConcurrentStreams = 64

makeMySettingsList :: Config -> Int -> WindowSize -> [(SettingsKey, Int)]
makeMySettingsList Config{..} maxConc winSiz = myInitialAlist
where
-- confBufferSize is the size of the write buffer.
-- But we assume that the size of the read buffer is the same size.
-- So, the size is announced to via SETTINGS_MAX_FRAME_SIZE.
len = confBufferSize - frameHeaderLength
payloadLen = max defaultPayloadLength len
myInitialAlist =
[ (SettingsMaxFrameSize, payloadLen)
, (SettingsMaxConcurrentStreams, maxConc)
, (SettingsInitialWindowSize, winSiz)
]

----------------------------------------------------------------

pendingMySettings :: Context -> IO [ByteString]
Expand Down
24 changes: 24 additions & 0 deletions Network/HTTP2/H2/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,9 @@ import Data.IORef
import Data.Typeable
import Network.Control
import qualified Network.HTTP.Types as H
import Network.Socket hiding (Stream)
import System.IO.Unsafe
import qualified System.TimeManager as T
import UnliftIO.Concurrent
import UnliftIO.Exception (SomeException)
import UnliftIO.STM
Expand Down Expand Up @@ -370,3 +372,25 @@ checkSettingsValue (SettingsMaxFrameSize, v)
0
"Max frame size must be in between 16384 and 16777215"
checkSettingsValue _ = Nothing

----------------------------------------------------------------

-- | HTTP/2 configuration.
data Config = Config
{ confWriteBuffer :: Buffer
-- ^ This is used only by frameSender.
-- This MUST be freed after frameSender is terminated.
, confBufferSize :: BufferSize
-- ^ The size of the write buffer.
-- We assume that the read buffer is the same size.
-- So, this value is announced via SETTINGS_MAX_FRAME_SIZE
-- to the peer.
, confSendAll :: ByteString -> IO ()
, confReadN :: Int -> IO ByteString
, confPositionReadMaker :: PositionReadMaker
, confTimeoutManager :: T.Manager
, confMySockAddr :: SockAddr
-- ^ This is copied into 'Aux', if exist, on server.
, confPeerSockAddr :: SockAddr
-- ^ This is copied into 'Aux', if exist, on server.
}
6 changes: 1 addition & 5 deletions Network/HTTP2/Server/Run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -95,15 +95,11 @@ checkPreface conf@Config{..} = do
setup :: ServerConfig -> Config -> IO (Context, Manager)
setup ServerConfig{..} conf@Config{..} = do
serverInfo <- newServerInfo
let myAlist = makeMySettingsList conf concurrentStreams windowSize
ctx <-
newContext
serverInfo
conf
0
confBufferSize
confMySockAddr
confPeerSockAddr
myAlist
concurrentStreams
windowSize
-- Workers, worker manager and timer manager
Expand Down

0 comments on commit 38e5bca

Please sign in to comment.