{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE CPP               #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes        #-}
{-# LANGUAGE LambdaCase #-}
{-# language ScopedTypeVariables #-}
module Web.Scotty.Action
    ( addHeader
    , body
    , bodyReader
    , file
    , rawResponse
    , files
    , finish
    , header
    , headers
    , html
    , liftAndCatchIO
    , json
    , jsonData
    , next
    , param
    , captureParam
    , formParam
    , queryParam
    , params
    , captureParams
    , formParams
    , queryParams
    , raise
    , raiseStatus
    , throw
    , raw
    , nested
    , readEither
    , redirect
    , request
    , rescue
    , setHeader
    , status
    , stream
    , text
    , Param
    , Parsable(..)
      -- private to Scotty
    , runAction
    ) where

import           Blaze.ByteString.Builder   (fromLazyByteString)

import qualified Control.Exception          as E
import           Control.Monad              (when)
import           Control.Monad.IO.Class     (MonadIO(..))
import UnliftIO (MonadUnliftIO(..))
import           Control.Monad.Reader       (MonadReader(..), ReaderT(..))

import           Control.Concurrent.MVar

import qualified Data.Aeson                 as A
import Data.Bool (bool)
import qualified Data.ByteString.Char8      as B
import qualified Data.ByteString.Lazy.Char8 as BL
import qualified Data.CaseInsensitive       as CI
import           Data.Int
import qualified Data.Text                  as ST
import qualified Data.Text.Encoding         as STE
import qualified Data.Text.Lazy             as T
import           Data.Text.Lazy.Encoding    (encodeUtf8)
import           Data.Word

import           Network.HTTP.Types
-- not re-exported until version 0.11
#if !MIN_VERSION_http_types(0,11,0)
import           Network.HTTP.Types.Status
#endif
import           Network.Wai (Request, Response, StreamingBody, Application, requestHeaders)

import           Numeric.Natural

import           Prelude ()
import "base-compat-batteries" Prelude.Compat

import           Web.Scotty.Internal.Types
import           Web.Scotty.Util (mkResponse, addIfNotPresent, add, replace, lazyTextToStrictByteString, strictByteStringToLazyText)
import Web.Scotty.Exceptions (Handler(..), catch, catchesOptionally, tryAny)

import Network.Wai.Internal (ResponseReceived(..))

-- | Evaluate a route, catch all exceptions (user-defined ones, internal and all remaining, in this order)
--   and construct the 'Response'
--
-- 'Nothing' indicates route failed (due to Next) and pattern matching should try the next available route.
-- 'Just' indicates a successful response.
runAction :: MonadUnliftIO m =>
             Maybe (ErrorHandler m) -- ^ this handler (if present) is in charge of user-defined exceptions
          -> ActionEnv
          -> ActionT m () -- ^ Route action to be evaluated
          -> m (Maybe Response)
runAction :: forall (m :: * -> *).
MonadUnliftIO m =>
Maybe (ErrorHandler m)
-> ActionEnv -> ActionT m () -> m (Maybe Response)
runAction Maybe (ErrorHandler m)
mh ActionEnv
env ActionT m ()
action = do
  let
    handlers :: [ErrorHandler m]
handlers = [
      forall (m :: * -> *). MonadIO m => ErrorHandler m
statusErrorHandler, -- StatusError
      forall (m :: * -> *). MonadIO m => ErrorHandler m
actionErrorHandler, -- ActionError i.e. Next, Finish, Redirect
      forall (m :: * -> *). MonadIO m => ErrorHandler m
someExceptionHandler -- all remaining exceptions
               ]
  Bool
ok <- forall a b c. (a -> b -> c) -> b -> a -> c
flip forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ActionEnv
env forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. ActionT m a -> ReaderT ActionEnv m a
runAM forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadUnliftIO m => m a -> m Bool
tryNext (forall (m :: * -> *) a.
MonadUnliftIO m =>
m a -> Maybe (Handler m a) -> [Handler m a] -> m a
catchesOptionally ActionT m ()
action Maybe (ErrorHandler m)
mh [ErrorHandler m]
handlers )
  ScottyResponse
res <- forall (m :: * -> *). MonadIO m => ActionEnv -> m ScottyResponse
getResponse ActionEnv
env
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> a -> Bool -> a
bool forall a. Maybe a
Nothing (forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ ScottyResponse -> Response
mkResponse ScottyResponse
res) Bool
ok

-- | Catches 'StatusError' and produces an appropriate HTTP response.
statusErrorHandler :: MonadIO m => ErrorHandler m
statusErrorHandler :: forall (m :: * -> *). MonadIO m => ErrorHandler m
statusErrorHandler = forall (m :: * -> *) a e. Exception e => (e -> m a) -> Handler m a
Handler forall a b. (a -> b) -> a -> b
$ \case
  StatusError Status
s Text
e -> do
    forall (m :: * -> *). MonadIO m => Status -> ActionT m ()
status Status
s
    let code :: Text
code = String -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ Status -> Int
statusCode Status
s
    let msg :: Text
msg = Text -> Text
T.fromStrict forall a b. (a -> b) -> a -> b
$ ByteString -> Text
STE.decodeUtf8 forall a b. (a -> b) -> a -> b
$ Status -> ByteString
statusMessage Status
s
    forall (m :: * -> *). MonadIO m => Text -> ActionT m ()
html forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [Text
"<h1>", Text
code, Text
" ", Text
msg, Text
"</h1>", Text
e]

-- | Exception handler in charge of 'ActionError'. Rethrowing 'Next' here is caught by 'tryNext'.
-- All other cases of 'ActionError' are converted to HTTP responses.
actionErrorHandler :: MonadIO m => ErrorHandler m
actionErrorHandler :: forall (m :: * -> *). MonadIO m => ErrorHandler m
actionErrorHandler = forall (m :: * -> *) a e. Exception e => (e -> m a) -> Handler m a
Handler forall a b. (a -> b) -> a -> b
$ \case
  AERedirect Text
url -> do
    forall (m :: * -> *). MonadIO m => Status -> ActionT m ()
status Status
status302
    forall (m :: * -> *). MonadIO m => Text -> Text -> ActionT m ()
setHeader Text
"Location" Text
url
  ActionError
AENext -> forall (m :: * -> *) a. Monad m => ActionT m a
next
  ActionError
AEFinish -> forall (m :: * -> *) a. Monad m => a -> m a
return ()

-- | Uncaught exceptions turn into HTTP 500 Server Error codes
someExceptionHandler :: MonadIO m => ErrorHandler m
someExceptionHandler :: forall (m :: * -> *). MonadIO m => ErrorHandler m
someExceptionHandler = forall (m :: * -> *) a e. Exception e => (e -> m a) -> Handler m a
Handler forall a b. (a -> b) -> a -> b
$ \case
  (SomeException
_ :: E.SomeException) -> forall (m :: * -> *). MonadIO m => Status -> ActionT m ()
status Status
status500

-- | Throw a "500 Server Error" 'StatusError', which can be caught with 'rescue'.
--
-- Uncaught exceptions turn into HTTP 500 responses.
raise :: (MonadIO m) =>
         T.Text -- ^ Error text
      -> ActionT m a
raise :: forall (m :: * -> *) a. MonadIO m => Text -> ActionT m a
raise  = forall (m :: * -> *) a. Monad m => Status -> Text -> ActionT m a
raiseStatus Status
status500

-- | Throw a 'StatusError' exception that has an associated HTTP error code and can be caught with 'rescue'.
--
-- Uncaught exceptions turn into HTTP responses corresponding to the given status.
raiseStatus :: Monad m => Status -> T.Text -> ActionT m a
raiseStatus :: forall (m :: * -> *) a. Monad m => Status -> Text -> ActionT m a
raiseStatus Status
s = forall a e. Exception e => e -> a
E.throw forall b c a. (b -> c) -> (a -> b) -> a -> c
. Status -> Text -> StatusError
StatusError Status
s

-- | Throw an exception which can be caught within the scope of the current Action with 'rescue' or 'catch'.
--
-- If the exception is not caught locally, another option is to implement a global 'Handler' (with 'defaultHandler') that defines its interpretation and a translation to HTTP error codes.
--
-- Uncaught exceptions turn into HTTP 500 responses.
throw :: (MonadIO m, E.Exception e) => e -> ActionT m a
throw :: forall (m :: * -> *) e a.
(MonadIO m, Exception e) =>
e -> ActionT m a
throw = forall a e. Exception e => e -> a
E.throw

-- | Abort execution of this action and continue pattern matching routes.
-- Like an exception, any code after 'next' is not executed.
--
-- NB : Internally, this is implemented with an exception that can only be
-- caught by the library, but not by the user.
--
-- As an example, these two routes overlap. The only way the second one will
-- ever run is if the first one calls 'next'.
--
-- > get "/foo/:bar" $ do
-- >   w :: Text <- captureParam "bar"
-- >   unless (w == "special") next
-- >   text "You made a request to /foo/special"
-- >
-- > get "/foo/:baz" $ do
-- >   w <- captureParam "baz"
-- >   text $ "You made a request to: " <> w
next :: Monad m => ActionT m a
next :: forall (m :: * -> *) a. Monad m => ActionT m a
next = forall a e. Exception e => e -> a
E.throw ActionError
AENext

-- | Catch an exception e.g. a 'StatusError' or a user-defined exception.
--
-- > raise JustKidding `rescue` (\msg -> text msg)
rescue :: (MonadUnliftIO m, E.Exception e) => ActionT m a -> (e -> ActionT m a) -> ActionT m a
rescue :: forall (m :: * -> *) e a.
(MonadUnliftIO m, Exception e) =>
ActionT m a -> (e -> ActionT m a) -> ActionT m a
rescue = forall (m :: * -> *) e a.
(MonadUnliftIO m, Exception e) =>
m a -> (e -> m a) -> m a
catch

-- | Catch any synchronous IO exceptions
liftAndCatchIO :: MonadIO m => IO a -> ActionT m a
liftAndCatchIO :: forall (m :: * -> *) a. MonadIO m => IO a -> ActionT m a
liftAndCatchIO IO a
io = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  Either SomeException a
r <- forall (m :: * -> *) a.
MonadUnliftIO m =>
m a -> m (Either SomeException a)
tryAny IO a
io
  forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall e a. Exception e => e -> IO a
E.throwIO forall (f :: * -> *) a. Applicative f => a -> f a
pure Either SomeException a
r


-- | Redirect to given URL. Like throwing an uncatchable exception. Any code after the call to redirect
-- will not be run.
--
-- > redirect "http://www.google.com"
--
-- OR
--
-- > redirect "/foo/bar"
redirect :: (Monad m) => T.Text -> ActionT m a
redirect :: forall (m :: * -> *) a. Monad m => Text -> ActionT m a
redirect = forall a e. Exception e => e -> a
E.throw forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ActionError
AERedirect

-- | Finish the execution of the current action. Like throwing an uncatchable
-- exception. Any code after the call to finish will not be run.
--
-- /Since: 0.10.3/
finish :: (Monad m) => ActionT m a
finish :: forall (m :: * -> *) a. Monad m => ActionT m a
finish = forall a e. Exception e => e -> a
E.throw ActionError
AEFinish

-- | Get the 'Request' object.
request :: Monad m => ActionT m Request
request :: forall (m :: * -> *). Monad m => ActionT m Request
request = forall (m :: * -> *) a. ReaderT ActionEnv m a -> ActionT m a
ActionT forall a b. (a -> b) -> a -> b
$ ActionEnv -> Request
envReq forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall r (m :: * -> *). MonadReader r m => m r
ask

-- | Get list of uploaded files.
files :: Monad m => ActionT m [File]
files :: forall (m :: * -> *). Monad m => ActionT m [File]
files = forall (m :: * -> *) a. ReaderT ActionEnv m a -> ActionT m a
ActionT forall a b. (a -> b) -> a -> b
$ ActionEnv -> [File]
envFiles forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall r (m :: * -> *). MonadReader r m => m r
ask

-- | Get a request header. Header name is case-insensitive.
header :: (Monad m) => T.Text -> ActionT m (Maybe T.Text)
header :: forall (m :: * -> *). Monad m => Text -> ActionT m (Maybe Text)
header Text
k = do
    RequestHeaders
hs <- Request -> RequestHeaders
requestHeaders forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). Monad m => ActionT m Request
request
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Text
strictByteStringToLazyText forall a b. (a -> b) -> a -> b
$ forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup (forall s. FoldCase s => s -> CI s
CI.mk (Text -> ByteString
lazyTextToStrictByteString Text
k)) RequestHeaders
hs

-- | Get all the request headers. Header names are case-insensitive.
headers :: (Monad m) => ActionT m [(T.Text, T.Text)]
headers :: forall (m :: * -> *). Monad m => ActionT m [Param]
headers = do
    RequestHeaders
hs <- Request -> RequestHeaders
requestHeaders forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). Monad m => ActionT m Request
request
    forall (m :: * -> *) a. Monad m => a -> m a
return [ ( ByteString -> Text
strictByteStringToLazyText (forall s. CI s -> s
CI.original CI ByteString
k)
             , ByteString -> Text
strictByteStringToLazyText ByteString
v)
           | (CI ByteString
k,ByteString
v) <- RequestHeaders
hs ]

-- | Get the request body.
body :: (MonadIO m) => ActionT m BL.ByteString
body :: forall (m :: * -> *). MonadIO m => ActionT m ByteString
body = forall (m :: * -> *) a. ReaderT ActionEnv m a -> ActionT m a
ActionT forall r (m :: * -> *). MonadReader r m => m r
ask forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. ActionEnv -> IO ByteString
envBody)

