Route Handling

Make a route predicate in the project handle the route and write out the response to current out

*/

    9:- module(sw_route_handling,
   10    [ init_routes/0
   11    , url_for/2
   12    , url_for/3
   13    ]
   14).   15
   16:- use_module(library(http/thread_httpd)).   17:- use_module(library(http/http_dispatch)).   18:- use_module(library(http/http_path)).
 init_routes is det
find all simple_web:routes and setup http_handlers for them.
   24init_routes :-
   25    findall(N-R, clause(sw:route(N, R, _Request), _), RoutesS),
   26    findall(N-R-M, clause(sw:route(N, R, M, _Req), _), RoutesM),
   27    append(RoutesS, RoutesM, Routes),
   28    handle_routes(Routes).
 handle_routes(+Routes) is det
recursively handle a route
Arguments:
Routes- A list of routes
   35handle_routes([]).
   36handle_routes([R| Routes]) :-
   37    handle_route(R),
   38    handle_routes(Routes).
 handle_route(+Route:atom) is det
create http_handler for Route
Arguments:
Route- an atom /route/to/page
   44handle_route(N-R-M) :-
   45    log_route(N, R),
   46    http_handler( R,
   47                  method_route(N, R, M),
   48                  []).
   49handle_route(N-R) :-
   50    \+ R = _-_,
   51    \+ N = _-_,
   52    ground(R),
   53    log_route(N, R),
   54    http_handler( R,
   55                  sw:route(N, R),
   56                  []).
   57handle_route(N-R) :-
   58    \+ R = _-_,
   59    \+ N = _-_,
   60    \+ ground(R),
   61    log_route(N, R),
   62    R =.. [P|_],
   63    Route =.. [P, '.'],
   64    http_handler( Route,
   65                  var_route(N, P),
   66                  [prefix]).
 log_route(Name, Route) is det
log the handler for the route to enable url_for
   70log_route(Name, Route) :-
   71    asserta(sw:handler_url(Name, Route)).
   72% unused, route is route without method
   73log_route(Name, Route, Method) :-
   74    asserta(sw:handler_url(Name, Route, Method)).
 url_for(+Handler, ?URL) is semidet
Find the URL for a given handler name, also can be used with static files: url_for("static('js/main.js')") ! url_for(+Handler, ?URL, +Options) is semidet. Find the URL for a given handler name
Arguments:
Options- Is a list of options. Only supported option is absolute, which returns an absolute URL
   84url_for("static", "/static").
   85url_for(StaticPath, URL) :-
   86    term_string(static(Path), StaticPath),
   87    string_concat("/static/", Path, URL).
   88url_for(Handler, URL) :-
   89    \+ string(Handler),
   90    sw:handler_url(Handler, Route),
   91    http_absolute_location(Route, URL, [relative_to(root)]).
   92url_for(SHandler, URL) :-
   93    string(SHandler), term_string(Handler, SHandler),
   94    sw:handler_url(Handler, Route),
   95    http_absolute_location(Route, URL, [relative_to(root)]).
   96url_for(Handler, URL, []) :-
   97    url_for(Handler, URL).
   98url_for(Handler, URL, [absolute]) :-
   99    ground(Handler),
  100    sw:handler_url(Handler, Route),
  101    http_absolute_uri(Route, URL).
  102% url_for(static(Path), URL)
 method_route(+Route, +Method, +Request) is semidet
route with a method
Arguments:
Route- an atom route/to/page
Method- term: method(get), method(post) etc.
Request-
  111method_route(N, R, M, Request) :-
  112    member(M, Request),
  113    sw:route(N, R, M, Request), !.
  114method_route(_, _, _, Request) :-
  115    http_404([], Request).
 var_route(+Predicate, +Request) is semidet
handle variables in a route, extract data from path info, split by '/'.
  120var_route(N, P, Request) :-
  121    member(path_info(A), Request),
  122    atomic_list_concat(Args, '/', A),
  123    R =.. [P|Args],
  124    sw:route(N, R, Request).
  125var_route(_, _, Request) :-
  126    http_404([], Request)