{-# LANGUAGE OverloadedStrings, RankNTypes #-}
module Web.Scotty.Trans
(
scottyT, scottyAppT, scottyOptsT, scottySocketT, Options(..)
, middleware, get, post, put, delete, patch, options, addroute, matchAny, notFound
, capture, regex, function, literal
, request, header, headers, body, bodyReader, param, params, jsonData, files
, status, addHeader, setHeader, redirect
, text, html, file, json, stream, raw
, raise, raiseStatus, rescue, next, finish, defaultHandler, ScottyError(..), liftAndCatchIO
, Param, Parsable(..), readEither
, RoutePattern, File
, ScottyT, ActionT
) where
import Blaze.ByteString.Builder (fromByteString)
import Control.Monad (when)
import Control.Monad.State.Strict (execState, modify)
import Control.Monad.IO.Class
import Data.Default.Class (def)
import Network.HTTP.Types (status404, status500)
import Network.Socket (Socket)
import Network.Wai
import Network.Wai.Handler.Warp (Port, runSettings, runSettingsSocket, setPort, getPort)
import Web.Scotty.Action
import Web.Scotty.Route
import Web.Scotty.Internal.Types hiding (Application, Middleware)
import Web.Scotty.Util (socketDescription)
import qualified Web.Scotty.Internal.Types as Scotty
scottyT :: (Monad m, MonadIO n)
=> Port
-> (m Response -> IO Response)
-> ScottyT e m ()
-> n ()
scottyT p = scottyOptsT $ def { settings = setPort p (settings def) }
scottyOptsT :: (Monad m, MonadIO n)
=> Options
-> (m Response -> IO Response)
-> ScottyT e m ()
-> n ()
scottyOptsT opts runActionToIO s = do
when (verbose opts > 0) $
liftIO $ putStrLn $ "Setting phasers to stun... (port " ++ show (getPort (settings opts)) ++ ") (ctrl-c to quit)"
liftIO . runSettings (settings opts) =<< scottyAppT runActionToIO s
scottySocketT :: (Monad m, MonadIO n)
=> Options
-> Socket
-> (m Response -> IO Response)
-> ScottyT e m ()
-> n ()
scottySocketT opts sock runActionToIO s = do
when (verbose opts > 0) $ do
d <- liftIO $ socketDescription sock
liftIO $ putStrLn $ "Setting phasers to stun... (" ++ d ++ ") (ctrl-c to quit)"
liftIO . runSettingsSocket (settings opts) sock =<< scottyAppT runActionToIO s
scottyAppT :: (Monad m, Monad n)
=> (m Response -> IO Response)
-> ScottyT e m ()
-> n Application
scottyAppT runActionToIO defs = do
let s = execState (runS defs) def
let rapp req callback = runActionToIO (foldl (flip ($)) notFoundApp (routes s) req) >>= callback
return $ foldl (flip ($)) rapp (middlewares s)
notFoundApp :: Monad m => Scotty.Application m
notFoundApp _ = return $ responseBuilder status404 [("Content-Type","text/html")]
$ fromByteString "<h1>404: File Not Found!</h1>"
defaultHandler :: (ScottyError e, Monad m) => (e -> ActionT e m ()) -> ScottyT e m ()
defaultHandler f = ScottyT $ modify $ addHandler $ Just (\e -> status status500 >> f e)
middleware :: Middleware -> ScottyT e m ()
middleware = ScottyT . modify . addMiddleware