module Web.Spock.Shared
    (
      runSpock, runSpockNoBanner, spockAsApp
     
    , SpockAction, SpockActionCtx, ActionT, W.ActionCtxT
     
    , request, header, rawHeader, cookie, reqMethod
    , preferredFormat, ClientPreferredFormat(..)
    , body, jsonBody, jsonBody'
    , files, UploadedFile (..)
    , params, param, param'
     
    , getContext, runInContext
     
    , setStatus, setHeader, redirect, jumpNext, CookieSettings(..), defaultCookieSettings, CookieEOL(..), setCookie, deleteCookie, bytes, lazyBytes
    , text, html, file, json, stream, response
      
    , middlewarePass, modifyVault, queryVault
      
    , SpockCfg (..), defaultSpockCfg
      
    , PoolOrConn (..), ConnBuilder (..), PoolCfg (..)
      
    , HasSpock (runQuery, getState), SpockConn, SpockState, SpockSession
      
    , requireBasicAuth, withBasicAuthData
     
    , defaultSessionCfg, SessionCfg (..)
    , defaultSessionHooks, SessionHooks (..)
    , SessionPersistCfg(..), readShowSessionPersist
    , SessionId
    , sessionRegenerateId, getSessionId, readSession, writeSession
    , modifySession, modifySession', modifyReadSession, mapAllSessions, clearAllSessions
     
    , getSpockHeart, runSpockIO, WebStateM, WebState
    )
where
import Web.Spock.Internal.Monad
import Web.Spock.Internal.SessionManager
import Web.Spock.Internal.Types
import Web.Spock.Internal.CoreAction
import Control.Monad
import Control.Concurrent.STM (STM)
import System.Directory
import qualified Web.Spock.Internal.Wire as W
import qualified Network.Wai as Wai
import qualified Network.Wai.Handler.Warp as Warp
runSpock :: Warp.Port -> IO Wai.Middleware -> IO ()
runSpock port mw =
    do putStrLn ("Spock is running on port " ++ show port)
       app <- spockAsApp mw
       Warp.run port app
runSpockNoBanner :: Warp.Port -> IO Wai.Middleware -> IO ()
runSpockNoBanner port mw =
    do app <- spockAsApp mw
       Warp.run port app
spockAsApp :: IO Wai.Middleware -> IO Wai.Application
spockAsApp = liftM W.middlewareToApp
sessionRegenerateId :: SpockActionCtx ctx conn sess st ()
sessionRegenerateId =
    getSessMgr >>= sm_regenerateSessionId
getSessionId :: SpockActionCtx ctx conn sess st SessionId
getSessionId =
    getSessMgr >>= sm_getSessionId
writeSession :: sess -> SpockActionCtx ctx conn sess st ()
writeSession d =
    do mgr <- getSessMgr
       sm_writeSession mgr d
modifySession :: (sess -> sess) -> SpockActionCtx ctx conn sess st ()
modifySession f =
    modifySession' $ \sess -> (f sess, ())
modifySession' :: (sess -> (sess, a)) -> SpockActionCtx ctx conn sess st a
modifySession' f =
    do mgr <- getSessMgr
       sm_modifySession mgr f
modifyReadSession :: (sess -> sess) -> SpockActionCtx ctx conn sess st sess
modifyReadSession f =
    modifySession' $ \sess ->
        let x = f sess
        in (x, x)
readSession :: SpockActionCtx ctx conn sess st sess
readSession =
    do mgr <- getSessMgr
       sm_readSession mgr
clearAllSessions :: SpockActionCtx ctx conn sess st ()
clearAllSessions =
    do mgr <- getSessMgr
       sm_clearAllSessions mgr
mapAllSessions :: (sess -> STM sess) -> SpockActionCtx ctx conn sess st ()
mapAllSessions f =
    do mgr <- getSessMgr
       sm_mapSessions mgr f
readShowSessionPersist :: (Read a, Show a) => FilePath -> SessionPersistCfg a
readShowSessionPersist fp =
    SessionPersistCfg
    { spc_load =
         do isThere <- doesFileExist fp
            if isThere
            then do str <- readFile fp
                    return (read str)
            else return []
    , spc_store = writeFile fp . show
    }