Safe Haskell | None |
---|---|
Language | Haskell98 |
- data Settings = Settings {
- settingsPort :: Port
- settingsHost :: HostPreference
- settingsOnException :: Maybe Request -> SomeException -> IO ()
- settingsOnExceptionResponse :: SomeException -> Response
- settingsOnOpen :: SockAddr -> IO Bool
- settingsOnClose :: SockAddr -> IO ()
- settingsTimeout :: Int
- settingsManager :: Maybe Manager
- settingsFdCacheDuration :: Int
- settingsBeforeMainLoop :: IO ()
- settingsFork :: ((forall a. IO a -> IO a) -> IO ()) -> IO ()
- settingsNoParsePath :: Bool
- settingsInstallShutdownHandler :: IO () -> IO ()
- settingsServerName :: ByteString
- settingsMaximumBodyFlush :: Maybe Int
- settingsProxyProtocol :: ProxyProtocol
- settingsSlowlorisSize :: Int
- settingsHTTP2Enabled :: Bool
- data ProxyProtocol
- runSettingsConnection :: Settings -> IO (Connection, SockAddr) -> Application -> IO ()
- runSettingsConnectionMaker :: Settings -> IO (IO Connection, SockAddr) -> Application -> IO ()
- runSettingsConnectionMakerSecure :: Settings -> IO (IO (Connection, Transport), SockAddr) -> Application -> IO ()
- runServe :: Port -> ServeConnection -> IO ()
- runServeEnv :: Port -> ServeConnection -> IO ()
- runServeSettings :: Settings -> ServeConnection -> IO ()
- runServeSettingsSocket :: Settings -> Socket -> ServeConnection -> IO ()
- runServeSettingsConnection :: Settings -> IO (Connection, SockAddr) -> ServeConnection -> IO ()
- runServeSettingsConnectionMaker :: Settings -> IO (IO Connection, SockAddr) -> ServeConnection -> IO ()
- runServeSettingsConnectionMakerSecure :: Settings -> IO (IO (Connection, Transport), SockAddr) -> ServeConnection -> IO ()
- data Transport
- type ServeConnection = Connection -> InternalInfo -> SockAddr -> Transport -> Settings -> IO ()
- serveDefault :: Application -> ServeConnection
- serveHTTP2 :: HTTP2Application -> Application -> ServeConnection
- data Connection = Connection {
- connSendMany :: [ByteString] -> IO ()
- connSendAll :: ByteString -> IO ()
- connSendFile :: SendFile
- connClose :: IO ()
- connRecv :: Recv
- connRecvBuf :: RecvBuf
- connWriteBuffer :: Buffer
- connBufferSize :: BufSize
- socketConnection :: Socket -> IO Connection
- type Recv = IO ByteString
- type RecvBuf = Buffer -> BufSize -> IO Bool
- makePlainReceiveN :: Socket -> ByteString -> IO (BufSize -> IO ByteString)
- type Buffer = Ptr Word8
- type BufSize = Int
- bufferSize :: BufSize
- allocateBuffer :: Int -> IO Buffer
- freeBuffer :: Buffer -> IO ()
- copy :: Buffer -> ByteString -> IO Buffer
- data FileId = FileId {
- fileIdPath :: FilePath
- fileIdFd :: Maybe Fd
- type SendFile = FileId -> Integer -> Integer -> IO () -> [ByteString] -> IO ()
- sendFile :: Socket -> Buffer -> BufSize -> (ByteString -> IO ()) -> SendFile
- readSendFile :: Buffer -> BufSize -> (ByteString -> IO ()) -> SendFile
- warpVersion :: String
- data InternalInfo = InternalInfo {}
- type HeaderValue = ByteString
- type IndexedHeader = Array Int (Maybe HeaderValue)
- requestMaxIndex :: Int
- type Manager = Reaper [Handle] Handle
- type TimeoutAction = IO ()
- data Handle
- initialize :: Int -> IO Manager
- stopManager :: Manager -> IO ()
- withManager :: Int -> (Manager -> IO a) -> IO a
- register :: Manager -> TimeoutAction -> IO Handle
- registerKillThread :: Manager -> IO Handle
- tickle :: Handle -> IO ()
- cancel :: Handle -> IO ()
- pause :: Handle -> IO ()
- resume :: Handle -> IO ()
- data TimeoutThread = TimeoutThread
- withFdCache :: Int -> (Maybe MutableFdCache -> IO a) -> IO a
- getFd :: MutableFdCache -> FilePath -> IO (Fd, Refresh)
- type MutableFdCache = Reaper FdCache (Hash, FdEntry)
- type Refresh = IO ()
- withDateCache :: (DateCache -> IO a) -> IO a
- getDate :: DateCache -> IO GMTDate
- type DateCache = IO GMTDate
- type GMTDate = ByteString
- data Source
- recvRequest :: Settings -> Connection -> InternalInfo -> SockAddr -> Source -> IO (Request, Maybe (IORef Int), IndexedHeader, IO ByteString)
- sendResponse :: ByteString -> Connection -> InternalInfo -> Request -> IndexedHeader -> IO ByteString -> Response -> IO Bool
Settings
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
Settings | |
|
data ProxyProtocol Source
Specify usage of the PROXY protocol.
ProxyProtocolNone | See |
ProxyProtocolRequired | See |
ProxyProtocolOptional | See |
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
runServeEnv :: Port -> ServeConnection -> IO () Source
The generalized form of runEnv
.
runServeSettings :: Settings -> ServeConnection -> IO () Source
The generalized form of runSettings
.
runServeSettingsSocket :: Settings -> Socket -> ServeConnection -> IO () Source
The generalized form of runSettingsSocket
.
runServeSettingsConnection :: Settings -> IO (Connection, SockAddr) -> ServeConnection -> IO () Source
The generalized form of runSettingsConnection
.
runServeSettingsConnectionMaker :: Settings -> IO (IO Connection, SockAddr) -> ServeConnection -> IO () Source
The generalized form of runSettingsConnectionMaker
.
runServeSettingsConnectionMakerSecure :: Settings -> IO (IO (Connection, Transport), SockAddr) -> ServeConnection -> IO () Source
The generalized form of runSettingsConnectionMakerSecure
.
What kind of transport is used for this connection?
TCP | Plain channel: TCP |
TLS | Encrypted channel: TLS or SSL |
|
ServeConnection
type ServeConnection = Connection -> InternalInfo -> SockAddr -> Transport -> Settings -> IO () Source
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.
Connection | |
|
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
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 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
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
The version of Warp.
Data types
data InternalInfo Source
Internal information.
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.
The size for IndexedHeader
for HTTP Request.
From 0 to this corresponds to "Content-Length", "Transfer-Encoding",
"Expect", "Connection", "Range", and "Host".
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 TimeoutAction = IO () Source
An action to be performed on timeout.
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.
Call the inner function with a timeout manager.
Registration
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.
Exceptions
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.
type MutableFdCache = Reaper FdCache (Hash, FdEntry) Source
Mutable Fd cacher.
Date
type GMTDate = ByteString Source
The type of the Date header value.
Request and response
:: Settings | |
-> Connection | |
-> InternalInfo | |
-> SockAddr | Peer's address. |
-> Source | Where HTTP request comes from. |
-> IO (Request, Maybe (IORef Int), IndexedHeader, IO ByteString) |
|
Receiving a HTTP request from Connection
and parsing its header
to create Request
.
:: 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
toMaybe
FilePart
. The size of the specified file is obtained by disk access. Then Range is handled. Sophisticated applications should specifyJust
toMaybe
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.