second-transfer-0.10.0.4: Second Transfer HTTP/2 web server

Copyright(c) Alcides Viamontes Esquivel, 2015
LicenseBSD
Maintaineralcidesv@zunzun.se
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

SecondTransfer

Contents

Description

SecondTransfer is a HTTP/1.1 and HTTP/2 server session library, with an emphasis towards experimentation (so far).

This library implements enough of the HTTP/2 to build compliant HTTP/2 servers. It also implements enough of HTTP/1.1 so you can actually use it to build polyglot web-servers.

For HTTP/2, frame encoding and decoding is done with Kazu Yamamoto's http2 package. This library just takes care of making sense of sent and received frames.

The library

  • Is concurrent, meaning that you can use amazing Haskell lightweight threads to process the requests.
  • Obeys HTTP2 flow control aspects, when talking HTTP2.
  • And gives you freedom to (ab)use the HTTP/2 protocol in all the ways envisioned by the standard. In particular you should be able to process streaming requests (long uploads in POST or PUT requests) and to deliver streaming responses. You should even be able to do both simultaneously.

Setting up TLS for HTTP/2 correctly is a shore, so we have bundled here the TLS setup logic. Enable always the threaded ghc runtime in your final programs if you want TLS to work.

Here is how you create a very basic HTTP/2 webserver:

import SecondTransfer(
    AwareWorker
    , Footers
    , DataAndConclusion
    , tlsServeWithALPN
    , http2Attendant
    , http11Attendant
    , coherentToAwareWorker
    )
import SecondTransfer.Sessions(
      makeSessionsContext
    , defaultSessionsConfig
    )

import Data.Conduit


saysHello :: DataAndConclusion
saysHello = do
    -- The data in each yield will be automatically split across multiple
    -- data frames if needed, so you can yield a large block of contents here
    -- if you wish.
    -- If you do multiple yields, no data will be left buffered between them,
    -- so that you can for example implement a chat client in a single HTTP/2 stream.
    -- Not that browsers support that. 
    yield "Hello world!"
    -- The HTTP/2 protocol supports sending headers *after* stream data. So, you usually
    -- return an empty list to signal that you don't want any of those headers. 
    -- In these docs, the post headers are often called "footers".
    return []


helloWorldWorker :: AwareWorker
helloWorldWorker (_request_headers, _maybe_post_data) = coherentToAwareWorker $ do
    dropIncomingData _maybe_post_data
    return (
        [
            (":status", "200")
        ],
        [], -- No pushed streams
        saysHello
        )


-- For this program to work, it should be run from the top of
-- the developement directory.
main = do
    sessions_context <- makeSessionsContext defaultSessionsConfig
    let
        http2_attendant = http2Attendant sessions_context helloWorldWorker
        http11_attendant = http11Attendant sessions_context helloWorldWorker
    tlsServeWithALPN
        "tests/support/servercert.pem"   -- Server certificate
        "tests/support/privkey.pem"      -- Certificate private key
        "127.0.0.1"                      -- On which interface to bind
        [
            ("no-protocol", http11_attendant), -- The first protocol in the list is used when
                                               -- when no ALPN negotiation happens, and the
                                               -- name is really a filler.
            ("h2-14", http2_attendant),    -- Protocols present in the ALPN negotiation
            ("h2",    http2_attendant),    -- they may be slightly different, but for this
                                           -- test it doesn't matter.

            ("http1.1", http11_attendant) -- Let's talk HTTP1.1 if everything else fails.
        ]
        8000

AwareWorker is the type of the basic callback function that you need to implement, but most times you can do with a simplified version called CoherentWorker. The function coherentToAwareWorker does the conversion. The difference between the two callbacks is the level of information that you manage. With AwareWorker, you get a record on the request with all sort of details, things like the session id, the protocol the client is using and in the future things like the remote address.

The callback is used to handle all requests to the server on a given negotiated ALPN protocol. If you need routing functionality (and you most certainly will need it), you need to build that functionality inside the callback.

