Safe Haskell | None |
---|---|
Language | Haskell2010 |
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.
{--} 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
- data ResponderM a
- get :: PathPattern -> ResponderM a -> Middleware
- put :: PathPattern -> ResponderM a -> Middleware
- patch :: PathPattern -> ResponderM a -> Middleware
- post :: PathPattern -> ResponderM a -> Middleware
- delete :: PathPattern -> ResponderM a -> Middleware
- route :: Maybe Method -> PathPattern -> ResponderM a -> Middleware
- notFound :: ResponderM a -> Application
- param :: ParsableParam a => Text -> ResponderM a
- paramEither :: ParsableParam a => Text -> ResponderM (Either HttpError a)
- paramMaybe :: ParsableParam a => Text -> ResponderM (Maybe a)
- params :: ResponderM [Param]
- file :: Text -> ResponderM (FileInfo ByteString)
- fileMaybe :: Text -> ResponderM (Maybe (FileInfo ByteString))
- files :: ResponderM [File ByteString]
- fromBody :: FromJSON a => ResponderM a
- header :: Text -> ResponderM (Maybe Text)
- headers :: ResponderM [Header]
- request :: ResponderM Request
- send :: Response -> ResponderM a
- next :: ResponderM a
- redirect301 :: Text -> Response
- redirect302 :: Text -> Response
- redirect303 :: Text -> Response
- text :: Text -> Response
- html :: ByteString -> Response
- json :: ToJSON a => a -> Response
- xml :: ByteString -> Response
- css :: ByteString -> Response
- raw :: Status -> [Header] -> ByteString -> Response
- status :: Status -> Response -> Response
- withHeader :: Header -> Response -> Response
- withCookie :: Text -> Text -> Response -> Response
- withCookie' :: SetCookie -> Response -> Response
- expireCookie :: Text -> Response -> Response
- data HttpError = HttpError Status String
- onException :: (SomeException -> ResponderM a) -> Middleware
- withParseBodyOpts :: ParseRequestBodyOptions -> Middleware
- withMaxBodySize :: Word64 -> Middleware
- class ParsableParam a where
- parseParam :: Text -> Either HttpError a
- parseParamList :: Text -> Either HttpError [a]
- module Network.HTTP.Types
- module Network.Wai
- data FileInfo c = FileInfo {}
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
Routing
get :: PathPattern -> ResponderM a -> Middleware Source #
put :: PathPattern -> ResponderM a -> Middleware Source #
patch :: PathPattern -> ResponderM a -> Middleware Source #
post :: PathPattern -> ResponderM a -> Middleware Source #
delete :: PathPattern -> ResponderM a -> Middleware Source #
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 #
params :: ResponderM [Param] Source #
Get all parameters from query, path, cookie, and body (in that order).
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 #
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.
withCookie :: Text -> Text -> Response -> Response Source #
Add a cookie to the response with the given key and value.
Note: This uses defaultSetCookie
.
expireCookie :: Text -> Response -> Response Source #
Add a header to expire (unset) a cookie with the given key.
Errors
Instances
Eq HttpError Source # | |
Show HttpError Source # | |
Exception HttpError Source # | |
Defined in Web.Twain.Types toException :: HttpError -> SomeException # fromException :: SomeException -> Maybe HttpError # displayException :: HttpError -> String # |
onException :: (SomeException -> ResponderM a) -> Middleware Source #
Middleware
withParseBodyOpts :: ParseRequestBodyOptions -> Middleware Source #
Specify ParseRequestBodyOptions
to use when parsing request body.
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.
parseParam :: Text -> Either HttpError a Source #
parseParamList :: Text -> Either HttpError [a] Source #
Default implementation parses comma-delimited lists.
Instances
Re-exports
module Network.HTTP.Types
module Network.Wai
Information on an uploaded file.
FileInfo | |
|