direct-http-0.5.3: Native webserver that acts as a library.

Safe HaskellNone

Network.HTTP

Contents

Description

This module provides facilities for implementing webservers, in a servelet-like style. The general philosophy is that direct-http makes as few decisions as possible for the user code, allowing such things as URL routing and virtual-host policies to be implemented in any desired fashion. It focuses on providing a robust transport layer which can integrate well with any higher layer.

Synopsis

The monad

type HTTP = ReaderT HTTPState IOSource

The monad within which each single request from a client is handled.

Note that there is an instance MonadBaseControl IO HTTP, so that exceptions can be thrown, caught, and otherwise manipulated with the lifted primitives from lifted-base's Lifted.

data HTTPState Source

An opaque type representing the state of the HTTP server during a single connection from a client.

Instances

class MonadBaseControl IO m => MonadHTTP m whereSource

The class of monads within which the HTTP calls are valid. You may wish to create your own monad implementing this class. Note that the prerequisite is MonadBaseControl IO m, which is similar to MonadIO m, but with, among other things, more capability for exception handling.

Methods

getHTTPState :: m HTTPStateSource

Returns the opaque HTTPState object representing the state of the HTTP server. Should not be called directly by user code, except implementations of MonadHTTP; exported so that user monads can implement the interface.

Instances

Accepting requests

data HTTPServerParameters Source

A record used to configure the server. Broken informally into the four categories of logging, job-control, concurrency, and networking. For logging, the configuration contains optional paths to files for the access and error logs (if these are omitted, logging is not done). For job-control, it contains a flag indicating whether to run as a daemon, and optionally the names of a Unix user and/or group to switch to in the process of daemonization. For concurrency, it contains a forking primitive such as forkIO or forkOS. Finally, for networking, it contains a list of parameters for ports to listen on, each of which has its own sub-configuration record.

Notice that checking the value of the Host: header, and implementing virtual-host policies, is not done by direct-http but rather is up to the user of the library; hence, there is no information in the configuration about the hostnames to accept from the user-agent.

If the access logfile path is not Nothing, acceptLoop opens this logfile in append mode and uses it to log all accesses; otherwise, access is not logged.

If the error logfile path is not Nothing, acceptLoop opens this logfile in append mode and uses it to log all errors; otherwise, if not daemonizing, errors are logged to standard output; if daemonizing, errors are not logged.

If the daemonize flag is True, acceptLoop closes the standard IO streams and moves the process into the background, doing all the usual Unix things to make it run as a daemon henceforth. This is optional because it might be useful to turn it off for debugging purposes.

The forking primitive is typically either forkIO or forkOS, and is used by acceptLoop both to create listener threads, and to create connection threads. It is valid to use a custom primitive, such as one that attempts to pool OS threads, but it must actually provide concurrency - otherwise there will be a deadlock. There is no support for single-threaded operation.

Notice that we take the forking primitive in terms of IO, even though we actually lift it (with liftBaseDiscard). This is because lifted-base, as of this writing and its version 0.1.1, only supports forkIO and not forkOS.

The loop never returns, but will terminate the program with status 0 if and when it ever has no child threads alive; child threads for this purpose are those created through httpFork, which means all listener-socket and connection threads created by acceptLoop, as well as any threads created by client code through httpFork, but not threads created by client code through other mechanisms.

The author of direct-http has made no effort to implement custom thread-pooling forking primitives, but has attempted not to preclude them. If anyone attempts to implement such a thing, feedback is hereby solicited.

data HTTPListenSocketParameters Source

A record used to configure an individual port listener and its socket as part of the general server configuration. Consists of a host address and port number to bind the socket to, and a flag indicating whether the listener should use the secure version of the protocol.

acceptLoopSource

Arguments

:: HTTPServerParameters

Parameters describing the behavior of the server to run.

-> HTTP ()

A handler which is invoked once for each incoming connection.

-> IO ()

Never actually returns.

Takes a server parameters record and a handler, and concurrently accepts requests from user agents, forking with the primitive specified by the parameters and invoking the handler in the forked thread inside the HTTP monad for each request.

