twain-2.1.2.0: Tiny web application framework for WAI.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Web.Twain

Description

Twain is a tiny web application framework for WAI

  • ResponderM for composing responses with do notation.
  • Routing with path captures that decompose ResponderM into middleware.
  • Parameter parsing for cookies, path, query, and body.
  • Helpers for redirects, headers, status codes, and errors.
{-# language OverloadedStrings #-}

import Network.Wai.Handler.Warp (run)
import Web.Twain

main :: IO ()
main = do
  run 8080 $
    foldr ($)
      (notFound missing)
      [ get "/" index
      , post "echo:name" echo
      ]

index :: ResponderM a
index = send $ html "Hello World!"

echo :: ResponderM a
echo = do
  name <- param "name"
  send $ html $ "Hello, " <> name

missing :: ResponderM a
missing = send $ html "Not found..."
Synopsis

Documentation

data ResponderM a Source #

ResponderM is an Either-like monad that can "short-circuit" and return a response, or pass control to the next middleware. This provides convenient branching with do notation for redirects, error responses, etc.

Instances

Instances details
MonadIO ResponderM Source # 
Instance details

Defined in Web.Twain.Types

Methods

liftIO :: IO a -> ResponderM a #

Applicative ResponderM Source # 
Instance details

Defined in Web.Twain.Types

Methods

pure :: a -> ResponderM a #

(<*>) :: ResponderM (a -> b) -> ResponderM a -> ResponderM b #

liftA2 :: (a -> b -> c) -> ResponderM a -> ResponderM b -> ResponderM c #

(*>) :: ResponderM a -> ResponderM b -> ResponderM b #

(<*) :: ResponderM a -> ResponderM b -> ResponderM a #

Functor ResponderM Source # 
Instance details

Defined in Web.Twain.Types

Methods

fmap :: (a -> b) -> ResponderM a -> ResponderM b #

(<$) :: a -> ResponderM b -> ResponderM a #

Monad ResponderM Source # 
Instance details

Defined in Web.Twain.Types

Methods

(>>=) :: ResponderM a -> (a -> ResponderM b) -> ResponderM b #

(>>) :: ResponderM a -> ResponderM b -> ResponderM b #

return :: a -> ResponderM a #

MonadCatch ResponderM Source # 
Instance details

Defined in Web.Twain.Types

Methods

catch :: Exception e => ResponderM a -> (e -> ResponderM a) -> ResponderM a #

MonadThrow ResponderM Source # 
Instance details

Defined in Web.Twain.Types

Methods

throwM :: Exception e => e -> ResponderM a #

Routing

route :: Maybe Method -> PathPattern -> ResponderM a -> Middleware Source #

Route request matching optional Method and PathPattern to ResponderM.

notFound :: ResponderM a -> Application Source #

Respond if no other route responds.

Sets the status to 404.

Requests

param :: ParsableParam a => Text -> ResponderM a Source #

Get a parameter. Looks in query, path, cookie, and body (in that order).

If no parameter is found, or parameter fails to parse, next is called which passes control to subsequent routes and middleware.

paramEither :: ParsableParam a => Text -> ResponderM (Either HttpError a) Source #

Get a parameter or error if missing or parse failure.

paramMaybe :: ParsableParam a => Text -> ResponderM (Maybe a) Source #

Get an optional parameter.

Returns Nothing for missing parameter. Throws HttpError on parse failure.

params :: ResponderM [Param] Source #

Get all parameters from query, path, cookie, and body (in that order).

queryParam :: ParsableParam a => Text -> ResponderM a Source #

Get a query parameter.

If no parameter is found, or parameter fails to parse, next is called which passes control to subsequent routes and middleware.

queryParamMaybe :: ParsableParam a => Text -> ResponderM (Maybe a) Source #

Get an optional query parameter.

Returns Nothing for missing parameter. Throws HttpError on parse failure.

queryParamEither :: ParsableParam a => Text -> ResponderM (Either HttpError a) Source #

Get a query parameter or error if missing or parse failure.

queryParams :: ResponderM [Param] Source #

Get all query parameters.

pathParam :: ParsableParam a => Text -> ResponderM a Source #

Get a path parameter.

If no parameter is found, or parameter fails to parse, next is called which passes control to subsequent routes and middleware.

pathParamMaybe :: ParsableParam a => Text -> ResponderM (Maybe a) Source #

Get an optional path parameter.

Returns Nothing for missing parameter. Throws HttpError on parse failure.

pathParamEither :: ParsableParam a => Text -> ResponderM (Either HttpError a) Source #

Get a path parameter or error if missing or parse failure.

pathParams :: ResponderM [Param] Source #

Get all path parameters.

cookieParam :: ParsableParam a => Text -> ResponderM a Source #

Get a cookie parameter.

If no parameter is found, or parameter fails to parse, next is called which passes control to subsequent routes and middleware.

cookieParamMaybe :: ParsableParam a => Text -> ResponderM (Maybe a) Source #

Get an optional cookie parameter.

Returns Nothing for missing parameter. Throws HttpError on parse failure.

cookieParamEither :: ParsableParam a => Text -> ResponderM (Either HttpError a) Source #

Get a cookie parameter or error if missing or parse failure.

cookieParams :: ResponderM [Param] Source #

Get all cookie parameters.

file :: Text -> ResponderM (FileInfo ByteString) Source #

Get uploaded FileInfo.

If missing parameter or empty file, pass control to subsequent routes and middleware.

fileMaybe :: Text -> ResponderM (Maybe (FileInfo ByteString)) Source #

Get optional uploaded FileInfo.

Nothing is returned for missing parameter or empty file content.

files :: ResponderM [File ByteString] Source #

Get all uploaded files.

fromBody :: FromJSON a => ResponderM a Source #

Get the JSON value from request body.

header :: Text -> ResponderM (Maybe Text) Source #

Get the value of a request Header. Header names are case-insensitive.

headers :: ResponderM [Header] Source #

Get the request headers.

Responses

send :: Response -> ResponderM a Source #

Send a Response.

send $ text "Hello, World!"

Send an html response:

send $ html "<h1>Hello, World!</h1>"

Modify the status:

send $ status status404 $ text "Not Found"

Send a response withHeader:

send $ withHeader (hServer, "Twain + Warp") $ text "Hello"

Send a response withCookie:

send $ withCookie "key" "val" $ text "Hello"

next :: ResponderM a Source #

Pass control to the next route or middleware.

redirect301 :: Text -> Response Source #

Create a redirect response with 301 status (Moved Permanently).

redirect302 :: Text -> Response Source #

Create a redirect response with 302 status (Found).

redirect303 :: Text -> Response Source #

Create a redirect response 303 status (See Other).

text :: Text -> Response Source #

Construct a Text response.

Sets the Content-Type and Content-Length headers.

html :: ByteString -> Response Source #

Construct an HTML response.

Sets the Content-Type and Content-Length headers.

json :: ToJSON a => a -> Response Source #

Construct a JSON response using ToJSON.

Sets the Content-Type and Content-Length headers.

xml :: ByteString -> Response Source #

Construct an XML response.

Sets the Content-Type and Content-Length headers.

css :: ByteString -> Response Source #

Construct a CSS response.

Sets the Content-Type and Content-Length headers.

raw :: Status -> [Header] -> ByteString -> Response Source #

Construct a raw response from a lazy ByteString.

Sets the Content-Length header if missing.

withHeader :: Header -> Response -> Response Source #

Add a Header to response.

withCookie :: Text -> Text -> Response -> Response Source #

Add a cookie to the response with the given key and value.

Note: This uses defaultSetCookie.

withCookie' :: SetCookie -> Response -> Response Source #

Add a SetCookie to the response.

expireCookie :: Text -> Response -> Response Source #

Add a header to expire (unset) a cookie with the given key.

Errors

data HttpError Source #

Constructors

HttpError Status String 

Instances

Instances details
Exception HttpError Source # 
Instance details

Defined in Web.Twain.Types

Show HttpError Source # 
Instance details

Defined in Web.Twain.Types

Eq HttpError Source # 
Instance details

Defined in Web.Twain.Types

Middleware

withMaxBodySize :: Word64 -> Middleware Source #

Specify maximum request body size in bytes.

Defaults to 64KB.

Parameters

class ParsableParam a where Source #

Parse values from request parameters.

Minimal complete definition

parseParam

Methods

parseParam :: Text -> Either HttpError a Source #

parseParamList :: Text -> Either HttpError [a] Source #

Default implementation parses comma-delimited lists.

Instances

Instances details
ParsableParam Int16 Source # 
Instance details

Defined in Web.Twain.Types

ParsableParam Int32 Source # 
Instance details

Defined in Web.Twain.Types

ParsableParam Int64 Source # 
Instance details

Defined in Web.Twain.Types

ParsableParam Int8 Source # 
Instance details

Defined in Web.Twain.Types

ParsableParam Word16 Source # 
Instance details

Defined in Web.Twain.Types

ParsableParam Word32 Source # 
Instance details

Defined in Web.Twain.Types

ParsableParam Word64 Source # 
Instance details

Defined in Web.Twain.Types

ParsableParam Word8 Source # 
Instance details

Defined in Web.Twain.Types

ParsableParam ByteString Source # 
Instance details

Defined in Web.Twain.Types

ParsableParam ByteString Source # 
Instance details

Defined in Web.Twain.Types

ParsableParam Text Source # 
Instance details

Defined in Web.Twain.Types

ParsableParam Text Source # 
Instance details

Defined in Web.Twain.Types

ParsableParam Integer Source # 
Instance details

Defined in Web.Twain.Types

ParsableParam Natural Source # 
Instance details

Defined in Web.Twain.Types

ParsableParam () Source # 
Instance details

Defined in Web.Twain.Types

ParsableParam Bool Source # 
Instance details

Defined in Web.Twain.Types

ParsableParam Char Source # 
Instance details

Defined in Web.Twain.Types

ParsableParam Double Source # 
Instance details

Defined in Web.Twain.Types

ParsableParam Float Source # 
Instance details

Defined in Web.Twain.Types

ParsableParam Int Source # 
Instance details

Defined in Web.Twain.Types

ParsableParam Word Source # 
Instance details

Defined in Web.Twain.Types

ParsableParam a => ParsableParam [a] Source # 
Instance details

Defined in Web.Twain.Types

Re-exports

data FileInfo c #

Information on an uploaded file.

Instances

Instances details
Show c => Show (FileInfo c) 
Instance details

Defined in Network.Wai.Parse

Methods

showsPrec :: Int -> FileInfo c -> ShowS #

show :: FileInfo c -> String #

showList :: [FileInfo c] -> ShowS #

Eq c => Eq (FileInfo c) 
Instance details

Defined in Network.Wai.Parse

Methods

(==) :: FileInfo c -> FileInfo c -> Bool #

(/=) :: FileInfo c -> FileInfo c -> Bool #