Template Handling

Run template handling from template directory. Uses simple-template: https://github.com/rla/simple-template

*/

    8:- module(sw_template_handling,
    9    [ reply_html/1
   10    , reply_html/2
   11    , reply_html/3
   12    , reply_template/2
   13    , reply_template/3
   14    ]
   15).   16
   17:- use_module(library(st/st_expr)).   18:- use_module(library(st/st_render)).   19
   20:- use_module(sw_config_handling).   21:- use_module(library(http/html_write)).   22
   23:- use_module(sw_route_handling,
   24    [ url_for/2
   25    , url_for/3
   26    ]
   27).   28
   29:- get_config(templates_dir, Dir),
   30   asserta(user:file_search_path(sweb_templates, sw_app(Dir))).   31
   32:- st_set_function(url_for, 1, url_for).   33:- st_set_function(from_templates, 1, from_templates).   34
   35from_templates(File, Path) :-
   36    absolute_file_name(sweb_templates(File), Path, []).
 reply_html(HTML:str) is det
Reply with raw string as html
Arguments:
HTML- a string assumed to be HTML ! reply_html(:Head, :Body) is det

wrapper to reply_html_page/2 replies with termerized html ! reply_html(+Style, :Head, :Body) is det

wrapper to reply_html_page/3 replies with termerized html

   51reply_html(HTML) :-
   52    string(HTML),
   53    format("Content-type: text/html~n~n~w~n", HTML).
   54reply_html(Head, Body) :-
   55    reply_html_page(Head, Body).
   56reply_html(Style, Head, Body) :-
   57    reply_html_page(Style, Head, Body).
 reply_template(+Template:atom, +Data:dict) is det
Reply with simple-template
Arguments:
Template- The name of the template, ".html" not required
Data- Dict of keys and values used in the template
   65reply_template(Template, Data) :-
   66    st_options(Options),
   67    render_reply(Template, Data, Options).
 reply_template(+Template:atom, +Data:dict, +Options:dict) is det
Reply with simple-template, providing simple-template options:
   83reply_template(Template, Data, Options) :-
   84    st_options(Config),
   85    Opts = Config.put(Options),
   86    render_reply(Template, Data, Opts).
 render_reply(+Template:atom, +Data:dict, +Options:dict) is det
Makes the template and sends the reply with text/html heading.
Arguments:
Template- The name of the template, ".html" not required
Data- Dict of keys and values used in the template
Options- Dict of options as described for simple-template
   95render_reply(Template, Data, Options) :-
   96    current_output(Out),
   97    format("Content-type: text/html~n~n"),
   98    st_render_file(sweb_templates(Template), Data, Out, Options).
 st_options(-Options:dict) is semidet
Arguments:
Options- Simple Template options from config
  103st_options(options{ encoding: Encoding,
  104                    extension: Extension,
  105                    cache: Cache,
  106                    strip: Strip,
  107                    frontend: Frontend,
  108                    undefined: Undefined}) :-
  109    get_config(st_encoding, Encoding),
  110    get_config(st_extension, Extension),
  111    get_config(st_cache, Cache),
  112    get_config(st_strip, Strip),
  113    get_config(st_frontend, Frontend),
  114    get_config(st_undefined, Undefined)