1:- module(print_table, [
    2    force_print_table/1,
    3    print_table/1, 
    4    print_table/2, 
    5    print_table/3, 
    6    print_table/4, 
    7    print_table/5,
    8    print_table/6
    9   ]).

Formats and prints a table on the terminal screen

The Data in the table is represented as a list of dicts, where each dict represents a Row. The Keys in the dict (i.e. Row) correspond to a Column. The Value associated to a Key, represents the contents of a Cell. It is wrapped to fit the Width of the Column (the wrapping alogyrithm alows a text to break at whitespace and hyphens, see wrap_text/3).

The formatting of the Table (i.e. Width and Height of Rows and Collumns) is automatically calculated. The heuristic used is prioritize the columns with the most content to use the largest share of available width (i.e minimize the hight of a row). If the content cannot be fit within the available width an Exception is raised.

The formatting and rendering of the Table can be adapted in a number of ways: Use a subset of available Columns, and define the order in which they are presented Define the formatting of an individual Column (e.g width, alignmet, header, ...) The Caption presented with the Table The visual style of the Table (currently sypported, default, unicode, mysql, github) The maximum Width the table can use.

print_table/6 allow the user to set all parrameters. The print_table/N with fewer arguments implement defaults.

Example

:- Data = [_{a:11,b:0.001,c:13},_{a:21,b:2.12,c:23},_{a:31,b:12.1111,c:33}],
print_table(Data,[b,c,a],_{b:_{align:right,format:"~2f"}},"Table",mysql,30).

