View source with formatted comments or as raw
    1/*  Part of SWISH
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2014-2020, VU University Amsterdam
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(swish_render_table,
   36          [ term_rendering//3                   % +Term, +Vars, +Options
   37          ]).   38:- use_module(library(apply)).   39:- use_module(library(lists)).   40:- use_module(library(pairs)).   41:- use_module(library(dicts)).   42:- use_module(library(option)).   43:- use_module(library(http/html_write)).   44:- use_module(library(http/term_html)).   45:- use_module('../render').   46:- use_module(library(error)).   47
   48:- register_renderer(table, "Render data as tables").   49
   50/** <module> SWISH table renderer
   51
   52Render table-like data.
   53*/
   54
   55%!  term_rendering(+Term, +Vars, +Options)//
   56%
   57%   Renders Term as  a  table.   This  renderer  recognises  several
   58%   representations of table-like data:
   59%
   60%     $ A list of dicts holding the same keys
   61%     $ A list of terms of equal arity :
   62%     $ A list of lists of equal length :
   63%
   64%   Options:
   65%
   66%     - header(+Header)
   67%     Specify the header row. This is either a row whose number of
   68%     columns must match the columns in the table or the atom
   69%     `first_row`, which causes the first row to be used as header.
   70%     Multiple `header` options may be present.  The first matching
   71%     row is used, next the `first_row` value and if nothing matches
   72%     no header is displayed.
   73%     - align(+Alignment)
   74%     Specify the column alignment as one of `l`, `c` or `r` or the
   75%     more verbose `left`, `center`, `right`.  Default is `left`,
   76%     except for columns holding only integers.
   77%
   78%   @tbd: recognise more formats
   79
   80term_rendering(Term, _Vars, Options) -->
   81    { is_list_of_dicts(Term, _NRows, ColNames),
   82      !,
   83      partition(is_header, Options, _HeaderOptions, Options1),
   84      fix_op_priority(Options1, Options2),
   85      column_alignment(Term, Options2, Options3)
   86    },
   87    !,
   88    html(div([ style('display:inline-block'),
   89               'data-render'('List of dicts as a table')
   90             ],
   91             [ table(class('render-table'),
   92                     [ \header_row(ColNames),
   93                       \rows(Term, Options3)
   94                     ])
   95             ])).
   96term_rendering(Term, _Vars, Options) -->
   97    { is_list_of_terms(Term, _NRows, _NCols),
   98      header(Term, Rows, Header, Options, Options1),
   99      fix_op_priority(Options1, Options2),
  100      column_alignment(Rows, Options2, Options3)
  101    },
  102    !,
  103    html(div([ style('display:inline-block'),
  104               'data-render'('List of terms as a table')
  105             ],
  106             [ table(class('render-table'),
  107                     [ \header_row(Header),
  108                       \rows(Rows, Options3)
  109                     ])
  110             ])).
  111term_rendering(Term, _Vars, Options) -->
  112    { is_list_of_lists(Term, _NRows, _MCols),
  113      header(Term, Rows, Header, Options, Options1),
  114      fix_op_priority(Options1, Options2),
  115      column_alignment(Rows, Options2, Options3)
  116    },
  117    !,
  118    html(div([ style('display:inline-block'),
  119               'data-render'('List of lists as a table')
  120             ],
  121             [ table(class('render-table'),
  122                     [ \header_row(Header),
  123                       \rows(Rows, Options3)
  124                     ])
  125             ])).
  126
  127%!  fix_op_priority(+Options0, -Options)
  128%
  129%   Bindings a normally printed with priority  699 (the right hand limit
  130%   for =/2). This is rather meaningless   for  tables. We therefore map
  131%   699  to  1200.  We  should  preserve    a   user  value  given  with
  132%   use_rendering/2, but we  cannot  distinguish   this  from  higher up
  133%   defaults.
  134
  135fix_op_priority(Options0, Options) :-
  136    select_option(priority(699), Options0, Options1),
  137    !,
  138    Options = [priority(1200)|Options1].
  139fix_op_priority(Options, Options).
  140
  141
  142rows([], _) --> [].
  143rows([H|T], Options) -->
  144    { cells(H, Cells),
  145      option(align(Alignments), Options)
  146    },
  147    html(tr(\row(Cells, Alignments, Options))),
  148    rows(T, Options).
  149
  150row([], [], _) --> [].
  151row([H|T], [AH|AT], Options) -->
  152    { functor(AH, Align, _),
  153      (   align_attrs(Align, Atts)
  154      ->  true
  155      ;   domain_error(alignment, Align)
  156      ),
  157      (   AH =.. [_,Format]
  158      ->  Options1 = [format(Format)|Options]
  159      ;   Options1 = Options
  160      )
  161    },
  162    html(td(Atts, \term(H, Options1))),
  163    row(T, AT, Options).
  164
  165align_attrs(left, []).
  166align_attrs(right,  [style('text-align:right')]).
  167align_attrs(center, [style('text-align:center')]).
  168align_attrs(l, Attrs) :- align_attrs(left, Attrs).
  169align_attrs(r, Attrs) :- align_attrs(right, Attrs).
  170align_attrs(c, Attrs) :- align_attrs(center, Attrs).
  171
  172cells(Row, Cells) :-
  173    is_list(Row),
  174    !,
  175    Cells = Row.
  176cells(Row, Cells) :-
  177    is_dict(Row),
  178    !,
  179    dict_pairs(Row, _Tag, Pairs),
  180    pairs_values(Pairs, Cells).
  181cells(Row, Cells) :-
  182    compound(Row),
  183    compound_name_arguments(Row, _, Cells).
  184
  185		 /*******************************
  186		 *            ALIGNMENT		*
  187		 *******************************/
  188
  189column_alignment([Row|_], Options0, Options) :-
  190    partition(is_align, Options0, AlignOptions, Options1),
  191    member(AlignOption, AlignOptions),
  192    align(AlignOption, Align),
  193    generalise(Row, GRow),
  194    generalise(Align, GRow),
  195    !,
  196    cells(Align, List),
  197    Options = [align(List)|Options1].
  198column_alignment(Rows, Options0, Options) :-
  199    partition(is_align, Options0, _AlignOptions, Options1),
  200    transpose_table(Rows, Cols),
  201    maplist(col_alignment, Cols, Alignments),
  202    Options = [align(Alignments)|Options1].
  203
  204is_align(0) :- !, fail.
  205is_align(align(_)).
  206is_align(align=_).
  207
  208align(align(H), H).
  209align(align=H, H).
  210
  211
  212
  213%!  transpose_table(+Table, -Columns)
  214%
  215%   Transpose the table to a list of   columns, each column being a list
  216%   of cells.
  217
  218transpose_table([], Cols) :-
  219    maplist(=([]), Cols).
  220transpose_table([Row|Rows], Cols) :-
  221    cells(Row, Cells),
  222    maplist(mkcol, Cells, Cols, Cols1),
  223    transpose_table(Rows, Cols1).
  224
  225mkcol(Cell, [Cell|T], T).
  226
  227col_alignment(Col, right('~D')) :-
  228    maplist(integer, Col),
  229    !.
  230col_alignment(Col, Align) :-
  231    maplist(non_rational_number, Col),
  232    !,
  233    (   maplist(nat_digits, Col, Digits),
  234        max_list(Digits, N),
  235        N < 6
  236    ->  format(atom(Fmt), '~~~df', [N]),
  237        Align = right(Fmt)
  238    ;   abs_min_max(Col, Min, Max),
  239        min_max_format(Min, Max, Align)
  240    ).
  241col_alignment(_, left).
  242
  243non_rational_number(X) :-
  244    (   integer(X)
  245    ->  true
  246    ;   float(X)
  247    ).
  248
  249abs_min_max([], 0, 0).
  250abs_min_max([H|T], Min, Max) :-
  251    abs_min_max(T, H, Min, H, Max).
  252
  253abs_min_max([], Min, Min, Max, Max).
  254abs_min_max([H|T], Min0, Min, Max0, Max) :-
  255    Min1 is min(abs(H), Min0),
  256    Max1 is max(abs(H), Max0),
  257    abs_min_max(T, Min1, Min, Max1, Max).
  258
  259min_max_format(Min, Max, right(Fmt)) :-
  260    (   Min =:= 0.0
  261    ;   Max/Min < 100 000
  262    ),
  263    !,
  264    Digits is round(max(2, 6-log10(Max))),
  265    format(atom(Fmt), '~~~df', [Digits]).
  266min_max_format(_, _, left('~q')).
  267
  268%!  nat_digits(+Number, -Digits)
  269%
  270%   Determine the number of digits that   should  naturally be displayed
  271%   for a number.
  272
  273nat_digits(F, N) :-
  274    integer(F),
  275    !,
  276    N = 0.
  277nat_digits(F, N) :-
  278    format(string(S), '~q', [F]),
  279    (   (   sub_string(S, Start, _, _, "0000")
  280        ;   sub_string(S, Start, _, _, "9999")
  281        ),
  282        !,
  283        sub_string(S, SDot, _, _, "."),
  284        N is Start - SDot - 1
  285    ;   sub_string(S, _, _, ADot, ".")
  286    ->  (   sub_string(S, _, _, 0, "0")
  287        ->  N = 0
  288        ;   N = ADot
  289        )
  290    ).
  291
  292
  293
  294		 /*******************************
  295		 *            HEADER		*
  296		 *******************************/
  297
  298%!  header(+Table, -Rows, -Header:list(Term), +Options, -RestOptions) is semidet.
  299%
  300%   Compute the header to use. Fails if   a  header is specified but
  301%   does not match.
  302
  303header(Rows, Rows, _, Options, Options) :-
  304    \+ option(header(_), Options),
  305    !.
  306header(Rows, TRows, ColHead, Options0, Options) :-
  307    Rows = [Row|TRows0],
  308    partition(is_header, Options0, HeaderOptions, Options),
  309    (   member(HeaderOption, HeaderOptions),
  310        header(HeaderOption, Header),
  311        Header \== first_row,
  312        generalise(Row, GRow),
  313        generalise(Header, GRow)
  314    ->  header_list(Header, ColHead),
  315        TRows = Rows
  316    ;   member(HeaderOption, HeaderOptions),
  317        header(HeaderOption, Header),
  318        Header == first_row
  319    ->  header_list(Row, ColHead),
  320        TRows = TRows0
  321    ),
  322    !.
  323
  324is_header(0) :- !, fail.
  325is_header(header(_)).
  326is_header(header=_).
  327
  328header(header(H), H).
  329header(header=H, H).
  330
  331generalise(List, VList) :-
  332    is_list(List),
  333    !,
  334    length(List, Len),
  335    length(VList0, Len),
  336    VList = VList0.
  337generalise(Compound, VCompound) :-
  338    compound(Compound),
  339    !,
  340    compound_name_arity(Compound, Name, Arity),
  341    compound_name_arity(VCompound0, Name, Arity),
  342    VCompound = VCompound0.
  343
  344header_list(List, List) :- is_list(List), !.
  345header_list(Compound, List) :-
  346    Compound =.. [_|List].
  347
  348
  349%!  header_row(ColNames:list)// is det.
  350%
  351%   Include a header row  if ColNames is not unbound.
  352
  353header_row(ColNames) -->
  354    { var(ColNames) },
  355    !.
  356header_row(ColNames) -->
  357    html(tr(class(hrow), \header_columns(ColNames))).
  358
  359header_columns([]) --> [].
  360header_columns([H|T]) -->
  361    html(th(\term(H, []))),
  362    header_columns(T).
  363
  364
  365%!  is_list_of_terms(@Term, -Rows, -Cols) is semidet.
  366%
  367%   Recognises a list of terms with   the  same functor and non-zero
  368%   arity.
  369
  370is_list_of_terms(Term, Rows, Cols) :-
  371    is_list(Term), Term \== [],
  372    length(Term, Rows),
  373    maplist(is_term_row(_Name, Cols), Term),
  374    Cols > 0.
  375
  376is_term_row(Name, Arity, Term) :-
  377    compound(Term),
  378    compound_name_arity(Term, Name, Arity).
  379
  380%!  is_list_of_dicts(@Term, -Rows, -ColNames) is semidet.
  381%
  382%   True when Term is a list of Rows dicts, each holding ColNames as
  383%   keys.
  384
  385is_list_of_dicts(Term, Rows, ColNames) :-
  386    is_list(Term), Term \== [],
  387    length(Term, Rows),
  388    maplist(is_dict_row(ColNames), Term).
  389
  390is_dict_row(ColNames, Dict) :-
  391    is_dict(Dict),
  392    dict_keys(Dict, ColNames).
  393
  394%!  is_list_of_lists(@Term, -Rows, -Cols) is semidet.
  395%
  396%   Recognise a list of lists of equal length.
  397
  398is_list_of_lists(Term, Rows, Cols) :-
  399    is_list(Term), Term \== [],
  400    length(Term, Rows),
  401    maplist(is_list_row(Cols), Term),
  402    Cols > 0.
  403
  404is_list_row(Length, Term) :-
  405    is_list(Term),
  406    length(Term, Length)