34
35:- module(text_format,
36 [ format_paragraph/2, 37 trim_line/2 38 ]). 39:- use_module(library(debug),[debug/3]). 40:- autoload(library(ansi_term),[ansi_format/3]). 41:- autoload(library(error),[must_be/2,type_error/2]). 42:- autoload(library(lists),[append/3,member/2,selectchk/3]). 43:- autoload(library(option),[select_option/3,option/2,option/3]).
52:- multifile
53 words/2.
75format_paragraph(Text, Options) :-
76 words(Text, Words),
77 format_lines(Words, 1, Options).
78
79format_lines([], _, _).
80format_lines(Words, LineNo, Options) :-
81 line_width(LineNo, Width, Options),
82 skip_spaces(Words, Words1),
83 take_words(Words1, 0, Width, Line0, HasBR, Words2),
84 skip_trailing_spaces(Line0, Line),
85 skip_spaces(Words2, Words3),
86 ( Words3 == []
87 -> align_last_line(Options, OptionsLast),
88 format_line(Line, Width, LineNo, OptionsLast)
89 ; HasBR == true
90 -> align_last_line(Options, OptionsLast),
91 format_line(Line, Width, LineNo, OptionsLast),
92 LineNo1 is LineNo + 1,
93 format_lines(Words3, LineNo1, Options)
94 ; format_line(Line, Width, LineNo, Options),
95 LineNo1 is LineNo + 1,
96 format_lines(Words3, LineNo1, Options)
97 ).
98
99take_words([br(_)|T], _, _, [], true, T) :-
100 !.
101take_words([H|T0], X, W, [H|T], BR, Rest) :-
102 element_length(H, Len),
103 X1 is X+Len,
104 ( X1 =< W
105 -> true
106 ; X == 0 107 ),
108 !,
109 take_words(T0, X1, W, T, BR, Rest).
110take_words(Rest, _, _, [], false, Rest).
116trim_line(Line0, Line) :-
117 skip_spaces(Line0, Line1),
118 skip_trailing_spaces(Line1, Line).
119
120skip_spaces([b(_,_)|T0], T) :-
121 !,
122 skip_spaces(T0, T).
123skip_spaces(L, L).
124
125skip_trailing_spaces(L, []) :-
126 skip_spaces(L, []),
127 !.
128skip_trailing_spaces([H|T0], [H|T]) :-
129 skip_trailing_spaces(T0, T).
130
131align_last_line(Options0, Options) :-
132 select_option(text_align(justify), Options0, Options1),
133 !,
134 Options = [text_align(left)|Options1].
135align_last_line(Options, Options).
140format_line(Line, Width, LineNo, Options) :-
141 option(pad(Char), Options),
142 option(margin_right(MR), Options),
143 MR > 0,
144 !,
145 must_be(oneof([' ']), Char), 146 format_line_(Line, Width, LineNo, Options),
147 forall(between(1, MR, _), put_char(' ')).
148format_line(Line, Width, LineNo, Options) :-
149 format_line_(Line, Width, LineNo, Options).
150
151format_line_(Line, Width, LineNo, Options) :-
152 float_right(Line, Line1, Right),
153 !,
154 trim_line(Line1, Line2), 155 trim_line(Right, Right2),
156 space_dim(Line2, _, WL),
157 space_dim(Right2, _, WR),
158 append(Line2, [b(0,Space)|Right2], Line3),
159 Space is Width - WL - WR,
160 emit_indent(LineNo, Options),
161 emit_line(Line3).
162format_line_(Line, Width, LineNo, Options) :-
163 option(text_align(justify), Options),
164 !,
165 justify(Line, Width),
166 emit_indent(LineNo, Options),
167 emit_line(Line).
168format_line_(Line, Width, LineNo, Options) :-
169 option(text_align(right), Options),
170 !,
171 flush_right(Line, Width, LineR),
172 emit_indent(LineNo, Options),
173 emit_line(LineR).
174format_line_(Line, Width, LineNo, Options) :-
175 option(text_align(center), Options),
176 option(pad(Pad), Options, _),
177 !,
178 center(Line, Width, Pad, LineR),
179 emit_indent(LineNo, Options),
180 emit_line(LineR).
181format_line_(Line, Width, LineNo, Options) :-
182 option(pad(_Char), Options),
183 !,
184 pad(Line, Width, Padded),
185 emit_indent(LineNo, Options),
186 emit_line(Padded).
187format_line_(Line, _Width, LineNo, Options) :-
188 emit_indent(LineNo, Options),
189 emit_line(Line).
190
191justify(Line, Width) :-
192 space_dim(Line, Spaces, W0),
193 Spread is Width - W0,
194 length(Spaces, SPC),
195 SPC > 0,
196 Spread > 0,
197 spread(Spread, SPC, Spaces),
198 !,
199 debug(format(justify), 'Justified ~d spaces over ~d gaps: ~p',
200 [Spread, SPC, Spaces]).
201justify(_, _).
202
203flush_right(Line, Width, [b(0,Spaces)|Line]) :-
204 space_dim(Line, _Spaces, W0),
205 Spaces is Width - W0.
206
207center(Line, Width, Pad, [b(0,Left)|Padded]) :-
208 space_dim(Line, _Spaces, W0),
209 Spaces is Width - W0,
210 Left is Spaces//2,
211 ( atom(Pad),
212 Right is Spaces - Left,
213 Right > 0
214 -> append(Line, [b(0,Right)], Padded)
215 ; Padded = Line
216 ).
217
218pad(Line, Width, Padded) :-
219 space_dim(Line, _Spaces, W0),
220 Spaces is Width - W0,
221 append(Line, [b(0,Spaces)], Padded).
228float_right(Line0, Line, Right) :-
229 member(w(_,_,Attrs), Line0),
230 memberchk(float(right), Attrs),
231 !,
232 do_float_right(Line0, Line, Right).
233
234do_float_right([], [], []).
235do_float_right([H0|T0], T, [H|R]) :-
236 float_right_word(H0, H),
237 !,
238 float_right_space(T0, T, R).
239do_float_right([H|T0], [H|T], R) :-
240 do_float_right(T0, T, R).
241
242float_right_word(w(W,L,A0), w(W,L,A)) :-
243 selectchk(float(right), A0, A).
244
245float_right_space([S|T0], T, [S|R]) :-
246 S = b(_,_),
247 !,
248 float_right_space(T0, T, R).
249float_right_space(Line0, Line, Right) :-
250 do_float_right(Line0, Line, Right).
255space_dim(Line, Spaces, Width) :-
256 space_dim(Line, Spaces, 0, Width).
257
258space_dim([], [], Width, Width).
259space_dim([b(L,Var)|T0], [Var|T], W0, W) :-
260 !,
261 W1 is W0+L,
262 space_dim(T0, T, W1, W).
263space_dim([H|T0], T, W0, W) :-
264 word_length(H, L),
265 !,
266 W1 is W0+L,
267 space_dim(T0, T, W1, W).
274spread(Spread, SPC, Spaces) :-
275 spread_spc(SPC, Spread, Spaces).
276
277spread_spc(Cnt, Spread, [H|T]) :-
278 Cnt > 0,
279 !,
280 H is round(Spread/Cnt),
281 Cnt1 is Cnt - 1,
282 Spread1 is Spread-H,
283 spread_spc(Cnt1, Spread1, T).
284spread_spc(_, _, []).
289emit_line([]).
290emit_line([H|T]) :-
291 ( emit_line_element(H)
292 -> true
293 ; type_error(line_element, H)
294 ),
295 emit_line(T).
296
297emit_line_element(w(W,_, Attrs)) :-
298 ( Attrs = []
299 -> write(W)
300 ; ansi_format(Attrs, '~w', [W])
301 ).
302emit_line_element(b(Len, Extra)) :-
303 ( var(Extra)
304 -> Extra = 0
305 ; true
306 ),
307 Spaces is Len+Extra,
308 forall(between(1, Spaces, _), put_char(' ')).
309
310emit_indent(1, Options) :-
311 !,
312 option(margin_left(Indent), Options, 0),
313 option(hang(Hang), Options, 0),
314 ( option(bullet(BulletSpec), Options)
315 -> bullet_text(BulletSpec, Bullet),
316 atom_length(Bullet, BLen),
317 TheIndent is Indent+Hang-1-BLen,
318 emit_indent(TheIndent),
319 format('~w ', [Bullet])
320 ; TheIndent is Indent+Hang,
321 emit_indent(TheIndent)
322 ).
323emit_indent(_, Options) :-
324 option(margin_left(Indent), Options, 0),
325 nl,
326 emit_indent(Indent).
327
328emit_indent(N) :-
329 forall(between(1, N, _),
330 put_char(' ')).
331
332line_width(1, Width, Options) :-
333 !,
334 option(width(Right), Options, 72),
335 option(margin_left(Indent), Options, 0),
336 option(margin_right(RightMargin), Options, 0),
337 option(hang(Hang), Options, 0),
338 Width is Right - (Indent+Hang) - RightMargin.
339line_width(_, Width, Options) :-
340 option(width(Right), Options, 72),
341 option(margin_left(Indent), Options, 0),
342 option(margin_right(RightMargin), Options, 0),
343 Width is Right - Indent - RightMargin.
349words(Text, Words) :-
350 string(Text),
351 !,
352 split_string(Text, " \n\t\r", " \n\t\r", Words0),
353 phrase(word_spaces(Words0), Words).
354words(Words, Words) :-
355 is_list(Words),
356 !.
357
358word_spaces([]) -->
359 [].
360word_spaces([""]) -->
361 !.
362word_spaces([H|T]) -->
363 { string_length(H, Len) },
364 [ w(H, Len, []) ],
365 ( {T==[]}
366 -> []
367 ; [b(1,_)],
368 word_spaces(T)
369 ).
370
371word_length(w(_,Len,_), Len).
372
373element_length(w(_,Len,_), Len).
374element_length(b(Len,_), Len).
375
376bullet_text(I, Bullet) :-
377 integer(I),
378 !,
379 format(string(Bullet), '~d.', [I]).
380bullet_text(Bullet, Bullet)
Print formatted text to a terminal
This module is the core of the plain text rendering module, providing format_paragraph/2 which formats a plain text block, respecting left and right margins, text alignment, ANSI style elements, etc. */