Note that although there is no mechanism to substitute another type of monad for HTTP, you can enter your own monad within the handler, much as you would enter your own monad within IO. You simply have to implement the MonadHTTP class.

Any exceptions not caught within the handler are caught by acceptLoop, and cause the termination of that handler, but not of the connection or the accept loop.

Logging

httpLog :: MonadHTTP m => String -> m ()Source

Logs a message using the web server's logging facility, prefixed with a timestamp.

Concurrency

httpFork :: MonadHTTP m => m () -> m ThreadIdSource

Forks a thread to run the given action, using the forking primitive that was passed in the configuration to acceptLoop, and additionally registers that thread with the main server thread, which has the sole effect and purpose of causing the server to not exit until and unless the child thread does. All of the listener-socket and connection threads created by the server go through this function.

Exceptions

data HTTPException Source

An exception originating within the HTTP infrastructure or the web server.

Constructors

ResponseHeadersAlreadySent

An exception thrown by operations which require the response headers not to have been sent yet.

ResponseHeadersNotModifiable

An exception thrown by operations which require the response headers to still be modifiable.

OutputAlreadyClosed

An exception thrown by operations which produce output when output has been closed, as by httpCloseOutput.

OutputIncomplete

An exception thrown when output is closed, as by httpCloseOutput, when the response headers imply that there will be a certain amount of data and there is not.

NotAResponseHeader Header

An exception thrown by operations which are given a header that does not meet their requirement of being valid in a response.

CookieNameInvalid String

An exception thrown by operations which are given cookie names that do not meet the appropriate syntax requirements.

NoConnection

An exception thrown by operations which expect a connection to exist (as it always does within a handler), when none does.

Request information

It is common practice for web servers to make their own extensions to the CGI/1.1 set of defined variables. For example, REMOTE_PORT is not defined by the specification, but often seen in the wild. Furthermore, it is also common for user agents to make their own extensions to the HTTP/1.1 set of defined headers. One might therefore expect to see functions defined here allowing direct interrogation of variables and headers by name. This is not done, because it is not the primary goal of direct-http to be a CGI/FastCGI host, and that functionality is trivial for any user code implementing such a host to provide. It would actually be rather more difficult for direct-http to provide many of the common values, because it does not implement the facilities they are supposed to give information about. Even as simple a concept as what server address is this must take into account name-canonicalization and virtual-host policies, which are left to user code. As for document root, it is possible to implement a server with no capacity to serve files, in which case the concept is nonsensical. Enough important values are necessarily absent for reasons such as these that there is little reason to provide the remaining ones either.

Too long, didn't read? Instead of providing access to CGI-like variables, direct-http provides higher-level calls which give convenient names and types to the same information. It does provide access to headers, however.

Cookies may also be manipulated through HTTP headers directly; the functions here are provided only as a convenience.

getRequestHeaderSource

Arguments

:: MonadHTTP m 
=> Header

The header to query. Must be a request or entity header.

-> m (Maybe String)

The value of the header, if the user agent provided one.

Queries the value from the user agent of the given HTTP/1.1 header. If the header is to be provided after the content as specified by the Trailer header, this is potentially time-consuming.

getAllRequestHeaders :: MonadHTTP m => m [(Header, String)]Source

Returns an association list of name-value pairs of all the HTTP/1.1 request or entity headers from the user agent. If some of these headers are to be provided after the content as specified by the Trailer header, this is potentially time-consuming.

data Cookie Source

An object representing a cookie (a small piece of information, mostly metadata, stored by a user-agent on behalf of the server), either one received as part of the request or one to be sent as part of the response.

Instances

getCookieSource

Arguments

:: MonadHTTP m 
=> String

The name of the cookie to look for.

-> m (Maybe Cookie)

The cookie, if the user agent provided it.

Returns a Cookie object for the given name, if the user agent provided one in accordance with RFC 2109.

getAllCookies :: MonadHTTP m => m [Cookie]Source

Returns all Cookie objects provided by the user agent in accordance RFC 2109.

getCookieValueSource

Arguments

:: MonadHTTP m 
=> String