-- | Get an IO action that reads body chunks
--
-- * This is incompatible with 'body' since 'body' consumes all chunks.
bodyReader :: Monad m => ActionT m (IO B.ByteString)
bodyReader :: forall (m :: * -> *). Monad m => ActionT m (IO ByteString)
bodyReader = forall (m :: * -> *) a. ReaderT ActionEnv m a -> ActionT m a
ActionT forall a b. (a -> b) -> a -> b
$ ActionEnv -> IO ByteString
envBodyChunk forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall r (m :: * -> *). MonadReader r m => m r
ask

-- | Parse the request body as a JSON object and return it.
--
--   If the JSON object is malformed, this sets the status to
--   400 Bad Request, and throws an exception.
--
--   If the JSON fails to parse, this sets the status to
--   422 Unprocessable Entity.
--
--   These status codes are as per https://www.restapitutorial.com/httpstatuscodes.html.
jsonData :: (A.FromJSON a, MonadIO m) => ActionT m a
jsonData :: forall a (m :: * -> *). (FromJSON a, MonadIO m) => ActionT m a
jsonData = do
    ByteString
b <- forall (m :: * -> *). MonadIO m => ActionT m ByteString
body
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (ByteString
b forall a. Eq a => a -> a -> Bool
== ByteString
"") forall a b. (a -> b) -> a -> b
$ do
      let htmlError :: String