%       Table (3 records)
%      +-------+----+----+
%      |     b | c  | a  |
%      +-------+----+----+
%      |  0.00 | 13 | 11 |
%      |  2.12 | 23 | 21 |
%      | 12.11 | 33 | 31 |
%      +-------+----+----+
author
- Joost Geurts
license
- MIT License */
   50:- use_module(library(wrap_text)).   51
   52:- use_module(library(clpfd)).   53:- use_module(library(debug)).   54:- debug(print_table).   55:- debug(print_table,"print_table pack loaded",[]).   56
   57%:- debug(print_table_style).
   58%:- debug(print_table_format).
   59%:- debug(print_table_label).
   60% :- debug(print_table_wrap).
   61% :- debug(print_table_size).
   62
   63
   64cell_template(cell{key:_, classes:[],style:default,format:"",content:"",column:_,row:_,
   65    width:_,height:_,cwidth:_,cheight:_,
   66    align:left, padding_left:0, padding_right:0,
   67    border_left:"",border_right:"",border_top:"",border_bottom:"",
   68    border_top_left:"",border_top_right:"",border_bottom_left:"",border_bottom_right:""}).
   69
   70cell_style(default, stylesheet{
   71    header :        _{align:center,border_bottom:"-",border_bottom_right:" "},
   72    first_row :     _{},
   73    last_row :      _{},
   74    first_column :  _{},
   75    last_column :   _{},
   76    default :       _{padding_left:1, border_right:" ",padding_right:1}
   77    }).
   78
   79cell_style(mysql, stylesheet{
   80    header :        _{align:center,border_top:"-",border_bottom:"-",border_top_left:"+",border_bottom_left:"+"},
   81    first_row :     _{},
   82    last_row :      _{border_bottom:"-",border_bottom_left:"+"},
   83    first_column :  _{},
   84    last_column :   _{border_right:"|",border_top_right:"+",border_bottom_right:"+"},
   85    default :       _{border_left:"|",padding_left:1, padding_right:1}
   86    }).
   87
   88cell_style(unicode, stylesheet{
   89    header :        _{align:center,border_top:"─",border_top_left:"┌"},
   90    first_row :     _{border_top:""},
   91    last_row :      _{border_bottom:"─",border_bottom_left:"┴"},
   92    first_column :  _{border_bottom_left:"└"},
   93    last_column :   _{border_right:"│",border_top_right:"┐",border_bottom_right:"┘"},
   94    default :       _{border_bottom:"─",border_left:"│",border_bottom_left:"┼",padding_left:1, padding_right:1}
   95    }).
   96
   97cell_style(github, stylesheet{
   98    header :        _{align:center,border_left:"|",border_bottom_left:"|",border_bottom:"-"},
   99    first_row :     _{},
  100    last_row :      _{},
  101    first_column :  _{},
  102    last_column :   _{border_right:"|"},
  103    default :       _{border_left:"|",padding_left:1, padding_right:1}
  104    }).
  105
  106force_print_table(Data) :-
  107    dicts_to_same_keys(Data, dict_fill(null), CData),
  108    dicts_same_keys(CData,Keys),
  109    ColumnsSpec = _{},
  110    Caption = "Table ",
  111    Style = default,
  112    MaxWidth is 5000,
  113    print_table(Data,Keys,ColumnsSpec,Caption,Style,MaxWidth).
 print_table(+Data:list(dict)) is det
 print_table(+Data:list(dict), +Keys:list(atom)) is det
 print_table(+Data:list(dict), +Keys:list(atom), +ColumnsSpec:dict) is det
 print_table(+Data:list(dict), +Keys:list(atom), +ColumnsSpec:dict, +Caption:string) is det
 print_table(+Data:list(dict), +Keys:list(atom), +ColumnsSpec:dict, +Caption:string, +Style:atom) is det
 print_table(+Data:list(dict), +Keys:list(atom), +ColumnsSpec:dict, +Caption:string, +Style:atom, +MaxWidth:integer) is det
  145print_table(Data) :-
  146    dicts_to_same_keys(Data,dict_fill(null),NData),
  147    dicts_same_keys(NData,Keys),
  148    print_table(Data,Keys).
  149
  150print_table(Data,Keys) :-
  151    ColumnsSpec = _{},
  152    print_table(Data,Keys,ColumnsSpec).
  153
  154print_table(Data,Keys,ColumnsSpec) :-
  155    Caption = "Table ",
  156    print_table(Data,Keys,ColumnsSpec,Caption).
  157
  158print_table(Data,Keys,ColumnsSpec,Caption) :-
  159    Style = default,
  160    print_table(Data,Keys,ColumnsSpec,Caption,Style).
  161
  162print_table(Data,Keys,ColumnsSpec,Caption,Style) :-
  163    tty_size(_,TerminalWidth),
  164    MaxWidth is TerminalWidth - 2,
  165    print_table(Data,Keys,ColumnsSpec,Caption,Style,MaxWidth).
  166
  167print_table(Data,Keys,ColumnsSpec,Caption,Style,MaxWidth) :-
  168    must_be(list(dict),Data),
  169    must_be(list(atom),Keys),
  170    must_be(dict,ColumnsSpec),
  171    must_be(positive_integer,MaxWidth),
  172    add_row_number(Data,Data1),
  173    normalise_table(Keys,Data1,NKeys,NData),
  174    catch_with_backtrace(
  175        format_table(NKeys,NData,Style,ColumnsSpec,MaxWidth,Table),Error,print_message(error, Error)),
  176    print_message(informational,print_table(table(Table,Caption,MaxWidth))).
  177
  178
  179add_row_number(Records,NRecords) :- 
  180    add_row_number(Records,1,NRecords).
  181
  182add_row_number([],_,[]) :- !. 
  183add_row_number([Record|Records],N,[NRecord|NRecords]) :-
  184    NRecord = Record.put(row_number,N),
  185    NN is N + 1,
  186    add_row_number(Records,NN,NRecords).
 normalise_table(Keys, Table, NTable)
ensures Keys and Data are defined
  191normalise_table(Keys,Data,NKeys,NData) :-
  192    dicts_slice(Keys,Data,SlicedData),
  193    dicts_to_same_keys(SlicedData,dict_fill(null),NData),
  194    dicts_same_keys(NData,KeysPresent),
  195    findall(Key,(member(Key,Keys),member(Key,KeysPresent)),NKeys).
 format_table(+Keys:list(atom), +Data:list(dict), +Style:atom, +ColumnsSpec:dict, +MaxWidth:int, -Table:list(list(dict))) is det