The name of the cookie to look for.

-> m (Maybe String)

The value of the cookie, if the user agent provided it.

A convenience method; as getCookie, but returns only the value of the cookie rather than a Cookie object.

getRemoteAddress :: MonadHTTP m => m SockAddrSource

Return the remote address, which includes both host and port information. They are provided in the aggregate like this because it is the most internet-protocol-agnostic representation.

getRequestMethod :: MonadHTTP m => m StringSource

Return the request method.

getRequestURI :: MonadHTTP m => m StringSource

Return the request URI.

getServerAddress :: MonadHTTP m => m SockAddrSource

Return the server address and port, as a SockAddr. Useful for implementing virtual-hosting policies.

getContentLength :: MonadHTTP m => m (Maybe Int)Source

Return the request content length, if this is knowable without actually receiving the content - in particular, if the Content-Length header was used. Otherwise, returns Nothing.

getContentType :: MonadHTTP m => m (Maybe String)Source

Return the request content type, as provided by the user agent.

Request content data

At the moment the handler is invoked, all request headers have been received, but content data has not necessarily been. Requests to read content data block the handler (but not other concurrent handlers) until there is enough data in the buffer to satisfy them, or until timeout where applicable.

httpGet :: MonadHTTP m => Int -> m ByteStringSource

Reads up to a specified amount of data from the content of the HTTP request, if any, and interprets it as binary data. If input has been closed, returns an empty bytestring. If no input is immediately available, blocks until there is some. If output has been closed, causes an OutputAlreadyClosed exception.

httpGetNonBlocking :: MonadHTTP m => Int -> m ByteStringSource

Reads up to a specified amount of data from the content of the HTTP request, if any, and interprets it as binary data. If input has been closed, returns an empty bytestring. If insufficient input is available, returns any input which is immediately available, or an empty bytestring if there is none, never blocking. If output has been closed, causes an OutputAlreadyClosed exception.

httpGetContents :: MonadHTTP m => m ByteStringSource

Reads all remaining data from the content of the HTTP request, if any, and interprets it as binary data. Blocks until all input has been read. If input has been closed, returns an empty bytestring. If output has been closed, causes an OutputAlreadyClosed exception.

httpIsReadable :: MonadHTTP m => m BoolSource

Returns whether the content of the HTTP request potentially has data remaining, either in the buffer or yet to be read.

Response information and content data

When the handler is first invoked, neither response headers nor content data have been sent to the client. Setting of response headers is lazy, merely setting internal variables, until something forces them to be output. For example, attempting to send content data will force response headers to be output first. It is not necessary to close the output stream explicitly, but it may be desirable, for example to continue processing after returning results to the user.

There is no reason that client scripts cannot use any encoding they wish, including the chunked encoding, if they have set appropriate headers. This package, however, does not explicitly support that, because client scripts can easily implement it for themselves.

At the start of each request, the response status is set to 200 OK and the only response header set is Content-Type: text/html. These may be overridden by later calls, at any time before headers have been sent.

Cookies may also be manipulated through HTTP headers directly; the functions here are provided only as a convenience.

setResponseStatusSource

Arguments

:: MonadHTTP m 
=> Int

The HTTP/1.1 status code to set.

-> m () 

Sets the response status which will be sent with the response headers. If the response headers have already been sent, or are no longer modifiable (because of a call to httpPut or similar), causes a ResponseHeadersAlreadySent or ResponseHeadersNotModifiable exception.

getResponseStatusSource

Arguments

:: MonadHTTP m 
=> m Int

The HTTP/1.1 status code.

Returns the response status which will be or has been sent with the response headers.

setResponseHeaderSource

Arguments

:: MonadHTTP m 
=> Header

The header to set. Must be a response header or an entity header.

-> String

The value to set.

-> m () 

Sets the given response header to the given string value, overriding any value which has previously been set. If the response headers have already been sent, or are no longer modifiable (because of a call to httpPut or similar), causes a ResponseHeadersAlreadySent or ResponseHeadersNotModifiable exception. If the header is not an HTTP/1.1 or extension response, entity, or general header, ie, is not valid as part of a response, causes a NotAResponseHeader exception.

