wai-3.2.4: Web Application Interface.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.Wai

Description

This module defines a generic web application interface. It is a common protocol between web servers and web applications.

The overriding design principles here are performance and generality. To address performance, this library uses a streaming interface for request and response bodies, paired with bytestring's Builder type. The advantages of a streaming API over lazy IO have been debated elsewhere and so will not be addressed here. However, helper functions like responseLBS allow you to continue using lazy IO if you so desire.

Generality is achieved by removing many variables commonly found in similar projects that are not universal to all servers. The goal is that the Request object contains only data which is meaningful in all circumstances.

Please remember when using this package that, while your application may compile without a hitch against many different servers, there are other considerations to be taken when moving to a new backend. For example, if you transfer from a CGI application to a FastCGI one, you might suddenly find you have a memory leak. Conversely, a FastCGI application would be well served to preload all templates from disk when first starting; this would kill the performance of a CGI application.

This package purposely provides very little functionality. You can find various middlewares, backends and utilities on Hackage. Some of the most commonly used include:

warp
http://hackage.haskell.org/package/warp
wai-extra
http://hackage.haskell.org/package/wai-extra
Synopsis

Types

type Application = Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived Source #

The WAI application.

Note that, since WAI 3.0, this type is structured in continuation passing style to allow for proper safe resource handling. This was handled in the past via other means (e.g., ResourceT). As a demonstration:

app :: Application
app req respond = bracket_
    (putStrLn "Allocating scarce resource")
    (putStrLn "Cleaning up")
    (respond $ responseLBS status200 [] "Hello World")

type Middleware = Application -> Application Source #

A Middleware is a component that sits between the server and application.

It can modify both the Request and Response, to provide simple transformations that are required for all (or most of) your web server’s routes.

Users of middleware

If you are trying to apply one or more Middlewares to your Application, just call them as functions.

For example, if you have corsMiddleware and authorizationMiddleware, and you want to authorize first, you can do:

let allMiddleware app = authorizationMiddleware (corsMiddleware app)

to get a new Middleware, which first authorizes, then sets, CORS headers. The “outer” middleware is called first.

You can also chain them via (.):

let allMiddleware =
        authorizationMiddleware
      . corsMiddleware
      . … more middleware here …

Then, once you have an app :: Application, you can wrap it in your middleware:

let myApp = allMiddleware app :: Application

and run it as usual:

Warp.run port myApp

Authors of middleware

When fully expanded, Middleware has the type signature:

(Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived) -> Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived

or if we shorten to type Respond = Response -> IO ResponseReceived:

(Request -> Respond -> IO ResponseReceived) -> Request -> Respond -> IO ResponseReceived

so a middleware definition takes 3 arguments, an inner application, a request and a response callback.

Compare with the type of a simple Application:

Request -> Respond -> IO ResponseReceived

It takes the Request and Respond, but not the extra application.

Said differently, a middleware has the power of a normal Application — it can inspect the Request and return a Response — but it can (and in many cases it should) also call the Application which was passed to it.

Modifying the Request

A lot of middleware just looks at the request and does something based on its values.

For example, the authorizationMiddleware from above could look at the Authorization HTTP header and run JWT verification logic against the database.

authorizationMiddleware app req respond = do
  case verifyJWT (requestHeaders req) of
    InvalidJWT err -> respond (invalidJWTResponse err)
    ValidJWT -> app req respond

Notice how the inner app is called when the validation was successful. If it was not, we can respond e.g. with HTTP 401 Unauthorized, by constructing a Response with responseLBS and passing it to respond.

Passing arguments to and from your Middleware

Middleware must often be configurable. Let’s say you have a type JWTSettings that you want to be passed to the middleware. Simply pass an extra argument to your middleware. Then your middleware type turns into:

authorizationMiddleware :: JWTSettings -> Application -> Request -> Respond -> IO ResponseReceived
authorizationMiddleware jwtSettings req respond =
  case verifyJWT jwtSettings (requestHeaders req) of
    InvalidJWT err -> respond (invalidJWTResponse err)
    ValidJWT -> app req respond

or alternatively:

authorizationMiddleware :: JWTSettings -> Middleware