Formats a Table within the given space constraints defined by MaxWidth
  199format_table(Keys,Data,Style,ColumnsSpec,MaxWidth,Table) :-
  200    pre_process_table(Keys,Data,ColumnsSpec,Table0),
  201    apply_style(Style,ColumnsSpec,Table0,Table1),
  202    size_columns(Table1,MaxWidth,Table),
  203    forall(member(Row,Table),
  204        (
  205            findall(CellSpec,(member(Cell,Row),format(atom(CellSpec),"(~w,~w)",[Cell.width,Cell.height])),CellSpecs),
  206            debug(print_table_size,"~w",[CellSpecs])
  207        )).
  208
  209%%  size_columns(+Rows,+MaxWidth,-NRows) is det.
  210%   For each column selects the cells that are most excessive in terms of necessary resources
  211%   Calculate the necessary width for each column (whilte not exceeding MaxWidth) to satistfy these requirements, 
  212%   noting that the less excesive cells will naturually fit.
  213%   @throws goal_failed If Rows cannot be fitted within MaxWidth x MaxHeight
  214size_columns(Rows,MaxWidth,NRows) :-
  215    transpose(Rows,Columns),
  216    compute_column_widths(Columns,ColSpecs),
  217    Height in 0..10000,
  218    set_equal_value(height,ColSpecs,Height),
  219    cell_widths(ColSpecs,CellWidths),
  220    sum(CellWidths,#=,TableWidth),
  221    TableWidth #=< MaxWidth,
  222    label([Height]),
  223    label_cells(ColSpecs),
  224    set_column_widths(Columns,ColSpecs,NColumns),
  225    transpose(NColumns,NRows),!.
  226
  227size_columns(Rows,MaxWidth,_) :-
  228    throw(error(insufficient_width(Rows,MaxWidth),_)).
  229
  230compute_column_widths([],[]).
  231compute_column_widths([Column|Columns],[ColSpec|ColSpecs]) :-
  232    compute_column_width(Column,ColSpec),
  233    compute_column_widths(Columns,ColSpecs).
  234    
  235compute_column_width(Column,_{key:Key,width:Width,height:Height}) :-
  236    Column = [C0|_],
  237    Width = C0.width,
  238    % findall(W,(member(C0,Column),W = C0.width, number(Width)),Ws),max_list(Ws,Width0),
  239    % (nonvar(Width0) -> Width = Width0 ; Width = _),
  240    sort(length,@>=,Column,[C1|_]), MaxLength = C1.length, Key = C1.key,
  241    sort(min_width,@>=,Column,[C2|_]), MinWidth = C2.min_width,
  242    sort(padding_left,@>=,Column,[C3|_]), MaxPL = C3.padding_left,
  243    sort(padding_right,@>=,Column,[C4|_]), MaxPR = C4.padding_right,
  244    findall(BLL,(member(C,Column),string_length(C.border_left,BLL)),BLLs),max_list(BLLs,MaxBL),
  245    findall(BRL,(member(C,Column),string_length(C.border_right,BRL)),BRLs),max_list(BRLs,MaxBR),
  246    Width #>= 0,
  247    CWidth #>= 0,
  248    Width #= MaxBL + MaxPL + CWidth + MaxPR + MaxBR,
  249    Height #>= 0,
  250    CWidth #>= MinWidth,
  251    CWidth * Height #>= MaxLength.
  252
  253set_column_widths([],_,[]).
  254set_column_widths([Column|Columns],ColSpecs,[NColumn|NColumns]) :-
  255    set_cells_widths(Column,ColSpecs,NColumn),
  256    set_column_widths(Columns,ColSpecs,NColumns).
  257
  258set_cells_widths([],_,[]).
  259set_cells_widths([Cell|Cells],ColSpecs,[NCell|NCells]) :-
  260    member(ColSpec,ColSpecs),
  261    ColSpec.key = Cell.key,
  262    set_cell_width(Cell,ColSpec,NCell),
  263    set_cells_widths(Cells,ColSpecs,NCells).
  264
  265set_cell_width(Cell,ColSpec,NCell) :-
  266    Width = ColSpec.width,
  267    string_length(Cell.border_left,BL),
  268    string_length(Cell.border_right,BR),
  269    CWidth is Width - BL - Cell.padding_left - Cell.padding_right - BR,
  270    NCell = Cell.put(_{width:Width,cwidth:CWidth}).
 set_equal_value(+Att, +Cells, +Value)
sets the attribute values denoted by Att within Cells to be equal Value
  274set_equal_value(_,[],_).
  275set_equal_value(Att,[Cell|Cells],Value) :-
  276    Cell.Att #= Value,
  277    set_equal_value(Att,Cells,Value).
  278
  279cell_widths([],[]).
  280cell_widths([Cell|Cells],[Width|Widths]) :-
  281    Width = Cell.width,
  282    cell_widths(Cells,Widths).
 label_cells(+Cells) is det
assigns a width and height to a cell (if there are options)
  286label_cells([]).
  287label_cells([Cell|Cells]) :-
  288    fd_inf(Cell.width,WidthInf),fd_sup(Cell.width,WidthSup),
  289    fd_inf(Cell.height,HeightInf),fd_sup(Cell.height,HeightSup),
  290    label([Cell.height,Cell.width]),
  291    DeltaWidth is Cell.width - WidthInf,
  292    DeltaHeight is Cell.height - HeightInf,
  293    debug(print_table_label,"label cell - width(~w .. ~w): ~w (+~w), height(~w .. ~w): ~w (+~w)",
  294        [WidthInf,WidthSup,Cell.width,DeltaWidth,HeightInf,HeightSup,Cell.height,DeltaHeight]),
  295    label_cells(Cells).
 pre_process_table(+Keys:list(atom), +Data:list(dict), +ColumnsSpec:dict, -Table:list(list(dict))) is det
creates an internal Table structure composed of Rows of Cells
  298pre_process_table(Keys,Data,ColumnsSpec,Table) :-
  299    create_header(Keys,ColumnsSpec,Header),
  300    table_to_cell_rows(Keys,[Header|Data],ColumnsSpec,TableData0),
  301    pre_process_rows(TableData0,TableRows),
  302    transpose(TableRows,TableColumns0),
  303    pre_process_columns(TableColumns0,TableColumns),
  304    transpose(TableColumns,Table),
  305    !.
  306
  307pre_process_rows(Rows,NRows) :-
  308    length(Rows,N), N = 2,!,
  309    Rows = [HeaderRow0,FirstRow0],
  310    set_class(header,HeaderRow0,HeaderRow),
  311    set_class(first_row,FirstRow0,FirstRow1),   %  FirstRow = first & last row
  312    set_class(last_row,FirstRow1,FirstRow),
  313    NRows = [HeaderRow,FirstRow].
  314
  315pre_process_rows(Rows,NRows) :-
  316    append([HeaderRow0,FirstRow0|RemainingRows],[LastRow0],Rows),  
  317    set_class(header,HeaderRow0,HeaderRow),
  318    set_class(first_row,FirstRow0,FirstRow),
  319    set_class(last_row,LastRow0,LastRow),
  320    append([HeaderRow,FirstRow|RemainingRows],[LastRow],NRows).
  321
  322pre_process_columns([Column0],[NColumn]) :-
  323    !,
  324    set_class(first_column,Column0,Column1),    %  Column = first & last column
  325    set_class(last_column,Column1,NColumn).
  326
  327pre_process_columns(Columns,NColumns) :-
  328    append([FirstColumn0|RemainingColumns],[LastColumn0],Columns), 
  329    set_class(first_column,FirstColumn0,FirstColumn),
  330    set_class(last_column,LastColumn0,LastColumn),
  331    append([FirstColumn|RemainingColumns],[LastColumn],NColumns).
  332
  333% creates a default representation for the Header (that can be manipulated later using ColumnSpec)
  334create_header(Keys,ColumnsSpec,Header) :-
  335    findall(Key:Value,
  336        (
  337            member(Key,Keys),
  338            (Value = ColumnsSpec.get(Key).get(header) -> true ; Value = Key)
  339        ), HeaderData),
  340    dict_create(Header,_,HeaderData).
 table_to_cell_rows(+Keys:list(atom), +TableData:list(dict), +ColumnSpecs:dict, -NTable:list(list(dict))) is det
converts the atomic values in a row (represented as dict) to a list of lists containing dict structure representing a table cell
  344table_to_cell_rows(Keys,TableData,ColumnsSpec,NTable) :-
  345    cell_template(CellTemplate0),
  346    findall(NRow,
  347        (
  348            nth0(RowIndex,TableData,Row),
  349            findall(Cell,
  350                (
  351                    nth0(ColumnIndex,Keys,Key),
  352                    (UserTemplate = ColumnsSpec.get(Key) -> CellTemplate = CellTemplate0.put(UserTemplate) ; CellTemplate = CellTemplate0),
  353                    Value = Row.get(Key),
  354                    (RowIndex = 0 -> FormatTemplate = "~w" ; FormatTemplate = CellTemplate.format),
  355                    format_content(Value,FormatTemplate,FormattedValue),
  356                    string_length(FormattedValue,Length),
  357                    min_wrap_width(FormattedValue,MinWidth),
  358                    Cell = CellTemplate.put(_{key:Key,content:Value,format:FormatTemplate,formatted_content:FormattedValue,length:Length,min_width:MinWidth,row:RowIndex,column:ColumnIndex})
  359                ),NRow),
  360            true
  361            % assertion((dict_keys(Row,Ks),forall(member(K,Ks),(member(Cell,NRow),Cell.key = K))))
  362        ),NTable),
  363    assertion((length(TableData,N),length(NTable,N))).
  364 
  365set_class(_,[],[]) :- !.   
  366set_class(Class,[Cell|Cells],[NCell|NCells]) :-
  367    append(Cell.classes,[Class],NClasses),
  368    NCell = Cell.put(classes,NClasses),
  369    set_class(Class,Cells,NCells).
  370
  371apply_style(_,_,[],[]) :- !.
  372apply_style(Style,ColumnsSpec,[Row|Rows],[NRow|NRows]) :-
  373    cell_style(Style, StyleSheet),
  374    findall(NCell,(
  375        member(Cell0,Row),
  376        (StyleObj = StyleSheet.get(default) -> true ; StyleObj = _{}),
  377        Cell1 = Cell0.put(StyleObj),
  378        apply_style_to_cell(StyleSheet,Cell1.classes,Cell1,Cell),
  379        ((Cell1.row > 0,ColumnSpec = ColumnsSpec.get(Cell.key)) -> true ; ColumnSpec = _{}),
  380        NCell = Cell.put(ColumnSpec)
  381        ),NRow),
  382    apply_style(Style,ColumnsSpec,Rows,NRows).
  383
  384apply_style_to_cell(_,[],NCell,NCell).
  385apply_style_to_cell(StyleSheet,[Class|Classes],Cell0,NCell) :-
  386    (StyleObj = StyleSheet.get(Class) -> true ; StyleObj = _{}),
  387    Cell = Cell0.put(StyleObj),
  388    debug(print_table_style,"apply style - content:~w, class:~w, style:~w",[Cell.content, Class, StyleObj]),
  389    apply_style_to_cell(StyleSheet,Classes,Cell,NCell).
 create_row_template(+Row, +StartPosition, -Template)
  392create_row_template(StartPosition,Row,Template) :-
  393    % Rs = [_{padding_left:1,padding_right:1,border_left:"*",border_right:"*",width:12},_{padding_left:1,padding_right:1,border_left:"*",border_right:"*",width:12}],create_row_template(0,Rs,T),format(T,[xxxxxx,yyyyyy]).
  394    format(string(Start),"~~~w|",[StartPosition]),
  395    create_row_template2(Row,Start,Template).
  396
  397create_row_template2([],Template,Template).
  398create_row_template2([Cell|Cells],Acc,Template) :-
  399    create_cell_template(Cell,CellTemplate),
  400    string_concat(Acc,CellTemplate,NAcc),
  401    create_row_template2(Cells,NAcc,Template).
  402
  403create_cell_template(Cell,Template) :-
  404    (Cell.align = left -> SubTemplate = "~~w~~t~~~w+" ;
  405        (Cell.align = right -> SubTemplate = "~~t~~w~~~w+" ;
  406            SubTemplate = "~~t~~w~~t~~~w+")), % center
  407    format(string(ContentTemplate),SubTemplate,[Cell.cwidth]),
  408    format(string(Template),"~w~~|~~t~~~w+~w~~t~~~w+~w", [Cell.border_left,Cell.padding_left,ContentTemplate,Cell.padding_right,Cell.border_right]),
  409    debug(print_table_format,"~w~30|content: ~w,~70|border_left:~w, padding_left:~w, cwidth:~w, cheight:~w, padding_right:~w, border_right:~w",
  410        [Template,Cell.content, Cell.border_left,Cell.padding_left,Cell.cwidth,Cell.cheight,Cell.padding_right,Cell.border_right]).
  411
  412create_border_template(StartPosition,Cells,Att,Str) :-
  413    % Rs = [_{border_top:"*",border_bottom:"*",width:12},_{border_top:"*",border_bottom:"*",width:12}],create_border_template(0,Rs,border_top,T),format(T).
  414    format(string(Start),"~~~w|",[StartPosition]),
  415    create_border_template2(Cells,Att,Start,Str).
  416
  417create_border_template2([],_,Template,Template).
  418create_border_template2([Cell|Cells],Att,Acc,Template) :-
  419    atom_concat(Att,'_left',CornerLeft),atom_concat(Att,'_right',CornerRight),
  420    (string_length(Cell.Att,1) -> BorderChar = Cell.Att ; BorderChar = " "),
  421    (string_length(Cell.CornerLeft,1) -> CornerLeftChar = Cell.CornerLeft ; CornerLeftChar = BorderChar),
  422    (string_length(Cell.CornerRight,1) -> CornerRightChar = Cell.CornerRight ; CornerRightChar = BorderChar),
  423    % format(string(CellTemplate),"~~|~~`~wt~~~w+",[BorderChar,Cell.width]),
  424    format(string(CellTemplate),"~~|~w~~`~wt~w~~~w+",[CornerLeftChar,BorderChar,CornerRightChar,Cell.width]),
  425    string_concat(Acc,CellTemplate,NAcc),
  426    create_border_template2(Cells,Att,NAcc,Template).
 pop_line(+Cells:list, -FirstLines:list, -RemainingRowLines:list) is det
returns the first lines, and the remaining lines
  430pop_line([],[],[]).
  431pop_line([Cell|Cells],[FirstLine|RowLines],[Rest|RemainingRowLines]) :-
  432    Cell = [FirstLine|Rest],!,
  433    pop_line(Cells,RowLines,RemainingRowLines).
  434
  435pop_line([Cell|Cells],[""|RowLines],[[]|RemainingRowLines]) :-
  436    Cell = [],
  437    pop_line(Cells,RowLines,RemainingRowLines).
  438
  439format_content(Content,FormatTemplate,Str) :-
  440    phrase(content(Content,FormatTemplate),Codes),
  441    string_codes(Str,Codes).
  442
  443         /*******************************
  444         *       MESSAGES               *
  445         *******************************/
  446
  447:- multifile prolog:message//1.  448:- multifile prolog:error_message//1.  449
  450prolog:message(print_table(Msg)) --> Msg.
  451
  452table(Rows,Caption,Width) --> {
  453    Rows = [Row|_],findall(CellWidth,(member(Cell,Row),CellWidth = Cell.width),Widths),
  454    sum_list(Widths,TableWidth),
  455    StartPos is floor((Width - TableWidth) / 2),
  456    length(Rows,N), NResults is N - 1
  457    },
  458    caption(Caption,StartPos,TableWidth,NResults),rows(Rows,StartPos).
  459
  460caption(Mesg,StartPos,TableWidth,NResults) --> {
  461    format(string(Template),"~~~w|~~t~~w (~w records)~~t~~~w+",[StartPos,NResults,TableWidth]),
  462    format(string(Caption),Template,[Mesg])
  463    },
  464    [Caption,nl].
  465
  466rows([],_) --> !.
  467rows([Row|Rows],StartPos) --> row(Row,StartPos),rows(Rows,StartPos).
  468
  469row(Row,StartPos) --> border_line(Row,border_top,StartPos),row_content(Row,StartPos),border_line(Row,border_bottom,StartPos).
  470
  471border_line([],_,_) --> !.
  472border_line(Row,Att,_) --> {forall(member(Cell,Row), Cell.Att = "")},!.
  473border_line(Row,Att,StartPos) --> {
  474    create_border_template(StartPos,Row,Att,Template),
  475    format(string(BorderLine),Template,[])
  476    },
  477    [BorderLine,nl].
  478
  479row_content(Row,StartPos) --> {
  480    create_row_template(StartPos,Row,RowTemplate),
  481    findall(WrappedLines, (
  482        member(Cell,Row),
  483        Content = Cell.formatted_content,
  484        wrap_text(Cell.cwidth,Content,WrappedLines),
  485        debug(print_table_wrap,"wrap_text: width:~w, content:~w, wrapped:~w",[Cell.width,Content,WrappedLines])
  486        ), RowLines)
  487    },
  488    row_lines(RowLines,RowTemplate).
  489
  490row_lines(RowLines,_) --> {forall(member(Lines,RowLines),Lines = [])},!.
  491row_lines(RowLines,Template) --> {
  492    pop_line(RowLines,FirstLines,Remaining),
  493    format(string(RowStr),Template,FirstLines)
  494    },[RowStr,nl],row_lines(Remaining,Template).
  495
  496% defaults
  497content(Content) --> {Content = date(_,_,_),!, format_time(string(DStr),"%Y-%m-%d",Content)},content(DStr,"~w").
  498content(Content) --> {integer(Content),!},content(Content,"~d").
  499content(Content) --> {float(Content),!},content(Content,"~2f").
  500content(Content) --> content(Content,"~w").
  501
  502content(Content,"") --> !,content(Content).
  503content(Content,Template) --> {format(string(Str),Template,[Content])},Str.
  504
  505prolog:error_message(insufficient_width(_,Width)) -->
  506    [ 'Insufficient width to print table (provided: ~w) -> use \'force_print_table/1\' to ignore max terminal width'-[Width] ]