If a value is set for the HttpSetCookie header, this overrides all cookies set for this request with setCookie.

unsetResponseHeaderSource

Arguments

:: MonadHTTP m 
=> Header

The header to unset. Must be a response header or an entity header.

-> m () 

Causes the given Header response header not to be sent, overriding any value which has previously been set. If the response headers have already been sent, or are no longer modifiable (because of a call to httpPut or similar), causes a ResponseHeadersAlreadySent or ResponseHeadersNotModifiable exception. If the header is not an HTTP/1.1 or extension response or entity header, ie, is not valid as part of a response, causes a NotAResponseHeader exception.

Does not prevent the HttpSetCookie header from being sent if cookies have been set for this request with setCookie.

getResponseHeaderSource

Arguments

:: MonadHTTP m 
=> Header

The header to query. Must be a response header or an entity header.

-> m (Maybe String)

The value of the queried header.

Returns the value of the given header which will be or has been sent with the response headers. If the header is not an HTTP/1.1 or extension response, entity, or general header, ie, is not valid as part of a response, causes a NotAResponseHeader exception.

setCookieSource

Arguments

:: MonadHTTP m 
=> Cookie

The cookie to set.

-> m () 

Causes the user agent to record the given cookie and send it back with future loads of this page. Does not take effect instantly, but rather when headers are sent. Cookies are set in accordance with RFC 2109. If an HttpCookie header is set for this request by a call to setResponseHeader, this function has no effect. If the response headers have already been sent, or are no longer modifiable (because of a call to httpPut or similar), causes a ResponseHeadersAlreadySent or ResponseHeadersNotModifiable exception. If the name is not a possible name for a cookie, causes a CookieNameInvalid exception.

unsetCookieSource

Arguments

:: MonadHTTP m 
=> String

The name of the cookie to unset.

-> m () 

Causes the user agent to unset any cookie applicable to this page with the given name. Does not take effect instantly, but rather when headers are sent. If an HttpCookie header is set for this request by a call to setResponseHeader, this function has no effect. If the response headers have already been sent, or are no longer modifiable (because of a call to httpPut or similar), causes a ResponseHeadersAlreadySent or ResponseHeadersNotModifiable exception. If the name is not a possible name for a cookie, causes a CookieNameInvalid exception.

mkSimpleCookieSource

Arguments

:: String

The name of the cookie to construct.

-> String

The value of the cookie to construct.

-> Cookie

A cookie with the given name and value.

Constructs a cookie with the given name and value. Version is set to 1; path, domain, and maximum age are set to Nothing; and the secure flag is set to False. Constructing the cookie does not cause it to be set; to do that, call setCookie on it.

mkCookieSource

Arguments

:: String

The name of the cookie to construct.

-> String

The value of the cookie to construct.

-> Maybe String

The path of the cookie to construct.

-> Maybe String

The domain of the cookie to construct.

-> Maybe Int

The maximum age of the cookie to construct, in seconds.

-> Bool

Whether to flag the cookie to construct as secure.

-> Cookie

A cookie with the given parameters.

Constructs a cookie with the given parameters. Version is set to 1. Constructing the cookie does not cause it to be set; to do that, call setCookie on it.

permanentRedirectSource

Arguments

:: MonadHTTP m 
=> String

The URL to redirect to, as a string.

-> m () 

Sets the HTTP/1.1 return status to 301 and sets the HttpLocation header to the provided URL. This has the effect of issuing a permanent redirect to the user agent. Permanent redirects, as opposed to temporary redirects, may cause bookmarks or incoming links to be updated. If the response headers have already been sent, or are no longer modifiable (because of a call to httpPut or similar), causes a ResponseHeadersAlreadySent or ResponseHeadersNotModifiable exception.

seeOtherRedirectSource

Arguments

:: MonadHTTP m 
=> String

The URL to redirect to, as a string.

-> m () 

