http-semantics-0.2.1: HTTP senmatics libarry
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.HTTP.Semantics.Server

Synopsis

HTTP server

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

Server type. 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.

The sending function must only be called once.

Request

data Request Source #

Request from client.

Instances

Instances details
Show Request Source # 
Instance details

Defined in Network.HTTP.Semantics.Server.Internal

Accessing request

requestMethod :: Request -> Maybe Method Source #

Getting the method from a request.

requestPath :: Request -> Maybe Path Source #

Getting the path from a request.

requestAuthority :: Request -> Maybe Authority Source #

Getting the authority from a request.

requestScheme :: Request -> Maybe Scheme Source #

Getting the scheme from a request.

requestHeaders :: Request -> TokenHeaderTable Source #

Getting the headers from a request.

requestBodySize :: Request -> Maybe Int Source #

Getting the body size from a request.

getRequestBodyChunk :: Request -> IO ByteString Source #

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

getRequestBodyChunk' :: Request -> IO (ByteString, Bool) Source #

Generalization of getRequestBodyChunk which also returns if the ByteString is the final one

getRequestTrailers :: Request -> IO (Maybe TokenHeaderTable) 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.

auxMySockAddr :: Aux -> SockAddr Source #

Local socket address copied from Config.

auxPeerSockAddr :: Aux -> SockAddr Source #

Remove socket address copied from Config.

Response

data Response Source #

Response from server.

Instances

Instances details
Show Response Source # 
Instance details

Defined in Network.HTTP.Semantics.Server.Internal

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.

Generalized streaming interface

data OutBodyIface Source #

Constructors

OutBodyIface 

Fields

  • outBodyUnmask :: forall x. IO x -> IO x

    Unmask exceptions in the thread spawned for the request body

    This is used in the client: we spawn the new thread for the request body with exceptions masked, and provide the body of OutBodyStreamingIface with a callback to unmask them again (typically after installing an exception handler).

    Unmasking in the server is a no-op, as here the scope of the thread that is spawned for the server is the entire handler, not just the response streaming body.

  • outBodyPush :: Builder -> IO ()

    Push a new chunk

    In http2, there is no direct correspondence between chunks and the resulting DATA frames sent: the chunks are collected (written to an internal write buffer) until we can fill a frame.

    See also outBodyFlush.

  • outBodyPushFinal :: Builder -> IO ()

    Push the final chunk

    Using this function instead of outBodyPush can be used to guarantee that the final HTTP2 DATA frame is marked end-of-stream; with outBodyPush it may happen that an additional empty DATA frame is used for this purpose. Additionally, after calling this function, outBodyCancel will be a no-op.

  • outBodyCancel :: Maybe SomeException -> IO ()

    Cancel the stream

    Sends a RST_STREAM to the peer. If cancelling as the result of an exception, a Just should be provided which specifies the exception which will be stored locally as the reason for cancelling the stream; in this case, the error code sent with the RST_STREAM will be INTERNAL_ERROR (see https://datatracker.ietf.org/doc/html/rfc7540#section-7). If Nothing is given, the error code will be CANCEL.

    If there is a partially constructed DATA frame at the time of cancellation, this frame is discarded. If this is undesirable, you should call outBodyFlush prior to cancelling.

  • outBodyFlush :: IO ()

    Flush

    This can be used to emit a DATA frame with the data collected so far (using outBodyPush), even if that DATA frame has not yet reached the maximum frame size. Calling outBodyFlush unnecessarily can therefore result in excessive overhead from frame headers.

    If no data is available to send, this is a no-op.

Accessing response

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.

Constructors

PushPromise 

Fields

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

Creating push promise. The third argument is traditional, not used.

Types

type Path = ByteString Source #

Path.

type Authority = String Source #

Authority.

type Scheme = ByteString Source #

"http" or "https".

data FileSpec Source #

File specification.

Instances

Instances details
Show FileSpec Source # 
Instance details

Defined in Network.HTTP.Semantics.Types

Eq FileSpec Source # 
Instance details

Defined in Network.HTTP.Semantics.Types

type FileOffset = Int64 Source #

Offset for file.

type ByteCount = Int64 Source #

How many bytes to read

Reading n bytes

type ReadN = Int -> IO ByteString Source #

Reading n bytes.

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

Naive implementation for readN.

NOTE: This function is intended to be used by a single thread only. (It is probably quite rare anyway to want concurrent reads from the same network socket.)

Position read

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

Position read for files.

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

Making a position read and its closer.

data Sentinel Source #

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.