module Web.Spock.Config
    ( SpockCfg (..), defaultSpockCfg
      
    , PoolOrConn (..), ConnBuilder (..), PoolCfg (..)
      
    , defaultSessionCfg, SessionCfg (..)
    , defaultSessionHooks, SessionHooks (..)
    , SessionStore(..), SessionStoreInstance(..)
    , SV.newStmSessionStore
    )
where
import Web.Spock.Action
import Web.Spock.Internal.Types
import qualified Web.Spock.Internal.SessionVault as SV
import Data.Monoid
import Network.HTTP.Types.Status
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
defaultSessionHooks :: SessionHooks a
defaultSessionHooks =
    SessionHooks
    { sh_removed = const $ return ()
    }
defaultSessionCfg :: a -> IO (SessionCfg conn a st)
defaultSessionCfg emptySession =
  do store <- SV.newStmSessionStore
     return
       SessionCfg
       { sc_cookieName = "spockcookie"
       , sc_sessionTTL = 3600
       , sc_sessionIdEntropy = 64
       , sc_sessionExpandTTL = True
       , sc_emptySession = emptySession
       , sc_store = store
       , sc_housekeepingInterval = 60 * 10
       , sc_hooks = defaultSessionHooks
       }
defaultSpockCfg :: sess -> PoolOrConn conn -> st -> IO (SpockCfg conn sess st)
defaultSpockCfg sess conn st =
  do defSess <- defaultSessionCfg sess
     return
       SpockCfg
       { spc_initialState = st
       , spc_database = conn
       , spc_sessionCfg = defSess
       , spc_maxRequestSize = Just (5 * 1024 * 1024)
       , spc_errorHandler = errorHandler
       , spc_csrfProtection = False
       , spc_csrfHeaderName = "X-Csrf-Token"
       , spc_csrfPostName = "__csrf_token"
       }
errorHandler :: Status -> ActionCtxT () IO ()
errorHandler status = html $ errorTemplate status
errorTemplate :: Status -> T.Text
errorTemplate s =
    "<html><head>"
    <> "<title>" <> message <> "</title>"
    <> "</head>"
    <> "<body>"
    <> "<h1>" <> message <> "</h1>"
    <> "<a href='https://www.spock.li'>powered by Spock</a>"
    <> "</body>"
    where
      message =
          showT (statusCode s) <> " - " <> T.decodeUtf8 (statusMessage s)
      showT = T.pack . show