wai-3.0.4.0: Web Application Interface.

Safe HaskellNone
LanguageHaskell98

Network.Wai.HTTP2

Contents

Description

An HTTP/2-aware variant of the Application type. Compared to the original, this exposes the new functionality of server push and trailers, allows stream fragments to be sent in the form of file ranges, and allows the stream body to produce a value to be used in constructing the trailers. Existing Applications can be faithfully upgraded to HTTP/2 with promoteApplication or served transparently over both protocols with the normal Warp run family of functions.

An HTTP2Application takes a Request and a PushFunc and produces a Responder that will push any associated resources and send the response body. The response is always a stream of Builders and file chunks. Equivalents of the responseBuilder family of functions are provided for creating Responders conveniently.

Pushed streams are handled by an IO action that triggers a server push. It returns True if the PUSH_PROMISE frame was sent, False if not. Note this means it will still return True if the client reset or ignored the stream. This gives handlers the freedom to implement their own heuristics for whether to actually push a resource, while also allowing middleware and frameworks to trigger server pushes automatically.

Synopsis

Applications

type HTTP2Application = Request -> PushFunc -> Responder Source

The HTTP/2-aware equivalent of Application.

Responder

newtype Responder Source

The result of an HTTP2Application; or, alternately, an application that's independent of the request. This is a continuation-passing style function that first provides a response by calling the given respond function, then returns the request's Trailers.

The respond function is similar to the one in Application, but it only takes a streaming body, the status and headers are curried, and it also produces trailers for the stream.

Constructors

Responder 

Fields

runResponder :: forall s. RespondFunc s -> IO s
 

type RespondFunc s = Status -> ResponseHeaders -> Body -> IO s Source

Given to Responders; provide a status, headers, and a stream body, and we'll give you a token proving you called the RespondFunc.

type Body = (Chunk -> IO ()) -> IO () -> IO Trailers Source

The streaming body of a response. Equivalent to StreamingBody except that it can also write file ranges and return the stream's trailers.

data Chunk Source

Part of a streaming response -- either a Builder or a range of a file.

type Trailers = [Header] Source

Headers sent after the end of a data stream, as defined by section 4.1.2 of the HTTP/1.1 spec (RFC 7230), and section 8.1 of the HTTP/2 spec.

Server push

type PushFunc = PushPromise -> Responder -> IO Bool Source

A function given to an HTTP2Application to initiate a server-pushed stream. Its argument is the same as the result of an HTTP2Application, so you can either implement the response inline, or call your own application to create the response.

The result is True if the PUSH_PROMISE frame will be sent, or False if it will not. This can happen if server push is disabled, the concurrency limit of server-initiated streams is reached, or the associated stream has already been closed.

This function shall ensure that stream data provided after it returns will be sent after the PUSH_PROMISE frame, so that servers can implement the requirement that any pushed stream for a resource be initiated before sending DATA frames that reference it.

data PushPromise Source

The synthesized request and headers of a pushed stream.

promiseHeaders :: PushPromise -> RequestHeaders Source

Create the RequestHeaders corresponding to the given PushPromise.

This is primarily useful for WAI handlers like Warp, and application implementers are unlikely to use it directly.

Conveniences

promoteApplication :: Application -> HTTP2Application Source

Promote a normal WAI Application to an HTTP2Application by ignoring the HTTP/2-specific features.

Responders

respond :: Status -> ResponseHeaders -> Body -> Responder Source

Construct a Responder that will just call the RespondFunc with the given arguments.

respondCont :: (forall r. ContT r IO Responder) -> Responder Source

Fold the ContT into the contained Responder.

respondIO :: IO Responder -> Responder Source

Fold the IO into the contained Responder.

respondFile :: Status -> ResponseHeaders -> FilePath -> RequestHeaders -> Responder Source

Serve the requested range of the specified file (based on the Range header), using the given Status and ResponseHeaders as a base. If the file is not accessible, the status will be replaced with 404 and a default not-found message will be served. If a partial file is requested, the status will be replaced with 206 and the Content-Range header will be added. The Content-Length header will always be added.

respondFilePart :: Status -> ResponseHeaders -> FilePath -> FilePart -> Responder Source

Respond with a single range of a file, adding the Accept-Ranges, Content-Length and Content-Range headers and changing the status to 206 as appropriate.

If you want the range to be inferred automatically from the Range header, use respondFile instead. On the other hand, if you want to avoid the automatic header and status adjustments, use respond and streamFilePart directly.

respondNotFound :: ResponseHeaders -> Responder Source

Respond with a minimal 404 page with the given headers.

respondWith :: (forall s. (a -> IO s) -> IO s) -> (a -> Responder) -> Responder Source

Fold the given bracketing action into a Responder. Note the first argument is isomorphic to Codensity IO a or forall s. ContT s IO a, and is the type of a partially-applied bracket or with-style function.

respondWith (bracket acquire release) $
    \x -> respondNotFound [("x", show x)]

is equivalent to

Responder $ \k -> bracket acquire release $
    \x -> runResponder (respondNotFound [("x", show x)] k

This is morally equivalent to (>>=) on Codensity IO.

Stream Bodies

streamFilePart :: FilePath -> FilePart -> Body Source

Create a response body consisting of a single range of a file. Does not set Content-Length or Content-Range headers. For that, use respondFilePart or respondFile.

streamBuilder :: Builder -> Body Source

Create a response body consisting of a single builder.

streamSimple :: StreamingBody -> Body Source

Create a response body of a stream of Builders.