warp-3.1.9: A fast, light-weight web server for WAI applications.

Safe HaskellNone
LanguageHaskell98

Network.Wai.Handler.Warp

Contents

Description

A fast, light-weight HTTP server handler for WAI.

HTTP/1.0, HTTP/1.1 and HTTP/2 are supported. For HTTP/2, Warp supports direct and ALPN (in TLS) but not upgrade.

Note on slowloris timeouts: to prevent slowloris attacks, timeouts are used at various points in request receiving and response sending. One interesting corner case is partial request body consumption; in that case, Warp's timeout handling is still in effect, and the timeout will not be triggered again. Therefore, it is recommended that once you start consuming the request body, you either:

  • consume the entire body promptly
  • call the pauseTimeout function

For more information, see https://github.com/yesodweb/wai/issues/351.

Synopsis

Run a Warp server

All of these automatically serve the same Application over HTTP/1, HTTP/1.1, and HTTP/2.

run :: Port -> Application -> IO () Source #

Run an Application on the given port. This calls runSettings with defaultSettings.

runEnv :: Port -> Application -> IO () Source #

Run an Application on the port present in the PORT environment variable. Uses the Port given when the variable is unset. This calls runSettings with defaultSettings.

Since 3.0.9

runSettings :: Settings -> Application -> IO () Source #

Run an Application with the given Settings. This opens a listen socket on the port defined in Settings and calls runSettingsSocket.

runSettingsSocket :: Settings -> Socket -> Application -> IO () Source #

This installs a shutdown handler for the given socket and calls runSettingsConnection with the default connection setup action which handles plain (non-cipher) HTTP. When the listen socket in the second argument is closed, all live connections are gracefully shut down.

The supplied socket can be a Unix named socket, which can be used when reverse HTTP proxying into your application.

Note that the settingsPort will still be passed to Applications via the serverPort record.

Run an HTTP/2-aware server

Each of these takes an HTTP/2-aware application as well as a backup Application to be used for HTTP/1.1 and HTTP/1 connections. These are only needed if your application needs access to HTTP/2-specific features such as trailers or pushed streams.

runHTTP2 :: Port -> HTTP2Application -> Application -> IO () Source #

Serve an HTTP2Application and an Application together on the given port.

runHTTP2Env :: Port -> HTTP2Application -> Application -> IO () Source #

The HTTP/2-aware form of runEnv.

Settings

data Settings Source #

Various Warp server settings. This is purposely kept as an abstract data type so that new settings can be added without breaking backwards compatibility. In order to create a Settings value, use defaultSettings and the various 'set' functions to modify individual fields. For example:

setTimeout 20 defaultSettings

defaultSettings :: Settings Source #

The default settings for the Warp server. See the individual settings for the default value.

Setters

setPort :: Port -> Settings -> Settings Source #

Port to listen on. Default value: 3000

Since 2.1.0

setHost :: HostPreference -> Settings -> Settings Source #

Interface to bind to. Default value: HostIPv4

Since 2.1.0

setOnException :: (Maybe Request -> SomeException -> IO ()) -> Settings -> Settings Source #

What to do with exceptions thrown by either the application or server. Default: defaultOnException

Since 2.1.0

setOnExceptionResponse :: (SomeException -> Response) -> Settings -> Settings Source #

A function to create a Response when an exception occurs.

Default: defaultOnExceptionResponse

Since 2.1.0

setOnOpen :: (SockAddr -> IO Bool) -> Settings -> Settings Source #

What to do when a connection is opened. When False is returned, the connection is closed immediately. Otherwise, the connection is going on. Default: always returns True.

Since 2.1.0

setOnClose :: (SockAddr -> IO ()) -> Settings -> Settings Source #

What to do when a connection is closed. Default: do nothing.

Since 2.1.0

setTimeout :: Int -> Settings -> Settings Source #

Timeout value in seconds. Default value: 30

Since 2.1.0

setManager :: Manager -> Settings -> Settings Source #

Use an existing timeout manager instead of spawning a new one. If used, settingsTimeout is ignored.

Since 2.1.0

setFdCacheDuration :: Int -> Settings -> Settings Source #

Cache duration time of file descriptors in seconds. 0 means that the cache mechanism is not used.

The FD cache is an optimization that is useful for servers dealing with static files. However, if files are being modified, it can cause incorrect results in some cases. Therefore, we disable it by default. If you know that your files will be static or you prefer performance to file consistency, it's recommended to turn this on; a reasonable value for those cases is 10. Enabling this cache results in drastic performance improvement for file transfers.

