Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Network.HTTP3.Server
Description
A server library for HTTP/3.
Synopsis
- run :: Connection -> Config -> Server -> IO ()
- data Config = Config {}
- allocSimpleConfig :: IO Config
- freeSimpleConfig :: Config -> IO ()
- data Hooks = Hooks {
- onControlFrameCreated :: [H3Frame] -> [H3Frame]
- onHeadersFrameCreated :: [H3Frame] -> [H3Frame]
- onControlStreamCreated :: Stream -> IO ()
- onEncoderStreamCreated :: Stream -> IO ()
- onDecoderStreamCreated :: Stream -> IO ()
- defaultHooks :: Hooks
- type Server = Request -> Aux -> (Response -> [PushPromise] -> IO ()) -> IO ()
- data Request
- requestMethod :: Request -> Maybe Method
- requestPath :: Request -> Maybe Path
- requestAuthority :: Request -> Maybe Authority
- requestScheme :: Request -> Maybe Scheme
- requestHeaders :: Request -> HeaderTable
- requestBodySize :: Request -> Maybe Int
- getRequestBodyChunk :: Request -> IO ByteString
- getRequestTrailers :: Request -> IO (Maybe HeaderTable)
- data Aux
- auxTimeHandle :: Aux -> Handle
- data Response
- responseNoBody :: Status -> ResponseHeaders -> Response
- responseFile :: Status -> ResponseHeaders -> FileSpec -> Response
- responseStreaming :: Status -> ResponseHeaders -> ((Builder -> IO ()) -> IO () -> IO ()) -> Response
- responseBuilder :: Status -> ResponseHeaders -> Builder -> Response
- responseBodySize :: Response -> Maybe Int
- type TrailersMaker = Maybe ByteString -> IO NextTrailersMaker
- data NextTrailersMaker
- defaultTrailersMaker :: TrailersMaker
- setResponseTrailersMaker :: Response -> TrailersMaker -> Response
- data PushPromise
- pushPromise :: ByteString -> Response -> Weight -> PushPromise
- promiseRequestPath :: PushPromise -> ByteString
- promiseResponse :: PushPromise -> Response
- type Path = ByteString
- type Authority = String
- type Scheme = ByteString
- data FileSpec = FileSpec FilePath FileOffset ByteCount
- type FileOffset = Int64
- type ByteCount = Int64
- defaultReadN :: Socket -> IORef (Maybe ByteString) -> Int -> IO ByteString
- type PositionReadMaker = FilePath -> IO (PositionRead, Sentinel)
- type PositionRead = FileOffset -> ByteCount -> Buffer -> IO ByteCount
- data Sentinel
- defaultPositionReadMaker :: PositionReadMaker
Runner
Runner arguments
Configuration for HTTP/3 or HQ.
Constructors
Config | |
Fields |
allocSimpleConfig :: IO Config Source #
Allocating a simple configuration with a handle-based position reader and a locally allocated timeout manager.
freeSimpleConfig :: Config -> IO () Source #
Freeing a simple configration.
Hooks mainly for error testing.
Constructors
Hooks | |
Fields
|
defaultHooks :: Hooks Source #
Default hooks.
HTTP/3 server
type Server = Request -> Aux -> (Response -> [PushPromise] -> IO ()) -> IO () #
Server type. Server takes a HTTP request, should generate a HTTP response and push promises, then should give them to the sending function. The sending function would throw exceptions so that they can be logged.
Request
Request from client.
Accessing request
requestMethod :: Request -> Maybe Method #
Getting the method from a request.
requestPath :: Request -> Maybe Path #
Getting the path from a request.
requestAuthority :: Request -> Maybe Authority #
Getting the authority from a request.
requestScheme :: Request -> Maybe Scheme #
Getting the scheme from a request.
requestHeaders :: Request -> HeaderTable #
Getting the headers from a request.
requestBodySize :: Request -> Maybe Int #
Getting the body size from a request.
getRequestBodyChunk :: Request -> IO ByteString #
Reading a chunk of the request body.
An empty ByteString
returned when finished.
getRequestTrailers :: Request -> IO (Maybe HeaderTable) #
Reading request trailers.
This function must be called after getRequestBodyChunk
returns an empty.
Aux
auxTimeHandle :: Aux -> Handle #
Time handle for the worker processing this request and response.
Response
Response from server.
Creating response
responseNoBody :: Status -> ResponseHeaders -> Response #
Creating response without body.
responseFile :: Status -> ResponseHeaders -> FileSpec -> Response #
Creating response with file.
responseStreaming :: Status -> ResponseHeaders -> ((Builder -> IO ()) -> IO () -> IO ()) -> Response #
Creating response with streaming.
responseBuilder :: Status -> ResponseHeaders -> Builder -> Response #
Creating response with builder.
Accessing response
responseBodySize :: Response -> Maybe Int #
Getter for response body size. This value is available for file body.
Trailers maker
type TrailersMaker = Maybe ByteString -> IO NextTrailersMaker #
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 #
Either the next trailers maker or final trailers.
Constructors
NextTrailersMaker TrailersMaker | |
Trailers [Header] |
defaultTrailersMaker :: TrailersMaker #
TrailersMake to create no trailers.
setResponseTrailersMaker :: Response -> TrailersMaker -> Response #
Setting TrailersMaker
to Response
.
Push promise
data PushPromise #
HTTP/2 push promise or sever push.
Pseudo REQUEST headers in push promise is automatically generated.
Then, a server push is sent according to promiseResponse
.
pushPromise :: ByteString -> Response -> Weight -> PushPromise #
Creating push promise. The third argument is traditional, not used.
promiseRequestPath :: PushPromise -> ByteString #
Accessor for a URL path in a push promise (a virtual request from a server). E.g. "/style/default.css".
promiseResponse :: PushPromise -> Response #
Accessor for response actually pushed from a server.
Types
type Path = ByteString #
Path.
type Scheme = ByteString #
"http" or "https".
File specification.
Constructors
FileSpec FilePath FileOffset ByteCount |
type FileOffset = Int64 #
Offset for file.
RecvN
defaultReadN :: Socket -> IORef (Maybe ByteString) -> Int -> IO ByteString #
Naive implementation for readN.
Position read for files
type PositionReadMaker = FilePath -> IO (PositionRead, Sentinel) #
Making a position read and its closer.
type PositionRead = FileOffset -> ByteCount -> Buffer -> IO ByteCount #
Position read for files.
Manipulating a file resource.
defaultPositionReadMaker :: PositionReadMaker #
Position read based on Handle
.