{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE PatternGuards #-}
{-# OPTIONS_GHC -fno-warn-deprecations #-}
module Network.Wai.Handler.Warp (
run
, runEnv
, runSettings
, runSettingsSocket
, Settings
, defaultSettings
, setPort
, setHost
, setOnException
, setOnExceptionResponse
, setOnOpen
, setOnClose
, setTimeout
, setManager
, setFdCacheDuration
, setFileInfoCacheDuration
, setBeforeMainLoop
, setNoParsePath
, setInstallShutdownHandler
, setServerName
, setMaximumBodyFlush
, setFork
, setProxyProtocolNone
, setProxyProtocolRequired
, setProxyProtocolOptional
, setSlowlorisSize
, setHTTP2Disabled
, setLogger
, setServerPushLogger
, setGracefulShutdownTimeout
, setGracefulCloseTimeout1
, setGracefulCloseTimeout2
, setMaxTotalHeaderLength
, setAltSvc
, getPort
, getHost
, getOnOpen
, getOnClose
, getOnException
, getGracefulShutdownTimeout
, getGracefulCloseTimeout1
, getGracefulCloseTimeout2
, defaultOnException
, defaultShouldDisplayException
, defaultOnExceptionResponse
, exceptionResponseForDebug
, HostPreference
, Port
, InvalidRequest (..)
, pauseTimeout
, FileInfo(..)
, getFileInfo
, clientCertificate
, withApplication
, withApplicationSettings
, testWithApplication
, testWithApplicationSettings
, openFreePort
, warpVersion
, HTTP2Data
, http2dataPushPromise
, http2dataTrailers
, defaultHTTP2Data
, getHTTP2Data
, setHTTP2Data
, modifyHTTP2Data
, PushPromise
, promisedPath
, promisedFile
, promisedResponseHeaders
, promisedWeight
, defaultPushPromise
) where
import UnliftIO.Exception (SomeException, throwIO)
import Data.Streaming.Network (HostPreference)
import qualified Data.Vault.Lazy as Vault
import Data.X509
import qualified Network.HTTP.Types as H
import Network.Socket (SockAddr)
import Network.Wai (Request, Response, vault)
import System.TimeManager
import Network.Wai.Handler.Warp.FileInfoCache
import Network.Wai.Handler.Warp.HTTP2.Request (getHTTP2Data, setHTTP2Data, modifyHTTP2Data)
import Network.Wai.Handler.Warp.HTTP2.Types
import Network.Wai.Handler.Warp.Imports
import Network.Wai.Handler.Warp.Request
import Network.Wai.Handler.Warp.Response (warpVersion)
import Network.Wai.Handler.Warp.Run
import Network.Wai.Handler.Warp.Settings
import Network.Wai.Handler.Warp.Types hiding (getFileInfo)
import Network.Wai.Handler.Warp.WithApplication
setPort :: Port -> Settings -> Settings
setPort :: Port -> Settings -> Settings
setPort Port
x Settings
y = Settings
y { settingsPort :: Port
settingsPort = Port
x }
setHost :: HostPreference -> Settings -> Settings
setHost :: HostPreference -> Settings -> Settings
setHost HostPreference
x Settings
y = Settings
y { settingsHost :: HostPreference
settingsHost = HostPreference
x }
setOnException :: (Maybe Request -> SomeException -> IO ()) -> Settings -> Settings
setOnException :: (Maybe Request -> SomeException -> IO ()) -> Settings -> Settings
setOnException Maybe Request -> SomeException -> IO ()
x Settings
y = Settings
y { settingsOnException :: Maybe Request -> SomeException -> IO ()
settingsOnException = Maybe Request -> SomeException -> IO ()
x }
setOnExceptionResponse :: (SomeException -> Response) -> Settings -> Settings
setOnExceptionResponse :: (SomeException -> Response) -> Settings -> Settings
setOnExceptionResponse SomeException -> Response
x Settings
y = Settings
y { settingsOnExceptionResponse :: SomeException -> Response
settingsOnExceptionResponse = SomeException -> Response
x }
setOnOpen :: (SockAddr -> IO Bool) -> Settings -> Settings
setOnOpen :: (SockAddr -> IO Bool) -> Settings -> Settings
setOnOpen SockAddr -> IO Bool
x Settings
y = Settings
y { settingsOnOpen :: SockAddr -> IO Bool
settingsOnOpen = SockAddr -> IO Bool
x }
setOnClose :: (SockAddr -> IO ()) -> Settings -> Settings
setOnClose :: (SockAddr -> IO ()) -> Settings -> Settings
setOnClose SockAddr -> IO ()
x Settings
y = Settings
y { settingsOnClose :: SockAddr -> IO ()
settingsOnClose = SockAddr -> IO ()
x }
setTimeout :: Int -> Settings -> Settings
setTimeout :: Port -> Settings -> Settings
setTimeout Port
x Settings
y = Settings
y { settingsTimeout :: Port
settingsTimeout = Port
x }
setManager :: Manager -> Settings -> Settings
setManager :: Manager -> Settings -> Settings
setManager Manager
x Settings
y = Settings
y { settingsManager :: Maybe Manager
settingsManager = Manager -> Maybe Manager
forall a. a -> Maybe a
Just Manager
x }
setFdCacheDuration :: Int -> Settings -> Settings
setFdCacheDuration :: Port -> Settings -> Settings
setFdCacheDuration Port
x Settings
y = Settings
y { settingsFdCacheDuration :: Port
settingsFdCacheDuration = Port
x }
setFileInfoCacheDuration :: Int -> Settings -> Settings
setFileInfoCacheDuration :: Port -> Settings -> Settings
setFileInfoCacheDuration Port
x Settings
y = Settings
y { settingsFileInfoCacheDuration :: Port
settingsFileInfoCacheDuration = Port
x }
setBeforeMainLoop :: IO () -> Settings -> Settings
setBeforeMainLoop :: IO () -> Settings -> Settings
setBeforeMainLoop IO ()
x Settings
y = Settings
y { settingsBeforeMainLoop :: IO ()
settingsBeforeMainLoop = IO ()
x }
setNoParsePath :: Bool -> Settings -> Settings
setNoParsePath :: Bool -> Settings -> Settings
setNoParsePath Bool
x Settings
y = Settings
y { settingsNoParsePath :: Bool
settingsNoParsePath = Bool
x }
getPort :: Settings -> Port
getPort :: Settings -> Port
getPort = Settings -> Port
settingsPort
getHost :: Settings -> HostPreference
getHost :: Settings -> HostPreference
getHost = Settings -> HostPreference
settingsHost
getOnOpen :: Settings -> SockAddr -> IO Bool
getOnOpen :: Settings -> SockAddr -> IO Bool
getOnOpen = Settings -> SockAddr -> IO Bool
settingsOnOpen
getOnClose :: Settings -> SockAddr -> IO ()
getOnClose :: Settings -> SockAddr -> IO ()
getOnClose = Settings -> SockAddr -> IO ()
settingsOnClose
getOnException :: Settings -> Maybe Request -> SomeException -> IO ()
getOnException :: Settings -> Maybe Request -> SomeException -> IO ()
getOnException = Settings -> Maybe Request -> SomeException -> IO ()
settingsOnException
getGracefulShutdownTimeout :: Settings -> Maybe Int
getGracefulShutdownTimeout :: Settings -> Maybe Port
getGracefulShutdownTimeout = Settings -> Maybe Port
settingsGracefulShutdownTimeout
setInstallShutdownHandler :: (IO () -> IO ()) -> Settings -> Settings
setInstallShutdownHandler :: (IO () -> IO ()) -> Settings -> Settings
setInstallShutdownHandler IO () -> IO ()
x Settings
y = Settings
y { settingsInstallShutdownHandler :: IO () -> IO ()
settingsInstallShutdownHandler = IO () -> IO ()
x }
setServerName :: ByteString -> Settings -> Settings
setServerName :: ByteString -> Settings -> Settings
setServerName ByteString
x Settings
y = Settings
y { settingsServerName :: ByteString
settingsServerName = ByteString
x }
setMaximumBodyFlush :: Maybe Int -> Settings -> Settings
setMaximumBodyFlush :: Maybe Port -> Settings -> Settings
setMaximumBodyFlush Maybe Port
x Settings
y
| Just Port
x' <- Maybe Port
x, Port
x' Port -> Port -> Bool
forall a. Ord a => a -> a -> Bool
< Port
0 = [Char] -> Settings
forall a. HasCallStack => [Char] -> a
error [Char]
"setMaximumBodyFlush: must be positive"
| Bool
otherwise = Settings
y { settingsMaximumBodyFlush :: Maybe Port
settingsMaximumBodyFlush = Maybe Port
x }
setFork :: (((forall a. IO a -> IO a) -> IO ()) -> IO ()) -> Settings -> Settings
setFork :: (((forall a. IO a -> IO a) -> IO ()) -> IO ())
-> Settings -> Settings
setFork ((forall a. IO a -> IO a) -> IO ()) -> IO ()
fork' Settings
s = Settings
s { settingsFork :: ((forall a. IO a -> IO a) -> IO ()) -> IO ()
settingsFork = ((forall a. IO a -> IO a) -> IO ()) -> IO ()
fork' }
setProxyProtocolNone :: Settings -> Settings
setProxyProtocolNone :: Settings -> Settings
setProxyProtocolNone Settings
y = Settings
y { settingsProxyProtocol :: ProxyProtocol
settingsProxyProtocol = ProxyProtocol
ProxyProtocolNone }
setProxyProtocolRequired :: Settings -> Settings
setProxyProtocolRequired :: Settings -> Settings
setProxyProtocolRequired Settings
y = Settings
y { settingsProxyProtocol :: ProxyProtocol
settingsProxyProtocol = ProxyProtocol
ProxyProtocolRequired }
setProxyProtocolOptional :: Settings -> Settings
setProxyProtocolOptional :: Settings -> Settings
setProxyProtocolOptional Settings
y = Settings
y { settingsProxyProtocol :: ProxyProtocol
settingsProxyProtocol = ProxyProtocol
ProxyProtocolOptional }
setSlowlorisSize :: Int -> Settings -> Settings
setSlowlorisSize :: Port -> Settings -> Settings
setSlowlorisSize Port
x Settings
y = Settings
y { settingsSlowlorisSize :: Port
settingsSlowlorisSize = Port
x }
setHTTP2Disabled :: Settings -> Settings
setHTTP2Disabled :: Settings -> Settings
setHTTP2Disabled Settings
y = Settings
y { settingsHTTP2Enabled :: Bool
settingsHTTP2Enabled = Bool
False }
setLogger :: (Request -> H.Status -> Maybe Integer -> IO ())
-> Settings
-> Settings
setLogger :: (Request -> Status -> Maybe Integer -> IO ())
-> Settings -> Settings
setLogger Request -> Status -> Maybe Integer -> IO ()
lgr Settings
y = Settings
y { settingsLogger :: Request -> Status -> Maybe Integer -> IO ()
settingsLogger = Request -> Status -> Maybe Integer -> IO ()
lgr }
setServerPushLogger :: (Request -> ByteString -> Integer -> IO ())
-> Settings
-> Settings
setServerPushLogger :: (Request -> ByteString -> Integer -> IO ()) -> Settings -> Settings
setServerPushLogger Request -> ByteString -> Integer -> IO ()
lgr Settings
y = Settings
y { settingsServerPushLogger :: Request -> ByteString -> Integer -> IO ()
settingsServerPushLogger = Request -> ByteString -> Integer -> IO ()
lgr }
setGracefulShutdownTimeout :: Maybe Int
-> Settings -> Settings
setGracefulShutdownTimeout :: Maybe Port -> Settings -> Settings
setGracefulShutdownTimeout Maybe Port
time Settings
y = Settings
y { settingsGracefulShutdownTimeout :: Maybe Port
settingsGracefulShutdownTimeout = Maybe Port
time }
setMaxTotalHeaderLength :: Int -> Settings -> Settings
Port
maxTotalHeaderLength Settings
settings = Settings
settings
{ settingsMaxTotalHeaderLength :: Port
settingsMaxTotalHeaderLength = Port
maxTotalHeaderLength }
setAltSvc :: ByteString -> Settings -> Settings
setAltSvc :: ByteString -> Settings -> Settings
setAltSvc ByteString
altsvc Settings
settings = Settings
settings { settingsAltSvc :: Maybe ByteString
settingsAltSvc = ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
altsvc }
pauseTimeout :: Request -> IO ()
pauseTimeout :: Request -> IO ()
pauseTimeout = IO () -> Maybe (IO ()) -> IO ()
forall a. a -> Maybe a -> a
fromMaybe (() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()) (Maybe (IO ()) -> IO ())
-> (Request -> Maybe (IO ())) -> Request -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key (IO ()) -> Vault -> Maybe (IO ())
forall a. Key a -> Vault -> Maybe a
Vault.lookup Key (IO ())
pauseTimeoutKey (Vault -> Maybe (IO ()))
-> (Request -> Vault) -> Request -> Maybe (IO ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Request -> Vault
vault
getFileInfo :: Request -> FilePath -> IO FileInfo
getFileInfo :: Request -> [Char] -> IO FileInfo
getFileInfo = ([Char] -> IO FileInfo)
-> Maybe ([Char] -> IO FileInfo) -> [Char] -> IO FileInfo
forall a. a -> Maybe a -> a
fromMaybe (\[Char]
_ -> IOError -> IO FileInfo
forall (m :: * -> *) e a. (MonadIO m, Exception e) => e -> m a
throwIO ([Char] -> IOError
userError [Char]
"getFileInfo")) (Maybe ([Char] -> IO FileInfo) -> [Char] -> IO FileInfo)
-> (Request -> Maybe ([Char] -> IO FileInfo))
-> Request
-> [Char]
-> IO FileInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key ([Char] -> IO FileInfo)
-> Vault -> Maybe ([Char] -> IO FileInfo)
forall a. Key a -> Vault -> Maybe a
Vault.lookup Key ([Char] -> IO FileInfo)
getFileInfoKey (Vault -> Maybe ([Char] -> IO FileInfo))
-> (Request -> Vault) -> Request -> Maybe ([Char] -> IO FileInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Request -> Vault
vault
setGracefulCloseTimeout1 :: Int -> Settings -> Settings
setGracefulCloseTimeout1 :: Port -> Settings -> Settings
setGracefulCloseTimeout1 Port
x Settings
y = Settings
y { settingsGracefulCloseTimeout1 :: Port
settingsGracefulCloseTimeout1 = Port
x }
getGracefulCloseTimeout1 :: Settings -> Int
getGracefulCloseTimeout1 :: Settings -> Port
getGracefulCloseTimeout1 = Settings -> Port
settingsGracefulCloseTimeout1
setGracefulCloseTimeout2 :: Int -> Settings -> Settings
setGracefulCloseTimeout2 :: Port -> Settings -> Settings
setGracefulCloseTimeout2 Port
x Settings
y = Settings
y { settingsGracefulCloseTimeout2 :: Port
settingsGracefulCloseTimeout2 = Port
x }
getGracefulCloseTimeout2 :: Settings -> Int
getGracefulCloseTimeout2 :: Settings -> Port
getGracefulCloseTimeout2 = Settings -> Port
settingsGracefulCloseTimeout2
clientCertificate :: Request -> Maybe CertificateChain
clientCertificate :: Request -> Maybe CertificateChain
clientCertificate = Maybe (Maybe CertificateChain) -> Maybe CertificateChain
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (Maybe (Maybe CertificateChain) -> Maybe CertificateChain)
-> (Request -> Maybe (Maybe CertificateChain))
-> Request
-> Maybe CertificateChain
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key (Maybe CertificateChain)
-> Vault -> Maybe (Maybe CertificateChain)
forall a. Key a -> Vault -> Maybe a
Vault.lookup Key (Maybe CertificateChain)
getClientCertificateKey (Vault -> Maybe (Maybe CertificateChain))
-> (Request -> Vault) -> Request -> Maybe (Maybe CertificateChain)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Request -> Vault
vault