{-# LANGUAGE OverloadedStrings, RankNTypes #-}
module Web.Scotty.Trans
(
scottyT, scottyAppT, scottyOptsT, scottySocketT, Options(..)
, middleware, get, post, put, delete, patch, options, addroute, matchAny, notFound, setMaxRequestBodySize
, 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, Kilobytes
, ScottyT, ActionT
) where
import Blaze.ByteString.Builder (fromByteString)
import Control.Exception (assert)
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 :: forall (m :: * -> *) (n :: * -> *) e.
(Monad m, MonadIO n) =>
Port -> (m Response -> IO Response) -> ScottyT e m () -> n ()
scottyT Port
p = forall (m :: * -> *) (n :: * -> *) e.
(Monad m, MonadIO n) =>
Options -> (m Response -> IO Response) -> ScottyT e m () -> n ()
scottyOptsT forall a b. (a -> b) -> a -> b
$ forall a. Default a => a
def { settings :: Settings
settings = Port -> Settings -> Settings
setPort Port
p (Options -> Settings
settings forall a. Default a => a
def) }
scottyOptsT :: (Monad m, MonadIO n)
=> Options
-> (m Response -> IO Response)
-> ScottyT e m ()
-> n ()
scottyOptsT :: forall (m :: * -> *) (n :: * -> *) e.
(Monad m, MonadIO n) =>
Options -> (m Response -> IO Response) -> ScottyT e m () -> n ()
scottyOptsT Options
opts m Response -> IO Response
runActionToIO ScottyT e m ()
s = do
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Options -> Port
verbose Options
opts forall a. Ord a => a -> a -> Bool
> Port
0) forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ [Char] -> IO ()
putStrLn forall a b. (a -> b) -> a -> b
$ [Char]
"Setting phasers to stun... (port " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show (Settings -> Port
getPort (Options -> Settings
settings Options
opts)) forall a. [a] -> [a] -> [a]
++ [Char]
") (ctrl-c to quit)"
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> Application -> IO ()
runSettings (Options -> Settings
settings Options
opts) forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall (m :: * -> *) (n :: * -> *) e.
(Monad m, Monad n) =>
(m Response -> IO Response) -> ScottyT e m () -> n Application
scottyAppT m Response -> IO Response
runActionToIO ScottyT e m ()
s
scottySocketT :: (Monad m, MonadIO n)
=> Options
-> Socket
-> (m Response -> IO Response)
-> ScottyT e m ()
-> n ()
scottySocketT :: forall (m :: * -> *) (n :: * -> *) e.
(Monad m, MonadIO n) =>
Options
-> Socket -> (m Response -> IO Response) -> ScottyT e m () -> n ()
scottySocketT Options
opts Socket
sock m Response -> IO Response
runActionToIO ScottyT e m ()
s = do
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Options -> Port
verbose Options
opts forall a. Ord a => a -> a -> Bool
> Port
0) forall a b. (a -> b) -> a -> b
$ do
[Char]
d <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Socket -> IO [Char]
socketDescription Socket
sock
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ [Char] -> IO ()
putStrLn forall a b. (a -> b) -> a -> b
$ [Char]
"Setting phasers to stun... (" forall a. [a] -> [a] -> [a]
++ [Char]
d forall a. [a] -> [a] -> [a]
++ [Char]
") (ctrl-c to quit)"
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> Socket -> Application -> IO ()
runSettingsSocket (Options -> Settings
settings Options
opts) Socket
sock forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall (m :: * -> *) (n :: * -> *) e.
(Monad m, Monad n) =>
(m Response -> IO Response) -> ScottyT e m () -> n Application
scottyAppT m Response -> IO Response
runActionToIO ScottyT e m ()
s
scottyAppT :: (Monad m, Monad n)
=> (m Response -> IO Response)
-> ScottyT e m ()
-> n Application
scottyAppT :: forall (m :: * -> *) (n :: * -> *) e.
(Monad m, Monad n) =>
(m Response -> IO Response) -> ScottyT e m () -> n Application
scottyAppT m Response -> IO Response
runActionToIO ScottyT e m ()
defs = do
let s :: ScottyState e m
s = forall s a. State s a -> s -> s
execState (forall e (m :: * -> *) a.
ScottyT e m a -> State (ScottyState e m) a
runS ScottyT e m ()
defs) forall a. Default a => a
def
let rapp :: Request -> (Response -> IO b) -> IO b
rapp Request
req Response -> IO b
callback = m Response -> IO Response
runActionToIO (forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. (a -> b) -> a -> b
($)) forall (m :: * -> *). Monad m => Application m
notFoundApp (forall e (m :: * -> *). ScottyState e m -> [Middleware m]
routes ScottyState e m
s) Request
req) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Response -> IO b
callback
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. (a -> b) -> a -> b
($)) forall {b}. Request -> (Response -> IO b) -> IO b
rapp (forall e (m :: * -> *). ScottyState e m -> [Middleware]
middlewares ScottyState e m
s)
notFoundApp :: Monad m => Scotty.Application m
notFoundApp :: forall (m :: * -> *). Monad m => Application m
notFoundApp Request
_ = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Status -> ResponseHeaders -> Builder -> Response
responseBuilder Status
status404 [(HeaderName
"Content-Type",ByteString
"text/html")]
forall a b. (a -> b) -> a -> b
$ ByteString -> Builder
fromByteString ByteString
"<h1>404: File Not Found!</h1>"
defaultHandler :: (ScottyError e, Monad m) => (e -> ActionT e m ()) -> ScottyT e m ()
defaultHandler :: forall e (m :: * -> *).
(ScottyError e, Monad m) =>
(e -> ActionT e m ()) -> ScottyT e m ()
defaultHandler e -> ActionT e m ()
f = forall e (m :: * -> *) a.
State (ScottyState e m) a -> ScottyT e m a
ScottyT forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ forall e (m :: * -> *).
ErrorHandler e m -> ScottyState e m -> ScottyState e m
addHandler forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just (\e
e -> forall (m :: * -> *) e. Monad m => Status -> ActionT e m ()
status Status
status500 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> e -> ActionT e m ()
f e
e)
middleware :: Middleware -> ScottyT e m ()
middleware :: forall e (m :: * -> *). Middleware -> ScottyT e m ()
middleware = forall e (m :: * -> *) a.
State (ScottyState e m) a -> ScottyT e m a
ScottyT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e (m :: * -> *).
Middleware -> ScottyState e m -> ScottyState e m
addMiddleware
setMaxRequestBodySize :: Kilobytes -> ScottyT e m ()
setMaxRequestBodySize :: forall e (m :: * -> *). Port -> ScottyT e m ()
setMaxRequestBodySize Port
i = forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Port
i forall a. Ord a => a -> a -> Bool
> Port
0) forall a b. (a -> b) -> a -> b
$ forall e (m :: * -> *) a.
State (ScottyState e m) a -> ScottyT e m a
ScottyT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e (m :: * -> *).
RouteOptions -> ScottyState e m -> ScottyState e m
updateMaxRequestBodySize forall a b. (a -> b) -> a -> b
$ forall a. Default a => a
def { maxRequestBodySize :: Maybe Port
maxRequestBodySize = forall a. a -> Maybe a
Just Port
i }