1:- module(wl_table, [wl_direct_table//1,
2 wl_table//2]).
10:- use_module(library(http/html_write)). 11:- use_module(library(option)). 12:- use_module(library(http/http_wrapper), [http_current_request/1]).
head(List)
, outputs an HTML table representing
the data.
Upon encountering a head(List)
term the elements of List are
output in th tags.
Bare lists are output as td tags
fails silently if it can't parse the data
The generated html sets the class of body rows to even or odd alternately to allow alternate row styling */
31wl_direct_table([]) --> []. 32wl_direct_table([H|T]) --> 33 html([table(\direct_table_body(1, [H|T]))]). 34 35direct_table_body(_, []) --> []. 36direct_table_body(RowNum, [H|T]) --> 37 { 38 is_list(H), 39 NewRowNum is RowNum + 1, 40 ( 0 =:= RowNum mod 2 41 -> EvenOdd = even 42 ; EvenOdd = odd 43 ) 44 }, 45 html(tr(class=EvenOdd, \direct_table_cells(td, H))), 46 direct_table_body(NewRowNum, T). 47direct_table_body(RowNum, [head(HR)|T]) --> 48 direct_header_row(HR), 49 direct_table_body(RowNum, T). 50 51direct_header_row([]) --> []. 52direct_header_row([H|T]) --> 53 html(tr([\direct_table_cells(th, [H|T])])). 54 55direct_table_cells(_, []) --> []. 56direct_table_cells(Tag, [H|T]) --> 57 { 58 Cell =.. [Tag, H] 59 }, 60 html([Cell]), 61 direct_table_cells(Tag, T). 62 63:- html_meta wl_table( , , , ). 64 65:- predicate_options(wl_table/4, 2, 66 [ header(goal), 67 columns(list), 68 rows(list) ]).
DataGen is expected to be an arity 3 predicate
my_data_gen(Key, Column, Value)
wl_table outputs an HTML table showing the data for all possible solutions to Key, Column
Note that if you want the keys you'll have to make sure the key is included as a column name.
Example, where my_key is the name of the primary key and my_data/3 is the underlying data.
... \wl_table(table_cells, []) ... table_cells(Key, my_key, Key) :- my_data(Key, _, _). table_cells(Key, Column, Value) :- my_data(Key, Column, Value).
The generated html sets the class of body rows to even or odd alternately to allow alternate row styling
fails silently if given invalid arguments
Options:
goal(Column, Label)
if the option is missing, the column ID's are used
as labels.
if the option header(none)
is provided, no headers are
produced
Note that you'll have to specify the module explicitly124wl_table(DataGen, OptionListIn) --> 125 { 126 meta_options(is_meta, OptionListIn, OptionList), 127 option(header(HeaderGoal) , OptionList, = ), 128 option(columns(OptionColumns), OptionList, true), 129 option(rows(OptionRows), OptionList, true), 130 findall(Key-Column, call(DataGen, Key, Column, _), Pairs), 131 pairs_keys_values(Pairs, DupKeyList, DupColumnList), 132 ( is_list(OptionColumns) -> 133 ColumnList = OptionColumns ; 134 list_to_set(DupColumnList, ColumnList) 135 ), 136 ( is_list(OptionRows) -> 137 KeyList = OptionRows ; 138 list_to_set(DupKeyList, KeyList) 139 ) 140 }, 141 html([table([tr(\table_header(HeaderGoal, ColumnList)), 142 \table_body(1, KeyList, ColumnList, DataGen)])]). 143 144:- html_meta table_header( , ). 145 146table_header(X, _) --> 147 { 148 strip_module(X, _, none) 149 }, 150 [],!. 151table_header(_HeaderGoal, []) --> []. 152table_header(HeaderGoal, [H|T]) --> 153 { 154 call(HeaderGoal, H, Label) 155 ; 156 Label = H 157 }, 158 html([th(Label), \table_header(HeaderGoal, T)]). 159 160:- html_meta table_body( , , , ). 161 162table_body(_RowNum, [], _ColumnList, _DataGen) --> []. 163table_body(RowNum, [H|T], ColumnList, DataGen) --> 164 { 165 NewRowNum is RowNum + 1, 166 ( 0 =:= RowNum mod 2 167 -> EvenOdd = even 168 ; EvenOdd = odd 169 ) 170 }, 171 html(tr(class=EvenOdd, \table_row(H, ColumnList, DataGen))), 172 table_body(NewRowNum, T, ColumnList, DataGen). 173 174:- html_meta table_row( , ). 175 176table_row(_, [], _) --> []. 177table_row(Key, [H|T], DataGen) --> 178 { 179 call(DataGen, Key, H, Value) 180 }, 181 html(td(Value)), 182 table_row(Key, T, DataGen). 183table_row(Key, [H|T], DataGen) --> 184 { 185 \+ call(DataGen, Key, H, _Value) 186 }, 187 html(td('')), 188 table_row(Key, T, DataGen). 189 190 191% 192% which options require module resolution 193% 194is_meta(header)
Utilities for laying out HTML tables
These are oriented towards presenting tables of data, not towards controlling layout
*/