Safe Haskell | None |
---|---|
Language | Haskell2010 |
This package provides a simple framework for routing and responses. The two primary goals are:
- All web handler functions are just plain IO. There is no Fn monad, or monad transformer. This has a lot of nice properties, foremost among them is that it is easier to call handlers from other contexts (like GHCi, when testing, in other threads, etc). As a result, these functions take a single extra parameter that has the context that they need (like database connection pools, the request, etc).
- Web handlers are functions with typed parameters. When routing, we specify many parameters (most commonly, numeric ids, but can be many things), so the handlers should be functions that take those as parameters.
- type FnRequest = (Request, ([Param], [File ByteString]))
- defaultFnRequest :: FnRequest
- class RequestContext ctxt where
- requestLens :: Functor f => (FnRequest -> f FnRequest) -> ctxt -> f ctxt
- getRequest :: ctxt -> FnRequest
- setRequest :: ctxt -> FnRequest -> ctxt
- toWAI :: RequestContext ctxt => ctxt -> (ctxt -> IO Response) -> Application
- type Req = ([Text], Query, StdMethod, ([Param], [File ByteString]))
- route :: RequestContext ctxt => ctxt -> [ctxt -> Req -> Maybe (IO (Maybe Response))] -> IO (Maybe Response)
- fallthrough :: IO (Maybe Response) -> IO Response -> IO Response
- (==>) :: RequestContext ctxt => (Req -> Maybe (Req, k -> a)) -> (ctxt -> k) -> ctxt -> Req -> Maybe a
- (//) :: (r -> Maybe (r, k -> k')) -> (r -> Maybe (r, k' -> a)) -> r -> Maybe (r, k -> a)
- (/?) :: (r -> Maybe (r, k -> k')) -> (r -> Maybe (r, k' -> a)) -> r -> Maybe (r, k -> a)
- path :: Text -> Req -> Maybe (Req, a -> a)
- end :: Req -> Maybe (Req, a -> a)
- anything :: Req -> Maybe (Req, a -> a)
- segment :: FromParam p => Req -> Maybe (Req, (p -> a) -> a)
- method :: StdMethod -> Req -> Maybe (Req, a -> a)
- class FromParam a where
- fromParam :: Text -> Either ParamError a
- data ParamError
- param :: FromParam p => Text -> Req -> Maybe (Req, (p -> a) -> a)
- paramMany :: FromParam p => Text -> Req -> Maybe (Req, ([p] -> a) -> a)
- paramOpt :: FromParam p => Text -> Req -> Maybe (Req, (Either ParamError [p] -> a) -> a)
- data File = File {}
- file :: Text -> Req -> Maybe (Req, (File -> a) -> a)
- files :: Req -> Maybe (Req, ([(Text, File)] -> a) -> a)
- staticServe :: RequestContext ctxt => Text -> ctxt -> IO (Maybe Response)
- okText :: Text -> IO (Maybe Response)
- okHtml :: Text -> IO (Maybe Response)
- errText :: Text -> IO (Maybe Response)
- errHtml :: Text -> IO (Maybe Response)
- notFoundText :: Text -> IO Response
- notFoundHtml :: Text -> IO Response
- redirect :: Text -> IO (Maybe Response)
Application setup
type FnRequest = (Request, ([Param], [File ByteString])) Source
A normal WAI Request
and the parsed post body (if present). We can
only parse the body once, so we need to have our request (which we
pass around) to be able to have the parsed body.
defaultFnRequest :: FnRequest Source
A default request, which is a WAI defaultRequest and no post info
class RequestContext ctxt where Source
Specify the way that Fn can get the FnRequest
out of your context.
The easiest way to instantiate this is to use the lens, but if you
don't want to use lenses, define getRequest
and setRequest
.
Note that requestLens
is defined in terms of getRequest
and
setRequest
and vice-versa, so you need to define _one_ of these.
Nothing
requestLens :: Functor f => (FnRequest -> f FnRequest) -> ctxt -> f ctxt Source
getRequest :: ctxt -> FnRequest Source
setRequest :: ctxt -> FnRequest -> ctxt Source
toWAI :: RequestContext ctxt => ctxt -> (ctxt -> IO Response) -> Application Source
Convert an Fn application (provide a context, a context to response
function and we'll create a WAI application by updating the FnRequest
value for each call).
Routing
type Req = ([Text], Query, StdMethod, ([Param], [File ByteString])) Source
The parts of the path, when split on /, and the query.
route :: RequestContext ctxt => ctxt -> [ctxt -> Req -> Maybe (IO (Maybe Response))] -> IO (Maybe Response) Source
The main construct for Fn, route
takes a context (which it will pass
to all handlers) and a list of potential matches (which, once they
match, may still end up deciding not to handle the request - hence
the double Maybe
). It can be nested.
app c = route c [ end ==> index , path "foo" // path "bar" // segment /? param "id ==> h] where index :: Ctxt -> IO (Maybe Response) index _ = okText "This is the index." h :: Ctxt -> Text -> Text -> IO (Maybe Response) h _ s i = okText ("got path /foo/" <> s <> ", with id=" <> i)
fallthrough :: IO (Maybe Response) -> IO Response -> IO Response Source
The route
function (and all your handlers) return
'IO (Maybe Response)', because each can elect to not respond (in
which case we will continue to match on routes). But to construct
an application, we need a response in the case that nothing matched
- this is what fallthrough
allows you to specify. In particular,
notFoundText
and notFoundHtml
may be useful.
(==>) :: RequestContext ctxt => (Req -> Maybe (Req, k -> a)) -> (ctxt -> k) -> ctxt -> Req -> Maybe a Source
The connective between route patterns and the handler that will be called if the pattern matches. The type is not particularly illuminating, as it uses polymorphism to be able to match route patterns with varying numbers (and types) of parts with functions of the corresponding number of arguments and types.
(//) :: (r -> Maybe (r, k -> k')) -> (r -> Maybe (r, k' -> a)) -> r -> Maybe (r, k -> a) Source
Connects two path segments. Note that when normally used, the
type parameter r is Req
. It is more general here to facilitate
testing.
path :: Text -> Req -> Maybe (Req, a -> a) Source
Matches a literal part of the path. If there is no path part left, or the next part does not match, the whole match fails.
end :: Req -> Maybe (Req, a -> a) Source
Matches there being no parts of the path left. This is useful when matching index routes.
segment :: FromParam p => Req -> Maybe (Req, (p -> a) -> a) Source
Captures a part of the path. It will parse the part into the type specified by the handler it is matched to. If there is no segment, or if the segment cannot be parsed as such, it won't match.
data ParamError Source
param :: FromParam p => Text -> Req -> Maybe (Req, (p -> a) -> a) Source
Matches on a single query parameter of the given name. If there is no parameters, or it cannot be parsed into the type needed by the handler, it won't match.
paramMany :: FromParam p => Text -> Req -> Maybe (Req, ([p] -> a) -> a) Source
Matches on query parameters of the given name. If there are no parameters, or they cannot be parsed into the type needed by the handler, it won't match.
paramOpt :: FromParam p => Text -> Req -> Maybe (Req, (Either ParamError [p] -> a) -> a) Source
If the specified parameters are present, they will be parsed into the type needed by the handler, but if they aren't present or cannot be parsed, the handler will still be called.
An uploaded file.
File | |
|
file :: Text -> Req -> Maybe (Req, (File -> a) -> a) Source
Matches an uploaded file with the given parameter name.
files :: Req -> Maybe (Req, ([(Text, File)] -> a) -> a) Source
Matches all uploaded files, passing their parameter names and contents.
Responses
staticServe :: RequestContext ctxt => Text -> ctxt -> IO (Maybe Response) Source
Serves static files out of the specified path according to the
request path. Note that if you have matched parts of the path,
those will not be included in the path used to find the static
file. For example, if you have a file static/img/a.png
, and do:
path "img" ==> staticServe "static"
It will match img/img/a.png
, not img/a.png
. If you wanted that,
you could:
anything ==> staticServe "static"
If no file is found, this will continue routing.
errHtml :: Text -> IO (Maybe Response) Source
Returns Html (in Text
) as a response with a 500 status code.
notFoundText :: Text -> IO Response Source
Returns a 404 with the given Text
as a body. Note that this
returns a 'IO Response' not an 'IO (Maybe Response)' because the
expectaiton is that you are calling this with fallthrough
.
notFoundHtml :: Text -> IO Response Source
Returns a 404 with the given html as a body. Note that this
returns a 'IO Response' not an 'IO (Maybe Response)' because the
expectaiton is that you are calling this with fallthrough
.