View source with raw 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-2016, 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
   47:- register_renderer(table, "Render data as tables").

SWISH table renderer

Render table-like data. */

 term_rendering(+Term, +Vars, +Options)//
Renders Term as a table. This renderer recognises several representations of table-like data:
A list of terms of equal arity
A list of lists of equal length
To be done
- : recognise more formats
   64term_rendering(Term, _Vars, Options) -->
   65	{ is_list_of_dicts(Term, _Rows, ColNames), !,
   66	  partition(is_header, Options, _HeaderOptions, Options1)
   67	}, !,
   68	html(div([ style('display:inline-block'),
   69		   'data-render'('List of terms as a table')
   70		 ],
   71		 [ table(class('render-table'),
   72			 [ \header_row(ColNames),
   73			   \rows(Term, Options1)
   74			 ])
   75		 ])).
   76term_rendering(Term, _Vars, Options) -->
   77	{ is_list_of_terms(Term, _Rows, _Cols),
   78	  header(Term, Header, Options, Options1)
   79	}, !,
   80	html(div([ style('display:inline-block'),
   81		   'data-render'('List of terms as a table')
   82		 ],
   83		 [ table(class('render-table'),
   84			 [ \header_row(Header),
   85			   \rows(Term, Options1)
   86			 ])
   87		 ])).
   88term_rendering(Term, _Vars, Options) -->
   89	{ is_list_of_lists(Term, _Rows, _Cols),
   90	  header(Term, Header, Options, Options1)
   91	}, !,
   92	html(div([ style('display:inline-block'),
   93		   'data-render'('List of lists as a table')
   94		 ],
   95		 [ table(class('render-table'),
   96			 [ \header_row(Header),
   97			   \rows(Term, Options1)
   98			 ])
   99		 ])).
  100
  101rows([], _) --> [].
  102rows([H|T], Options) -->
  103	{ cells(H, Cells) },
  104	html(tr(\row(Cells, Options))),
  105	rows(T, Options).
  106
  107row([], _) --> [].
  108row([H|T], Options) -->
  109	html(td(\term(H, Options))),
  110	row(T, Options).
  111row([H|T], Options) -->
  112	html(td(\term(H, []))),
  113	row(T, Options).
  114
  115cells(Row, Cells) :-
  116	is_list(Row), !,
  117	Cells = Row.
  118cells(Row, Cells) :-
  119	is_dict(Row), !,
  120	dict_pairs(Row, _Tag, Pairs),
  121	pairs_values(Pairs, Cells).
  122cells(Row, Cells) :-
  123	compound(Row),
  124	compound_name_arguments(Row, _, Cells).
 header(+Table, -Header:list(Term), +Options, -RestOptions) is semidet
Compute the header to use. Fails if a header is specified but does not match.
  131header(_, _, Options0, Options) :-
  132	\+ option(header(_), Options0), !,
  133	Options = Options0.
  134header([Row|_], ColHead, Options0, Options) :-
  135	partition(is_header, Options0, HeaderOptions, Options),
  136	member(HeaderOption, HeaderOptions),
  137	header(HeaderOption, Header),
  138	generalise(Row, GRow),
  139	generalise(Header, GRow), !,
  140	header_list(Header, ColHead).
  141
  142is_header(0) :- !, fail.
  143is_header(header(_)).
  144is_header(header=_).
  145
  146header(header(H), H).
  147header(header=H, H).
  148
  149generalise(List, VList) :-
  150	is_list(List), !,
  151	length(List, Len),
  152	length(VList0, Len),
  153	VList = VList0.
  154generalise(Compound, VCompound) :-
  155	compound(Compound), !,
  156	compound_name_arity(Compound, Name, Arity),
  157	compound_name_arity(VCompound0, Name, Arity),
  158	VCompound = VCompound0.
  159
  160header_list(List, List) :- is_list(List), !.
  161header_list(Compound, List) :-
  162	Compound =.. [_|List].
 header_row(ColNames:list)// is det
Include a header row if ColNames is not unbound.
  169header_row(ColNames) -->
  170	{ var(ColNames) }, !.
  171header_row(ColNames) -->
  172	html(tr(class(hrow), \header_columns(ColNames))).
  173
  174header_columns([]) --> [].
  175header_columns([H|T]) -->
  176	html(th(\term(H, []))),
  177	header_columns(T).
 is_list_of_terms(@Term, -Rows, -Cols) is semidet
Recognises a list of terms with the same functor and non-zero ariry.
  185is_list_of_terms(Term, Rows, Cols) :-
  186	is_list(Term), Term \== [],
  187	length(Term, Rows),
  188	maplist(is_term_row(_Name, Cols), Term),
  189	Cols > 0.
  190
  191is_term_row(Name, Arity, Term) :-
  192	compound(Term),
  193	compound_name_arity(Term, Name, Arity).
 is_list_of_dicts(@Term, -Rows, -ColNames) is semidet
True when Term is a list of Rows dicts, each holding ColNames as keys.
  200is_list_of_dicts(Term, Rows, ColNames) :-
  201	is_list(Term), Term \== [],
  202	length(Term, Rows),
  203	maplist(is_dict_row(ColNames), Term).
  204
  205is_dict_row(ColNames, Dict) :-
  206	is_dict(Dict),
  207	dict_keys(Dict, ColNames).
 is_list_of_lists(@Term, -Rows, -Cols) is semidet
Recognise a list of lists of equal length.
  213is_list_of_lists(Term, Rows, Cols) :-
  214	is_list(Term), Term \== [],
  215	length(Term, Rows),
  216	maplist(is_list_row(Cols), Term),
  217	Cols > 0.
  218
  219is_list_row(Length, Term) :-
  220	is_list(Term),
  221	length(Term, Length)