Default value: since 3.0.13, default value is 0, was previously 10

setBeforeMainLoop :: IO () -> Settings -> Settings Source #

Code to run after the listening socket is ready but before entering the main event loop. Useful for signaling to tests that they can start running, or to drop permissions after binding to a restricted port.

Default: do nothing.

Since 2.1.0

setNoParsePath :: Bool -> Settings -> Settings Source #

Perform no parsing on the rawPathInfo.

This is useful for writing HTTP proxies.

Default: False

Since 2.1.0

setInstallShutdownHandler :: (IO () -> IO ()) -> Settings -> Settings Source #

A code to install shutdown handler.

For instance, this code should set up a UNIX signal handler. The handler should call the first argument, which close the listen socket, at shutdown.

Default: does not install any code.

Since 3.0.1

setServerName :: ByteString -> Settings -> Settings Source #

Default server name if application does not set one.

Since 3.0.2

setMaximumBodyFlush :: Maybe Int -> Settings -> Settings Source #

The maximum number of bytes to flush from an unconsumed request body.

By default, Warp does not flush the request body so that, if a large body is present, the connection is simply terminated instead of wasting time and bandwidth on transmitting it. However, some clients do not deal with that situation well. You can either change this setting to Nothing to flush the entire body in all cases, or in your application ensure that you always consume the entire request body.

Default: 8192 bytes.

Since 3.0.3

setFork :: (((forall a. IO a -> IO a) -> IO ()) -> IO ()) -> Settings -> Settings Source #

Code to fork a new thread to accept a connection.

This may be useful if you need OS bound threads, or if you wish to develop an alternative threading model.

Default: void . forkIOWithUnmask

Since 3.0.4

setProxyProtocolNone :: Settings -> Settings Source #

Do not use the PROXY protocol.

Since 3.0.5

setProxyProtocolRequired :: Settings -> Settings Source #

Require PROXY header.

This is for cases where a "dumb" TCP/SSL proxy is being used, which cannot add an X-Forwarded-For HTTP header field but has enabled support for the PROXY protocol.

See http://www.haproxy.org/download/1.5/doc/proxy-protocol.txt and http://docs.aws.amazon.com/ElasticLoadBalancing/latest/DeveloperGuide/TerminologyandKeyConcepts.html#proxy-protocol.

Only the human-readable header format (version 1) is supported. The binary header format (version 2) is not supported.

Since 3.0.5

setProxyProtocolOptional :: Settings -> Settings Source #

Use the PROXY header if it exists, but also accept connections without the header. See setProxyProtocolRequired.

WARNING: This is contrary to the PROXY protocol specification and using it can indicate a security problem with your architecture if the web server is directly accessable to the public, since it would allow easy IP address spoofing. However, it can be useful in some cases, such as if a load balancer health check uses regular HTTP without the PROXY header, but proxied connections do include the PROXY header.

Since 3.0.5

setSlowlorisSize :: Int -> Settings -> Settings Source #

Size in bytes read to prevent Slowloris protection. Default value: 2048

Since 3.1.2

setHTTP2Disabled :: Settings -> Settings Source #

Disable HTTP2.

Since 3.1.7

Getters

getPort :: Settings -> Port Source #

Get the listening port.

Since 2.1.1

getHost :: Settings -> HostPreference Source #

Get the interface to bind to.

Since 2.1.1

getOnOpen :: Settings -> SockAddr -> IO Bool Source #

Get the action on opening connection.

getOnClose :: Settings -> SockAddr -> IO () Source #

Get the action on closeing connection.

getOnException :: Settings -> Maybe Request -> SomeException -> IO () Source #

Get the exception handler.

Exception handler

defaultOnException :: Maybe Request -> SomeException -> IO () Source #

Printing an exception to standard error if defaultShouldDisplayException returns True.

Since: 3.1.0

defaultShouldDisplayException :: SomeException -> Bool Source #

Apply the logic provided by defaultOnException to determine if an exception should be shown or not. The goal is to hide exceptions which occur under the normal course of the web server running.

Since 2.1.3

Exception response handler

defaultOnExceptionResponse :: SomeException -> Response Source #

Sending 400 for bad requests. Sending 500 for internal server errors.

Since: 3.1.0

exceptionResponseForDebug :: SomeException -> Response Source #

Exception handler for the debugging purpose. 500, text/plain, a showed exception.

Since: 2.0.3.2

Data types

data HostPreference :: * #

Which host to bind.

