1:- module(st_render, [
    2    st_render_string/5, % +String, +Data, +Stream, +File, +Options
    3    st_render_file/4,   % +File, +Data, +Stream, +Options
    4    st_render_codes/5   % +Codes, +Data, +Stream, +File, +Options
    5]).

Template renderer

Turns template together with data into output. */

   12:- use_module(library(readutil)).   13:- use_module(library(error)).   14:- use_module(library(debug)).   15:- use_module(library(option)).   16
   17:- use_module(st_parse).   18:- use_module(st_expr).   19:- use_module(st_file).   20:- use_module(st_escape).   21:- use_module(st_funs).   22
   23% Default options for the renderer.
   24
   25default_options(_{
   26    encoding: utf8,
   27    extension: html,
   28    cache: false,
   29    strip: false,
   30    frontend: simple,
   31    undefined: error
   32}).
   33
   34% Merges the given options with
   35% default ones.
   36
   37merge_defaults(Options, Actual):-
   38    default_options(Defaults),
   39    merge_options(Options, Defaults, Actual).
 st_render_string(+String, +Data, +Stream, +File, +Options) is det
Renders given string with the given data into the stream.
   46st_render_string(String, Data, Stream, File, Options):-
   47    must_be(string, String),
   48    string_codes(String, Codes),
   49    merge_defaults(Options, ActualOptions),
   50    st_render_codes(Codes, Data, Stream, File, ActualOptions).
 st_render_file(+File, +Data, +Stream, +Options) is det
Renders given file with the given data into the stream.
   57st_render_file(File, Data, Stream, Options):-
   58    must_be(ground, File),
   59    merge_defaults(Options, ActualOptions),
   60    render_file(File, Data, Stream, ActualOptions).
 st_render_codes(+Codes, +Data, +Stream, +File) is det
