webby-0.4.0: A super-simple web server framework

Safe HaskellNone
LanguageHaskell2010

Webby

Contents

Synopsis

Documentation

data WebbyM env 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
Monad (WebbyM env) Source # 
Instance details

Defined in Webby.Types

Methods

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

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

return :: a -> WebbyM env a #

fail :: String -> WebbyM env a #

Functor (WebbyM env) Source # 
Instance details

Defined in Webby.Types

Methods

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

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

Applicative (WebbyM env) Source # 
Instance details

Defined in Webby.Types

Methods

pure :: a -> WebbyM env a #

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

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

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

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

MonadIO (WebbyM env) Source # 
Instance details

Defined in Webby.Types

Methods

liftIO :: IO a -> WebbyM env a #

MonadUnliftIO (WebbyM appData) Source # 
Instance details

Defined in Webby.Types

Methods

askUnliftIO :: WebbyM appData (UnliftIO (WebbyM appData)) #

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

MonadReader (WEnv env) (WebbyM env) Source # 
Instance details

Defined in Webby.Types

Methods

ask :: WebbyM env (WEnv env) #

local :: (WEnv env -> WEnv env) -> WebbyM env a -> WebbyM env a #

reader :: (WEnv env -> a) -> WebbyM env a #

Routing and handler functions

data RoutePattern Source #

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

Instances
Eq RoutePattern Source # 
Instance details

Defined in Webby.Types

Show 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 (TODO: extend?)

Request parsing

flag :: Text -> WebbyM appEnv Bool Source #

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

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

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

requestBodyLBS :: WebbyM appEnv LByteString Source #

Return the raw request body as a lazy bytestring

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 #

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

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

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

json :: ToJSON b => b -> WebbyM appEnv () Source #

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

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")

Application context

data WEnv env Source #

The reader environment used by the web framework. It is parameterized by the application's environment data type.

Instances
MonadReader (WEnv env) (WebbyM env) Source # 
Instance details

Defined in Webby.Types

Methods

ask :: WebbyM env (WEnv env) #

local :: (WEnv env -> WEnv env) -> WebbyM env a -> WebbyM env a #

reader :: (WEnv env -> a) -> WebbyM env a #

getAppEnv :: WebbyM appEnv appEnv Source #

Retrieve the app environment given to the application at initialization.

runAppEnv :: ReaderT appEnv (WebbyM appEnv) a -> WebbyM appEnv a Source #

Webby server configuration

Handler flow control

finish :: WebbyM appEnv a Source #

Exceptions thrown

data WebbyError Source #

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