scotty-0.10.2: Haskell web framework inspired by Ruby's Sinatra, using WAI and Warp

Safe HaskellNone
LanguageHaskell2010

Web.Scotty.Trans

Contents

Description

It should be noted that most of the code snippets below depend on the OverloadedStrings language pragma.

The functions in this module allow an arbitrary monad to be embedded in Scotty's monad transformer stack in order that Scotty be combined with other DSLs.

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.

Synopsis

scotty-to-WAI

scottyT Source

Arguments

:: (Monad m, MonadIO n) 
=> Port 
-> (m Response -> IO Response)

Run monad m into IO, called at each action.

-> ScottyT e m () 
-> n () 

Run a scotty application using the warp server. NB: scotty p === scottyT p id

scottyAppT Source

Arguments

:: (Monad m, Monad n) 
=> (m Response -> IO Response)

Run monad m into IO, called at each action.

-> ScottyT e m () 
-> n Application 

Turn a scotty application into a WAI Application, which can be run with any WAI handler. NB: scottyApp === scottyAppT id

scottyOptsT Source

Arguments

:: (Monad m, MonadIO n) 
=> Options 
-> (m Response -> IO Response)

Run monad m into IO, called at each action.

-> ScottyT e m () 
-> n () 

Run a scotty application using the warp server, passing extra options. NB: scottyOpts opts === scottyOptsT opts id

scottySocketT :: (Monad m, MonadIO n) => Options -> Socket -> (m Response -> IO Response) -> ScottyT e m () -> n () Source

Run a scotty application using the warp server, passing extra options, and listening on the provided socket. NB: scottySocket opts sock === scottySocketT opts sock id

data Options Source

Constructors

Options 

Fields

verbose :: Int

0 = silent, 1(def) = startup banner

settings :: Settings

Warp Settings Note: to work around an issue in warp, the default FD cache duration is set to 0 so changes to static files are always picked up. This likely has performance implications, so you may want to modify this for production servers using setFdCacheDuration.

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 -> ScottyT e m () 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.

get :: (ScottyError e, MonadIO m) => RoutePattern -> ActionT e m () -> ScottyT e m () Source

post :: (ScottyError e, MonadIO m) => RoutePattern -> ActionT e m () -> ScottyT e m () Source

post = addroute POST

put :: (ScottyError e, MonadIO m) => RoutePattern -> ActionT e m () -> ScottyT e m () Source

delete :: (ScottyError e, MonadIO m) => RoutePattern -> ActionT e m () -> ScottyT e m () Source

delete = addroute DELETE

patch :: (ScottyError e, MonadIO m) => RoutePattern -> ActionT e m () -> ScottyT e m () Source

patch = addroute PATCH

options :: (ScottyError e, MonadIO m) => RoutePattern -> ActionT e m () -> ScottyT e m () Source

options = addroute OPTIONS

addroute :: (ScottyError e, MonadIO m) => StdMethod -> RoutePattern -> ActionT e m () -> ScottyT e m () Source

Define a route with a StdMethod, Text value representing the path spec, and a body (Action) which modifies the response.

addroute GET "/" $ text "beam me up!"

The path spec can include values starting with a colon, which are interpreted as captures. These are named wildcards that can be looked up with param.

addroute GET "/foo/:bar" $ do
    v <- param "bar"
    text v
>>> curl http://localhost:3000/foo/something
something

matchAny :: (ScottyError e, MonadIO m) => RoutePattern -> ActionT e m () -> ScottyT e m () Source

Add a route that matches regardless of the HTTP verb.

notFound :: (ScottyError e, MonadIO m) => ActionT e m () -> ScottyT e m () Source

Specify an action to take if nothing else is found. Note: this _always_ matches, so should generally be the last route specified.

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.

get (regex "^/f(.*)r$") $ do
   path <- param "0"
   cap <- param "1"
   text $ mconcat ["Path: ", path, "\nCapture: ", cap]
