http-listen-0.1.0.0: Listen to HTTP requests and handle them in arbitrary ways.

Safe HaskellNone
LanguageHaskell2010

Network.HTTP.Listen

Contents

Description

This module offers several ways to create an HTTP listener, hopefully covering common use cases. They are described below, from high level to low level. But before that, here's a quick start example.

Quickstart

Create a source file containing the following:

import qualified Data.ByteString.Lazy as B
import           Network.HTTP
import           Network.HTTP.Listen

listener :: Listener B.ByteString IO
listener request = print request >> return Nothing

main :: IO
main = run 8999 listener

Install the http-listen package from Hackage:

$ cabal install http-listen

Run the program:

$ runhaskell hello.hs

Now point your web browser to http://localhost:8999. It will fail to load anything, since our listener doesn't send any response, but in the terminal you'll see the HTTP request printed.

Running a Listener

A Listener is a function which takes an HTTP request and returns an action in some monad m. Since receiving HTTP requests is an IO activity, m must be a MonadIO instance. For example, the IO monad itself, or a monad transformer stack on top of IO.

The IO action optionally returns an HTTP response, which is then sent back to the client. Setting up the headers of the response, and in particular the connection header (which affects HTTP connection persistence), are up to the listener. The library decides based on it (and based on the request) whether to close the connection or keep it open. If you don't need to send anything back to the client, just write your listener function to return Nothing.

A Listener handles requests with content encoded into a specific type. That type must be an instance of HStream (a class from the HTTP package). The HTTP package provides instances for String and for strict and lazy bytestrings. You can write your own instances, but in most cases you probably won't need to. Perhaps instances for Text and its lazy version could be useful.

Here is an example listener, which takes requests containing lazy ByteString data, and returns an IO action. All it does is print the HTTP request it got into standard output.

import qualified Data.ByteString.Lazy as B
import           Network.HTTP
import           Network.HTTP.Listen

listener :: Listener B.ByteString IO
listener request = do
    print request
    return Nothing

Once we've defined the listener, we can run a loop which listens to TCP connections, reads HTTP responses from them and applies our listener function. There are two ready functions which run such a loop, run and runWithBlocking. The difference is that run handles each connection in a separate thread (using forkIO), while runWithBlocking does everything in a single thread.

Both functions take 2 parameters. A port number and the listener function. For example, run our listener on port 8999 like this:

run 8999 listener

Another difference between blocking and non-blocking runs, is that blocking runs support listeners operating in any instance of MonadIO and MonadMask, while non-blocking ones are IO only. This may seem like a restriction, but it actually makes sense: When using a single thread, you can use some monad transformer stack with state and logging and other effects. When forking to a new thread on each connection, you don't use or need any extra effects because the logic happens in a separate thread. In that separate thread you can use whatever monad(s) you wish.

On the technical side, forkIO takes an IO action of type IO (), so that's what the non-blocking run needs to use.

Handling Clients

To get a bit more control, you can write your own (blocking or non-blocking) client handling loop. The primary components are:

There are a few more utility functions you may find useful.

Let's write a simple loop which accepts connections from clients and handles them in separate worker threads which apply our listener. We'll use the same listener from the previous section.

listener :: Listener B.ByteString IO
listener request = { ... same as above .... }

main =
    bracket
        (prepareSocket 8999)
        close
        (\ sock -> forever $ handleClient sock listener)

Manual Control

This is the lowest level layer provided by this module. It wraps the relevant parts of the network and HTTP packages, creating a network API for web listeners. It may be useful if you need more flexibility that the higher level layers can provide.

Let's write a simple program using this API, which handles a single connection and exits. For simplicity, we'll assume a single HTTP request is received per connection, so we'll close the connection after getting one request. In reality, connections can be used for sending multiple requests (in HTTP 1.1, connection reuse is the default behavior).

As usual, we begin by preparing a server socket:

main :: IO ()
main = do
    sock <- prepareSocket 8999
    -- ...

Then we wait for a connection from a client:

main = do
    sock <- prepareSocket 8999
    conn <- acceptConnection sock
    -- ...

Once we have a connection, we open a stream for receiving data. After opening a stream successfully, we don't need the connection value anymore (the stream value is now holding the newly open socket).

Opening a stream and further actions could happen in a separate thread, so that all the main thread does is accept connections. For simplicity, let's just do this in the same thread.

main = do
    sock <- prepareSocket 8999
    conn <- acceptConnection sock
    stream <- openStream conn
    -- ...

Now we can read an HTTP request from the client:

main = do
    sock <- prepareSocket 8999
    conn <- acceptConnection sock
    stream <- openStream conn
    result <- receiveRequest stream
    -- ...

Since we're done with the connection, let's close the stream. We're also done accepting connections, so let's close the server socket too.

