http2-5.3.4: HTTP/2 library
Safe HaskellNone
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

Methods

showsPrec :: Int -> ServerConfig -> ShowS

show :: ServerConfig -> String

showList :: [ServerConfig] -> ShowS

Eq ServerConfig Source # 
Instance details

Defined in Network.HTTP2.Server.Run

Methods

(==) :: ServerConfig -> ServerConfig -> Bool

(/=) :: ServerConfig -> ServerConfig -> Bool

defaultServerConfig :: ServerConfig Source #

The default server config.

>>> defaultServerConfig
ServerConfig {numberOfWorkers = 8, connectionWindowSize = 16777216, settings = Settings {headerTableSize = 4096, enablePush = True, maxConcurrentStreams = Just 64, initialWindowSize = 262144, maxFrameSize = 16384, maxHeaderListSize = Nothing, pingRateLimit = 10, emptyFrameRateLimit = 4, settingsRateLimit = 4, rstRateLimit = 4}}

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

Methods

showsPrec :: Int -> Settings -> ShowS

show :: Settings -> String

showList :: [Settings] -> ShowS

Eq Settings Source # 
Instance details

Defined in Network.HTTP2.H2.Settings

Methods

(==) :: Settings -> Settings -> Bool

(/=) :: Settings -> Settings -> Bool

defaultSettings :: Settings Source #

The default settings.

>>> defaultSettings
Settings {headerTableSize = 4096, enablePush = True, maxConcurrentStreams = Just 64, initialWindowSize = 262144, maxFrameSize = 16384, maxHeaderListSize = Nothing, pingRateLimit = 10, emptyFrameRateLimit = 4, settingsRateLimit = 4, rstRateLimit = 4}

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

Rate limits

pingRateLimit :: Settings -> Int Source #

Maximum number of pings allowed per second (CVE-2019-9512)

settingsRateLimit :: Settings -> Int Source #

Maximum number of settings frames allowed per second (CVE-2019-9515)

emptyFrameRateLimit :: Settings -> Int Source #

Maximum number of empty data frames allowed per second (CVE-2019-9518)

rstRateLimit :: Settings -> Int Source #

Maximum number of reset frames allowed per second (CVE-2023-44487)

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.

data Request #

Instances

Instances details
Show Request 
Instance details

Defined in Network.HTTP.Semantics.Server.Internal

Methods

showsPrec :: Int -> Request -> ShowS

show :: Request -> String

showList :: [Request] -> ShowS

data Response #

Instances

Instances details
Show Response 
Instance details

Defined in Network.HTTP.Semantics.Server.Internal

Methods

showsPrec :: Int -> Response -> ShowS

show :: Response -> String

showList :: [Response] -> ShowS

data Aux #

type Server = Request -> Aux -> (Response -> [PushPromise] -> IO ()) -> IO () #

type TrailersMaker = Maybe ByteString -> IO NextTrailersMaker #

type Authority = String #

type ByteCount = Int64 #

type FileOffset = Int64 #

data FileSpec #

Constructors

FileSpec FilePath FileOffset ByteCount 

Instances

Instances details
Show FileSpec 
Instance details

Defined in Network.HTTP.Semantics.Types

Methods

showsPrec :: Int -> FileSpec -> ShowS

show :: FileSpec -> String

showList :: [FileSpec] -> ShowS

Eq FileSpec 
Instance details

Defined in Network.HTTP.Semantics.Types

Methods

(==) :: FileSpec -> FileSpec -> Bool

(/=) :: FileSpec -> FileSpec -> Bool

data OutBodyIface #

Constructors

OutBodyIface 

Fields

type Path = ByteString #

type Scheme = ByteString #

type PositionReadMaker = FilePath -> IO (PositionRead, Sentinel) #

data Sentinel #

Constructors

Closer (IO ()) 
Refresher (IO ()) 

type ReadN = Int -> IO ByteString #

defaultReadN :: Socket -> IORef (Maybe ByteString) -> ReadN #

responseBodySize :: Response -> Maybe Int #

pushPromise :: ByteString -> Response -> Int -> PushPromise #

data PushPromise #

Constructors

PushPromise 

Fields

getRequestBodyChunk :: Request -> IO ByteString #

getRequestBodyChunk' :: Request -> IO (ByteString, Bool) #

requestBodySize :: Request -> Maybe Int #

responseBuilder :: Status -> ResponseHeaders -> Builder -> Response #

responseFile :: Status -> ResponseHeaders -> FileSpec -> Response #

responseNoBody :: Status -> ResponseHeaders -> Response #

responseStreaming :: Status -> ResponseHeaders -> ((Builder -> IO ()) -> IO () -> IO ()) -> Response #

responseStreamingIface :: Status -> ResponseHeaders -> (OutBodyIface -> IO ()) -> Response #