{-# LANGUAGE OverloadedStrings, ScopedTypeVariables, ViewPatterns #-}
{-# LANGUAGE PatternGuards, RankNTypes #-}
{-# LANGUAGE ImpredicativeTypes, CPP #-}
{-# LANGUAGE MagicHash, UnboxedTuples #-}
module Network.Wai.Handler.Warp.Settings where
import GHC.IO (unsafeUnmask, IO (IO))
import GHC.Prim (fork#)
import UnliftIO (SomeException, fromException)
import qualified Data.ByteString.Char8 as C8
import qualified Data.ByteString.Builder as Builder
import Data.ByteString.Lazy (fromStrict)
import Data.Streaming.Network (HostPreference)
import qualified Data.Text as T
import qualified Data.Text.IO as TIO
import Data.Version (showVersion)
import GHC.IO.Exception (IOErrorType(..), AsyncException (ThreadKilled))
import qualified Network.HTTP.Types as H
import Network.HTTP2.Frame (HTTP2Error (..), ErrorCodeId (..))
import Network.Socket (SockAddr)
import Network.Wai
import qualified Paths_warp
import System.IO (stderr)
import System.IO.Error (ioeGetErrorType)
import System.TimeManager
import Network.Wai.Handler.Warp.Imports
import Network.Wai.Handler.Warp.Types
data Settings = Settings
    { Settings -> Port
settingsPort :: Port 
    , Settings -> HostPreference
settingsHost :: HostPreference 
    , Settings -> Maybe Request -> SomeException -> IO ()
settingsOnException :: Maybe Request -> SomeException -> IO () 
    , Settings -> SomeException -> Response
settingsOnExceptionResponse :: SomeException -> Response
      
      
      
      
      
    , Settings -> SockAddr -> IO Bool
settingsOnOpen :: SockAddr -> IO Bool 
    , Settings -> SockAddr -> IO ()
settingsOnClose :: SockAddr -> IO ()  
    , Settings -> Port
settingsTimeout :: Int 
    , Settings -> Maybe Manager
settingsManager :: Maybe Manager 
    , Settings -> Port
settingsFdCacheDuration :: Int 
    , Settings -> Port
settingsFileInfoCacheDuration :: Int 
    , Settings -> IO ()
settingsBeforeMainLoop :: IO ()
      
      
      
      
      
      
      
    , Settings -> ((forall a. IO a -> IO a) -> IO ()) -> IO ()
settingsFork :: ((forall a. IO a -> IO a) -> IO ()) -> IO ()
      
      
      
      
      
      
      
      
    , Settings -> Bool
settingsNoParsePath :: Bool
      
      
      
      
      
      
      
    , Settings -> IO () -> IO ()
settingsInstallShutdownHandler :: IO () -> IO ()
      
      
      
      
      
      
      
    , Settings -> ByteString
settingsServerName :: ByteString
      
      
      
    , Settings -> Maybe Port
settingsMaximumBodyFlush :: Maybe Int
      
      
      
    , Settings -> ProxyProtocol
settingsProxyProtocol :: ProxyProtocol
      
      
      
    , Settings -> Port
settingsSlowlorisSize :: Int
      
      
      
    , Settings -> Bool
settingsHTTP2Enabled :: Bool
      
      
      
    , Settings -> Request -> Status -> Maybe Integer -> IO ()
settingsLogger :: Request -> H.Status -> Maybe Integer -> IO ()
      
      
      
    , Settings -> Request -> ByteString -> Integer -> IO ()
settingsServerPushLogger :: Request -> ByteString -> Integer -> IO ()
      
      
      
    , Settings -> Maybe Port
settingsGracefulShutdownTimeout :: Maybe Int
      
      
      
      
    , Settings -> Port
settingsGracefulCloseTimeout1 :: Int
      
      
      
      
      
    , Settings -> Port
settingsGracefulCloseTimeout2 :: Int
      
      
      
      
      
    ,  :: Int
      
      
      
    , Settings -> Maybe ByteString
settingsAltSvc :: Maybe ByteString
      
      
      
      
      
    }
data ProxyProtocol = ProxyProtocolNone
                     
                   | ProxyProtocolRequired
                     
                   | ProxyProtocolOptional
                     
defaultSettings :: Settings
defaultSettings :: Settings
defaultSettings = Settings :: Port
-> HostPreference
-> (Maybe Request -> SomeException -> IO ())
-> (SomeException -> Response)
-> (SockAddr -> IO Bool)
-> (SockAddr -> IO ())
-> Port
-> Maybe Manager
-> Port
-> Port
-> IO ()
-> (((forall a. IO a -> IO a) -> IO ()) -> IO ())
-> Bool
-> (IO () -> IO ())
-> ByteString
-> Maybe Port
-> ProxyProtocol
-> Port
-> Bool
-> (Request -> Status -> Maybe Integer -> IO ())
-> (Request -> ByteString -> Integer -> IO ())
-> Maybe Port
-> Port
-> Port
-> Port
-> Maybe ByteString
-> Settings
Settings
    { settingsPort :: Port
settingsPort = Port
3000
    , settingsHost :: HostPreference
settingsHost = HostPreference
"*4"
    , settingsOnException :: Maybe Request -> SomeException -> IO ()
settingsOnException = Maybe Request -> SomeException -> IO ()
defaultOnException
    , settingsOnExceptionResponse :: SomeException -> Response
settingsOnExceptionResponse = SomeException -> Response
defaultOnExceptionResponse
    , settingsOnOpen :: SockAddr -> IO Bool
settingsOnOpen = IO Bool -> SockAddr -> IO Bool
forall a b. a -> b -> a
const (IO Bool -> SockAddr -> IO Bool) -> IO Bool -> SockAddr -> IO Bool
forall a b. (a -> b) -> a -> b
$ Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
    , settingsOnClose :: SockAddr -> IO ()
settingsOnClose = IO () -> SockAddr -> IO ()
forall a b. a -> b -> a
const (IO () -> SockAddr -> IO ()) -> IO () -> SockAddr -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    , settingsTimeout :: Port
settingsTimeout = Port
30
    , settingsManager :: Maybe Manager
settingsManager = Maybe Manager
forall a. Maybe a
Nothing
    , settingsFdCacheDuration :: Port
settingsFdCacheDuration = Port
0
    , settingsFileInfoCacheDuration :: Port
settingsFileInfoCacheDuration = Port
0
    , settingsBeforeMainLoop :: IO ()
settingsBeforeMainLoop = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    , settingsFork :: ((forall a. IO a -> IO a) -> IO ()) -> IO ()
settingsFork = ((forall a. IO a -> IO a) -> IO ()) -> IO ()
defaultFork
    , settingsNoParsePath :: Bool
settingsNoParsePath = Bool
False
    , settingsInstallShutdownHandler :: IO () -> IO ()
settingsInstallShutdownHandler = IO () -> IO () -> IO ()
forall a b. a -> b -> a
const (IO () -> IO () -> IO ()) -> IO () -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    , settingsServerName :: ByteString
settingsServerName = String -> ByteString
C8.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ String
"Warp/" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Version -> String
showVersion Version
Paths_warp.version
    , settingsMaximumBodyFlush :: Maybe Port
settingsMaximumBodyFlush = Port -> Maybe Port
forall a. a -> Maybe a
Just Port
8192
    , settingsProxyProtocol :: ProxyProtocol
settingsProxyProtocol = ProxyProtocol
ProxyProtocolNone
    , settingsSlowlorisSize :: Port
settingsSlowlorisSize = Port
2048
    , settingsHTTP2Enabled :: Bool
settingsHTTP2Enabled = Bool
True
    , settingsLogger :: Request -> Status -> Maybe Integer -> IO ()
settingsLogger = \Request
_ Status
_ Maybe Integer
_ -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    , settingsServerPushLogger :: Request -> ByteString -> Integer -> IO ()
settingsServerPushLogger = \Request
_ ByteString
_ Integer
_ -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    , settingsGracefulShutdownTimeout :: Maybe Port
settingsGracefulShutdownTimeout = Maybe Port
forall a. Maybe a
Nothing
    , settingsGracefulCloseTimeout1 :: Port
settingsGracefulCloseTimeout1 = Port
0
    , settingsGracefulCloseTimeout2 :: Port
settingsGracefulCloseTimeout2 = Port
2000
    , settingsMaxTotalHeaderLength :: Port
settingsMaxTotalHeaderLength = Port
50 Port -> Port -> Port
forall a. Num a => a -> a -> a
* Port
1024
    , settingsAltSvc :: Maybe ByteString
settingsAltSvc = Maybe ByteString
forall a. Maybe a
Nothing
    }
defaultShouldDisplayException :: SomeException -> Bool
defaultShouldDisplayException :: SomeException -> Bool
defaultShouldDisplayException SomeException
se
    | Just AsyncException
ThreadKilled <- SomeException -> Maybe AsyncException
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
se = Bool
False
    | Just (InvalidRequest
_ :: InvalidRequest) <- SomeException -> Maybe InvalidRequest
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
se = Bool
False
    | Just (IOError -> IOErrorType
ioeGetErrorType -> IOErrorType
et) <- SomeException -> Maybe IOError
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
se
        , IOErrorType
et IOErrorType -> IOErrorType -> Bool
forall a. Eq a => a -> a -> Bool
== IOErrorType
ResourceVanished Bool -> Bool -> Bool
|| IOErrorType
et IOErrorType -> IOErrorType -> Bool
forall a. Eq a => a -> a -> Bool
== IOErrorType
InvalidArgument = Bool
False
    | Just TimeoutThread
TimeoutThread <- SomeException -> Maybe TimeoutThread
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
se = Bool
False
    | Bool
otherwise = Bool
True
defaultOnException :: Maybe Request -> SomeException -> IO ()
defaultOnException :: Maybe Request -> SomeException -> IO ()
defaultOnException Maybe Request
_ SomeException
e =
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (SomeException -> Bool
defaultShouldDisplayException SomeException
e)
        (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Handle -> Text -> IO ()
TIO.hPutStrLn Handle
stderr (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ SomeException -> String
forall a. Show a => a -> String
show SomeException
e
defaultOnExceptionResponse :: SomeException -> Response
defaultOnExceptionResponse :: SomeException -> Response
defaultOnExceptionResponse SomeException
e
  | Just (InvalidRequest
_ :: InvalidRequest) <-
    SomeException -> Maybe InvalidRequest
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e = Status -> ResponseHeaders -> ByteString -> Response
responseLBS Status
H.badRequest400
                                [(HeaderName
H.hContentType, ByteString
"text/plain; charset=utf-8")]
                                 ByteString
"Bad Request"
  | Just (ConnectionError (UnknownErrorCode ErrorCode
413) ByteString
t) <-
    SomeException -> Maybe HTTP2Error
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e = Status -> ResponseHeaders -> ByteString -> Response
responseLBS Status
H.status413
                                [(HeaderName
H.hContentType, ByteString
"text/plain; charset=utf-8")]
                                 (ByteString -> ByteString
fromStrict ByteString
t)
  | Just (ConnectionError (UnknownErrorCode ErrorCode
431) ByteString
t) <-
    SomeException -> Maybe HTTP2Error
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e = Status -> ResponseHeaders -> ByteString -> Response
responseLBS Status
H.status431
                                [(HeaderName
H.hContentType, ByteString
"text/plain; charset=utf-8")]
                                 (ByteString -> ByteString
fromStrict ByteString
t)
  | Bool
otherwise       = Status -> ResponseHeaders -> ByteString -> Response
responseLBS Status
H.internalServerError500
                                [(HeaderName
H.hContentType, ByteString
"text/plain; charset=utf-8")]
                                 ByteString
"Something went wrong"
exceptionResponseForDebug :: SomeException -> Response
exceptionResponseForDebug :: SomeException -> Response
exceptionResponseForDebug SomeException
e =
    Status -> ResponseHeaders -> Builder -> Response
responseBuilder Status
H.internalServerError500
                    [(HeaderName
H.hContentType, ByteString
"text/plain; charset=utf-8")]
                    (Builder -> Response) -> Builder -> Response
forall a b. (a -> b) -> a -> b
$ Builder
"Exception: " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> String -> Builder
Builder.stringUtf8 (SomeException -> String
forall a. Show a => a -> String
show SomeException
e)
defaultFork :: ((forall a. IO a -> IO a) -> IO ()) -> IO ()
defaultFork :: ((forall a. IO a -> IO a) -> IO ()) -> IO ()
defaultFork (forall a. IO a -> IO a) -> IO ()
io =
  (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, () #)) -> IO ())
-> (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s0 ->
    case (IO () -> State# RealWorld -> (# State# RealWorld, ThreadId# #)
forall a.
a -> State# RealWorld -> (# State# RealWorld, ThreadId# #)
fork# ((forall a. IO a -> IO a) -> IO ()
io forall a. IO a -> IO a
unsafeUnmask) State# RealWorld
s0) of
      (# State# RealWorld
s1, ThreadId#
_tid #) ->
        (# State# RealWorld
s1, () #)