Library
Module
Module type
Parameter
Class
Class type
Well Typed Router - is a HTTP request routing library for OCaml web applications.
Given a HTTP request_target and a HTTP method, Wtr
attempts to match the two properties to a pre-defined set of routes. If a match is found then the corresponding route handler function of the matched route is executed.
The route matching algorithm is radix trie.
The well typed part in Wtr
means that the route handler functions can capture and receive arguments which are typed in a variety of OCaml types.
There are two ways to specify route and request targets:
[%routes ""]
- ppx based which is provided by a separate opam package wtr-ppx
.route
is a HTTP request route. A route encapsulates a HTTP method'
, a request_target
and a route handler. A route handler is either of the following:
'a
'a
.and 'a routes = 'a route list
request_target
is a HTTP request target value to be matched. It consists of either just a path
value or a combination of path
and query
values.
Example request_target values:
/home/about/
- path only/home/contact
- path only/home/contact?name=a&no=123
- path (/home/contact
) and query (name=a&no=123
). Path and query are delimited by ?
character token if both are specified.Consult Request Target DSL for creating values of this type.
path
is a part of request_target
. It consists of one or more path components. path components are tokens which are delimited by a /
character token.
Example of path and path components:
/
has path a component /
/home/about
has path components home, about
/home/contact/
has path components home
, contact
and /
Consult Request Target DSL for creating values of this type.
rest
represents a part of request target from a given path component to the rest of a request_target.
Use rest_to_string
to convert to string representation.
query
is a part of request_target
. It consists of one of more query components which are delimited by a &
character token. A query component further consists of a pair of values called name
and value
. name
and value
tokens are delimited by a =
character token. A query component is represented syntactically as (name,value)
.
Given a request_target /home/about?a=2&b=3
, the query components are (a,2)
and (b,3)
.
Consult Request Target DSL for creating values of this type.
method'
is a HTTP request method. See HTTP RFC 7231 - HTTP Methods
arg
is a component which can convert a path component or a query component value
token into an OCaml typed value represented by 'a
. The successfully converted value is then fed to a route handler function as an argument.
val arg : string -> (string -> 'a option) -> 'a arg
arg name convert
is arg
with name name
and convert
as the function which will convert/decode a string value to an OCaml value of type 'a
.
name
is used during the pretty-printing of request_target by pp_request_target
.
convert v
is Some a
if convert
can successfully convert v
to a
. Otherwise it is None
.
Although not strictly necessary if we are only working with Request Target DSL, it is recommended to adhere to the following convention when creating a custom arg. Such an 'a arg
value can be used with both Request Target DSL and wtr-ppx
ppxes. The convention is as follows:
t
t
which is of type t Wtr.arg
name
value of the arg match the name of the module.An example of such an 'a arg
component - Fruit.t arg
is as below:
module Fruit = struct
type t = Apple | Orange | Pineapple
let t : t Wtr.arg =
Wtr.arg "Fruit" (function
| "apple" -> Some Apple
| "orange" -> Some Orange
| "pineapple" -> Some Pineapple
| _ -> None)
end
Request Target combinators implement a DSL(domain specific language) to specify request_target
, path component and query component values.
Let's assume that we want to specify a HTTP route which matches a request target value as such:
int
valuestring
valueThe request target is implemented as such:
let target1 = Wtr.(exact "hello" / int / string /. pend)
target1
above matches the following instances of HTTP request target:
/home/2/str1
/home/-10/str3
Let's assume that we want to specify a HTTP route which matches a request target value which consists of both path and query as such:
bool
valueint
value.string
value.The request_target is implemented as such:
let target2 = Wtr.(exact "hello" / bool /? qint "i" / qstring "s" /?. ())
target2
above matches the following instances of HTTP request target:
/hello/true?i=233&s=str1
/hello/false?i=-1234&s=str2
p1 / p2
is a closure that combines p1
and p2
. p1
and p2
are closures which encapsulate path
value.
q1 /& q1
is a closure that combines q1
and q2
. q1
and q2
are closures which encapsulate query
value.
p //. pe
is path
that consists of only path components p
and pe
. pe
is a path value that matches the last path component.
val (/.) :
(('d, 'e) path -> ('b, 'c) path) ->
('d, 'e) path ->
('b, 'c) request_target
p /. pe
is a request_target
value that consists of only path components p
and pe
. pe
is a path value that matches the last path component. It is equivalent to the following:
let p = Wtr.(exact "hello" / exact "about" //. pend) |> Wtr.of_path
val (/?.) :
(('b, 'b) query -> ('c, 'd) path) ->
unit ->
('c, 'd) request_target
pq /?. ()
is request_target
. pq
is a closure which encapulates both path
and query
components.
let request_target1 =
Wtr.(
exact "hello"
/ bool
/? qint "hello"
/& qstring "hh"
/& qbool "b"
/?. ())
val of_path : ('a, 'b) path -> ('a, 'b) request_target
of_path path
converts path
to request_target
exact e p
matches a path component to e
exactly.
qexact (field, e)
matches a query component to e
exactly. The query component token name
value is field
.
val to_request_target : ('a, 'b) path -> ('a, 'b) request_target
to_request_target p
is request_target
consisting of only path p
.
val root : ('a, 'a) request_target
root
is a request_target with /
as the only component, i.e. it matches exactly the root HTTP request.
Path/Query arg components encapsulate arg
value which are then fed to a route handler function as an argument.
float
matches valid OCaml float
and int
values.
Note In addition to OCaml float
values, the combinator can also match OCaml int
values. Therefore:
Given, p
is
let p = Wtr.(float /. pend)
then, it can match the following instances of HTTP request targets:
/123
/-234
/123.
/123.02
/-123.
/-123.22
bool
matches a path component if it is equal to either "true"
or "false"
and converts them to valid OCaml bool
values.
parg d p
matches a path component if d
can successfully convert path component to a value of type 'c
.
The example below uses the Fruit.t arg
defined above:
let p = Wtr.(parg Fruit.t /. pend)
p
matchs the following instances of HTTP request target values:
/pineapple
/apple
/orange
qint field
matches a valid OCaml int
value. field
is the name
token of query component.
qint32 field
matches a valid OCaml int32
value. field
is the name
token of query component.
qint64 field
matches a valid OCaml int64
value. field
is the name
token of query component.
qfloat field
matches a valid OCaml float
value. field
is the name
token of query component.
The values matched by this combinator is the same as the float
combinator.
qbool field
matches query component if value
token is equal to either "true"
or "false"
. The value
token is then converted to a valid OCaml bool
value. field
is the name
token of query component.
qstring field
matches a valid OCaml string
value. field
is the name
token of query component.
qarg (field, d)
matches a query component if d
can successfully convert path component to a value of type 'c
. field
is the name
token of query component.
The example below uses the Fruit.t arg
defined above:
let p = Wtr.(exact "hello" /? qarg ("fruit", Fruit.t) /?. ())
p
matchs the following instances of HTTP request target values:
/hello?fruit=pineapple
/hello?fruit=apple
/hello?fruit=orange
These combinators match the last - end - path component. They are used with (/.)
function.
rest
matches and captures all of the remaining path and query components. The captured value is then fed to a route handler.
let%expect_test "rest: comb" =
(Wtr.(
router [ routes [ `GET ] (exact "public" /. rest) rest_to_string ])
|> Wtr.match' `GET "/public/styles/style.css"
|> function
| Some s -> print_string s
| None -> ());
[%expect {| styles/style.css |}]
val slash : ('a, 'a) path
slash
matches path component /
first and then matches the end of the path
value.
let%expect_test "slash matched" =
(Wtr.(router [ routes [ `GET ] (exact "public" /. slash) "slash" ])
|> Wtr.match' `GET "/public/"
|> function
| Some s -> print_string s
| None -> ());
[%expect {| slash |}]
let%expect_test "slash not matched" =
(Wtr.(router [ routes [ `GET ] (exact "public" /. slash) "slash" ])
|> Wtr.match' `GET "/public"
|> function
| Some s -> print_string s
| None -> ());
[%expect {| |}]
val rest_to_string : rest -> string
rest_to_string rest
converts rest
to string.
val route : method' -> ('a, 'b) request_target -> 'a -> 'b route
route method' request_target handler
is a route
.
val routes : method' list -> ('a, 'b) request_target -> 'a -> 'b routes
routes methods request_target route_handler
is a product of methods X request_target X route_handler
. This is equivalent to calling route
like so:
List.map (fun m -> route ~method:m request_target route_handler) [meth1; meth2; meth3]
match' method' request_target router
is Some a
if method'
and request_target
together matches one of the routes defined in router
. Otherwise it is None. The value Some a
is returned by the route handler of the matched route.
The routes are matched based on the lexical order of the routes. This means they are matched from top to bottom, left to right and to the longest match. See pp
to visualize the router and the route matching mechanism.
method_equal m1 m2
is true
if m1
and m2
is the same value. Otherwise it is false
.
Note if both m1
and m2
are `Method m
then the string comparison is case insensitive.
Wtr.method_equal `GET `GET = true;;
Wtr.method_equal `POST `GET = false;;
Wtr.method_equal (`Method "meth") (`Method "METH") = true
val method' : string -> method'
method' m
is method'
where string value m
is converted to method'
as follows:
"GET"
to `GET
"HEAD"
to `HEAD
"POST"
to `POST
"PUT"
to `PUT
"DELETE"
to `DELETE
"CONNECT"
to `CONNECT
"OPTIONS"
to `OPTIONS
"TRACE"
to `TRACE
m
to `Method m
Note String comparison is case insensitive.
Wtr.method' "GET" = `GET;;
Wtr.method' "get" = `GET;;
Wtr.method' "method" = `Method "method"
Pretty printers can be useful during debugging of routing and/or route related issues.
val pp_request_target : Format.formatter -> ('a, 'b) request_target -> unit
pp_request_target fmt target
pretty prints target
onto fmt
.
Path components
arg components - name of the combinator prefixed by :
token, eg. int
is printed as :int
, float
is printed as :float
. Path Arg Components
parg
component - name of the arg followed by :
token e.g. parg Fruit.t
is printed as :Fruit
.
exact
component - the string literal given to exact
is printed, e.g. exact "hello"
is printed as hello
.
slash
- printed as /
rest
- printed as **
A /
character is inserted in between the components when printing a sequence of path components, e.g.
let p = Wtr.(exact "hello" / int / bool /. rest)
is printed as /hello/:int/:bool/**
.
Query components
arg components - query arg components are printed similar to path arg components; with the addition of name
token, e.g. qint "h"
is printed as h=:int
, qbool "b"
is printed as b=:bool
.
qarg component - is printed similar to parg
; with the addition of field name, e.g. qarg ("h", Fruit.t)
is printed as h=:fruit
.
qexact component - is printed similar to exact
; with the addition of field name, e.g. qexact ("h", "hello")
is printed as h=hello
.
A &
character is inserted in between the components when printing a sequence of query components. Additionally, a ?
character is printed in between path components and query components, e.g.
let target1 =
Wtr.(
exact "hello"
/ bool
/ int
/ string
/? qexact ("h", "hello")
/& qbool "b"
/?. ())
in
Wtr.pp_request_target Format.std_formatter target1
will print the following: /hello/:bool/:int/:string?h=hello&b=:bool
val pp_method : Format.formatter -> method' -> unit
pp_method fmt m
pretty prints m
onto fmt
. It does the inverse of method'
.
val pp_route : Format.formatter -> 'b route -> unit
pp_route fmt route
first pretty prints the method
followed by the request_target
of a route
, e.g.
let route1 =
Wtr.(route ~method':`GET (exact "hello" / bool /. slash)) (fun _ -> ())
route1
is pretty printed as GET/hello/:bool/
The route2
contains both path and query components:
let route2 =
Wtr.(
route ~method':`GET
(exact "hello" / bool /? qexact ("h", "hello") /& qbool "b" /?. ()))
(fun _ _ -> ())
in
Wtr.pp_route Format.std_formatter route2
It is printed as follows: GET/hello/:bool?h=hello?b=:bool
val pp : Format.formatter -> 'a router -> unit
pp fmt router
pretty prints router
onto fmt
. It follows the same mechanism as pp_route
and pp_request_target
. However, unlike the two functions, it prints each component - path and query - onto a separate line. The component in each line is indented.
The indentation and line printing is meant to convey the order of a route component evaluation. The evaluation is from top to bottom and left to right. This gives some indication of how the routes are evaluated and thus can be used to aid in debugging routing issues.
For example, router1
which is defined as:
let router1 =
Wtr.(
router'
[
routes
[ `GET; `POST; `HEAD; `DELETE ]
(exact "home" / exact "about" /. slash)
about_page;
routes [ `GET ]
(exact "contact" / string / int /. pend)
contact_page;
routes [ `GET ]
(exact "product" / string /? qint "section" /& qbool "q" /?. ())
product1;
routes [ `GET ]
(exact "product"
/ string
/? qint "section"
/& qexact ("q1", "yes")
/?. ())
product2;
routes [ `GET ] (exact "fruit" / parg Fruit.t /. pend) fruit_page;
])
is pretty printed as below:
GET /home /about / /contact /:string /:int /product /:string ?section=:int &q=:bool &q1=yes /fruit /:Fruit POST /home /about / HEAD /home /about / DELETE /home /about /