View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2018-2020, CWI Amsterdam
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(text_format,
   36          [ format_paragraph/2,         % +Text, +Options
   37            trim_line/2               % +LineIn, -Line
   38          ]).   39:- autoload(library(ansi_term),[ansi_format/3]).   40:- autoload(library(debug),[debug/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]).

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. */

   52:- multifile
   53    words/2.                            % +Input, -Words
 format_paragraph(+Text, +Options)
Format a paragraph to the current output. Options defined are:
width(+Width)
Width of a line. Default is 72.
margin_left(+Indent)
Indent all lines with Indent spaces.
margin_right(+Margin)
Additional right margin (same as reducing width)
hang(+Hang)
Additional indent for the first line. Can be negative.
bullet(+Bullet)
Bullet placed before the first line.
text_align(Alignment)
One of left, right, center or justify
pad(+Char)
If present, padd to the right using Char. Currently Char must be ' '.
   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                          % take at least one word
  107    ),
  108    !,
  109    take_words(T0, X1, W, T, BR, Rest).
  110take_words(Rest, _, _, [], false, Rest).
 trim_line(Line0, Line) is det
Remove leading and trailing white space (b(_,_)) tokens from a line.
  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).
 format_line(+Line, +Width, +LineNo, +Options) is det
  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),        % For now
  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),                  % TBD: Alignment with floats
  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).
 float_right(+Line0, -Line, -Right) is semidet
  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(Line, Line, []).
 space_dim(+Line, -SpaceVars, -Width)
  254space_dim(Line, Spaces, Width) :-
  255    space_dim(Line, Spaces, 0, Width).
  256
  257space_dim([], [], Width, Width).
  258space_dim([b(L,Var)|T0], [Var|T], W0, W) :-
  259    !,
  260    W1 is W0+L,
  261    space_dim(T0, T, W1, W).
  262space_dim([H|T0], T, W0, W) :-
  263    word_length(H, L),
  264    !,
  265    W1 is W0+L,
  266    space_dim(T0, T, W1, W).
 spread(+Spread, +SPC, -Spaces)
Distribute Spread spaces over SPC places, producing a list of counts.
  273spread(Spread, SPC, Spaces) :-
  274    spread_spc(SPC, Spread, Spaces).
  275
  276spread_spc(Cnt, Spread, [H|T]) :-
  277    Cnt > 0,
  278    !,
  279    H is round(Spread/Cnt),
  280    Cnt1 is Cnt - 1,
  281    Spread1 is Spread-H,
  282    spread_spc(Cnt1, Spread1, T).
  283spread_spc(_, _, []).
 emit_line(+Content)
  288emit_line([]).
  289emit_line([H|T]) :-
  290    (   emit_line_element(H)
  291    ->  true
  292    ;   type_error(line_element, H)
  293    ),
  294    emit_line(T).
  295
  296emit_line_element(w(W,_, Attrs)) :-
  297    (   Attrs = []
  298    ->  write(W)
  299    ;   ansi_format(Attrs, '~w', [W])
  300    ).
  301emit_line_element(b(Len, Extra)) :-
  302    (   var(Extra)
  303    ->  Extra = 0
  304    ;   true
  305    ),
  306    Spaces is Len+Extra,
  307    forall(between(1, Spaces, _), put_char(' ')).
  308
  309emit_indent(1, Options) :-
  310    !,
  311    option(margin_left(Indent), Options, 0),
  312    option(hang(Hang), Options, 0),
  313    (   option(bullet(BulletSpec), Options)
  314    ->  bullet_text(BulletSpec, Bullet),
  315        atom_length(Bullet, BLen),
  316        TheIndent is Indent+Hang-1-BLen,
  317        emit_indent(TheIndent),
  318        format('~w ', [Bullet])
  319    ;   TheIndent is Indent+Hang,
  320        emit_indent(TheIndent)
  321    ).
  322emit_indent(_, Options) :-
  323    option(margin_left(Indent), Options, 0),
  324    nl,
  325    emit_indent(Indent).
  326
  327emit_indent(N) :-
  328    forall(between(1, N, _),
  329           put_char(' ')).
  330
  331line_width(1, Width, Options) :-
  332    !,
  333    option(width(Right), Options, 72),
  334    option(margin_left(Indent), Options, 0),
  335    option(margin_right(RightMargin), Options, 0),
  336    option(hang(Hang), Options, 0),
  337    Width is Right - (Indent+Hang) - RightMargin.
  338line_width(_, Width, Options) :-
  339    option(width(Right), Options, 72),
  340    option(margin_left(Indent), Options, 0),
  341    option(margin_right(RightMargin), Options, 0),
  342    Width is Right - Indent - RightMargin.
 words(+Input, -Words) is det
Turn the Input into a list of w(Word, Len, Attributes) terms.
  348words(Text, Words) :-
  349    string(Text),
  350    !,
  351    split_string(Text, " \n\t\r", " \n\t\r", Words0),
  352    phrase(word_spaces(Words0), Words).
  353words(Words, Words) :-
  354    is_list(Words),
  355    !.
  356
  357word_spaces([]) -->
  358    [].
  359word_spaces([""]) -->
  360    !.
  361word_spaces([H|T]) -->
  362    { string_length(H, Len) },
  363    [ w(H, Len, []) ],
  364    (   {T==[]}
  365    ->  []
  366    ;   [b(1,_)],
  367        word_spaces(T)
  368    ).
  369
  370word_length(w(_,Len,_), Len).
  371
  372element_length(w(_,Len,_), Len).
  373element_length(b(Len,_), Len).
  374
  375bullet_text(I, Bullet) :-
  376    integer(I),
  377    !,
  378    format(string(Bullet), '~d.', [I]).
  379bullet_text(Bullet, Bullet)