http2-2.0.0: HTTP/2 library

Safe HaskellNone
LanguageHaskell2010

Network.HTTP2.Server

Contents

Description

HTTP/2 server library.

Example:

{-# LANGUAGE OverloadedStrings #-}
module Main (main) where

import Control.Concurrent (forkFinally)
import qualified Control.Exception as E
import Control.Monad (forever, void)
import Data.ByteString.Builder (byteString)
import Network.HTTP.Types (ok200)
import Network.HTTP2.Server
import Network.Socket

main :: IO ()
main = withSocketsDo $ do
    addr <- resolve "80"
    E.bracket (open addr) close loop
  where
    server _req _ctl sendResponse = sendResponse response []
      where
        response = responseBuilder ok200 [("Content-Type", "text/plain")] (byteString "Hello, world!\n")
    loop sock = forever $ do
        (s, _peer) <- accept sock
        (config, cleanup) <- makeSimpleConfig s 4096
        void $ forkFinally (run config server) (\_ -> close s >> cleanup)
    resolve port = do
        let hints = defaultHints {
                addrFlags = [AI_PASSIVE]
              , addrSocketType = Stream
              }
        addr:_ <- getAddrInfo (Just hints) Nothing (Just port)
        return addr
    open addr = do
        sock <- socket (addrFamily addr) (addrSocketType addr) (addrProtocol addr)
        setSocketOption sock ReuseAddr 1
        withFdSocket sock $ setCloseOnExecIfNeeded
        bind sock (addrAddress addr)
        listen sock 10
        return sock
Synopsis

Runner

run :: Config -> Server -> IO () Source #

Running HTTP/2 server.

Runner arguments

makeSimpleConfig :: Socket -> BufferSize -> IO (Config, IO ()) Source #

Making configuration whose IO is not efficient. A write buffer is allocated internally. That should be deallocated by the returned action.

HTTP/2 server

type Server = Request -> Aux -> (Response -> [PushPromise] -> IO ()) -> IO () Source #

HTTP/2 server takes a HTTP request, should generate a HTTP response and push promises, then should give them to the sending function. The sending function would throw exceptions so that they can be logged.

Request

data Request Source #

HTTP request.

requestHeaders :: Request -> HeaderTable Source #

Accessor for request headers.

requestBodySize :: Request -> Maybe Int Source #

Accessor for body length specified in content-length:.

getRequestBodyChunk :: Request -> IO ByteString Source #

Reading a chunk of the request body. An empty ByteString returned when finished.

getRequestTrailers :: Request -> IO (Maybe HeaderTable) Source #

Reading request trailers. This function must be called after getRequestBodyChunk returns an empty.

Aux

data Aux Source #

Additional information.

auxTimeHandle :: Aux -> Handle Source #

Time handle for the worker processing this request and response.

Response

data Response Source #

HTTP response.

Creating response

responseNoBody :: Status -> ResponseHeaders -> Response Source #

Creating response without body.

responseFile :: Status -> ResponseHeaders -> FileSpec -> Response Source #

Creating response with file.

responseStreaming :: Status -> ResponseHeaders -> ((Builder -> IO ()) -> IO () -> IO ()) -> Response Source #

Creating response with streaming.

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

Creating response with builder.

Accessing response

responseStatus :: Response -> Status Source #

Accessor for response status.

responseBodySize :: Response -> Maybe Int Source #

Getter for response body size. This value is available for file body.

Trailers maker

type TrailersMaker = Maybe ByteString -> IO NextTrailersMaker Source #

Trailers maker. A chunks of the response body is passed with Just. The maker should update internal state with the ByteString and return the next trailers maker. When response body reaches its end, Nothing is passed and the maker should generate trailers. An example:

{-# LANGUAGE BangPatterns #-}
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as C8
import Crypto.Hash (Context, SHA1) -- cryptonite
import qualified Crypto.Hash as CH

-- Strictness is important for Context.
trailersMaker :: Context SHA1 -> Maybe ByteString -> IO NextTrailersMaker
trailersMaker ctx Nothing = return $ Trailers [("X-SHA1", sha1)]
  where
    !sha1 = C8.pack $ show $ CH.hashFinalize ctx
trailersMaker ctx (Just bs) = return $ NextTrailersMaker $ trailersMaker ctx'
  where
    !ctx' = CH.hashUpdate ctx bs

Usage example:

let h2rsp = responseFile ...
    maker = trailersMaker (CH.hashInit :: Context SHA1)
    h2rsp' = setResponseTrailersMaker h2rsp maker

data NextTrailersMaker Source #

Either the next trailers maker or final trailers.

defaultTrailersMaker :: TrailersMaker Source #

TrailersMake to create no trailers.

Push promise

data PushPromise Source #

HTTP/2 push promise or sever push. Pseudo REQUEST headers in push promise is automatically generated. Then, a server push is sent according to promiseResponse.

pushPromise :: ByteString -> Response -> Weight -> PushPromise Source #

Creating push promise.

promiseRequestPath :: PushPromise -> ByteString Source #

Accessor for a URL path in a push promise (a virtual request from a server). E.g. "/style/default.css".

promiseResponse :: PushPromise -> Response Source #

Accessor for response actually pushed from a server.

promiseWeight :: PushPromise -> Weight Source #

Accessor for response weight.

Types

data FileSpec Source #

File specification.

Instances
Eq FileSpec Source # 
Instance details

Defined in Network.HTTP2.Server.API

Show FileSpec Source # 
Instance details

Defined in Network.HTTP2.Server.API

type FileOffset = Int64 Source #

Offset for file.

type ByteCount = Int64 Source #

How many bytes to read

RecvN

defaultReadN :: Socket -> IORef (Maybe ByteString) -> Int -> IO ByteString Source #

Naive implementation for readN.

Position read for files

type PositionReadMaker = FilePath -> IO (PositionRead, Sentinel) Source #

Making a position read and its closer.

type PositionRead = FileOffset -> ByteCount -> Buffer -> IO ByteCount Source #

Position read for files.

data Sentinel Source #

Manipulating a file resource.

Constructors

Closer (IO ())

Closing a file resource. Its refresher is automatiaclly generated by the internal timer.

Refresher (IO ())

Refreshing a file resource while reading. Closing the file must be done by its own timer or something.