htmlError = String
"jsonData - No data was provided."
      forall (m :: * -> *) a. Monad m => Status -> Text -> ActionT m a
raiseStatus Status
status400 forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
htmlError
    case forall a. FromJSON a => ByteString -> Either String a
A.eitherDecode ByteString
b of
      Left String
err -> do
        let htmlError :: String
htmlError = String
"jsonData - malformed."
              forall a. Monoid a => a -> a -> a
`mappend` String
" Data was: " forall a. Monoid a => a -> a -> a
`mappend` ByteString -> String
BL.unpack ByteString
b
              forall a. Monoid a => a -> a -> a
`mappend` String
" Error was: " forall a. Monoid a => a -> a -> a
`mappend` String
err
        forall (m :: * -> *) a. Monad m => Status -> Text -> ActionT m a
raiseStatus Status
status400 forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
htmlError
      Right Value
value -> case forall a. FromJSON a => Value -> Result a
A.fromJSON Value
value of
        A.Error String
err -> do
          let htmlError :: String
htmlError = String
"jsonData - failed parse."
                forall a. Monoid a => a -> a -> a
`mappend` String
" Data was: " forall a. Monoid a => a -> a -> a
`mappend` ByteString -> String
BL.unpack ByteString
b forall a. Monoid a => a -> a -> a
`mappend` String
"."
                forall a. Monoid a => a -> a -> a