Note: The IsString instance recognizes the following special values:

  • * means HostAny - "any IPv4 or IPv6 hostname"
  • *4 means HostIPv4 - "any IPv4 or IPv6 hostname, IPv4 preferred"
  • !4 means HostIPv4Only - "any IPv4 hostname"
  • *6 means HostIPv6@ - "any IPv4 or IPv6 hostname, IPv6 preferred"
  • !6 means HostIPv6Only - "any IPv6 hostname"

Note that the permissive * values allow binding to an IPv4 or an IPv6 hostname, which means you might be able to successfully bind to a port more times than you expect (eg once on the IPv4 localhost 127.0.0.1 and again on the IPv6 localhost 0:0:0:0:0:0:0:1).

Any other value is treated as a hostname. As an example, to bind to the IPv4 local host only, use "127.0.0.1".

type Port = Int Source #

TCP port number.

Utilities

pauseTimeout :: Request -> IO () Source #

Explicitly pause the slowloris timeout.

This is useful for cases where you partially consume a request body. For more information, see https://github.com/yesodweb/wai/issues/351

Since 3.0.10

Internal

The following APIs will be removed in Warp 3.2.0. Please use ones exported from Network.Wai.Handler.Warp.Internal.

Low level run functions

runSettingsConnection :: Settings -> IO (Connection, SockAddr) -> Application -> IO () Source #

The connection setup action would be expensive. A good example is initialization of TLS. So, this converts the connection setup action to the connection maker which will be executed after forking a new worker thread. Then this calls runSettingsConnectionMaker with the connection maker. This allows the expensive computations to be performed in a separate worker thread instead of the main server loop.

Since 1.3.5

runSettingsConnectionMaker :: Settings -> IO (IO Connection, SockAddr) -> Application -> IO () Source #

This modifies the connection maker so that it returns TCP for Transport (i.e. plain HTTP) then calls runSettingsConnectionMakerSecure.

runSettingsConnectionMakerSecure :: Settings -> IO (IO (Connection, Transport), SockAddr) -> Application -> IO () Source #

The core run function which takes Settings, a connection maker and Application. The connection maker can return a connection of either plain HTTP or HTTP over TLS.

Since 2.1.4

data Transport Source #

What kind of transport is used for this connection?

Constructors

TCP

Plain channel: TCP

TLS

Encrypted channel: TLS or SSL

Fields

Connection

data Connection Source #

Data type to manipulate IO actions for connections. This is used to abstract IO actions for plain HTTP and HTTP over TLS.

Constructors

Connection 

Fields

socketConnection :: Socket -> IO Connection Source #

Creating Connection for plain HTTP based on a given socket.

Buffer

type Buffer = Ptr Word8 Source #

Type for buffer

type BufSize = Int Source #

Type for buffer size

bufferSize :: BufSize Source #

The default size of the write buffer: 16384 (2^14 = 1024 * 16). This is the maximum size of TLS record. This is also the maximum size of HTTP/2 frame payload (excluding frame header).

allocateBuffer :: Int -> IO Buffer Source #

Allocating a buffer with malloc().

freeBuffer :: Buffer -> IO () Source #

Releasing a buffer with free().

Sendfile

data FileId Source #

Data type to abstract file identifiers. On Unix, a file descriptor would be specified to make use of the file descriptor cache.

Since: 3.1.0

Constructors

FileId 

type SendFile = FileId -> Integer -> Integer -> IO () -> [ByteString] -> IO () Source #

fileid, offset, length, hook action, HTTP headers

Since: 3.1.0

sendFile :: Socket -> Buffer -> BufSize -> (ByteString -> IO ()) -> SendFile Source #

Function to send a file based on sendfile() for Linux/Mac/FreeBSD. This makes use of the file descriptor cache. For other OSes, this is identical to readSendFile.

Since: 3.1.0

readSendFile :: Buffer -> BufSize -> (ByteString -> IO ()) -> SendFile Source #

Function to send a file based on pread()/send() for Unix. This makes use of the file descriptor cache. For Windows, this is emulated by Handle.

Since: 3.1.0

Version

warpVersion :: String Source #

The version of Warp.

Data types

type HeaderValue = ByteString Source #

The type for header value used with HeaderName.

type IndexedHeader = Array Int (Maybe HeaderValue) Source #

Array for a set of HTTP headers.

requestMaxIndex :: Int Source #

The size for IndexedHeader for HTTP Request. From 0 to this corresponds to "Content-Length", "Transfer-Encoding", "Expect", "Connection", "Range", and "Host".

