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