`mappend` String
" Error was: " forall a. Monoid a => a -> a -> a
`mappend` String
err
          forall (m :: * -> *) a. Monad m => Status -> Text -> ActionT m a
raiseStatus Status
status422 forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
htmlError
        A.Success a
a -> do
          forall (m :: * -> *) a. Monad m => a -> m a
return a
a

-- | Get a parameter. First looks in captures, then form data, then query parameters.
--
-- * Raises an exception which can be caught by 'rescue' if parameter is not found.
--
-- * If parameter is found, but 'parseParam' fails to parse to the correct type, 'next' is called.
--   This means captures are somewhat typed, in that a route won't match if a correctly typed
--   capture cannot be parsed.
param :: (Parsable a, MonadIO m) => T.Text -> ActionT m a
param :: forall a (m :: * -> *).
(Parsable a, MonadIO m) =>
Text -> ActionT m a
param Text
k = do
    Maybe Text
val <- forall (m :: * -> *) a. ReaderT ActionEnv m a -> ActionT m a
ActionT forall a b. (a -> b) -> a -> b
$ (forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
k forall b c a. (b -> c) -> (a -> b) -> a -> c
. ActionEnv -> [Param]
getParams) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall r (m :: * -> *). MonadReader r m => m r
ask
    case Maybe Text
val of
        Maybe Text
Nothing -> forall (m :: * -> *) a. Monad m => Status -> Text -> ActionT m a
raiseStatus Status
status500 forall a b. (a -> b) -> a -> b
$ Text
"Param: " forall a. Semigroup a => a -> a -> a
<> Text
k forall a. Semigroup a => a -> a -> a
<> Text
" not found!" -- FIXME
        Just Text
