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

Network.HTTP2.Server

Description

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

Runner

run :: ServerConfig -> Config -> Server -> IO () Source #

Running HTTP/2 server.

Server configuration

data ServerConfig Source #

Server configuration

Instances

Instances details
Show ServerConfig Source # 
Instance details

Defined in Network.HTTP2.Server.Run

Eq ServerConfig Source # 
Instance details

Defined in Network.HTTP2.Server.Run

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

HTTP/2 setting

data Settings Source #

Instances

Instances details
Show Settings Source # 
Instance details

Defined in Network.HTTP2.H2.Settings

Eq Settings Source # 
Instance details

Defined in Network.HTTP2.H2.Settings

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

maxConcurrentStreams :: Settings -> Maybe Int Source #

SETTINGS_MAX_CONCURRENT_STREAMS

initialWindowSize :: Settings -> WindowSize Source #

SETTINGS_INITIAL_WINDOW_SIZE

maxFrameSize :: Settings -> Int Source #

SETTINGS_MAX_FRAME_SIZE

maxHeaderListSize :: Settings -> Maybe Int Source #

SETTINGS_MAX_HEADER_LIST_SIZE

Common configuration

data Config Source #

HTTP/2 configuration.

Constructors

Config 

Fields

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.