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

Safe HaskellNone
LanguageHaskell98

Network.Wai.Handler.Warp.Internal

Contents

Synopsis

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

Constructors

Settings 

Fields

data ProxyProtocol Source #

Specify usage of the PROXY protocol.

Constructors

ProxyProtocolNone

See setProxyProtocolNone.

ProxyProtocolRequired

See setProxyProtocolRequired.

ProxyProtocolOptional

See setProxyProtocolOptional.

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.

Receive

type Recv = IO ByteString Source #

Type for the action to receive input data

type RecvBuf = Buffer -> BufSize -> IO Bool Source #

Type for the action to receive input data with a buffer. The result boolean indicates whether or not the buffer is fully filled.

makePlainReceiveN :: Socket -> ByteString -> IO (BufSize -> IO ByteString) Source #

This function returns a receiving function based on two receiving functions. The returned function efficiently manages received data which is initialized by the first argument. The returned function may allocate a byte string with malloc().

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().

copy :: Buffer -> ByteString -> IO Buffer Source #

Copying the bytestring to the buffer. This function returns the point where the next copy should start.

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", "Host", "If-Modified-Since", "If-Unmodified-Since" and "If-Range".

Time out manager

In order to provide slowloris protection, Warp provides timeout handlers. We follow these rules:

  • A timeout is created when a connection is opened.
  • When all request headers are read, the timeout is tickled.
  • Every time at least the slowloris size settings number of bytes of the request body are read, the timeout is tickled.
  • The timeout is paused while executing user code. This will apply to both the application itself, and a ResponseSource response. The timeout is resumed as soon as we return from user code.
  • Every time data is successfully sent to the client, the timeout is tickled.

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 with onTimeout fired.

killManager :: Manager -> IO () Source #

Killing timeout manager immediately without firing onTimeout.

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 -> TimeoutAction -> 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

File descriptor cache

withFdCache :: Int -> ((Hash -> FilePath -> IO (Maybe Fd, Refresh)) -> IO a) -> IO a Source #

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

data Fd :: * #

Instances

Bounded Fd 

Methods

minBound :: Fd #

maxBound :: Fd #

Enum Fd 

Methods

succ :: Fd -> Fd #

pred :: Fd -> Fd #

toEnum :: Int -> Fd #

fromEnum :: Fd -> Int #

enumFrom :: Fd -> [Fd] #

enumFromThen :: Fd -> Fd -> [Fd] #

enumFromTo :: Fd -> Fd -> [Fd] #

enumFromThenTo :: Fd -> Fd -> Fd -> [Fd] #

Eq Fd 

Methods

(==) :: Fd -> Fd -> Bool #

(/=) :: Fd -> Fd -> Bool #

Integral Fd 

Methods

quot :: Fd -> Fd -> Fd #

rem :: Fd -> Fd -> Fd #

div :: Fd -> Fd -> Fd #

mod :: Fd -> Fd -> Fd #

quotRem :: Fd -> Fd -> (Fd, Fd) #

divMod :: Fd -> Fd -> (Fd, Fd) #

toInteger :: Fd -> Integer #

Num Fd 

Methods

(+) :: Fd -> Fd -> Fd #

(-) :: Fd -> Fd -> Fd #

(*) :: Fd -> Fd -> Fd #

negate :: Fd -> Fd #

abs :: Fd -> Fd #

signum :: Fd -> Fd #

fromInteger :: Integer -> Fd #

Ord Fd 

Methods

compare :: Fd -> Fd -> Ordering #

(<) :: Fd -> Fd -> Bool #

(<=) :: Fd -> Fd -> Bool #

(>) :: Fd -> Fd -> Bool #

(>=) :: Fd -> Fd -> Bool #

max :: Fd -> Fd -> Fd #

min :: Fd -> Fd -> Fd #

Read Fd 
Real Fd 

Methods

toRational :: Fd -> Rational #

Show Fd 

Methods

showsPrec :: Int -> Fd -> ShowS #

show :: Fd -> String #

showList :: [Fd] -> ShowS #

Storable Fd 

Methods

sizeOf :: Fd -> Int #

alignment :: Fd -> Int #

peekElemOff :: Ptr Fd -> Int -> IO Fd #

pokeElemOff :: Ptr Fd -> Int -> Fd -> IO () #

peekByteOff :: Ptr b -> Int -> IO Fd #

pokeByteOff :: Ptr b -> Int -> Fd -> IO () #

peek :: Ptr Fd -> IO Fd #

poke :: Ptr Fd -> Fd -> IO () #

Bits Fd 

Methods

(.&.) :: Fd -> Fd -> Fd #

(.|.) :: Fd -> Fd -> Fd #

xor :: Fd -> Fd -> Fd #

complement :: Fd -> Fd #

shift :: Fd -> Int -> Fd #

rotate :: Fd -> Int -> Fd #

zeroBits :: Fd #

bit :: Int -> Fd #

setBit :: Fd -> Int -> Fd #

clearBit :: Fd -> Int -> Fd #

complementBit :: Fd -> Int -> Fd #

testBit :: Fd -> Int -> Bool #

bitSizeMaybe :: Fd -> Maybe Int #

bitSize :: Fd -> Int #

isSigned :: Fd -> Bool #

shiftL :: Fd -> Int -> Fd #

unsafeShiftL :: Fd -> Int -> Fd #

shiftR :: Fd -> Int -> Fd #

unsafeShiftR :: Fd -> Int -> Fd #

rotateL :: Fd -> Int -> Fd #

rotateR :: Fd -> Int -> Fd #

popCount :: Fd -> Int #

FiniteBits Fd 

type Refresh = IO () Source #

An action to activate a Fd cache entry.

File information cache

data FileInfo Source #

File information.

Constructors

FileInfo 

Fields

type Hash = Int Source #

withFileInfoCache :: Int -> ((Hash -> FilePath -> IO FileInfo) -> IO a) -> IO a Source #

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

getInfo :: FilePath -> IO FileInfo Source #

Getting the file information corresponding to the file.

Date

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

Creating DateCache and executing the action.

type GMTDate = ByteString Source #

The type of the Date header value.

Request and response

data Source Source #

Type for input streaming.

recvRequest Source #

Arguments

:: Bool

first request on this connection?

-> Settings 
-> Connection 
-> InternalInfo1 
-> SockAddr

Peer's address.

-> Source

Where HTTP request comes from.

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

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

:: Settings 
-> 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 provide a proper ResponseHeaders. so that inconsistency does not happen. No header is deleted by this function.

Especially, Applications/middlewares MUST provide a proper Content-Type. They MUST NOT provide 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:

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.
responseFile :: Status -> ResponseHeaders -> FilePath -> Maybe FilePart -> Response
HTTP response body is sent (by sendfile(), if possible) for GET method. HTTP response body is not sent by HEAD method. Content-Length and Content-Range are automatically added into the HTTP response header if necessary. If Content-Length and Content-Range exist in the HTTP response header, they would cause inconsistency. "Accept-Ranges: bytes" is also inserted.

Applications are categorized into simple and sophisticated. Sophisticated applications should specify Just to Maybe FilePart. They should treat the conditional request by themselves. A proper Status (200 or 206) must be provided.

Simple applications should specify Nothing to Maybe FilePart. The size of the specified file is obtained by disk access or from the file infor cache. If-Modified-Since, If-Unmodified-Since, If-Range and Range are processed. Since a proper status is chosen, Status is ignored. Last-Modified is inserted.