v  -> forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a b. a -> b -> a
const forall (m :: * -> *) a. Monad m => ActionT m a
next) forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. Parsable a => Text -> Either Text a
parseParam Text
v
{-# DEPRECATED param "(#204) Not a good idea to treat all parameters identically. Use captureParam, formParam and queryParam instead. "#-}

-- | Get a capture parameter.
--
-- * Raises an exception which can be caught by 'rescue' if parameter is not found. If the exception is not caught, scotty will return a HTTP error code 500 ("Internal Server Error") to the client.
--
-- * If the parameter is found, but 'parseParam' fails to parse to the correct type, 'next' is called.
captureParam :: (Parsable a, Monad m) => T.Text -> ActionT m a
captureParam :: forall a (m :: * -> *).
(Parsable a, Monad m) =>
Text -> ActionT m a
captureParam = forall (m :: * -> *) b.
(Monad m, Parsable b) =>
ParamType
-> (ActionEnv -> [Param]) -> Status -> Text -> ActionT m b
paramWith ParamType
CaptureParam ActionEnv -> [Param]
envCaptureParams Status
status500

-- | Get a form parameter.
--
-- * Raises an exception which can be caught by 'rescue' if parameter is not found. If the exception is not caught, scotty will return a HTTP error code 400 ("Bad Request") to the client.
--
-- * This function raises a code 400 also if the parameter is found, but 'parseParam' fails to parse to the correct type.
formParam :: (Parsable a, Monad m) => T.Text -> ActionT m a
formParam :: forall a (m :: * -> *).
(Parsable a, Monad m) =>
Text -> ActionT m a
formParam = forall (m :: * -> *) b.
(Monad m, Parsable b) =>
ParamType
-> (ActionEnv -> [Param]) -> Status -> Text -> ActionT m b
paramWith ParamType
FormParam ActionEnv -> [Param]
envFormParams Status
status400

-- | Get a query parameter.
--
-- * Raises an exception which can be caught by 'rescue' if parameter is not found. If the exception is not caught, scotty will return a HTTP error code 400 ("Bad Request") to the client.
--
-- * This function raises a code 400 also if the parameter is found, but 'parseParam' fails to parse to the correct type.
queryParam :: (Parsable a, Monad m) => T.Text -> ActionT m a
queryParam :: forall a (m :: * -> *).
(Parsable a, Monad m) =>
Text -> ActionT m a
queryParam = forall (m :: * -> *) b.
(Monad m, Parsable b) =>
ParamType
-> (ActionEnv -> [Param]) -> Status -> Text -> ActionT m b
paramWith ParamType
QueryParam ActionEnv -> [Param]
envQueryParams Status
status400

data ParamType = CaptureParam
               | FormParam
               | QueryParam
instance Show ParamType where
  show :: ParamType -> String
show = \case
    ParamType
CaptureParam -> String
"capture"
    ParamType
FormParam -> String
"form"
    ParamType
QueryParam -> String
"query"

paramWith :: (Monad m, Parsable b) =>
             ParamType
          -> (ActionEnv -> [Param])
          -> Status -- ^ HTTP status to return if parameter is not found
          -> T.Text -- ^ parameter name
          -> ActionT m b
paramWith :: forall (m :: * -> *) b.
(Monad m, Parsable b) =>
ParamType
-> (ActionEnv -> [Param]) -> Status -> Text -> ActionT m b
paramWith ParamType
ty ActionEnv -> [Param]
f Status
err Text
k = do
    Maybe Text
val <- forall (m :: * -> *) a. ReaderT ActionEnv m a -> ActionT m a
ActionT forall a b. (a -> b) -> a -> b
$ (forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
k forall b c a. (b -> c) -> (a -> b) -> a -> c
. ActionEnv -> [Param]
f) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall r (m :: * -> *). MonadReader r m => m r
ask
    case Maybe Text
val of
      Maybe Text
Nothing -> forall (m :: * -> *) a. Monad m => Status -> Text -> ActionT m a
raiseStatus Status
err ([Text] -> Text
T.unwords [String -> Text
T.pack (forall a. Show a => a -> String
show ParamType
ty), Text
"parameter:", Text
k, Text
"not found!"])
      Just Text
v ->
        let handleParseError :: ParamType -> ActionT m a
handleParseError = \case
              ParamType
CaptureParam -> forall (m :: * -> *) a. Monad m => ActionT m a
next
              ParamType
_ -> forall (m :: * -> *) a. Monad m => Status -> Text -> ActionT m a
raiseStatus Status
err ([Text] -> Text
T.unwords [Text
"Cannot parse", Text
v, Text
"as a", String -> Text
T.pack (forall a. Show a => a -> String
show ParamType
ty), Text
"parameter"])
        in forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall {a}. ParamType -> ActionT m a
handleParseError ParamType
ty) forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. Parsable a => Text -> Either Text a
parseParam Text
v