Sets the HTTP/1.1 return status to 303 and sets the HttpLocation header to the provided URL. This has the effect of issuing a see-other or temporary redirect to the user agent. Temporary redirects, as opposed to permanent redirects, do not cause bookmarks or incoming links to be updated. If the response headers have already been sent, or are no longer modifiable (because of a call to httpPut or similar), causes a ResponseHeadersAlreadySent or ResponseHeadersNotModifiable exception.

sendResponseHeaders :: MonadHTTP m => m ()Source

Ensures that the response headers have been sent. If they are already sent, does nothing. If output has already been closed, causes an OutputAlreadyClosed exception. Note that if the buffered identity output mode (the first mode of operation described for httpPut) is to be used, this function implies that there is no additional content beyond what has already been sent.

responseHeadersSent :: MonadHTTP m => m BoolSource

Returns whether the response headers have been sent, regardless of whether they are modifiable (they might not be because of a call to httpPut or similar).

responseHeadersModifiable :: MonadHTTP m => m BoolSource

Returns whether the response headers are modifiable, a prerequisite of which is that they have not already been sent. (They might not be modifiable because of a call to httpPut or similar.)

httpPut :: MonadHTTP m => ByteString -> m ()Source

Appends data, interpreted as binary, to the content of the HTTP response. Makes the response headers no longer modifiable, effective immediately. If output has already been closed, causes an OutputAlreadyClosed exception. If the response Transfer-Encoding as set in the response headers is identity or omitted, and the response Content-Length is omitted, data is buffered until output is closed, then sent all at once with an appropriate Content-Length header. Otherwise - that is, if there is a Transfer-Encoding other than identity set, or if Content-Length is set - data is sent immediately. If Content-Length is set, and the provided data would cause the cumulative data sent to exceed that length, causes an OutputAlreadyClosed exception. At the time that data is actually sent, if the response headers have not been sent, first sends them.

In other words, there are effectively three modes of operation for output. The first, simplest mode is used if the handler does nothing special. In this mode output is buffered and sent all at once; headers are not sent until this time. In this mode httpCloseOutput may be useful to force output to be sent before the handler returns, perhaps so that additional time-consuming processing can be done. This mode is easiest to use, in the sense that it requires no support on the handler's part, but probably the second mode should always be used instead.

The second mode is used if the handler sets a Transfer-Encoding, for example chunked, and no Content-Length. In this case headers are sent immediately upon the first httpPut or httpPutStr, and output is sent as it is provided. Output in this mode is transformed by httpPut into the appropriate transfer encoding. Thus handler code need only specify a transfer encoding, not actually implement that encoding itself. This mode is advantageous to allow user agents to begin displaying partial content as it is received, and particularly useful when the content is quite large or takes significant time to generate. If you are unsure which mode to use, it should probably be this one.

The third mode is used if the handler sets a Content-Length and no Transfer-Encoding. In this case headers are again sent immediately upon the first httpPut or httpPutStr, and output is again sent as it is provided. Output in this mode is not transformed. This may be more efficient than the second mode if output is generated in many small pieces, as it avoids computing and sending the length tags of the chunked encoding. However, it requires the content length to be known in advance of actually sending any content. It may be useful if you wish to have direct-http validate that the handler is well-behaved in sending a binary object of known size with no garbage inserted by spurious additional puts.

httpPutStr :: MonadHTTP m => String -> m ()Source

Appends text, encoded as UTF8, to the content of the HTTP response. In all respects this behaves as httpPut, but for the fact that it takes text rather than binary data.

httpCloseOutput :: MonadHTTP m => m ()Source

Informs the web server and the user agent that the request has completed. As side-effects, the response headers are sent if they have not yet been, any unread input is discarded and no more can be read, and any unsent output is sent. This is implicitly called, if it has not already been, after the handler returns; it may be useful within a handler if the handler wishes to return results and then perform time-consuming computations before exiting. If output has already been closed, causes an OutputAlreadyClosed exception. If the response headers imply that there will be a certain amount of data and there is not, causes an OutputIncomplete exception.

httpIsWritable :: MonadHTTP m => m BoolSource

Returns whether it is possible to write more data; ie, whether output has not yet been closed as by httpCloseOutput.