{-# LANGUAGE RankNTypes #-}
module Web.Spock.Internal.Config where

import qualified Web.Spock.Internal.Wire as W

import Data.Word
import Network.HTTP.Types.Status
import System.IO
import Web.Spock.Internal.CoreAction
import qualified Data.Text as T
import qualified Data.Text.IO as T


data SpockConfig
    = SpockConfig
    { SpockConfig -> Maybe Word64
sc_maxRequestSize :: Maybe Word64
      -- ^ Maximum request size in bytes
    , SpockConfig -> Status -> ActionCtxT () IO ()
sc_errorHandler :: Status -> W.ActionCtxT () IO ()
      -- ^ Error handler. Given status is set in response by default, but you
      -- can always override it with `setStatus`
    , SpockConfig -> Text -> IO ()
sc_logError :: T.Text -> IO ()
      -- ^ Function that should be called to log errors.
    }

-- | Default Spock configuration. No restriction on maximum request size; error
-- handler simply prints status message as plain text and all errors are logged
-- to stderr.
defaultSpockConfig :: SpockConfig
defaultSpockConfig :: SpockConfig
defaultSpockConfig = Maybe Word64
-> (Status -> ActionCtxT () IO ())
-> (Text -> IO ())
-> SpockConfig
SpockConfig Maybe Word64
forall a. Maybe a
Nothing Status -> ActionCtxT () IO ()
forall ctx a. Status -> ActionCtxT ctx IO a
defaultHandler (Handle -> Text -> IO ()
T.hPutStrLn Handle
stderr)
  where
    defaultHandler :: Status -> ActionCtxT ctx IO a
defaultHandler = ByteString -> ActionCtxT ctx IO a
forall (m :: * -> *) ctx a.
MonadIO m =>
ByteString -> ActionCtxT ctx m a
bytes (ByteString -> ActionCtxT ctx IO a)
-> (Status -> ByteString) -> Status -> ActionCtxT ctx IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Status -> ByteString
statusMessage