webby-1.1.1: A super-simple web server framework
LicenseApache License 2.0
Maintaineraditya.mmy@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Webby

Description

 
Synopsis

Documentation

data WebbyM appEnv a Source #

The main monad transformer stack used in the web-framework.

The type of a handler for a request is WebbyM appEnv (). The appEnv parameter is used by the web application to store an (read-only) environment. For e.g. it can be used to store a database connection pool.

Instances

Instances details
MonadReader appEnv (WebbyM appEnv) Source # 
Instance details

Defined in Webby.Types

Methods

ask :: WebbyM appEnv appEnv #

local :: (appEnv -> appEnv) -> WebbyM appEnv a -> WebbyM appEnv a #

reader :: (appEnv -> a) -> WebbyM appEnv a #

MonadIO (WebbyM appEnv) Source # 
Instance details

Defined in Webby.Types

Methods

liftIO :: IO a -> WebbyM appEnv a #

Applicative (WebbyM appEnv) Source # 
Instance details

Defined in Webby.Types

Methods

pure :: a -> WebbyM appEnv a #

(<*>) :: WebbyM appEnv (a -> b) -> WebbyM appEnv a -> WebbyM appEnv b #

liftA2 :: (a -> b -> c) -> WebbyM appEnv a -> WebbyM appEnv b -> WebbyM appEnv c #

(*>) :: WebbyM appEnv a -> WebbyM appEnv b -> WebbyM appEnv b #

(<*) :: WebbyM appEnv a -> WebbyM appEnv b -> WebbyM appEnv a #

Functor (WebbyM appEnv) Source # 
Instance details

Defined in Webby.Types

Methods

fmap :: (a -> b) -> WebbyM appEnv a -> WebbyM appEnv b #

(<$) :: a -> WebbyM appEnv b -> WebbyM appEnv a #

Monad (WebbyM appEnv) Source # 
Instance details

Defined in Webby.Types

Methods

(>>=) :: WebbyM appEnv a -> (a -> WebbyM appEnv b) -> WebbyM appEnv b #

(>>) :: WebbyM appEnv a -> WebbyM appEnv b -> WebbyM appEnv b #

return :: a -> WebbyM appEnv a #

MonadUnliftIO (WebbyM appEnv) Source # 
Instance details

Defined in Webby.Types

Methods

withRunInIO :: ((forall a. WebbyM appEnv a -> IO a) -> IO b) -> WebbyM appEnv b #

Routing and handler functions

data RoutePattern Source #

A route pattern represents logic to match a request to a handler.

Instances

Instances details
Show RoutePattern Source # 
Instance details

Defined in Webby.Types

Eq RoutePattern Source # 
Instance details

Defined in Webby.Types

type Route env = (RoutePattern, WebbyM env ()) Source #

A route is a pair of a route pattern and a handler.

mkRoute :: Method -> Text -> WebbyM appEnv () -> (RoutePattern, WebbyM appEnv ()) Source #

Create a route for a user-provided HTTP request method, pattern and handler function.

post :: Text -> WebbyM appEnv () -> (RoutePattern, WebbyM appEnv ()) Source #

Create a route for a POST request method, given the path pattern and handler.

get :: Text -> WebbyM appEnv () -> (RoutePattern, WebbyM appEnv ()) Source #

Create a route for a GET request method, given the path pattern and handler.

put :: Text -> WebbyM appEnv () -> (RoutePattern, WebbyM appEnv ()) Source #

Create a route for a PUT request method, given the path pattern and handler.

delete :: Text -> WebbyM appEnv () -> (RoutePattern, WebbyM appEnv ()) Source #

Create a route for a DELETE request method, given path pattern and handler.

Captures

type Captures = HashMap Text Text Source #

Captures are simply extracted path elements in a HashMap

captures :: WebbyM appEnv Captures Source #

Retrieve all path captures

getCapture :: FromHttpApiData a => Text -> WebbyM appEnv a Source #

