1:- module(bc_admin_file, [
    2    bc_admin_send_file/1, % +Path
    3    bc_admin_relative/2   % +Spec, -Path
    4]).

Helper module to send admin-related files */

    8:- use_module(library(http/http_dispatch)).    9:- use_module(library(http/http_wrapper)).   10:- use_module(library(http/http_header)).   11:- use_module(bc_env).   12
   13bc_admin_send_file(Spec):-
   14    bc_admin_relative(Spec, Full),
   15    check_path(Full),
   16    send_file_unsafe(Full).
   17
   18send_file_unsafe(Path):-
   19    bc_env_production, !,
   20    http_current_request(Request),
   21    get_time(TimeStamp),
   22    MaxAge is 365 * 24 * 60 * 60,
   23    Expire is TimeStamp + MaxAge,
   24    http_timestamp(Expire, ExpireString),
   25    atom_concat('max-age=', MaxAge, CacheControl),
   26    http_reply_file(Path,
   27        [unsafe(true), headers([
   28            cache_control(CacheControl),
   29            expires(ExpireString)])], Request).
   30
   31% In development, send without strong caching headers.
   32
   33send_file_unsafe(Path):-
   34    http_current_request(Request),
   35    http_reply_file(Path, [unsafe(true)], Request).
   36
   37% Checks that the path is safe. It
   38% must not contain '..'.
   39
   40check_path(Path):-
   41    sub_atom(Path, _, _, _, '..'), !,
   42    throw(error('Path must not contain ..')).
   43
   44check_path(_).
   45
   46% Turns admin-local URL path
   47% to absolute filesystem path.
   48
   49bc_admin_relative(Spec, Path):-
   50    public_path(Public),
   51    spec_to_path(Public/Spec, Path).
   52
   53spec_to_path(Atom, Atom):-
   54    atom(Atom), !.
   55
   56spec_to_path(/(Prefix, Name), Path):-
   57    spec_to_path(Prefix, PrefixPath),
   58    spec_to_path(Name, NamePath),
   59    atom_concat(PrefixPath, '/', PrefixPathSlash),
   60    atom_concat(PrefixPathSlash, NamePath, Path).
   61
   62public_path(Public):-
   63    module_property(bc_admin_file, file(File)),
   64    file_directory_name(File, Dir),
   65    atom_concat(Dir, '/public', Public)