module Network.Wai.Handler.Warp.Settings where
import Control.Concurrent (forkIOWithUnmask)
import Control.Exception
import Control.Monad (when, void)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as S8
import Data.ByteString.Builder (byteString)
#if __GLASGOW_HASKELL__ < 709
import Data.Monoid (mappend)
#endif
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(..))
import qualified Network.HTTP.Types as H
import Network.Socket (SockAddr)
import Network.Wai
import Network.Wai.Handler.Warp.Timeout
import Network.Wai.Handler.Warp.Types
import qualified Paths_warp
import System.IO (stderr)
import System.IO.Error (ioeGetErrorType)
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 = ProxyProtocolNone
                     
                   | ProxyProtocolRequired
                     
                   | ProxyProtocolOptional
                     
defaultSettings :: Settings
defaultSettings = Settings
    { settingsPort = 3000
    , settingsHost = "*4"
    , settingsOnException = defaultOnException
    , settingsOnExceptionResponse = defaultOnExceptionResponse
    , settingsOnOpen = const $ return True
    , settingsOnClose = const $ return ()
    , settingsTimeout = 30
    , settingsManager = Nothing
    , settingsFdCacheDuration = 0
    , settingsBeforeMainLoop = return ()
    , settingsFork = void . forkIOWithUnmask
    , settingsNoParsePath = False
    , settingsInstallShutdownHandler = const $ return ()
    , settingsServerName = S8.pack $ "Warp/" ++ showVersion Paths_warp.version
    , settingsMaximumBodyFlush = Just 8192
    , settingsProxyProtocol = ProxyProtocolNone
    , settingsSlowlorisSize = 2048
    , settingsHTTP2Enabled = True
    }
defaultShouldDisplayException :: SomeException -> Bool
defaultShouldDisplayException se
    | Just ThreadKilled <- fromException se = False
    | Just (_ :: InvalidRequest) <- fromException se = False
    | Just (ioeGetErrorType -> et) <- fromException se
        , et == ResourceVanished || et == InvalidArgument = False
    | Just TimeoutThread <- fromException se = False
    | otherwise = True
defaultOnException :: Maybe Request -> SomeException -> IO ()
defaultOnException _ e =
    when (defaultShouldDisplayException e)
        $ TIO.hPutStrLn stderr $ T.pack $ show e
defaultOnExceptionResponse :: SomeException -> Response
defaultOnExceptionResponse e
  | Just (_ :: InvalidRequest) <- fromException e = responseLBS H.badRequest400  [(H.hContentType, "text/plain; charset=utf-8")] "Bad Request"
  | otherwise                                     = responseLBS H.internalServerError500 [(H.hContentType, "text/plain; charset=utf-8")] "Something went wrong"
exceptionResponseForDebug :: SomeException -> Response
exceptionResponseForDebug e =
    responseBuilder H.internalServerError500
                    [(H.hContentType, "text/plain; charset=utf-8")]
                    $ byteString . S8.pack $ "Exception: " ++ show e