-- | Get all parameters from capture, form and query (in that order).
params :: Monad m => ActionT m [Param]
params :: forall (m :: * -> *). Monad m => ActionT m [Param]
params = forall (m :: * -> *) a. Monad m => (ActionEnv -> a) -> ActionT m a
paramsWith ActionEnv -> [Param]
getParams
{-# DEPRECATED params "(#204) Not a good idea to treat all parameters identically. Use captureParams, formParams and queryParams instead. "#-}

-- | Get capture parameters
captureParams :: Monad m => ActionT m [Param]
captureParams :: forall (m :: * -> *). Monad m => ActionT m [Param]
captureParams = forall (m :: * -> *) a. Monad m => (ActionEnv -> a) -> ActionT m a
paramsWith ActionEnv -> [Param]
envCaptureParams
-- | Get form parameters
formParams :: Monad m => ActionT m [Param]
formParams :: forall (m :: * -> *). Monad m => ActionT m [Param]
formParams = forall (m :: * -> *) a. Monad m => (ActionEnv -> a) -> ActionT m a
paramsWith ActionEnv -> [Param]
envFormParams
-- | Get query parameters
queryParams :: Monad m => ActionT m [Param]
queryParams :: forall (m :: * -> *). Monad m => ActionT m [Param]
queryParams = forall (m :: * -> *) a. Monad m => (ActionEnv -> a) -> ActionT m a
paramsWith ActionEnv -> [Param]
envQueryParams

paramsWith :: Monad m => (ActionEnv -> a) -> ActionT m a
paramsWith :: forall (m :: * -> *) a. Monad m => (ActionEnv -> a) -> ActionT m a
paramsWith ActionEnv -> a
f = forall (m :: * -> *) a. ReaderT ActionEnv m a -> ActionT m a
ActionT (ActionEnv -> a
f forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall r (m :: * -> *). MonadReader r m => m r
ask)

{-# DEPRECATED getParams "(#204) Not a good idea to treat all parameters identically" #-}
getParams :: ActionEnv -> [Param]
getParams :: ActionEnv -> [Param]
getParams ActionEnv
e = ActionEnv -> [Param]
envCaptureParams ActionEnv
e forall a. Semigroup a => a -> a -> a
<> ActionEnv -> [Param]
envFormParams ActionEnv
e forall a. Semigroup a => a -> a -> a
<> ActionEnv -> [Param]
envQueryParams ActionEnv
e

-- | Minimum implemention: 'parseParam'
class Parsable a where
    -- | Take a 'T.Text' value and parse it as 'a', or fail with a message.
    parseParam :: T.Text -> Either T.Text a

    -- | Default implementation parses comma-delimited lists.
    --
    -- > parseParamList t = mapM parseParam (T.split (== ',') t)
    parseParamList :: T.Text -> Either T.Text [a]
    parseParamList Text
t = forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall a. Parsable a => Text -> Either Text a
parseParam ((Char -> Bool) -> Text -> [Text]
T.split (forall a. Eq a => a -> a -> Bool
== Char
',') Text
t)

-- No point using 'read' for Text, ByteString, Char, and String.
instance Parsable T.Text where parseParam :: Text -> Either Text Text
parseParam = forall a b. b -> Either a b
Right
instance Parsable ST.Text where parseParam :: Text -> Either Text Text
parseParam = forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.toStrict
instance Parsable B.ByteString where parseParam :: Text -> Either Text ByteString
parseParam = forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
lazyTextToStrictByteString
instance Parsable BL.ByteString where parseParam :: Text -> Either Text ByteString
parseParam = forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8
-- | Overrides default 'parseParamList' to parse String.
instance Parsable Char where
    parseParam :: Text -> Either Text Char
parseParam Text
t = case Text -> String
T.unpack Text
t of
                    [Char
c] -> forall a b. b -> Either a b
Right Char
c
                    String
_   -> forall a b. a -> Either a b
Left Text
"parseParam Char: no parse"
    parseParamList :: Text -> Either Text String
parseParamList = forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack -- String
-- | Checks if parameter is present and is null-valued, not a literal '()'.
-- If the URI requested is: '/foo?bar=()&baz' then 'baz' will parse as (), where 'bar' will not.
instance Parsable () where
    parseParam :: Text -> Either Text ()
parseParam Text
t = if Text -> Bool
T.null Text
t then forall a b. b -> Either a b
Right () else forall a b. a -> Either a b
Left Text
"parseParam Unit: no parse"

instance (Parsable a) => Parsable [a] where parseParam :: Text -> Either Text [a]
parseParam = forall a. Parsable a => Text -> Either Text [a]
parseParamList

instance Parsable Bool where
    parseParam :: Text -> Either Text Bool
parseParam Text
t = if Text
t' forall a. Eq a => a -> a -> Bool
== Text -> Text
T.toCaseFold Text
"true"
                   then forall a b. b -> Either a b
Right Bool
True
                   else if Text
t' forall a. Eq a => a -> a -> Bool
== Text -> Text
T.toCaseFold Text
"false"
                        then forall a b. b -> Either a b
Right Bool
False
                        else forall a b. a -> Either a b
Left Text
"parseParam Bool: no parse"
        where t' :: Text
t' = Text -> Text
T.toCaseFold Text
t

instance Parsable Double where parseParam :: Text -> Either Text Double
parseParam = forall a. Read a => Text -> Either Text a
readEither
instance Parsable Float where parseParam :: Text -> Either Text Float
parseParam = forall a. Read a => Text -> Either Text a
readEither

instance Parsable Int where parseParam :: Text -> Either Text Int
parseParam = forall a. Read a => Text -> Either Text a
readEither
instance Parsable Int8 where parseParam :: Text -> Either Text Int8
parseParam = forall a. Read a => Text -> Either Text a
readEither
instance Parsable Int16 where parseParam :: Text -> Either Text Int16
parseParam = forall a. Read a => Text -> Either Text a
readEither
instance Parsable Int32 where parseParam :: Text -> Either Text Int32
parseParam = forall a. Read a => Text -> Either Text a
readEither
instance Parsable Int64 where parseParam :: Text -> Either Text Int64
parseParam = forall a. Read a => Text -> Either Text a
readEither
instance Parsable Integer where parseParam :: Text -> Either Text Integer
parseParam = forall a. Read a => Text -> Either Text a
readEither

instance Parsable Word where parseParam :: Text -> Either Text Word
parseParam = forall a. Read a => Text -> Either Text a
readEither
instance Parsable Word8 where parseParam :: Text -> Either Text Word8
parseParam = forall a. Read a => Text -> Either Text a
readEither
instance Parsable Word16 where parseParam :: Text -> Either Text Word16
parseParam = forall a. Read a => Text -> Either Text a
readEither
instance Parsable Word32 where parseParam :: Text -> Either Text Word32
parseParam = forall a. Read a => Text -> Either Text a
readEither
instance Parsable Word64 where parseParam :: Text -> Either Text Word64
parseParam = forall a. Read a => Text -> Either Text a
readEither
instance Parsable Natural where parseParam :: Text -> Either Text Natural
parseParam = forall a. Read a => Text -> Either Text a
readEither

-- | Useful for creating 'Parsable' instances for things that already implement 'Read'. Ex:
--
-- > instance Parsable Int where parseParam = readEither
readEither :: Read a => T.Text -> Either T.Text a
readEither :: forall a. Read a => Text -> Either Text a
readEither Text
t = case [ a
x | (a
x,String
"") <- forall a. Read a => ReadS a
reads (Text -> String
T.unpack Text
t) ] of
                [a
x] -> forall a b. b -> Either a b
Right a
x
                []  -> forall a b. a -> Either a b
Left Text
"readEither: no parse"
                [a]
_   -> forall a b. a -> Either a b
Left Text
"readEither: ambiguous parse"

-- | Set the HTTP response status.
status :: MonadIO m => Status -> ActionT m ()
status :: forall (m :: * -> *). MonadIO m => Status -> ActionT m ()
status = forall (m :: * -> *).
MonadIO m =>
(ScottyResponse -> ScottyResponse) -> ActionT m ()
modifyResponse forall b c a. (b -> c) -> (a -> b) -> a -> c
. Status -> ScottyResponse -> ScottyResponse
setStatus

-- Not exported, but useful in the functions below.
changeHeader :: MonadIO m
             => (CI.CI B.ByteString -> B.ByteString -> [(HeaderName, B.ByteString)] -> [(HeaderName, B.ByteString)])
             -> T.Text -> T.Text -> ActionT m ()
changeHeader :: forall (m :: * -> *).
MonadIO m =>
(CI ByteString -> ByteString -> RequestHeaders -> RequestHeaders)
-> Text -> Text -> ActionT m ()
changeHeader CI ByteString -> ByteString -> RequestHeaders -> RequestHeaders
f Text
k =
  forall (m :: * -> *).
MonadIO m =>
(ScottyResponse -> ScottyResponse) -> ActionT m ()
modifyResponse forall b c a. (b -> c) -> (a -> b) -> a -> c
. (RequestHeaders -> RequestHeaders)
-> ScottyResponse -> ScottyResponse
setHeaderWith forall b c a. (b -> c) -> (a -> b) -> a -> c
. CI ByteString -> ByteString -> RequestHeaders -> RequestHeaders
f (forall s. FoldCase s => s -> CI s
CI.mk forall a b. (a -> b) -> a -> b
$ Text -> ByteString
lazyTextToStrictByteString Text
k) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
lazyTextToStrictByteString

-- | Add to the response headers. Header names are case-insensitive.
addHeader :: MonadIO m => T.Text -> T.Text -> ActionT m ()
addHeader :: forall (m :: * -> *). MonadIO m => Text -> Text -> ActionT m ()
addHeader = forall (m :: * -> *).
MonadIO m =>
(CI ByteString -> ByteString -> RequestHeaders -> RequestHeaders)
-> Text -> Text -> ActionT m ()
changeHeader forall a b. a -> b -> [(a, b)] -> [(a, b)]
add

-- | Set one of the response headers. Will override any previously set value for that header.
-- Header names are case-insensitive.
setHeader :: MonadIO m => T.Text -> T.Text -> ActionT m ()
setHeader :: forall (m :: * -> *). MonadIO m => Text -> Text -> ActionT m ()
setHeader = forall (m :: * -> *).
MonadIO m =>
(CI ByteString -> ByteString -> RequestHeaders -> RequestHeaders)
-> Text -> Text -> ActionT m ()
changeHeader forall a b. Eq a => a -> b -> [(a, b)] -> [(a, b)]
replace

-- | Set the body of the response to the given 'T.Text' value. Also sets \"Content-Type\"
-- header to \"text/plain; charset=utf-8\" if it has not already been set.
text :: (MonadIO m) => T.Text -> ActionT m ()
text :: forall (m :: * -> *). MonadIO m => Text -> ActionT m ()
text Text
t = do
    forall (m :: * -> *).
MonadIO m =>
(CI ByteString -> ByteString -> RequestHeaders -> RequestHeaders)
-> Text -> Text -> ActionT m ()
changeHeader forall a b. Eq a => a -> b -> [(a, b)] -> [(a, b)]
addIfNotPresent Text
"Content-Type" Text
"text/plain; charset=utf-8"
    forall (m :: * -> *). MonadIO m => ByteString -> ActionT m ()
raw forall a b. (a -> b) -> a -> b
$ Text -> ByteString
encodeUtf8 Text
t

-- | Set the body of the response to the given 'T.Text' value. Also sets \"Content-Type\"
-- header to \"text/html; charset=utf-8\" if it has not already been set.
html :: (MonadIO m) => T.Text -> ActionT m ()
html :: forall (m :: * -> *). MonadIO m => Text -> ActionT m ()
html Text
t = do
    forall (m :: * -> *).
MonadIO m =>
(CI ByteString -> ByteString -> RequestHeaders -> RequestHeaders)
-> Text -> Text -> ActionT m ()
changeHeader forall a b. Eq a => a -> b -> [(a, b)] -> [(a, b)]
addIfNotPresent Text
"Content-Type" Text
"text/html; charset=utf-8"
    forall (m :: * -> *). MonadIO m => ByteString -> ActionT m ()
raw forall a b. (a -> b) -> a -> b
$ Text -> ByteString
encodeUtf8 Text
t

-- | Send a file as the response. Doesn't set the \"Content-Type\" header, so you probably
-- want to do that on your own with 'setHeader'. Setting a status code will have no effect
-- because Warp will overwrite that to 200 (see 'Network.Wai.Handler.Warp.Internal.sendResponse').
file :: MonadIO m => FilePath -> ActionT m ()
file :: forall (m :: * -> *). MonadIO m => String -> ActionT m ()
file = forall (m :: * -> *).
MonadIO m =>
(ScottyResponse -> ScottyResponse) -> ActionT m ()
modifyResponse forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> ScottyResponse -> ScottyResponse
setContent forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Content
ContentFile

rawResponse :: MonadIO m => Response -> ActionT m ()
rawResponse :: forall (m :: * -> *). MonadIO m => Response -> ActionT m ()
rawResponse = forall (m :: * -> *).
MonadIO m =>
(ScottyResponse -> ScottyResponse) -> ActionT m ()
modifyResponse forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> ScottyResponse -> ScottyResponse
setContent forall b c a. (b -> c) -> (a -> b) -> a -> c
. Response -> Content
ContentResponse

-- | Set the body of the response to the JSON encoding of the given value. Also sets \"Content-Type\"
-- header to \"application/json; charset=utf-8\" if it has not already been set.
json :: (A.ToJSON a, MonadIO m) => a -> ActionT m ()
json :: forall a (m :: * -> *). (ToJSON a, MonadIO m) => a -> ActionT m ()
json a
v = do
    forall (m :: * -> *).
MonadIO m =>
(CI ByteString -> ByteString -> RequestHeaders -> RequestHeaders)
-> Text -> Text -> ActionT m ()
changeHeader forall a b. Eq a => a -> b -> [(a, b)] -> [(a, b)]
addIfNotPresent Text
"Content-Type" Text
"application/json; charset=utf-8"
    forall (m :: * -> *). MonadIO m => ByteString -> ActionT m ()
raw forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> ByteString
A.encode a
v

-- | Set the body of the response to a Source. Doesn't set the
-- \"Content-Type\" header, so you probably want to do that on your
-- own with 'setHeader'.
stream :: MonadIO m => StreamingBody -> ActionT m ()
stream :: forall (m :: * -> *). MonadIO m => StreamingBody -> ActionT m ()
stream = forall (m :: * -> *).
MonadIO m =>
(ScottyResponse -> ScottyResponse) -> ActionT m ()
modifyResponse forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> ScottyResponse -> ScottyResponse
setContent forall b c a. (b -> c) -> (a -> b) -> a -> c
. StreamingBody -> Content
ContentStream

-- | Set the body of the response to the given 'BL.ByteString' value. Doesn't set the
-- \"Content-Type\" header, so you probably want to do that on your
-- own with 'setHeader'.
raw :: MonadIO m => BL.ByteString -> ActionT m ()
raw :: forall (m :: * -> *). MonadIO m => ByteString -> ActionT m ()
raw = forall (m :: * -> *).
MonadIO m =>
(ScottyResponse -> ScottyResponse) -> ActionT m ()
modifyResponse forall b c a. (b -> c) -> (a -> b) -> a -> c
. Content -> ScottyResponse -> ScottyResponse
setContent forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Content
ContentBuilder forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
fromLazyByteString

-- | Nest a whole WAI application inside a Scotty handler.
-- See Web.Scotty for further documentation
nested :: (MonadIO m) => Network.Wai.Application -> ActionT m ()
nested :: forall (m :: * -> *). MonadIO m => Application -> ActionT m ()
nested Application
app = do
  -- Is MVar really the best choice here? Not sure.
  Request
r <- forall (m :: * -> *). Monad m => ActionT m Request
request
  MVar Response
ref <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. IO (MVar a)
newEmptyMVar
  ResponseReceived
_ <- forall (m :: * -> *) a. MonadIO m => IO a -> ActionT m a
liftAndCatchIO forall a b. (a -> b) -> a -> b
$ Application
app Request
r (\Response
res -> forall a. MVar a -> a -> IO ()
putMVar MVar Response
ref Response
res forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ResponseReceived
ResponseReceived)
  Response
res <- forall (m :: * -> *) a. MonadIO m => IO a -> ActionT m a
liftAndCatchIO forall a b. (a -> b) -> a -> b
$ forall a. MVar a -> IO a
readMVar MVar Response
ref
  forall (m :: * -> *). MonadIO m => Response -> ActionT m ()
rawResponse Response
res