main = do
    sock <- prepareSocket 8999
    conn <- acceptConnection sock
    stream <- openStream conn
    result <- receiveRequest stream
    closeStream stream
    close sock
    -- ...

Finally, let's display what we got:

main = do
    sock <- prepareSocket 8999
    conn <- acceptConnection sock
    stream <- openStream conn
    result <- receiveRequest stream
    closeStream stream
    close sock
    case result of
        Left err -> print err
        Right (request :: Request B.ByteString) -> print request

This is of course over simplified. We didn't consider connection persistence. We should probably handle exceptions here to make sure the sockets are safely closed even in case of error, e.g. using bracket. We could also use a timeout to avoid accumulating unused connections. But all of that can be done on top of the basics shown above, or using the higher level APIs.

Synopsis

Basics

data Connection Source

Handle to a connection from an HTTP client (technically, a TCP client in general).

data Stream t Source

A stream of data passing over a Connection.

prepareSocket :: Int -> IO Socket Source

Initialize a server socket and start listening to connections from clients. After calling this, the returned socket can accept connections.

acceptConnection :: Socket -> IO Connection Source

Given an initialized server socket, wait for a connection from a client. It can be called repeatedly, in a loop, by the main server thread to accept all the incoming connections.

openStream :: HStream t => Connection -> IO (Stream t) Source

Open a data stream over a connection. The stream holds the connection state too, so after calling this function you don't need the Connection value anymore.

receiveRequest :: HStream t => Stream t -> IO (Result (Request t)) Source

Read an HTTP request from an open stream.

sendResponse :: HStream t => Stream t -> Response t -> IO () Source

Send an HTTP response back to the client through the open stream.

closeStream :: HStream t => Stream t -> IO () Source

Close an open stream. This closes the connection with the client. Don't try to send or receive anything from the stream after closing it.

closeConnection :: Connection -> IO () Source

Close an open connection. Use this only if you want to close the connection before opening a stream. If you opened a stream over the connection, use closeStream to close it.

Utilities

data HttpVersion Source

An HTTP protocol version.

Constructors

HttpVersion Int Int 

Instances

parseHttpVersion :: String -> Maybe HttpVersion Source

Parse an HTTP version string, e.g. "HTTP/1.1", into an HttpVersion value. If the string isn't a valid version string, return Nothing.

class HasHttpVersion a where Source

A class for types which have an HTTP version. In other words, an HTTP request or an HTTP response (but other instances are of course possible if you need then for any reason).

httpVersion' :: HasHttpVersion r => r -> HttpVersion Source

This is like httpVersion, but returns a default version (currently HTTP 1.0) if the no version is explicity specified.

reqPersist :: Request t -> Bool Source

Check whether the request indicates the connection should be persistent.

respPersist :: Response t -> Bool Source

Check whether, assuming the request indicated a persistent connection, the given response too indicates the connection should persist.

persist :: Request t -> Response t -> Bool Source

Check whether, given the request and its response, the connection should persist (i.e. kept open after the response it sent).

pipelined :: Request t -> Bool Source

Check whether the connection should be pipelined, i.e. whether the server should allow the client to receive multiple requests without waiting for the response every time.

Client Handling

type Listener t m = Request t -> m (Maybe (Response t)) Source

An HTTP listener application. It gets an HTTP request with a body encoded as type t, and returns an IO action to run in reaction to the request. The action can optionally return an HTTP response, which will be sent back to the client.

listenerNull :: Listener ByteString IO Source

This listener does nothing. Perhaps it can be useful for benchmarking. Anyway, it's here for completeness.

listenerPrint :: Listener ByteString IO Source

This listener prints the request details to the console (stdout).

listenerPong :: Listener ByteString IO Source

This listener sends the message "It works!", and the request body if any, back to the client.

handleRequest :: (HStream t, MonadIO m) => Stream t -> Listener t m -> m Bool Source

Read a single request from the stream. If successful, apply the listener function to it and send back a response if it returns one. Finally, return whether the connection should persist (True) or close (False).

handleClient :: HStream t => Socket -> Listener t IO -> IO () Source

Wait for a connection from a client. When it arrives, fork to a new thread. In that thread, receive HTTP requests and handle them using the listener. Finally, close the connection.

handleClientBlocking :: (HStream t, MonadIO m) => Socket -> Listener t m -> m () Source

Like handleClient, but run everything in the current thread instead of forking to a new one. Note that the listener itself could launch actions in new threads.

Running

run :: HStream t => Int -> Listener t IO -> IO () Source

Run an HTTP listener. Open a server socket, listen to connections from clients and handle them using the listener in separate worker threads.

runWithBlocking :: (HStream t, MonadIO m, MonadMask m) => Int -> Listener t m -> m () Source

Like run, but does everything in the current thread instead of forking to a new one. Note that the listener itself could launch actions in new threads.