Perhaps less intuitively, you can also pass on data from middleware to the wrapped Application:

authorizationMiddleware :: JWTSettings -> (JWT -> Application) -> Request -> Respond -> IO ResponseReceived
authorizationMiddleware jwtSettings req respond =
  case verifyJWT jwtSettings (requestHeaders req) of
    InvalidJWT err -> respond (invalidJWTResponse err)
    ValidJWT jwt -> app jwt req respond

although then, chaining different middleware has to take this extra argument into account:

let finalApp =
      authorizationMiddleware
        (\jwt -> corsMiddleware
           (… more middleware here …
             (app jwt)))

Modifying the Response

Middleware can also modify the Response that is returned by the inner application.

This is done by taking the respond callback, using it to define a new respond', and passing this new respond' to the app:

gzipMiddleware app req respond = do
  let respond' resp = do
        resp' <- gzipResponseBody resp
        respond resp'
  app req respond'

However, modifying the response (especially the response body) is not trivial, so in order to get a sense of how to do it (dealing with the type of responseToStream), it’s best to look at an example, for example the GZIP middleware of wai-extra.

data ResponseReceived Source #

A special datatype to indicate that the WAI handler has received the response. This is to avoid the need for Rank2Types in the definition of Application.

It is highly advised that only WAI handlers import and use the data constructor for this data type.

Since: 3.0.0

Request

data Request Source #

Information on the request sent by the client. This abstracts away the details of the underlying implementation.

Instances

Instances details
Show Request Source # 
Instance details

Defined in Network.Wai.Internal

defaultRequest :: Request Source #

A default, blank request.

Since: 2.0.0

data RequestBodyLength Source #

The size of the request body. In the case of chunked bodies, the size will not be known.

Since: 1.4.0

Instances

Instances details
Show RequestBodyLength Source # 
Instance details

Defined in Network.Wai.Internal

Request accessors

requestMethod :: Request -> Method Source #

Request method such as GET.

httpVersion :: Request -> HttpVersion Source #

HTTP version such as 1.1.

rawPathInfo :: Request -> ByteString Source #

Extra path information sent by the client. The meaning varies slightly depending on backend; in a standalone server setting, this is most likely all information after the domain name. In a CGI application, this would be the information following the path to the CGI executable itself.

Middlewares and routing tools should not modify this raw value, as it may be used for such things as creating redirect destinations by applications. Instead, if you are writing a middleware or routing framework, modify the pathInfo instead. This is the approach taken by systems like Yesod subsites.

Note: At the time of writing this documentation, there is at least one system (Network.Wai.UrlMap from wai-extra) that does not follow the above recommendation. Therefore, it is recommended that you test the behavior of your application when using rawPathInfo and any form of library that might modify the Request.

rawQueryString :: Request -> ByteString Source #

If no query string was specified, this should be empty. This value will include the leading question mark. Do not modify this raw value - modify queryString instead.

requestHeaders :: Request -> RequestHeaders Source #

A list of headers (a pair of key and value) in an HTTP request.

isSecure :: Request -> Bool Source #

Was this request made over an SSL connection?

Note that this value will not tell you if the client originally made this request over SSL, but rather whether the current connection is SSL. The distinction lies with reverse proxies. In many cases, the client will connect to a load balancer over SSL, but connect to the WAI handler without SSL. In such a case, isSecure will be False, but from a user perspective, there is a secure connection.

remoteHost :: Request -> SockAddr Source #

The client's host information.

pathInfo :: Request -> [Text] Source #

Path info in individual pieces - the URL without a hostname/port and without a query string, split on forward slashes.

queryString :: Request -> Query Source #

Parsed query string information.

getRequestBodyChunk :: Request -> IO ByteString Source #

Get the next chunk of the body. Returns empty when the body is fully consumed.

Since: 3.2.2

requestBody :: Request -> IO ByteString Source #

Deprecated: requestBody's name is misleading because it only gets a partial chunk of the body. Use getRequestBodyChunk instead when getting the field, and setRequestBodyChunks when setting the field.

Get the next chunk of the body. Returns empty when the body is fully consumed. Since 3.2.2, this is deprecated in favor of getRequestBodyChunk.

vault :: Request -> Vault Source #