Renders codes with the given data into the stream. File argument is used for resolving includes.
   67st_render_codes(Codes, Data, Stream, File, Options):-
   68    must_be(list, Codes),
   69    must_be(ground, File),
   70    merge_defaults(Options, ActualOptions),
   71    st_parse(Codes, Templ, ActualOptions),
   72    render_scope(Templ, Data, Stream, File, ActualOptions).
   73
   74render_file(File, Data, Stream, Options):-
   75    st_resolve(File, AbsFile, Options),
   76    template(AbsFile, Templ, Options),
   77    render_scope(Templ, Data, Stream, AbsFile, Options).
   78
   79% Reads template from file.
   80% Uses cached template when
   81% it is available.
   82
   83template(File, Templ, Options):-
   84    (   option(cache(true), Options)
   85    ->  (   st_cached(File, Templ)
   86        ->  true
   87        ;   read_file(File, Templ, Options),
   88            st_cache_put(File, Templ))
   89    ;   read_file(File, Templ, Options)).
   90
   91% Actually reads the template file.
   92
   93read_file(File, Template, Options):-
   94    option(encoding(Encoding), Options),
   95    read_file_to_codes(File, Codes, [encoding(Encoding)]),
   96    st_parse(Codes, Template, Options).
   97
   98% Renders escaped output.
   99% Example: {{ title }}.
  100
  101render_scope([Block|Blocks], Scope, Stream, File, Options):-
  102    Block = out(Expr), !,
  103    st_eval(Expr, Scope, Options, Value),
  104    st_write_escape(Stream, Value),
  105    render_scope(Blocks, Scope, Stream, File, Options).
  106
  107% Renders unescaped output.
  108% Example: {{- title }}.
  109
  110render_scope([Block|Blocks], Scope, Stream, File, Options):-
  111    Block = out_unescaped(Expr), !,
  112    st_eval(Expr, Scope, Options, Value),
  113    write(Stream, Value),
  114    render_scope(Blocks, Scope, Stream, File, Options).
  115
  116% Renders each loop with element variable.
  117% Example: {{ each items, item }}.
  118
  119render_scope([Block|Blocks], Scope, Stream, File, Options):-
  120    Block = each(Expr, Var, Nested), !,
  121    st_eval(Expr, Scope, Options, Values),
  122    (   is_list(Values)
  123    ->  ((  member(Value, Values),
  124            put_dict(Var, Scope, Value, NestScope),
  125            render_scope(Nested, NestScope, Stream, File, Options),
  126            fail) ; true),
  127        render_scope(Blocks, Scope, Stream, File, Options)
  128    ;   throw(error(expr_in_each_not_list(Expr)))).
  129
  130% Renders each loop with element and index variables.
  131% Example: {{ each items, item, i }}.
  132
  133render_scope([Block|Blocks], Scope, Stream, File, Options):-
  134    Block = each(Expr, Var, IVar, Nested), !,
  135    st_eval(Expr, Scope, Options, Values),
  136    (   is_list(Values)
  137    ->  Counter = counter(0),
  138        ((  member(Value, Values),
  139            arg(1, Counter, I0),
  140            I is I0 + 1,
  141            nb_setarg(1, Counter, I),
  142            put_dict(Var, Scope, Value, Tmp),
  143            put_dict(IVar, Tmp, I0, NestScope),
  144            render_scope(Nested, NestScope, Stream, File, Options),
  145            fail) ; true),
  146        render_scope(Blocks, Scope, Stream, File, Options)
  147    ;   throw(error(expr_in_each_not_list(Expr)))).
  148
  149% Renders each loop with element, index and length
  150% variables.
  151% Example: {{ each items, item, i, len }}.
  152
  153render_scope([Block|Blocks], Scope, Stream, File, Options):-
  154    Block = each(Expr, Var, IVar, LVar, Nested), !,
  155    st_eval(Expr, Scope, Options, Values),
  156    (   is_list(Values)
  157    ->  length(Values, Length),
  158        put_dict(LVar, Scope, Length, Tmp1),
  159        Counter = counter(0),
  160        ((  member(Value, Values),
  161            arg(1, Counter, I0),
  162            I is I0 + 1,
  163            nb_setarg(1, Counter, I),
  164            put_dict(Var, Tmp1, Value, Tmp2),
  165            put_dict(IVar, Tmp2, I0, NestScope),
  166            render_scope(Nested, NestScope, Stream, File, Options),
  167            fail) ; true),
  168        render_scope(Blocks, Scope, Stream, File, Options)
  169    ;   throw(error(expr_in_each_not_list(Expr)))).
  170
  171% Renders normal text blocks.
  172
  173render_scope([Block|Blocks], Scope, Stream, File, Options):-
  174    Block = text(Text), !,
  175    write(Stream, Text),
  176    render_scope(Blocks, Scope, Stream, File, Options).
  177
  178% Renders include block {{ include path/to/file }}.
  179
  180render_scope([Block|Blocks], Scope, Stream, File, Options):-
  181    Block = include(Path), !,
  182    st_resolve_include(Path, File, AbsFile),
  183    render_file(AbsFile, Scope, Stream, Options),
  184    render_scope(Blocks, Scope, Stream, File, Options).
  185
  186% Renders include with specific scope variable.
  187% Example: {{ include path/to/file, variable }}.
  188
  189render_scope([Block|Blocks], Scope, Stream, File, Options):-
  190    Block = include(Path, Var), !,
  191    st_resolve_include(Path, File, AbsFile),
  192    st_eval(Var, Scope, Options, Value),
  193    render_file(AbsFile, Value, Stream, Options),
  194    render_scope(Blocks, Scope, Stream, File, Options).
  195
  196% Renders dynamic include block.
  197% Example: {{ dynamic_include file }}.
  198
  199render_scope([Block|Blocks], Scope, Stream, File, Options):-
  200    Block = dynamic_include(FileVar), !,
  201    st_eval(FileVar, Scope, Options, Path),
  202    st_resolve_include(Path, File, AbsFile),
  203    render_file(AbsFile, Scope, Stream, Options),
  204    render_scope(Blocks, Scope, Stream, File, Options).
  205
  206% Renders dynamic include with specific scope variable.
  207% Example: {{ dynamic_include file variable }}.
  208
  209render_scope([Block|Blocks], Scope, Stream, File, Options):-
  210    Block = dynamic_include(FileVar, Var), !,
  211    st_eval(FileVar, Scope, Options, Path),
  212    st_resolve_include(Path, File, AbsFile),
  213    st_eval(Var, Scope, Options, Value),
  214    render_file(AbsFile, Value, Stream, Options),
  215    render_scope(Blocks, Scope, Stream, File, Options).
  216
  217% Renders slot. The content for the slot must be given
  218% in the upper scope.
  219
  220render_scope([Block|Blocks], Scope, Stream, File, Options):-
  221    Block = slot, !,
  222    (   del_dict('_slot', Options, slot(Content, SlotScope), PassOptions)
  223    ->  render_scope(Content, SlotScope, Stream, File, PassOptions),
  224        render_scope(Blocks, Scope, Stream, File, PassOptions)
  225    ;   throw(error(no_content_for_slot(File)))).
  226
  227% Renders block. The block content is passed to the block
  228% with the current scope preserved.
  229
  230render_scope([Block|Blocks], Scope, Stream, File, Options):-
  231    Block = block(Path, Children), !,
  232    st_resolve_include(Path, File, AbsFile),
  233    Slot = slot(Children, Scope),
  234    put_dict('_slot', Options, Slot, BlockOptions),
  235    render_file(AbsFile, Scope, Stream, BlockOptions),
  236    render_scope(Blocks, Scope, Stream, File, Options).
  237
  238% Renders block. The block content is passed to the block
  239% and the scope for the block is selected by an expression.
  240
  241render_scope([Block|Blocks], Scope, Stream, File, Options):-
  242    Block = block(Path, Var, Children), !,
  243    st_resolve_include(Path, File, AbsFile),
  244    st_eval(Var, Scope, Options, Value),
  245    Slot = slot(Children, Scope),
  246    put_dict('_slot', Options, Slot, BlockOptions),
  247    render_file(AbsFile, Value, Stream, BlockOptions),
  248    render_scope(Blocks, Scope, Stream, File, Options).
  249
  250% Renders conditional block.
  251% Example: {{ if Cond }} a {{ else }} b {{ end }}
  252
  253render_scope([Block|Blocks], Scope, Stream, File, Options):-
  254    Block = if(Cond, True, False), !,
  255    st_eval(Cond, Scope, Options, CondValue),
  256    (   (CondValue = 0 ; CondValue = false)
  257    ->  render_scope(False, Scope, Stream, File, Options)
  258    ;   render_scope(True, Scope, Stream, File, Options)),
  259    render_scope(Blocks, Scope, Stream, File, Options).
  260
  261render_scope([Block|_], _, _, _, _):-
  262    throw(error(unknown_block(Block))).
  263
  264render_scope([], _, _, _, _)