Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
It should be noted that most of the code snippets below depend on the OverloadedStrings language pragma.
Scotty is set up by default for development mode. For production servers,
you will likely want to modify settings
and the defaultHandler
. See
the comments on each of these functions for more information.
Please refer to the examples
directory and the spec
test suite for concrete use cases, e.g. constructing responses, exception handling and useful implementation details.
Synopsis
- scotty :: Port -> ScottyM () -> IO ()
- scottyOpts :: Options -> ScottyM () -> IO ()
- scottySocket :: Options -> Socket -> ScottyM () -> IO ()
- data Options = Options {}
- defaultOptions :: Options
- scottyApp :: ScottyM () -> IO Application
- middleware :: Middleware -> ScottyM ()
- get :: RoutePattern -> ActionM () -> ScottyM ()
- post :: RoutePattern -> ActionM () -> ScottyM ()
- put :: RoutePattern -> ActionM () -> ScottyM ()
- delete :: RoutePattern -> ActionM () -> ScottyM ()
- patch :: RoutePattern -> ActionM () -> ScottyM ()
- options :: RoutePattern -> ActionM () -> ScottyM ()
- addroute :: StdMethod -> RoutePattern -> ActionM () -> ScottyM ()
- matchAny :: RoutePattern -> ActionM () -> ScottyM ()
- notFound :: ActionM () -> ScottyM ()
- nested :: Application -> ActionM ()
- setMaxRequestBodySize :: Kilobytes -> ScottyM ()
- capture :: String -> RoutePattern
- regex :: String -> RoutePattern
- function :: (Request -> Maybe [Param]) -> RoutePattern
- literal :: String -> RoutePattern
- request :: ActionM Request
- header :: Text -> ActionM (Maybe Text)
- headers :: ActionM [(Text, Text)]
- body :: ActionM ByteString
- bodyReader :: ActionM (IO ByteString)
- jsonData :: FromJSON a => ActionM a
- param :: Parsable a => Text -> ActionM a
- params :: ActionM [Param]
- pathParam :: Parsable a => Text -> ActionM a
- captureParam :: Parsable a => Text -> ActionM a
- formParam :: Parsable a => Text -> ActionM a
- queryParam :: Parsable a => Text -> ActionM a
- pathParamMaybe :: Parsable a => Text -> ActionM (Maybe a)
- captureParamMaybe :: Parsable a => Text -> ActionM (Maybe a)
- formParamMaybe :: Parsable a => Text -> ActionM (Maybe a)
- queryParamMaybe :: Parsable a => Text -> ActionM (Maybe a)
- pathParams :: ActionM [Param]
- captureParams :: ActionM [Param]
- formParams :: ActionM [Param]
- queryParams :: ActionM [Param]
- files :: ActionM [File ByteString]
- filesOpts :: ParseRequestBodyOptions -> ([Param] -> [File FilePath] -> ActionM a) -> ActionM a
- data ParseRequestBodyOptions
- status :: Status -> ActionM ()
- addHeader :: Text -> Text -> ActionM ()
- setHeader :: Text -> Text -> ActionM ()
- redirect :: Text -> ActionM a
- text :: Text -> ActionM ()
- html :: Text -> ActionM ()
- file :: FilePath -> ActionM ()
- json :: ToJSON a => a -> ActionM ()
- stream :: StreamingBody -> ActionM ()
- raw :: ByteString -> ActionM ()
- getResponseHeaders :: ActionM ResponseHeaders
- getResponseStatus :: ActionM Status
- getResponseContent :: ActionM Content
- raise :: Text -> ActionM a
- raiseStatus :: Status -> Text -> ActionM a
- throw :: Exception e => e -> ActionM a
- rescue :: Exception e => ActionM a -> (e -> ActionM a) -> ActionM a
- next :: ActionM ()
- finish :: ActionM a
- defaultHandler :: ErrorHandler IO -> ScottyM ()
- liftAndCatchIO :: IO a -> ActionM a
- liftIO :: MonadIO m => IO a -> m a
- catch :: (MonadUnliftIO m, Exception e) => m a -> (e -> m a) -> m a
- data StatusError = StatusError Status Text
- data ScottyException
- = RequestTooLarge
- | MalformedJSON ByteString Text
- | FailedToParseJSON ByteString Text
- | PathParameterNotFound Text
- | QueryParameterNotFound Text
- | FormFieldNotFound Text
- | FailedToParseParameter Text Text Text
- | WarpRequestException InvalidRequest
- | WaiRequestParseException RequestParseException
- | ResourceTException InvalidAccess
- type Param = (Text, Text)
- class Parsable a where
- parseParam :: Text -> Either Text a
- parseParamList :: Text -> Either Text [a]
- readEither :: Read a => Text -> Either Text a
- type ScottyM = ScottyT IO
- type ActionM = ActionT IO
- data RoutePattern
- type File t = (Text, FileInfo t)
- data Content
- type Kilobytes = Int
- type ErrorHandler m = Handler (ActionT m) ()
- data Handler (m :: Type -> Type) a = Exception e => Handler (e -> m a)
- data ScottyState m
- defaultScottyState :: ScottyState m
Running scotty
servers
scottyOpts :: Options -> ScottyM () -> IO () Source #
Run a scotty application using the warp server, passing extra options.
scottySocket :: Options -> Socket -> ScottyM () -> IO () Source #
Run a scotty application using the warp server, passing extra options, and listening on the provided socket. This allows the user to provide, for example, a Unix named socket, which can be used when reverse HTTP proxying into your application.
Options | |
|
scotty-to-WAI
scottyApp :: ScottyM () -> IO Application Source #
Turn a scotty application into a WAI Application
, which can be
run with any WAI handler.
Defining Middleware and Routes
Middleware
and routes are run in the order in which they
are defined. All middleware is run first, followed by the first
route that matches. If no route matches, a 404 response is given.
middleware :: Middleware -> ScottyM () Source #
Use given middleware. Middleware is nested such that the first declared is the outermost middleware (it has first dibs on the request and last action on the response). Every middleware is run on each request.
addroute :: StdMethod -> RoutePattern -> ActionM () -> ScottyM () Source #
Define a route with a StdMethod
, a route pattern representing the path spec,
and an Action
which may modify the response.
get "/" $ text "beam me up!"
The path spec can include values starting with a colon, which are interpreted
as captures. These are parameters that can be looked up with pathParam
.
>>>
:{
let server = S.get "/foo/:bar" (S.pathParam "bar" >>= S.text) in do withScotty server $ curl "http://localhost:3000/foo/something" :} "something"
matchAny :: RoutePattern -> ActionM () -> ScottyM () Source #
Add a route that matches regardless of the HTTP verb.
notFound :: ActionM () -> ScottyM () Source #
Specify an action to take if nothing else is found. Note: this _always_ matches, so should generally be the last route specified.
nested :: Application -> ActionM () Source #
Nest a whole WAI application inside a Scotty handler. Note: You will want to ensure that this route fully handles the response, as there is no easy delegation as per normal Scotty actions. Also, you will have to carefully ensure that you are expecting the correct routes, this could require stripping the current prefix, or adding the prefix to your application's handlers if it depends on them. One potential use-case for this is hosting a web-socket handler under a specific route.
setMaxRequestBodySize :: Kilobytes -> ScottyM () Source #
Set global size limit for the request body. Requests with body size exceeding the limit will not be processed and an HTTP response 413 will be returned to the client. Size limit needs to be greater than 0, otherwise the application will terminate on start.
Route Patterns
capture :: String -> RoutePattern Source #
Standard Sinatra-style route. Named captures are prepended with colons. This is the default route type generated by OverloadedString routes. i.e.
get (capture "/foo/:bar") $ ...
and
{-# LANGUAGE OverloadedStrings #-} ... get "/foo/:bar" $ ...
are equivalent.
regex :: String -> RoutePattern Source #
Match requests using a regular expression. Named captures are not yet supported.
>>>
:{
let server = S.get (S.regex "^/f(.*)r$") $ do cap <- S.pathParam "1" S.text cap in do withScotty server $ curl "http://localhost:3000/foo/bar" :} "oo/ba"
function :: (Request -> Maybe [Param]) -> RoutePattern Source #
Build a route based on a function which can match using the entire Request
object.
Nothing
indicates the route does not match. A Just
value indicates
a successful match, optionally returning a list of key-value pairs accessible by param
.
>>>
:{
let server = S.get (function $ \req -> Just [("version", T.pack $ show $ W.httpVersion req)]) $ do v <- S.pathParam "version" S.text v in do withScotty server $ curl "http://localhost:3000/" :} "HTTP/1.1"
literal :: String -> RoutePattern Source #
Build a route that requires the requested path match exactly, without captures.
Accessing the Request and its fields
header :: Text -> ActionM (Maybe Text) Source #
Get a request header. Header name is case-insensitive.
headers :: ActionM [(Text, Text)] Source #
Get all the request headers. Header names are case-insensitive.
body :: ActionM ByteString Source #
Get the request body.
NB: loads the entire request body in memory
bodyReader :: ActionM (IO ByteString) Source #
jsonData :: FromJSON a => ActionM a Source #
Parse the request body as a JSON object and return it. Raises an exception if parse is unsuccessful.
NB: uses body
internally
Accessing Path, Form and Query Parameters
param :: Parsable a => Text -> ActionM a Source #
Deprecated: (#204) Not a good idea to treat all parameters identically. Use pathParam, formParam and queryParam instead.
Get a parameter. First looks in captures, then form data, then query parameters.
params :: ActionM [Param] Source #
Deprecated: (#204) Not a good idea to treat all parameters identically. Use pathParams, formParams and queryParams instead.
Get all parameters from path, form and query (in that order).
pathParam :: Parsable a => Text -> ActionM a Source #
Get a path parameter.
- Raises an exception which can be caught by
catch
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.
Since: 0.21
formParam :: Parsable a => Text -> ActionM a Source #
Get a form parameter.
- Raises an exception which can be caught by
catch
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.
Since: 0.20
queryParam :: Parsable a => Text -> ActionM a Source #
Get a query parameter.
- Raises an exception which can be caught by
catch
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.
Since: 0.20
pathParamMaybe :: Parsable a => Text -> ActionM (Maybe a) Source #
Look up a path parameter. Returns Nothing
if the parameter is not found or cannot be parsed at the right type.
NB : Doesn't throw exceptions. In particular, route pattern matching will not continue, so developers
must raiseStatus
or throw
to signal something went wrong.
Since: 0.21
captureParamMaybe :: Parsable a => Text -> ActionM (Maybe a) Source #
Synonym for pathParamMaybe
Since: 0.21
formParamMaybe :: Parsable a => Text -> ActionM (Maybe a) Source #
Look up a form parameter. Returns Nothing
if the parameter is not found or cannot be parsed at the right type.
NB : Doesn't throw exceptions, so developers must raiseStatus
or throw
to signal something went wrong.
Since: 0.21
queryParamMaybe :: Parsable a => Text -> ActionM (Maybe a) Source #
Look up a query parameter. Returns Nothing
if the parameter is not found or cannot be parsed at the right type.
NB : Doesn't throw exceptions, so developers must raiseStatus
or throw
to signal something went wrong.
Since: 0.21
pathParams :: ActionM [Param] Source #
Get path parameters
captureParams :: ActionM [Param] Source #
Synonym for pathParams
formParams :: ActionM [Param] Source #
Get form parameters
queryParams :: ActionM [Param] Source #
Get query parameters
Files
files :: ActionM [File ByteString] Source #
Get list of uploaded files.
NB: Loads all file contents in memory with options defaultParseRequestBodyOptions
:: ParseRequestBodyOptions | |
-> ([Param] -> [File FilePath] -> ActionM a) | temp files validation, storage etc |
-> ActionM a |
Get list of temp files and form parameters decoded from multipart payloads.
NB the temp files are deleted when the continuation exits
data ParseRequestBodyOptions #
A data structure that describes the behavior of the parseRequestBodyEx function.
Since: wai-extra-3.0.16.0
Modifying the Response and Redirecting
addHeader :: Text -> Text -> ActionM () Source #
Add to the response headers. Header names are case-insensitive.
setHeader :: Text -> Text -> ActionM () Source #
Set one of the response headers. Will override any previously set value for that header. Header names are case-insensitive.
redirect :: Text -> ActionM a Source #
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"
Setting Response Body
Note: only one of these should be present in any given route
definition, as they completely replace the current Response
body.
text :: Text -> ActionM () Source #
Set the body of the response to the given Text
value. Also sets "Content-Type"
header to "text/plain; charset=utf-8" if it has not already been set.
html :: Text -> ActionM () Source #
Set the body of the response to the given Text
value. Also sets "Content-Type"
header to "text/html; charset=utf-8" if it has not already been set.
file :: FilePath -> ActionM () Source #
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
.
json :: ToJSON a => a -> ActionM () Source #
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.
stream :: StreamingBody -> ActionM () Source #
Set the body of the response to a StreamingBody. Doesn't set the
"Content-Type" header, so you probably want to do that on your
own with setHeader
.
raw :: ByteString -> ActionM () Source #
Set the body of the response to the given ByteString
value. Doesn't set the
"Content-Type" header, so you probably want to do that on your own with setHeader
.
Accessing the fields of the Response
getResponseHeaders :: ActionM ResponseHeaders Source #
Access the HTTP headers of the Response
Since: 0.21
getResponseContent :: ActionM Content Source #
Access the content of the Response
Since: 0.21
Exceptions
raise :: Text -> ActionM a Source #
Deprecated: Throw an exception instead
Throw a "500 Server Error" StatusError
, which can be caught with catch
.
Uncaught exceptions turn into HTTP 500 responses.
raiseStatus :: Status -> Text -> ActionM a Source #
Deprecated: Use status, text, and finish instead
Throw a StatusError
exception that has an associated HTTP error code and can be caught with catch
.
Uncaught exceptions turn into HTTP responses corresponding to the given status.
throw :: Exception e => e -> ActionM a Source #
Throw an exception which can be caught within the scope of the current Action with 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.
rescue :: Exception e => ActionM a -> (e -> ActionM a) -> ActionM a Source #
Deprecated: Use catch instead
Catch an exception e.g. a StatusError
or a user-defined exception.
raise JustKidding `catch` (\msg -> text msg)
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 <- pathParam "bar" unless (w == "special") next text "You made a request to /foo/special" get "/foo/:baz" $ do w <- pathParam "baz" text $ "You made a request to: " <> w
Abort execution of this action. Like an exception, any code after finish
is not executed.
As an example only requests to /foo/special
will include in the response
content the text message.
get "/foo/:bar" $ do w :: Text <- pathParam "bar" unless (w == "special") finish text "You made a request to /foo/special"
Since: 0.10.3
defaultHandler :: ErrorHandler IO -> ScottyM () Source #
Global handler for user-defined exceptions.
liftAndCatchIO :: IO a -> ActionM a Source #
Deprecated: Use liftIO instead
Like liftIO
, but catch any IO exceptions and turn them into Scotty exceptions.
liftIO :: MonadIO m => IO a -> m a #
Lift a computation from the IO
monad.
This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations
(i.e. IO
is the base monad for the stack).
Example
import Control.Monad.Trans.State -- from the "transformers" library printState :: Show s => StateT s IO () printState = do state <- get liftIO $ print state
Had we omitted
, we would have ended up with this error:liftIO
• Couldn't match type ‘IO’ with ‘StateT s IO’ Expected type: StateT s IO () Actual type: IO ()
The important part here is the mismatch between StateT s IO ()
and
.IO
()
Luckily, we know of a function that takes an
and returns an IO
a(m a)
:
,
enabling us to run the program and see the expected results:liftIO
> evalStateT printState "hello" "hello" > evalStateT printState 3 3
:: (MonadUnliftIO m, Exception e) | |
=> m a | action |
-> (e -> m a) | handler |
-> m a |
Catch a synchronous (but not asynchronous) exception and recover from it.
This is parameterized on the exception type. To catch all synchronous exceptions,
use catchAny
.
Since: unliftio-0.1.0.0
data StatusError Source #
Deprecated: If it is supposed to be caught, a proper exception type should be defined
E.g. when a parameter is not found in a query string (400 Bad Request) or when parsing a JSON body fails (422 Unprocessable Entity)
StatusError Status Text | Deprecated: If it is supposed to be caught, a proper exception type should be defined |
Instances
Exception StatusError Source # | |
Defined in Web.Scotty.Internal.Types | |
Show StatusError Source # | |
Defined in Web.Scotty.Internal.Types showsPrec :: Int -> StatusError -> ShowS # show :: StatusError -> String # showList :: [StatusError] -> ShowS # | |
MonadUnliftIO m => MonadError StatusError (ActionT m) Source # | Models the invariant that only |
Defined in Web.Scotty.Internal.Types throwError :: StatusError -> ActionT m a # catchError :: ActionT m a -> (StatusError -> ActionT m a) -> ActionT m a # |
data ScottyException Source #
Thrown e.g. when a request is too large
Instances
Exception ScottyException Source # | |
Defined in Web.Scotty.Internal.Types | |
Show ScottyException Source # | |
Defined in Web.Scotty.Internal.Types showsPrec :: Int -> ScottyException -> ShowS # show :: ScottyException -> String # showList :: [ScottyException] -> ShowS # |
Parsing Parameters
class Parsable a where Source #
Minimum implemention: parseParam
parseParam :: Text -> Either Text a Source #
Take a Text
value and parse it as a
, or fail with a message.
parseParamList :: Text -> Either Text [a] Source #
Default implementation parses comma-delimited lists.
parseParamList t = mapM parseParam (T.split (== ',') t)
Instances
Types
data RoutePattern Source #
Instances
IsString RoutePattern Source # | |
Defined in Web.Scotty.Internal.Types fromString :: String -> RoutePattern # |
type File t = (Text, FileInfo t) Source #
Type parameter t
is the file content. Could be ()
when not needed or a FilePath
for temp files instead.
data ScottyState m Source #