Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
HTTP/2 server library.
Example:
{-# LANGUAGE OverloadedStrings #-} module Main (main) where import qualified UnliftIO.Exception as E import Data.ByteString.Builder (byteString) import Network.HTTP.Types (ok200) import Network.Run.TCP (runTCPServer) -- network-run import Network.HTTP2.Server main :: IO () main = runTCPServer Nothing "80" runHTTP2Server where runHTTP2Server s = E.bracket (allocSimpleConfig s 4096) freeSimpleConfig (\config -> run defaultServerConfig config server) server _req _aux sendResponse = sendResponse response [] where response = responseBuilder ok200 header body header = [("Content-Type", "text/plain")] body = byteString "Hello, world!\n"
Synopsis
- run :: ServerConfig -> Config -> Server -> IO ()
- data ServerConfig
- defaultServerConfig :: ServerConfig
- numberOfWorkers :: ServerConfig -> Int
- connectionWindowSize :: ServerConfig -> WindowSize
- settings :: ServerConfig -> Settings
- data Settings
- defaultSettings :: Settings
- headerTableSize :: Settings -> Int
- enablePush :: Settings -> Bool
- maxConcurrentStreams :: Settings -> Maybe Int
- initialWindowSize :: Settings -> WindowSize
- maxFrameSize :: Settings -> Int
- maxHeaderListSize :: Settings -> Maybe Int
- data Config = Config {}
- allocSimpleConfig :: Socket -> BufferSize -> IO Config
- freeSimpleConfig :: Config -> IO ()
- module Network.HTTP.Semantics.Server
Runner
Server configuration
data ServerConfig Source #
Server configuration
Instances
Show ServerConfig Source # | |
Defined in Network.HTTP2.Server.Run showsPrec :: Int -> ServerConfig -> ShowS # show :: ServerConfig -> String # showList :: [ServerConfig] -> ShowS # | |
Eq ServerConfig Source # | |
Defined in Network.HTTP2.Server.Run (==) :: ServerConfig -> ServerConfig -> Bool # (/=) :: ServerConfig -> ServerConfig -> Bool # |
defaultServerConfig :: ServerConfig Source #
The default server config.
>>>
defaultServerConfig
ServerConfig {numberOfWorkers = 8, connectionWindowSize = 1048576, settings = Settings {headerTableSize = 4096, enablePush = True, maxConcurrentStreams = Just 64, initialWindowSize = 262144, maxFrameSize = 16384, maxHeaderListSize = Nothing, pingRateLimit = 10}}
numberOfWorkers :: ServerConfig -> Int Source #
The number of workers
connectionWindowSize :: ServerConfig -> WindowSize Source #
The window size of incoming streams
settings :: ServerConfig -> Settings Source #
Settings
HTTP/2 setting
HTTP/2 settings. See https://datatracker.ietf.org/doc/html/rfc9113#name-defined-settings.
Instances
defaultSettings :: Settings Source #
The default settings.
>>>
defaultSettings
Settings {headerTableSize = 4096, enablePush = True, maxConcurrentStreams = Just 64, initialWindowSize = 262144, maxFrameSize = 16384, maxHeaderListSize = Nothing, pingRateLimit = 10}
headerTableSize :: Settings -> Int Source #
SETTINGS_HEADER_TABLE_SIZE
enablePush :: Settings -> Bool Source #
SETTINGS_ENABLE_PUSH
initialWindowSize :: Settings -> WindowSize Source #
SETTINGS_INITIAL_WINDOW_SIZE
maxFrameSize :: Settings -> Int Source #
SETTINGS_MAX_FRAME_SIZE
Common configuration
HTTP/2 configuration.
Config | |
|
allocSimpleConfig :: Socket -> BufferSize -> IO Config Source #
Making simple configuration whose IO is not efficient. A write buffer is allocated internally.
freeSimpleConfig :: Config -> IO () Source #
Deallocating the resource of the simple configuration.