welshy-0.1.0.0: Haskell web framework (because Scotty had trouble yodeling)

Safe HaskellNone

Web.Welshy

Contents

Synopsis

Documentation

welshy :: Port -> Welshy () -> IO ()Source

Run a Welshy app using the Warp server.

welshyApp :: Welshy () -> ApplicationSource

Turns a Welshy app into a WAI Application.

Middleware & Routing

data Welshy a Source

We use this monad to compose WAI Middleware, using the middleware and route functions.

middleware :: Middleware -> Welshy ()Source

Insert middleware into the app. Note that unlike in Scotty, each middleware is run at the point of insertion.

route :: StdMethod -> RoutePattern -> Action () -> Welshy ()Source

Define a route for an HTTP method and URL pattern that runs the given action. Routes are matched in the order they are defined. If no route matches, a 404 response is returned.

type RoutePattern = TextSource

Sinatra-style route pattern. Named parameters are prepended with a colon (e.g. "/users/:id") and can be accessed with capture.

Actions

halt :: Action () -> Action aSource

Stop running the current action and continue with another one. The other action will live in the same request environment and can access the same route captures, but it will start with a fresh default response.

This is incredibly useful for error handling. For example:

 patch "/users/:uid" $ do
     uid <- capture "uid"
     user <- getUserFromDB uid
             `catchIO` (\_ -> halt $ status notFound404)
     ...

pass :: Action aSource

Stop the current action and continue with the next matching route.

catchIO :: Exception e => IO a -> (e -> Action a) -> Action aSource

Like catch but with the exception handler and result in Action.

Request

request :: Action RequestSource

Get the raw WAI Request.

body :: Action ByteStringSource

Get the request body.

capture :: FromText a => Text -> Action aSource

Get a parameter captured by the route pattern.

  • If the parameter does not exist, fails with an error.
  • If the parameter was found but could not be parsed, pass is called. This means routes are typed to a degree.

captures :: Action [Param]Source

Get all route captures.

queryParam :: FromText a => Text -> Action aSource

Get a query parameter.

  • If the parameter does not exist or could not be parsed, the action halts with HTTP status 400 Bad Request.

maybeQueryParam :: FromText a => Text -> Action (Maybe a)Source

Like queryParam, but returns Nothing if the parameter wasn't found.

  • If the parameter could not be parsed, the action halts with HTTP status 400 BadRequest

queryParams :: Action [Param]Source

Get all query parameters.

jsonParam :: FromJSON a => Text -> Action aSource

Get a JSON parameter.

  • If the request body is not a JSON dictionary, or if the parameter does not exist or could not be parsed, the action halts with HTTP status 400 Bad Request.

maybeJsonParam :: FromJSON a => Text -> Action (Maybe a)Source

Like jsonParam, but returns Nothing if the parameter wasn't found.

  • If the request body is not a JSON dictionary, the action halts with HTTP status 400 Bad Request.

jsonParams :: Action ObjectSource

Get all JSON parameters.

  • If the request body is not a JSON dictionary, the action halts with HTTP status 400 Bad Request.

jsonData :: FromJSON a => Action aSource

Parse the request body as a JSON object.

  • If the body could not be parsed, the action halts with HTTP status 400 Bad Request.

bearerAuth :: FromText a => Action aSource

Get the bearer token from an authorization header using the Bearer authentication scheme (RFC 6750).

If the request does not have a (syntactically) valid authorization header for the Bearer scheme, the action halts with HTTP status 401 Unauthorized.

Response

status :: Status -> Action ()Source

Set the HTTP status of the response. The default is ok200.

header :: HeaderName -> ByteString -> Action ()Source

Add or replace one of the response headers.

text :: Text -> Action ()Source

Set the response body to the given lazy Text and the content-type to text/plain.

text' :: Text -> Action ()Source

Like text but with a strict Text value.

html :: Text -> Action ()Source

Set the response body to the given lazy Text and the content-type to text/html.

html' :: Text -> Action ()Source

Like html but with a strict Text value.

json :: ToJSON a => a -> Action ()Source

Set the response body to the JSON encoding of the given value and the content-type to application/json.

file :: FilePath -> Action ()Source

Sends the given file as the response.

filePart :: FilePath -> Integer -> Integer -> Action ()Source

filePart f offset byteCount sends byteCount bytes of the file f, beginning at offset, as the response.

source :: Source (ResourceT IO) (Flush Builder) -> Action ()Source

Set the response body to the given Source.

Parameter Parsing

type Param = (Text, Text)Source

A route, query or form parameter and its value.

class FromText a whereSource

A type that can be converted from a strict Text value. Used for parsing route captures, query parameters, header values, etc.

Minimal complete definition: fromText.

Methods

fromText :: Text -> Either String aSource

fromTextList :: Text -> Either String [a]Source

Allows a specialized way of parsing lists of values. The default definition uses fromText to parse comma-delimited lists.

maybeFromText :: FromText a => Text -> Maybe aSource

 maybeFromText = either (const Nothing) Just . fromText