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

Network.HTTP2.Client

Description

HTTP/2 client library.

Example:

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}

module Main where

import qualified Data.ByteString.Char8 as C8
import Network.HTTP.Types
import Network.Run.TCP (runTCPClient) -- network-run
import UnliftIO.Async -- unliftio
import qualified UnliftIO.Exception as E -- unliftio

import Network.HTTP2.Client

serverName :: String
serverName = "127.0.0.1"

main :: IO ()
main = runTCPClient serverName "80" $ runHTTP2Client serverName
  where
    cliconf host = defaultClientConfig { authority = C8.pack host }
    runHTTP2Client host s = E.bracket (allocSimpleConfig s 4096)
                                      freeSimpleConfig
                                      (\conf -> run (cliconf host) conf client)
    client :: Client ()
    client sendRequest _aux = do
        let req0 = requestNoBody methodGet "/" []
            client0 = sendRequest req0 $ \rsp -> do
                print rsp
                getResponseBodyChunk rsp >>= C8.putStrLn
            req1 = requestNoBody methodGet "/foo" []
            client1 = sendRequest req1 $ \rsp -> do
                print rsp
                getResponseBodyChunk rsp >>= C8.putStrLn
        ex <- E.try $ concurrently_ client0 client1
        case ex of
          Left  e  -> print (e :: HTTP2Error)
          Right () -> putStrLn "OK"
Synopsis

Runner

run :: ClientConfig -> Config -> Client a -> IO a Source #

Running HTTP/2 client.

Client configuration

data ClientConfig Source #

Client configuration

Instances

Instances details
Show ClientConfig Source # 
Instance details

Defined in Network.HTTP2.Client.Run

Eq ClientConfig Source # 
Instance details

Defined in Network.HTTP2.Client.Run

defaultClientConfig :: ClientConfig Source #

The default client config.

The authority field will be used to set the HTTP2 :authority pseudo-header. In most cases you will want to override it to be equal to host.

Further background on authority: RFC 3986 also allows host:port, and most servers will accept this too. However, when using TLS, many servers will expect the TLS SNI server name and the :authority pseudo-header to be equal, and for TLS SNI the server name should not include the port. Note that HTTP2 explicitly disallows using userinfo@ as part of the authority.

>>> defaultClientConfig
ClientConfig {scheme = "http", authority = "localhost", cacheLimit = 64, connectionWindowSize = 1048576, settings = Settings {headerTableSize = 4096, enablePush = True, maxConcurrentStreams = Just 64, initialWindowSize = 262144, maxFrameSize = 16384, maxHeaderListSize = Nothing, pingRateLimit = 10}}

scheme :: ClientConfig -> Scheme Source #

https or http

cacheLimit :: ClientConfig -> Int Source #

The maximum number of incoming streams on the net

connectionWindowSize :: ClientConfig -> WindowSize Source #

The window size of connection.

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

pingRateLimit :: Settings -> Int Source #

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

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.

Error

data HTTP2Error Source #

The connection error or the stream error. Stream errors are treated as connection errors since there are no good recovery ways. ErrorCode in connection errors should be the highest stream identifier but in this implementation it identifies the stream that caused this error.

newtype ErrorCode Source #

The type for raw error code.

Constructors

ErrorCode Word32 

Bundled Patterns

pattern NoError :: ErrorCode

The type for error code. See https://www.rfc-editor.org/rfc/rfc9113#ErrorCodes.

pattern ProtocolError :: ErrorCode 
pattern InternalError :: ErrorCode 
pattern FlowControlError :: ErrorCode 
pattern SettingsTimeout :: ErrorCode 
pattern StreamClosed :: ErrorCode 
pattern FrameSizeError :: ErrorCode 
pattern RefusedStream :: ErrorCode 
pattern Cancel :: ErrorCode 
pattern CompressionError :: ErrorCode 
pattern ConnectError :: ErrorCode 
pattern EnhanceYourCalm :: ErrorCode 
pattern InadequateSecurity :: ErrorCode 
pattern HTTP11Required :: ErrorCode