File descriptor cache

withFdCache :: Int -> (Maybe MutableFdCache -> IO a) -> IO a Source #

Creating MutableFdCache and executing the action in the second argument. The first argument is a cache duration in second.

getFd :: MutableFdCache -> FilePath -> IO (Fd, Refresh) Source #

Getting Fd and Refresh from the mutable Fd cacher.

type MutableFdCache = Reaper FdCache (Hash, FdEntry) Source #

Mutable Fd cacher.

type Refresh = IO () Source #

An action to activate a Fd cache entry.

Date

withDateCache :: (DateCache -> IO a) -> IO a Source #

Creating DateCache and executing the action.

type DateCache = IO GMTDate Source #

The type of the cache of the Date header value.

type GMTDate = ByteString Source #

The type of the Date header value.

Request and response

data Source Source #

Type for input streaming.

recvRequest Source #

Arguments

:: Settings 
-> Connection 
-> InternalInfo 
-> SockAddr

Peer's address.

-> Source

Where HTTP request comes from.

-> IO (Request, Maybe (IORef Int), IndexedHeader, IO ByteString)

Request passed to Application, how many bytes remain to be consumed, if known IndexedHeader of HTTP request for internal use, Body producing action used for flushing the request body

Receiving a HTTP request from Connection and parsing its header to create Request.

sendResponse Source #

Arguments

:: ByteString

default server value

-> Connection 
-> InternalInfo 
-> Request

HTTP request.

-> IndexedHeader

Indexed header of HTTP request.

-> IO ByteString

source from client, for raw response

-> Response

HTTP response including status code and response header.

-> IO Bool

Returing True if the connection is persistent.

Sending a HTTP response to Connection according to Response.

Applications/middlewares MUST specify a proper ResponseHeaders. so that inconsistency does not happen. No header is deleted by this function.

Especially, Applications/middlewares MUST take care of Content-Length, Content-Range, and Transfer-Encoding because they are inserted, when necessary, regardless they already exist. This function does not insert Content-Encoding. It's middleware's responsibility.

The Date and Server header is added if not exist in HTTP response header.

There are three basic APIs to create Response:

responseFile :: Status -> ResponseHeaders -> FilePath -> Maybe FilePart -> Response
HTTP response body is sent by sendfile() for GET method. HTTP response body is not sent by HEAD method. Applications are categorized into simple and sophisticated. Simple applications should specify Nothing to Maybe FilePart. The size of the specified file is obtained by disk access. Then Range is handled. Sophisticated applications should specify Just to Maybe FilePart. They should treat Range (and If-Range) by themselves. In both cases, Content-Length and Content-Range (if necessary) are automatically added into the HTTP response header. If Content-Length and Content-Range exist in the HTTP response header, they would cause inconsistency. Status is also changed to 206 (Partial Content) if necessary.
responseBuilder :: Status -> ResponseHeaders -> Builder -> Response
HTTP response body is created from Builder. Transfer-Encoding: chunked is used in HTTP/1.1.
responseStream :: Status -> ResponseHeaders -> StreamingBody -> Response
HTTP response body is created from Builder. Transfer-Encoding: chunked is used in HTTP/1.1.
responseRaw :: (IO ByteString -> (ByteString -> IO ()) -> IO ()) -> Response -> Response
No header is added and no Transfer-Encoding: is applied.

Time out manager

Types

type Manager = Reaper [Handle] Handle Source #

A timeout manager

type TimeoutAction = IO () Source #

An action to be performed on timeout.

data Handle Source #

A handle used by Manager

Manager

initialize :: Int -> IO Manager Source #

Creating timeout manager which works every N micro seconds where N is the first argument.

stopManager :: Manager -> IO () Source #

Stopping timeout manager.

withManager Source #

Arguments

:: Int

timeout in microseconds

-> (Manager -> IO a) 
-> IO a 

Call the inner function with a timeout manager.

Registration

register :: Manager -> TimeoutAction -> IO Handle Source #

Registering a timeout action.

registerKillThread :: Manager -> IO Handle Source #

Registering a timeout action of killing this thread.

Control

tickle :: Handle -> IO () Source #

Setting the state to active. Manager turns active to inactive repeatedly.

cancel :: Handle -> IO () Source #

Setting the state to canceled. Manager eventually removes this without timeout action.

pause :: Handle -> IO () Source #

Setting the state to paused. Manager does not change the value.

resume :: Handle -> IO () Source #

Setting the paused state to active. This is an alias to tickle.

Exceptions