A location for arbitrary data to be shared by applications and middleware.

requestBodyLength :: Request -> RequestBodyLength Source #

The size of the request body. In the case of a chunked request body, this may be unknown.

Since: 1.4.0

requestHeaderHost :: Request -> Maybe ByteString Source #

The value of the Host header in a HTTP request.

Since: 2.0.0

requestHeaderRange :: Request -> Maybe ByteString Source #

The value of the Range header in a HTTP request.

Since: 2.0.0

requestHeaderReferer :: Request -> Maybe ByteString Source #

The value of the Referer header in a HTTP request.

Since: 3.2.0

requestHeaderUserAgent :: Request -> Maybe ByteString Source #

The value of the User-Agent header in a HTTP request.

Since: 3.2.0

Streaming Request Bodies

WAI is designed for streaming in request bodies, which allows you to process them incrementally. You can stream in the request body using functions like getRequestBodyChunk, the wai-conduit package, or Yesod's rawRequestBody.

In the normal case, incremental processing is more efficient, since it reduces maximum total memory usage. In the worst case, it helps protect your server against denial-of-service (DOS) attacks, in which an attacker sends huge request bodies to your server.

Consider these tips to avoid reading the entire request body into memory:

  • Look for library functions that support incremental processing. Sometimes these will use streaming libraries like conduit, pipes, or streaming.
  • Any attoparsec parser supports streaming input. For an example of this, see the Data.Conduit.Attoparsec module in conduit-extra.
  • Consider streaming directly to a file on disk. For an example of this, see the Data.Conduit.Binary module in conduit-extra.
  • If you need to direct the request body to multiple destinations, you can stream to both those destinations at the same time. For example, if you wanted to run an HMAC on the request body as well as parse it into JSON, you could use Conduit's zipSinks to send the data to cryptonite-conduit's sinkHMAC and aeson's Attoparsec parser.
  • If possible, avoid processing large data on your server at all. For example, instead of uploading a file to your server and then to AWS S3, you can have the browser upload directly to S3.

That said, sometimes it is convenient, or even necessary to read the whole request body into memory. For these purposes, functions like strictRequestBody or lazyRequestBody can be used. When this is the case, consider these strategies to mitigating potential DOS attacks:

  • Set a limit on the request body size you allow. If certain endpoints need larger bodies, whitelist just those endpoints for the large size. Be especially cautious about endpoints that don't require authentication, since these are easier to DOS. You can accomplish this with wai-extra's requestSizeLimitMiddleware or Yesod's maximumContentLength.
  • Consider rate limiting not just on total requests, but also on total bytes sent in.
  • Consider using services that allow you to identify and blacklist attackers.
  • Minimize the amount of time the request body stays in memory.
  • If you need to share request bodies across middleware and your application, you can do so using Wai's vault. If you do this, remove the request body from the vault as soon as possible.

Warning: Incremental processing will not always be sufficient to prevent a DOS attack. For example, if an attacker sends you a JSON body with a 2MB long string inside, even if you process the body incrementally, you'll still end up with a 2MB-sized Text.

To mitigate this, employ some of the countermeasures listed above, and try to reject such payloads as early as possible in your codebase.

strictRequestBody :: Request -> IO ByteString Source #

Get the request body as a lazy ByteString. However, do not use any lazy I/O, instead reading the entire body into memory strictly.

Note: Since this function consumes the request body, future calls to it will return the empty string.

Since: 3.0.1

consumeRequestBodyStrict :: Request -> IO ByteString Source #

Synonym for strictRequestBody. This function name is meant to signal the non-idempotent nature of strictRequestBody.

Since: 3.2.3

lazyRequestBody :: Request -> IO ByteString Source #

Get the request body as a lazy ByteString. This uses lazy I/O under the surface, and therefore all typical warnings regarding lazy I/O apply.

Note: Since this function consumes the request body, future calls to it will return the empty string.

Since: 1.4.1

consumeRequestBodyLazy :: Request -> IO ByteString Source #

Synonym for lazyRequestBody. This function name is meant to signal the non-idempotent nature of lazyRequestBody.

Since: 3.2.3

Request modifiers

setRequestBodyChunks :: IO ByteString -> Request -> Request Source #

