| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Network.Wai.Handler.Warp.Internal
Synopsis
- 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
- settingsFileInfoCacheDuration :: Int
- settingsBeforeMainLoop :: IO ()
- settingsFork :: ((forall a. IO a -> IO a) -> IO ()) -> IO ()
- settingsAccept :: Socket -> IO (Socket, SockAddr)
- settingsNoParsePath :: Bool
- settingsInstallShutdownHandler :: IO () -> IO ()
- settingsServerName :: ByteString
- settingsMaximumBodyFlush :: Maybe Int
- settingsProxyProtocol :: ProxyProtocol
- settingsSlowlorisSize :: Int
- settingsHTTP2Enabled :: Bool
- settingsLogger :: Request -> Status -> Maybe Integer -> IO ()
- settingsServerPushLogger :: Request -> ByteString -> Integer -> IO ()
- settingsGracefulShutdownTimeout :: Maybe Int
- settingsGracefulCloseTimeout1 :: Int
- settingsGracefulCloseTimeout2 :: Int
- settingsMaxTotalHeaderLength :: Int
- settingsAltSvc :: Maybe ByteString
- settingsMaxBuilderResponseBufferSize :: Int
 
- 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 ()
- data Transport
- data Connection = Connection {- connSendMany :: [ByteString] -> IO ()
- connSendAll :: ByteString -> IO ()
- connSendFile :: SendFile
- connClose :: IO ()
- connRecv :: Recv
- connRecvBuf :: RecvBuf
- connWriteBuffer :: IORef WriteBuffer
- connHTTP2 :: IORef Bool
- connMySockAddr :: SockAddr
 
- socketConnection :: Settings -> Socket -> IO Connection
- type Recv = IO ByteString
- type RecvBuf = Buffer -> BufSize -> IO Bool
- type Buffer = Ptr Word8
- type BufSize = Int
- data WriteBuffer = WriteBuffer {}
- createWriteBuffer :: BufSize -> IO WriteBuffer
- 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
- module System.TimeManager
- withFdCache :: Int -> ((FilePath -> IO (Maybe Fd, Refresh)) -> IO a) -> IO a
- data Fd
- type Refresh = IO ()
- closeFile :: Fd -> IO ()
- openFile :: FilePath -> IO Fd
- setFileCloseOnExec :: Fd -> IO ()
- data FileInfo = FileInfo {}
- withFileInfoCache :: Int -> ((FilePath -> IO FileInfo) -> IO a) -> IO a
- getInfo :: FilePath -> IO FileInfo
- withDateCache :: (IO GMTDate -> IO a) -> IO a
- type GMTDate = ByteString
- data Source
- data FirstRequest
- recvRequest :: FirstRequest -> Settings -> Connection -> InternalInfo -> Handle -> SockAddr -> Source -> Transport -> IO (Request, Maybe (IORef Int), IndexedHeader, IO ByteString)
- sendResponse :: Settings -> Connection -> InternalInfo -> Handle -> Request -> IndexedHeader -> IO ByteString -> Response -> IO Bool
- setSocketCloseOnExec :: Socket -> IO ()
- windowsThreadBlockHack :: IO a -> IO a
- http2server :: Settings -> InternalInfo -> Transport -> SockAddr -> Application -> Server
- withII :: Settings -> (InternalInfo -> IO a) -> IO a
- serveConnection :: Connection -> InternalInfo -> Handle -> SockAddr -> Transport -> Settings -> Application -> IO ()
- pReadMaker :: InternalInfo -> PositionReadMaker
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
Constructors
| Settings | |
| Fields 
 | |
data ProxyProtocol Source #
Specify usage of the PROXY protocol.
Constructors
| 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
What kind of transport is used for this connection?
Constructors
| TCP | Plain channel: TCP | 
| TLS | |
| Fields 
 | |
| QUIC | |
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 :: Settings -> Socket -> IO Connection Source #
Creating Connection for plain HTTP based on a given socket.
Receive
type Recv = IO ByteString #
Type for the receiving function with a buffer pool.
Buffer
data WriteBuffer Source #
A write buffer of a specified size containing bytes and a way to free the buffer.
createWriteBuffer :: BufSize -> IO WriteBuffer Source #
Allocate a buffer of the given size and wrap it in a WriteBuffer
 containing that size and a finalizer.
freeBuffer :: Buffer -> IO () Source #
Releasing a buffer with free().
copy :: Buffer -> ByteString -> IO Buffer #
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
warpVersion :: String Source #
The version of Warp.
Data types
data InternalInfo Source #
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"
- "If-Range"
- "Referer"
- "User-Agent"
- "If-Match"
- "If-None-Match"
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.
module System.TimeManager
File descriptor cache
withFdCache :: Int -> ((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.
Instances
| Storable Fd | |
| Defined in System.Posix.Types | |
| Bits Fd | |
| Defined in System.Posix.Types | |
| FiniteBits Fd | |
| Defined in System.Posix.Types Methods finiteBitSize :: Fd -> Int # countLeadingZeros :: Fd -> Int # countTrailingZeros :: Fd -> Int # | |
| Bounded Fd | |
| Enum Fd | |
| Ix Fd | |
| Num Fd | |
| Read Fd | |
| Integral Fd | |
| Real Fd | |
| Defined in System.Posix.Types Methods toRational :: Fd -> Rational # | |
| Show Fd | |
| Eq Fd | |
| Ord Fd | |
| ControlMessage [Fd] | |
| Defined in Network.Socket.Posix.Cmsg | |
setFileCloseOnExec :: Fd -> IO () Source #
File information cache
File information.
Constructors
| FileInfo | |
| Fields 
 | |
withFileInfoCache :: Int -> ((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.
Date
type GMTDate = ByteString Source #
The type of the Date header value.
Request and response
data FirstRequest Source #
first request on this connection?
Constructors
| FirstRequest | |
| SubsequentRequest | 
Arguments
| :: FirstRequest | |
| -> Settings | |
| -> Connection | |
| -> InternalInfo | |
| -> Handle | |
| -> SockAddr | Peer's address. | 
| -> Source | Where HTTP request comes from. | 
| -> Transport | |
| -> IO (Request, Maybe (IORef Int), IndexedHeader, IO ByteString) | 
 | 
Receiving a HTTP request from Connection and parsing its header
   to create Request.
Arguments
| :: Settings | |
| -> Connection | |
| -> InternalInfo | |
| -> Handle | |
| -> 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 info 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.
Platform dependent helper functions
setSocketCloseOnExec :: Socket -> IO () Source #
Set flag FileCloseOnExec flag on a socket (on Unix)
Copied from: https://github.com/mzero/plush/blob/master/src/Plush/Server/Warp.hs
Since: 3.2.17
windowsThreadBlockHack :: IO a -> IO a Source #
Misc
http2server :: Settings -> InternalInfo -> Transport -> SockAddr -> Application -> Server Source #
Converting WAI application to the server type of http2 library.
Since 3.3.11
withII :: Settings -> (InternalInfo -> IO a) -> IO a Source #
Running an action with internal info.
Since 3.3.11
serveConnection :: Connection -> InternalInfo -> Handle -> SockAddr -> Transport -> Settings -> Application -> IO () Source #
pReadMaker :: InternalInfo -> PositionReadMaker Source #
PositionReadMaker based on file descriptor cache.
Since 3.3.13