34
35:- module(tabulator, [tabulate/3, align/4]). 36
37:- use_module(library(apply)). 38:- use_module(library(lists)). 39
40tabulate(FillChar, Table1, Table) :-
41 maplist(tabulate_row(Lists), Table1, Table),
42 maplist(close_list(FillChar), Lists).
43
44close_list(FillChar, List) :-
45 maplist('='(FillChar), List),
46 !.
47
48tabulate_row(Lengths, Row1, Row) :-
49 maplist(tabulate_element, Lengths, Row1, Row).
50
51tabulate_element(List, Column1, Column) :-
52 length(Column1, Length1),
53 length(List1, Length1),
54 append(Column1, Tail1, Column),
55 append(List1, Tail1, List).
56
57align(FillChar, Scheme, Table1, Table) :-
58 maplist(align_row(FillChar, Scheme), Table1, Table).
59
60align_row(FillChar, Scheme, Row1, Row) :-
61 maplist(align_cell_(FillChar), Scheme, Row1, Row).
62
63align_cell_(FillChar, Align, Cell1, Cell) :-
64 align_cell(Align, FillChar, Cell1, Cell).
65
66align_cell(left, FillChar, Cell1, Cell) :-
67 align_cell_left(Cell1, FillChar, Cell).
68align_cell(right, FillChar, Cell1, Cell) :-
69 align_cell_right(Cell1, FillChar, Cell).
70align_cell(center, FillChar, Cell1, Cell) :-
71 align_cell_center(Cell1, FillChar, Cell).
72align_cell(none, _, Cell, Cell).
73
74align_cell_left(Cell1, FillChar, Cell) :-
75 discompose_cell(Cell1, FillChar, [], FillStr, Cell2),
76 append(Cell2, FillStr, Cell).
77
78discompose_cell([], _, FillStr, FillStr, []).
79discompose_cell([Char|Cell1], Char, FillStr1, FillStr, Cell) :- !,
80 discompose_cell(Cell1, Char, [Char|FillStr1], FillStr, Cell).
81discompose_cell(Cell, _, FillStr, FillStr, Cell).
82
83align_cell_right(Cell1, FillChar, Cell) :-
84 reverse(Cell1, Cell2),
85 discompose_cell(Cell2, FillChar, [], FillStr, Cell3),
86 reverse(Cell3, Cell4),
87 append(FillStr, Cell4, Cell).
88
89align_cell_center(Cell1, FillChar, Cell) :-
90 discompose_cell(Cell1, FillChar, [], Fill1, Cell2),
91 reverse(Cell2, Cell3),
92 discompose_cell(Cell3, FillChar, [], Fill2, Cell4),
93 reverse(Cell4, Cell5),
94 length(Fill1, N1),
95 length(Fill2, N2),
96 NL is (N1 + N2) // 2,
97 length(FillL, NL),
98 append(Fill1, Fill2, Fill),
99 append(FillL, FillR, Fill),
100 append([FillL, Cell5, FillR], Cell)