The above program uses a test certificate by a fake certificate authority. The certificate is valid for the server name ("authority", in HTTP/2 lingo) www.httpdos.com. So, in order for the above program to run, you probably need to add an alias to your /etc/hosts file. You also need very up-to-date versions of OpenSSL (I'm using OpenSSL 1.0.2) to be compliant with the cipher suites demanded by HTTP/2. The easiest way to test the above program is using a fairly recent version of curl. If everything is allright, you should be able to do:

   $ curl -k --http2 https://www.httpdos.com:8000/
   Hello world!

Synopsis

Types related to coherent workers

A coherent worker is an abstraction that can dance at the tune of HTTP2 and HTTP1.1. That is, it should be able to take headers from a request first, then a source of data coming in the request (for example, POST data). Even before exhausting the source, the coherent worker can post the response headers and its source for the response data. A coherent worker can also present streams to push to the client.

type Headers = [Header]

List of headers. The first part of each tuple is the header name (be sure to conform to the HTTP/2 convention of using lowercase) and the second part is the headers contents. This list needs to include the special :method, :scheme, :authority and :path pseudo-headers for requests; and :status (with a plain numeric value represented in ascii digits) for responses.

type HeaderName = ByteString

The name part of a header

type HeaderValue = ByteString

The value part of a header

type Header = (HeaderName, HeaderValue)

The complete header

data Request

A request is a set of headers and a request body.... which will normally be empty, except for POST and PUT requests. But this library enforces none of that.

type Footers = FinalizationHeaders

Finalization headers

type CoherentWorker = TupledRequest -> IO TupledPrincipalStream

A CoherentWorker is a simplified callback that you can implement to handle requests. Then you can convert it to an AwareWorker with tupledPrincipalStreamToPrincipalStream.

type AwareWorker = Request -> IO PrincipalStream

Main type of this library. You implement one of these for your server. This is a callback that the library calls as soon as it has all the headers of a request. For GET requests that's the entire request basically, but for POST and PUT requests this is just before the data starts arriving to the server.

It is important that you consume the data in the cases where there is an input stream, otherwise the memory is lost for the duration of the request, and a malicious client can use that.

Also, notice that when handling requests your worker can be interrupted with an asynchronous exception of type StreamCancelledException, if the peer cancels the stream

data PrincipalStream

You use this type to answer a request. The Headers are thus response headers and they should contain the :status pseudo-header. The PushedStreams is a list of pushed streams... they will be pushed to the client.

type PushedStreams = [IO PushedStream]

A list of pushed streams. Notice that a list of IO computations is required here. These computations only happen when and if the streams are pushed to the client. The lazy nature of Haskell helps to avoid unneeded computations if the streams are not going to be sent to the client.

data PushedStream

A pushed stream, represented by a list of request headers, a list of response headers, and the usual response body (which may include final footers (not implemented yet)).

type DataAndConclusion = ConduitM () ByteString AwareWorkerStack Footers

A source-like conduit with the data returned in the response. The return value of the conduit is a list of footers. For now that list can be anything (even bottom), I'm not handling it just yet.

type InputDataStream = Source AwareWorkerStack ByteString

This is a Source conduit (see Haskell Data.Conduit library from Michael Snoyman) that you can use to retrieve the data sent by the peer piece-wise.

type FinalizationHeaders = Headers

Finalization headers. If you don't know what they are, chances are that you don't need to worry about them for now. The support in this library for those are at best sketchy.

How to couple bidirectional data channels to sessions

type Attendant = ConnectionData -> IOCallbacks -> IO ()

An Attendant is an entity that can speak a protocol, given the presented I/O callbacks. It's work is to spawn a set of threads to handle a client's session, and then return to the caller. It shouldn'r busy the calling thread.

http11Attendant :: SessionsContext -> AwareWorker -> Attendant

Session attendant that speaks HTTP/1.1

This attendant should be OK with keep-alive, but not with pipelining.

http2Attendant :: SessionsContext -> AwareWorker -> Attendant

     http2Attendant :: AwareWorker -> AttendantCallbacks ->  IO ()

Given a AwareWorker, this function wraps it with flow control, multiplexing, and state maintenance needed to run an HTTP/2 session.

Notice that this function is using HTTP/2 over TLS.

High level OpenSSL functions.

Use these functions to create your TLS-compliant HTTP/2 server in a snap.

tlsServeWithALPN

Arguments

:: TLSContext ctx session 
=> Proxy ctx

This is a simple proxy type from Typeable that is used to select the type of TLS backend to use during the invocation

-> ConnectionCallbacks

Control and log connections

-> ByteString

String with contents of certificate chain

-> ByteString

String with contents of PKCS #8 key

-> String

Name of the network interface

-> NamedAttendants

List of attendants and their handlers

-> Int

Port to listen for connections

-> IO () 

Convenience function to open a port and listen there for connections and select protocols and so on.

dropIncomingData :: MonadIO m => Maybe InputDataStream -> m ()

If you are not processing the potential POST input in a request, use this consumer to drop the data to oblivion. Otherwise it will remain in an internal queue until the client closes the stream, and if the client doesn't want to do so....