>>> curl http://localhost:3000/foo/bar
Path: /foo/bar
Capture: 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.

get (function $ \req -> Just [("version", T.pack $ show $ httpVersion req)]) $ do
    v <- param "version"
    text v
>>> 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, Captures, and Query Parameters

request :: Monad m => ActionT e m Request Source

Get the Request object.

header :: (ScottyError e, Monad m) => Text -> ActionT e m (Maybe Text) Source

Get a request header. Header name is case-insensitive.

headers :: (ScottyError e, Monad m) => ActionT e m [(Text, Text)] Source

Get all the request headers. Header names are case-insensitive.

body :: (ScottyError e, MonadIO m) => ActionT e m ByteString Source

Get the request body.

bodyReader :: Monad m => ActionT e m (IO ByteString) Source

Get an IO action that reads body chunks

  • This is incompatible with body since body consumes all chunks.

param :: (Parsable a, ScottyError e, Monad m) => Text -> ActionT e m a Source

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 read 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.

params :: Monad m => ActionT e m [Param] Source

Get all parameters from capture, form and query (in that order).

jsonData :: (FromJSON a, ScottyError e, MonadIO m) => ActionT e m a Source

Parse the request body as a JSON object and return it. Raises an exception if parse is unsuccessful.

files :: Monad m => ActionT e m [File] Source

Get list of uploaded files.

Modifying the Response and Redirecting

status :: Monad m => Status -> ActionT e m () Source

Set the HTTP response status. Default is 200.

addHeader :: Monad m => Text -> Text -> ActionT e m () Source

Add to the response headers. Header names are case-insensitive.

setHeader :: Monad m => Text -> Text -> ActionT e m () Source

Set one of the response headers. Will override any previously set value for that header. Header names are case-insensitive.

redirect :: (ScottyError e, Monad m) => Text -> ActionT e m 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 :: (ScottyError e, Monad m) => Text -> ActionT e m () 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 :: (ScottyError e, Monad m) => Text -> ActionT e m () 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 :: Monad m => FilePath -> ActionT e m () 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, ScottyError e, Monad m) => a -> ActionT e m () 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 :: Monad m => StreamingBody -> ActionT e m () Source

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.

raw :: Monad m => ByteString -> ActionT e m () 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.

Exceptions

raise :: (ScottyError e, Monad m) => e -> ActionT e m a Source

Throw an exception, which can be caught with rescue. Uncaught exceptions turn into HTTP 500 responses.

rescue :: (ScottyError e, Monad m) => ActionT e m a -> (e -> ActionT e m a) -> ActionT e m a Source

Catch an exception thrown by raise.

raise "just kidding" `rescue` (\msg -> text msg)

next :: (ScottyError e, Monad m) => ActionT e m a Source

Abort execution of this action and continue pattern matching routes. Like an exception, any code after next is not executed.

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 <- param "bar"
  unless (w == "special") next
  text "You made a request to /foo/special"

get "/foo/:baz" $ do
  w <- param "baz"
  text $ "You made a request to: " <> w

defaultHandler :: (ScottyError e, Monad m) => (e -> ActionT e m ()) -> ScottyT e m () Source

Global handler for uncaught exceptions.

Uncaught exceptions normally become 500 responses. You can use this to selectively override that behavior.

Note: IO exceptions are lifted into ScottyErrors by stringError. This has security implications, so you probably want to provide your own defaultHandler in production which does not send out the error strings as 500 responses.

class ScottyError e where Source

In order to use a custom exception type (aside from Text), you must define an instance of ScottyError for that type.

Parsing Parameters

type Param = (Text, Text) Source

class Parsable a where Source

Minimum implemention: parseParam

Minimal complete definition

parseParam

Methods

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

readEither :: Read a => Text -> Either Text a Source

Useful for creating Parsable instances for things that already implement Read. Ex:

instance Parsable Int where parseParam = readEither

Types

Monad Transformers

data ScottyT e m a Source