1:- module(print_table,
    2          [ print_table/1,                      % :Goal
    3            print_table/2                       % :Goal,+Variables:list
    4          ]).    5
    6:- meta_predicate print_table(0).    7:- meta_predicate print_table(0, +).    8
    9:- use_module(library(clpfd), [transpose/2]).   10:- use_module(library(swi/lists)).
 print_table(:Goal) is det
 print_table(:Goal, +Variables:list) is det
Prints all the variables within the given non-deterministic Goal term formatted as a table of centre-padded columns to current_output. One Goal solution becomes one line of text. Solutions to free variables become printed cells.

Makes an important assumption: that codes equate to character columns; one code, one column. This will be true for most languages on a teletype like terminal. Ignores any exceptions by design.

?- print_table(user:prolog_file_type(_, _)).
+------+----------+
|  pl  |  prolog  |
|prolog|  prolog  |
| qlf  |  prolog  |
| qlf  |   qlf    |
| dll  |executable|
+------+----------+
   33print_table(Goal) :-
   34    term_variables(Goal, Variables),
   35    print_table(Goal, Variables).
   36
   37print_table(Goal, Variables) :-
   38    findall(Variables, Goal, Rows0),
   39    maplist(
   40        maplist(
   41            [Column, Codes]>>
   42            with_output_to_codes(
   43                print(Column), Codes)), Rows0, Rows),
   44    transpose(Rows, Columns),
   45    maplist(maplist(length), Columns, Lengths),
   46    maplist(max_list, Lengths, Widths),
   47    print_border(Widths),
   48    forall(member(Row, Rows), print_row(Widths, Row)),
   49    print_border(Widths).
   50
   51print_row(Widths, Row) :-
   52    zip(Widths, Row, Columns),
   53    forall(member(Column, Columns), print_column(Column)),
   54    put_code(0'|),
   55    nl.
   56
   57print_column([Width, Column]) :-
   58    format('|~|~t~s~t~*+', [Column, Width]).
   59
   60print_border(Widths) :-
   61    forall(member(Width, Widths), format('+~|~`-t~*+', [Width])),
   62    put_code(0'+),
   63    nl