1:- module(bc_router, [
    2    bc_route/1,         % +Request
    3    bc_enable_expires/0
    4]).

HTTP routing

Top-level HTTP handler that provides file serving, routing through arouter and fallback to http_dispatch/1. */

   13:- use_module(library(http/http_dispatch)).   14:- use_module(library(http/http_header)).   15:- use_module(library(debug)).   16:- use_module(library(arouter)).   17
   18:- use_module(bc_view).   19:- use_module(bc_headers).   20
   21:- dynamic(expires/0).
 bc_enable_expires is det
Enables Cache-Control and Expires headers.
   28bc_enable_expires:-
   29    (   expires
   30    ->  true
   31    ;   asserta(expires)),
   32    debug(bc_route, 'static file Expires/Cache-Control enabled', []).
   33
   34% Time in seconds for files
   35% to be cached by clients.
   36
   37cache_control(5184000). % 60 days
 bc_route(+Request) is det
Routes the given HTTP request. First tries ar_route/1. If it fails then it tries serve_file/1. Finally tries http_dispatch/1.
   46bc_route(Request):-    
   47    memberchk(path(Path), Request),
   48    debug(bc_router, 'Routing ~p', [Path]),
   49    (   try_route(Request)
   50    ;   (   serve_file(Request)
   51        ;   http_dispatch(Request))).
   52
   53try_route(Request):-
   54    memberchk(path(Path), Request),
   55    (   bc_view_cached(Path)
   56    ;   (   route(Request)
   57        ;   atom_concat(Prefix, '/', Path),
   58            Prefix \= '',
   59            http_redirect(moved, Prefix, Request))).
 serve_file(+Request) is semidet
Tries to serve matching file from the public folder. If it does not exist, the predicate fails.
   67serve_file(Request):-
   68    memberchk(path(Path), Request),
   69    atom_concat(public, Path, File),
   70    exists_file(File),
   71    (   expires,
   72        memberchk(cache_token(true), Request)
   73    ->  cache_control(MaxAge),
   74        get_time(Time),
   75        Expires is Time + MaxAge,
   76        http_timestamp(Expires, ExpiresString), % TODO move to bc_headers
   77        format('Expires: ~w\r\n', [ExpiresString]),
   78        format('Cache-Control: max-age=~w\r\n', [MaxAge])
   79    ;   true),
   80    http_reply_file(File, [cache(true)], Request)