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

Network.HTTP2.Client

Description

HTTP/2 client library.

Example:

{-# LANGUAGE OverloadedStrings #-}

module Main where

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

import Network.HTTP2.Client

serverName :: String
serverName = "127.0.0.1"

main :: IO ()
main = runTCPClient serverName "80" $ runHTTP2Client serverName
  where
    cliconf host = ClientConfig "http" (C8.pack host) 20
    runHTTP2Client host s = E.bracket (allocSimpleConfig s 4096)
                                      freeSimpleConfig
                                      (\conf -> run (cliconf host) conf client)
    client sendRequest = 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.

type Scheme = ByteString Source #

"http" or "https".

type Authority = ByteString Source #

Authority.

Runner arguments

data ClientConfig Source #

Client configuration

Constructors

ClientConfig 

Fields

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.

HTTP/2 client

type Client a = (Request -> (Response -> IO a) -> IO a) -> IO a Source #

Client type.

Request

data Request Source #

Request from client.

Instances

Instances details
Show Request Source # 
Instance details

Defined in Network.HTTP2.Client.Types

Creating request

requestNoBody :: Method -> Path -> RequestHeaders -> Request Source #

Creating request without body.

requestFile :: Method -> Path -> RequestHeaders -> FileSpec -> Request Source #

Creating request with file.

requestStreaming :: Method -> Path -> RequestHeaders -> ((Builder -> IO ()) -> IO () -> IO ()) -> Request Source #

Creating request with streaming.

requestBuilder :: Method -> Path -> RequestHeaders -> Builder -> Request Source #

Creating request with builder.

Trailers maker

type TrailersMaker = Maybe ByteString -> IO NextTrailersMaker Source #

Trailers maker. A chunks of the response body is passed with Just. The maker should update internal state with the ByteString and return the next trailers maker. When response body reaches its end, Nothing is passed and the maker should generate trailers. An example:

{-# LANGUAGE BangPatterns #-}
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as C8
import Crypto.Hash (Context, SHA1) -- cryptonite
import qualified Crypto.Hash as CH

-- Strictness is important for Context.
trailersMaker :: Context SHA1 -> Maybe ByteString -> IO NextTrailersMaker
trailersMaker ctx Nothing = return $ Trailers [("X-SHA1", sha1)]
  where
    !sha1 = C8.pack $ show $ CH.hashFinalize ctx
trailersMaker ctx (Just bs) = return $ NextTrailersMaker $ trailersMaker ctx'
  where
    !ctx' = CH.hashUpdate ctx bs

Usage example:

let h2rsp = responseFile ...
    maker = trailersMaker (CH.hashInit :: Context SHA1)
    h2rsp' = setResponseTrailersMaker h2rsp maker

data NextTrailersMaker Source #

Either the next trailers maker or final trailers.

defaultTrailersMaker :: TrailersMaker Source #

TrailersMake to create no trailers.

Response

data Response Source #

Response from server.

Instances

Instances details
Show Response Source # 
Instance details

Defined in Network.HTTP2.Client.Types

Accessing response

responseStatus :: Response -> Maybe Status Source #

Getting the status of a response.

responseHeaders :: Response -> HeaderTable Source #

Getting the headers from a response.

responseBodySize :: Response -> Maybe Int Source #

Getting the body size from a response.

getResponseBodyChunk :: Response -> IO ByteString Source #

Reading a chunk of the response body. An empty ByteString returned when finished.

getResponseTrailers :: Response -> IO (Maybe HeaderTable) Source #

Reading response trailers. This function must be called after getResponseBodyChunk returns an empty.

Types

type Method = ByteString #

HTTP method (flat string type).

type Path = ByteString Source #

Path.

data FileSpec Source #

File specification.

Instances

Instances details
Show FileSpec Source # 
Instance details

Defined in Network.HTTP2.Arch.Types

Eq FileSpec Source # 
Instance details

Defined in Network.HTTP2.Arch.Types

type FileOffset = Int64 Source #

Offset for file.

type ByteCount = Int64 Source #

How many bytes to read

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 

RecvN

defaultReadN :: Socket -> IORef (Maybe ByteString) -> Int -> IO ByteString Source #

Naive implementation for readN.

Position read for files

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

Making a position read and its closer.

type PositionRead = FileOffset -> ByteCount -> Buffer -> IO ByteCount Source #

Position read for files.

data Sentinel Source #

Manipulating a file resource.

Constructors

Closer (IO ())

Closing a file resource. Its refresher is automatiaclly generated by the internal timer.

Refresher (IO ())

Refreshing a file resource while reading. Closing the file must be done by its own timer or something.