growler-0.6.0: A revised version of the scotty library that attempts to be simpler and more performant.

Safe HaskellNone
LanguageHaskell2010

Web.Growler

Contents

Description

A Haskell web framework inspired by the Scotty framework, with an eye towards performance, extensibility, and ease of use.

module Main where
import Data.Monoid ((<>))
import Web.Growler

main = growl id defaultConfig $ do
  get "/" $ text "Hello, World!"
  get "/:name" $ do
    name <- param "name"
    text ("Hello, " <> name <> "!")

Synopsis

Running a growler app

growl Source

Arguments

:: MonadIO m 
=> (forall a. m a -> IO a)

A function to convert your base monad of choice into IO.

-> GrowlerConfig m 
-> GrowlerT m ()

The router for all the other routes

-> IO () 

The simple approach to starting up a web server

growler Source

Arguments

:: MonadIO m 
=> (forall a. m a -> IO a)

A function to convert your base monad of choice into IO.

-> GrowlerConfig m 
-> GrowlerT m ()

The router for all the other routes

-> IO Application 

For more complex needs, access to the actual WAI Application. Useful for adding middleware.

data GrowlerConfig m Source

Constructors

GrowlerConfig 

Fields

growlerConfigNotFoundHandler :: HandlerT m ()

The 404 not found handler. If no route matches, then this handler will be evaluated.

growlerConfigErrorHandler :: SomeException -> HandlerT m ()

The uncaught exception handler. If an exception is thrown and not caught while trying to service a request, then this handler will be evaluated.

Routing

data GrowlerT m a Source

Instances

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

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.

function :: (Request -> Text) -> (Request -> MatchResult) -> 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.

handlerHook :: Monad m => (HandlerT m () -> HandlerT m ()) -> GrowlerT m () Source

notFound :: Monad m => HandlerT m () Source

A blank 404 Not Found handler for convenience.

HTTP Methods

matchAny :: MonadIO m => RoutePattern -> HandlerT m () -> GrowlerT m () Source

Add a route that matches regardless of the HTTP verb.

Primitives

addRoute :: MonadIO m => StdMethod -> RoutePattern -> HandlerT m () -> GrowlerT 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

Handlers

Primitive request functions

request :: Monad m => HandlerT m Request Source

Get the underlying WAI Request

routePattern :: Monad m => HandlerT m (Maybe Text) Source

Get the pattern that was matched in the router, e.g. "foo:bar"

params :: Monad m => HandlerT m [Param] Source

Get all matched params.

Primitive response functions

file Source

Arguments

:: Monad m 
=> FilePath

The file to send

-> Maybe FilePart

If Nothing, then send the whole file, otherwise, the part specified

-> HandlerT m () 

Send a file as the response body.

builder :: Monad m => Builder -> HandlerT m () Source

Set the response body to a ByteString Builder. Sets no headers.

bytestring :: Monad m => ByteString -> HandlerT m () Source

Set the response body to a lazy ByteString. Sets no headers.

stream :: Monad m => StreamingBody -> HandlerT m () Source

Send a streaming response body. Sets no headers.

raw Source

Arguments

:: MonadIO m 
=> (IO ByteString -> (ByteString -> IO ()) -> IO ()) 
-> Response

Backup response when the WAI provider doesn't support upgrading (e.g. CGI)

-> HandlerT m () 

Send raw output as the response body. Useful for e.g. websockets. See WAI's responseRaw for more details.

abort :: Monad m => ResponseState -> HandlerT m () Source

End the handler early with an arbitrary ResponseState.

Convenience functions

Request helpers

formData :: MonadIO m => BackEnd y -> HandlerT m ([(ByteString, ByteString)], [File y]) Source

Parse out the form parameters and the uploaded files. Consumes the request body.

headers :: Monad m => HandlerT m RequestHeaders Source

Get all the request headers.

jsonData :: (FromJSON a, MonadIO m) => HandlerT m (Either JsonInputError a) Source

Consume the request body as a JSON value. Returns a JsonInputError on failure.

Response helpers

status :: Monad m => Status -> HandlerT m () Source

Set the response status code.

addHeader :: Monad m => CI ByteString -> ByteString -> HandlerT m () Source

Add a header to the response. Header names are case-insensitive.

setHeader :: Monad m => CI ByteString -> ByteString -> HandlerT m () Source

Set a response header. Overrides duplicate headers of the same name.

redirect Source

Arguments

:: Monad m 
=> Text

URL to redirect to.

-> HandlerT m () 

Terminate the current handler and send a 302 Found redirect to the provided URL. Other headers that have already been set will also be returned in the request.

text :: Monad m => Text -> HandlerT m () Source

Return plain text as the response body. Sets the Content-Type header to "text/plain; charset=utf-8".

html :: Monad m => Text -> HandlerT m () Source

Return HTML as the response body. Sets the Content-Type header to "text/html; charset=utf-8". If you're using something like blaze-html or lucid, you'll probably get better performance by rolling your own function that sets the response body to a Builder.

json :: Monad m => ToJSON a => a -> HandlerT m () Source

Send a value as JSON as the response body. Also sets the content type to application/json.

data DecodingError :: *

An error while decoding a JSON value.

Constructors

AttoparsecError ParsingError

An attoparsec error that happened while parsing the raw JSON string.

FromJSONError String

An aeson error that happened while trying to convert a Value to an FromJSON instance, as reported by Error.

Parsable

class Parsable a where Source

Minimum implemention: parseParam

Minimal complete definition

parseParam

Methods

parseParam :: ByteString -> Either ByteString a Source

Take a ByteString value and parse it as a, or fail with a message.

parseParamList :: ByteString -> Either ByteString [a] Source

Default implementation parses comma-delimited lists.

parseParamList t = mapM parseParam (BS.split ',' t)

Instances

Parsable Bool 
Parsable Char

Overrides default parseParamList to parse String.

Parsable Double 
Parsable Float 
Parsable Int 
Parsable Integer 
Parsable ()

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.

Parsable ByteString 
Parsable Text 
Parsable Text 
Parsable a => Parsable [a] 

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

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

instance Parsable Int where parseParam = readEither

Internals

body :: Monad m => BodySource -> HandlerT m () Source

Set an arbitrary body source for the response.