Set the requestBody attribute on a request without triggering a deprecation warning.

The supplied IO action should return the next chunk of the body each time it is called and empty when it has been fully consumed.

Since: 3.2.4

mapRequestHeaders :: (RequestHeaders -> RequestHeaders) -> Request -> Request Source #

Apply the provided function to the request header list of the Request.

Since: 3.2.4

Response

type StreamingBody = (Builder -> IO ()) -> IO () -> IO () Source #

Represents a streaming HTTP response body. It's a function of two parameters; the first parameter provides a means of sending another chunk of data, and the second parameter provides a means of flushing the data to the client.

Since: 3.0.0

data FilePart Source #

Information on which part to be sent. Sophisticated application handles Range (and If-Range) then create FilePart.

Since: 0.4.0

Instances

Instances details
Show FilePart Source # 
Instance details

Defined in Network.Wai.Internal

Response composers

responseFile :: Status -> ResponseHeaders -> FilePath -> Maybe FilePart -> Response Source #

Creating Response from a file.

Since: 2.0.0

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

Creating Response from Builder.

Some questions and answers about the usage of Builder here:

Q1. Shouldn't it be at the user's discretion to use Builders internally and then create a stream of ByteStrings?

A1. That would be less efficient, as we wouldn't get cheap concatenation with the response headers.

Q2. Isn't it really inefficient to convert from ByteString to Builder, and then right back to ByteString?

A2. No. If the ByteStrings are small, then they will be copied into a larger buffer, which should be a performance gain overall (less system calls). If they are already large, then an insert operation is used to avoid copying.

Q3. Doesn't this prevent us from creating comet-style servers, since data will be cached?

A3. You can force a Builder to output a ByteString before it is an optimal size by sending a flush command.

Since: 2.0.0

responseLBS :: Status -> ResponseHeaders -> ByteString -> Response Source #

Creating Response from ByteString. This is a wrapper for responseBuilder.

Since: 0.3.0

responseStream :: Status -> ResponseHeaders -> StreamingBody -> Response Source #

Creating Response from a stream of values.

In order to allocate resources in an exception-safe manner, you can use the bracket pattern outside of the call to responseStream. As a trivial example:

app :: Application
app req respond = bracket_
    (putStrLn "Allocating scarce resource")
    (putStrLn "Cleaning up")
    $ respond $ responseStream status200 [] $ \write flush -> do
        write $ byteString "Hello\n"
        flush
        write $ byteString "World\n"

Note that in some cases you can use bracket from inside responseStream as well. However, placing the call on the outside allows your status value and response headers to depend on the scarce resource.

Since: 3.0.0

responseRaw :: (IO ByteString -> (ByteString -> IO ()) -> IO ()) -> Response -> Response Source #

Create a response for a raw application. This is useful for "upgrade" situations such as WebSockets, where an application requests for the server to grant it raw network access.

This function requires a backup response to be provided, for the case where the handler in question does not support such upgrading (e.g., CGI apps).

In the event that you read from the request body before returning a responseRaw, behavior is undefined.

Since: 2.1.0

Response accessors

responseStatus :: Response -> Status Source #

Accessing Status in Response.

Since: 1.2.0

Response modifiers

responseToStream :: Response -> (Status, ResponseHeaders, (StreamingBody -> IO a) -> IO a) Source #

Converting the body information in Response to a StreamingBody.

Since: 3.0.0

mapResponseHeaders :: (ResponseHeaders -> ResponseHeaders) -> Response -> Response Source #

Apply the provided function to the response header list of the Response.

Since: 3.0.3.0

mapResponseStatus :: (Status -> Status) -> Response -> Response Source #

Apply the provided function to the response status of the Response.

Since: 3.2.1

Middleware composition

ifRequest :: (Request -> Bool) -> Middleware -> Middleware Source #

Conditionally apply a Middleware

Since: 3.0.3.0

modifyRequest :: (Request -> Request) -> Middleware Source #

Apply a function that modifies a request as a Middleware

Since: 3.2.4

modifyResponse :: (Response -> Response) -> Middleware Source #

Apply a function that modifies a response as a Middleware

Since: 3.0.3.0