Safe Haskell | None |
---|
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 is built on top of the conduit and
blaze-builder packages. The advantages of conduits 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:
- type Application = Request -> IO Response
- type Middleware = Application -> Application
- data Request
- defaultRequest :: Request
- data RequestBodyLength
- requestMethod :: Request -> Method
- httpVersion :: Request -> HttpVersion
- rawPathInfo :: Request -> ByteString
- rawQueryString :: Request -> ByteString
- requestHeaders :: Request -> RequestHeaders
- isSecure :: Request -> Bool
- remoteHost :: Request -> SockAddr
- pathInfo :: Request -> [Text]
- queryString :: Request -> Query
- requestBody :: Request -> Source IO ByteString
- vault :: Request -> Vault
- requestBodyLength :: Request -> RequestBodyLength
- requestHeaderHost :: Request -> Maybe ByteString
- requestHeaderRange :: Request -> Maybe ByteString
- lazyRequestBody :: Request -> IO ByteString
- data Response
- data FilePart = FilePart {}
- type WithSource m a b = (Source m a -> m b) -> m b
- responseFile :: Status -> ResponseHeaders -> FilePath -> Maybe FilePart -> Response
- responseBuilder :: Status -> ResponseHeaders -> Builder -> Response
- responseLBS :: Status -> ResponseHeaders -> ByteString -> Response
- responseSource :: Status -> ResponseHeaders -> Source IO (Flush Builder) -> Response
- responseSourceBracket :: IO a -> (a -> IO ()) -> (a -> IO (Status, ResponseHeaders, Source IO (Flush Builder))) -> IO Response
- responseStatus :: Response -> Status
- responseHeaders :: Response -> ResponseHeaders
- responseToSource :: Response -> (Status, ResponseHeaders, WithSource IO (Flush Builder) b)
Ttypes
type Application = Request -> IO ResponseSource
The WAI application.
type Middleware = Application -> ApplicationSource
Middleware is a component that sits between the server and application. It can do such tasks as GZIP encoding or response caching. What follows is the general definition of middleware, though a middleware author should feel free to modify this.
As an example of an alternate type for middleware, suppose you write a function to load up session information. The session information is simply a string map [(String, String)]. A logical type signatures for this middleware might be:
loadSession :: ([(String, String)] -> Application) -> Application
Here, instead of taking a standard Application
as its first argument, the
middleware takes a function which consumes the session information as well.
Request
Information on the request sent by the client. This abstracts away the details of the underlying implementation.
defaultRequest :: RequestSource
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
Request accessors
requestMethod :: Request -> MethodSource
Request method such as GET.
httpVersion :: Request -> HttpVersionSource
HTTP version such as 1.1.
rawPathInfo :: Request -> ByteStringSource
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. Do not modify this raw value- modify pathInfo instead.
rawQueryString :: Request -> ByteStringSource
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 -> RequestHeadersSource
A list of header (a pair of key and value) in an HTTP request.
isSecure :: Request -> BoolSource
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 -> SockAddrSource
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 -> QuerySource
Parsed query string information
requestBody :: Request -> Source IO ByteStringSource
A request body provided as Source
.
vault :: Request -> VaultSource
A location for arbitrary data to be shared by applications and middleware.
requestBodyLength :: Request -> RequestBodyLengthSource
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 ByteStringSource
The value of the Host header in a HTTP request.
Since 2.0.0
requestHeaderRange :: Request -> Maybe ByteStringSource
The value of the Range header in a HTTP request.
Since 2.0.0
lazyRequestBody :: Request -> IO ByteStringSource
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.
Since 1.4.1
Response
The strange structure of the third field or ResponseSource is to allow for exception-safe resource allocation. As an example:
app :: Application app _ = return $ ResponseSource status200 [] $ \f -> bracket (putStrLn "Allocation" >> return 5) (\i -> putStrLn $ "Cleaning up: " ++ show i) (\_ -> f $ do yield $ Chunk $ fromByteString "Hello " yield $ Chunk $ fromByteString "World!")
Information on which part to be sent.
Sophisticated application handles Range (and If-Range) then
create FilePart
.
type WithSource m a b = (Source m a -> m b) -> m bSource
Auxiliary type for ResponseSource
.
Response composers
responseFile :: Status -> ResponseHeaders -> FilePath -> Maybe FilePart -> ResponseSource
Creating Response
from a file.
responseBuilder :: Status -> ResponseHeaders -> Builder -> ResponseSource
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 blaze-builder uses an InsertByteString instruction to avoid copying.
Q3. Doesn't this prevent us from creating comet-style servers, since data will be cached?
A3. You can force blaze-builder to output a ByteString before it is an optimal size by sending a flush command.
responseLBS :: Status -> ResponseHeaders -> ByteString -> ResponseSource
Creating Response
from ByteString
. This is a wrapper for
responseBuilder
.
responseSource :: Status -> ResponseHeaders -> Source IO (Flush Builder) -> ResponseSource
responseSourceBracket :: IO a -> (a -> IO ()) -> (a -> IO (Status, ResponseHeaders, Source IO (Flush Builder))) -> IO ResponseSource
Response accessors
responseToSource :: Response -> (Status, ResponseHeaders, WithSource IO (Flush Builder) b)Source
Converting the body information in Response
to Source
.