Retrieve a particular capture

Request parsing

flag :: Text -> WebbyM appEnv Bool Source #

Checks if the request contains the given query param

header :: HeaderName -> WebbyM appEnv (Maybe Text) Source #

Get the given header value

headers :: WebbyM appEnv [Header] Source #

Get all the request headers

jsonData :: FromJSON a => WebbyM appEnv a Source #

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

param :: FromHttpApiData a => Text -> WebbyM appEnv (Maybe a) Source #

Gets the given query param's value

param_ :: FromHttpApiData a => Text -> WebbyM appEnv a Source #

Similar to param except that it returns the handler with a '400 BadRequest' if the query param is missing.

params :: WebbyM appEnv [(Text, Text)] Source #

Get all request query params as a list of key-value pairs

request :: WebbyM appEnv Request Source #

Get the Request of the handler

requestBodyLBS :: WebbyM appEnv LByteString Source #

Return the raw request body as a lazy bytestring

requestBodyLength :: WebbyM appEnv (Maybe Int64) Source #

Returns request body size in bytes

getRequestBodyChunkAction :: WebbyM appEnv (WebbyM appEnv ByteString) Source #

Returns an action that returns successive chunks of the rquest body. It returns an empty bytestring after the request body is consumed.

Response modification

setStatus :: Status -> WebbyM appEnv () Source #

Set response status

addHeader :: Header -> WebbyM appEnv () Source #

Append given header to the response headers

setHeader :: Header -> WebbyM appEnv () Source #

Similar to addHeader but replaces a header

blob :: ByteString -> WebbyM appEnv () Source #

Send a binary stream in the response body. Also sets Content-Type header to application/octet-stream

json :: ToJSON b => b -> WebbyM appEnv () 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

text :: Text -> WebbyM appEnv () Source #

Send plain-text in the response body. Also sets Content-Type header to text/plain; charset=utf-8

stream :: StreamingBody -> WebbyM appEnv () 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.

image :: ByteString -> MimeType -> WebbyM appEnv () Source #

Send an image in the response body. Also sets Content-Type header to @mimeType e.g. image/svg+xml

raw :: ByteString -> WebbyM appEnv () Source #

Send a binary stream in the response body. Doesn't set Content-Type header

Application

mkWebbyApp :: env -> WebbyServerConfig env -> IO Application Source #

Use this function to create a WAI application. It takes a user/application defined appEnv data type and a list of routes. Routes are matched in the given order. If none of the requests match a request, a default 404 response is returned.

type Application = Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived #

The WAI application.

Note that, since WAI 3.0, this type is structured in continuation passing style to allow for proper safe resource handling. This was handled in the past via other means (e.g., ResourceT). As a demonstration:

app :: Application
app req respond = bracket_
    (putStrLn "Allocating scarce resource")
    (putStrLn "Cleaning up")
    (respond $ responseLBS status200 [] "Hello World")

Webby server configuration

data WebbyServerConfig env Source #

Holds web server configuration like API routes, handlers and an optional exception handler

defaultWebbyServerConfig :: WebbyServerConfig env Source #

Default WebbyServerConfig typically used in conjunction with setRoutes and setExceptionHandler

setRoutes :: [Route env] -> WebbyServerConfig env -> WebbyServerConfig env Source #

Sets API routes and their handlers of a WebbyServerConfig

setExceptionHandler :: Exception e => (e -> WebbyM env ()) -> WebbyServerConfig env -> WebbyServerConfig env Source #

Sets the exception handler of a WebbyServerConfig

Handler flow control

finish :: WebbyM appEnv a Source #

Used to return early from an API handler

Exceptions thrown

data WebbyError Source #

Various kinds of errors thrown by this library - these can be caught by handler code.

Instances

Instances details
Exception WebbyError Source # 
Instance details

Defined in Webby.Types

Show WebbyError Source # 
Instance details

Defined in Webby.Types