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
   36:- module(html_text,
   37          [ html_text/1,                        % +FileName
   38            html_text/2                         % +FileName, Options
   39          ]).   40:- use_module(library(debug),[debug/3]).   41:- autoload(library(ansi_term),[ansi_format/3]).   42:- autoload(library(apply),[foldl/4,maplist/3,maplist/2]).   43:- autoload(library(error),[must_be/2]).   44:- autoload(library(lists),
   45	    [ append/3, list_to_set/2, reverse/2, delete/3, sum_list/2,
   46	      nth1/3, max_list/2
   47	    ]).   48:- autoload(library(option),[select_option/4,merge_options/3,option/3]).   49:- autoload(library(sgml),[xml_is_dom/1,load_html/3]).   50:- autoload(library(lynx/format),[format_paragraph/2,trim_line/2]).   51:- autoload(library(lynx/html_style),
   52	    [ element_css/3, css_block_options/5, css_inline_options/3,
   53	      attrs_classes/2, style_css_attrs/2
   54	    ]).   55
   56:- predicate_options(html_text/2, 2,
   57                     [ margin_left(integer),
   58                       margin_right(integer),
   59                       width(integer),
   60                       text_align(oneof([justify, left]))
   61                     ]).

Render HTML as plain text

This module renders HTML markup as plain text, just like the open lynx program does. It is (as yet), limited to and spacialized for dealing with the SWI-Prolog documentation. This library first of all supports help/1. */

 html_text(+Input) is det
 html_text(+Input, +Options) is det
Render HTML from Input to current_output. Input is either an HTML DOM or a valid input for load_html/3. Options defined are:
margin_left(+N)
margin_right(+N)
Initial margins.
width(+N)
Total preceived line width.
text_align(+Align)
One of justify or left. Default is justify.
   85html_text(Input) :-
   86    html_text(Input, []).
   87
   88html_text(Input, Options) :-
   89    (   xml_is_dom(Input)
   90    ->  DOM = Input
   91    ;   load_html(Input, DOM, Options)
   92    ),
   93    default_state(State0),
   94    state_options(Options, State0, State),
   95    init_nl,
   96    format_dom(DOM, State).
   97
   98state_options([], State, State).
   99state_options([H|T], State0, State) :-
  100    H =.. [Key,Value],
  101    (   fmt_option(Key, Type, _Default)
  102    ->  must_be(Type, Value),
  103        State1 = State0.put(Key,Value)
  104    ;   State1 = State0
  105    ),
  106    state_options(T, State1, State).
  107
  108fmt_option(margin_left,  integer, 0).
  109fmt_option(margin_right, integer, 0).
  110fmt_option(text_align,   oneof([justify, left]), justify).
  111fmt_option(width,        between(10,1000), 72).
  112
  113default_state(State) :-
  114    findall(Key-Value, fmt_option(Key, _, Value), Pairs),
  115    dict_pairs(Dict, _, Pairs),
  116    State = Dict.put(_{ style:[], list:[]}).
 format_dom(+DOM, +State) is det
Format the given HTML DOM to current_output according to State.
  122format_dom([], _) :-
  123    !.
  124format_dom([H|T], State) :-
  125    format_dom(H, State),
  126    !,
  127    format_dom(T, State).
  128format_dom(Content, State) :-
  129    Content = [H0|_],
  130    \+ is_block_element(H0),
  131    !,
  132    (   append(Inline, [H|T], Content),
  133        is_block_element(H)
  134    ->  true
  135    ;   Inline = Content
  136    ),
  137    format_dom(element(p, [], Inline), State),
  138    format_dom([H|T], State).
  139format_dom(element(html, _, Content), State) :-
  140    !,
  141    format_dom(Content, State).
  142format_dom(element(head, _, _), _) :-
  143    !.
  144format_dom(element(body, _, Content), State) :-
  145    !,
  146    format_dom(Content, State).
  147format_dom(element(E, Attrs, Content), State) :-
  148    !,
  149    (   format_element(E, Attrs, Content, State)
  150    ->  true
  151    ;   debug(format(html), 'Skipped block element ~q', [E])
  152    ).
  153
  154format_element(pre, Attrs, [Content], State) :-
  155    !,
  156    block_element(pre, Attrs, Top-Bottom, BlockAttrs, Style),
  157    update_style(Style, State, State1),
  158    ask_nl(Top),
  159    emit_code(Content, BlockAttrs, State1),
  160    ask_nl(Bottom).
  161format_element(table, Attrs, Content, State) :-
  162    !,
  163    block_element(table, Attrs, Top-Bottom, BlockAttrs, Style),
  164    update_style(Style, State, State1),
  165    state_par_properties(State1, BlockAttrs, BlockOptions),
  166    ask_nl(Top),
  167    emit_nl,
  168    format_table(Content, Attrs, BlockOptions, State1),
  169    ask_nl(Bottom).
  170format_element(hr, Attrs, _, State) :-
  171    !,
  172    block_element(hr, Attrs, Top-Bottom, BlockAttrs, Style),
  173    update_style(Style, State, State1),
  174    state_par_properties(State1, BlockAttrs, BlockOptions),
  175    ask_nl(Top),
  176    emit_nl,
  177    emit_hr(Attrs, BlockOptions, State1),
  178    ask_nl(Bottom).
  179format_element(Elem, Attrs, Content, State) :-
  180    block_element(Elem, Attrs, Top-Bottom, BlockAttrs, Style),
  181    !,
  182    update_style(Style, State, State1),
  183    block_words(Content, SubBlocks, Words, State1),
  184    (   Words == []
  185    ->  true
  186    ;   ask_nl(Top),
  187        emit_block(Words, BlockAttrs, State1),
  188        ask_nl(Bottom)
  189    ),
  190    (   SubBlocks \== []
  191    ->  update_state_par_properties(BlockAttrs, State1, State2),
  192        format_dom(SubBlocks, State2)
  193    ;   true
  194    ).
  195format_element(Elem, Attrs, Content, State) :-
  196    list_element(Elem, Attrs, Top-Bottom, State, State1),
  197    !,
  198    open_list(Elem, State1, State2),
  199    ask_nl(Top),
  200    format_list(Content, Elem, 1, State2),
  201    ask_nl(Bottom).
  202format_element(Elem, Attrs, Content, State) :-
  203    format_list_element(element(Elem, Attrs, Content), none, 0, State).
 block_element(+El, +Attrs, -Margin, -ParOPtions, -Style)
Describe a block element
  209block_element(El, Attrs, Margins, ParOptions, Style) :-
  210    block_element(El, Margins0, ParOptions0, Style0),
  211    (   nonvar(Attrs),
  212        element_css(El, Attrs, CSS)
  213    ->  css_block_options(CSS, Margins0, Margins, ParOptions, Style1),
  214        append(Style1, Style0, Style2),
  215        list_to_set(Style2, Style)
  216    ;   Margins = Margins0,
  217        ParOptions = ParOptions0,
  218        Style = Style0
  219    ).
  220
  221block_element(p,          1-2, [],                                []).
  222block_element(div,        1-1, [],                                []).
  223block_element(hr,         1-1, [],                                []).
  224block_element(h1,         2-2, [],                                [bold]).
  225block_element(h2,         2-2, [],                                [bold]).
  226block_element(h3,         2-2, [],                                [bold]).
  227block_element(h4,         2-2, [],                                [bold]).
  228block_element(pre,        2-2, [],                                []).
  229block_element(blockquote, 2-2, [margin_left(4), margin_right(4)], []).
  230block_element(table,      2-2, [],                                []).
  231
  232list_element(ul, _, Margins, State0, State) :-
  233    margins(4, 4, State0, State),
  234    list_level_margins(State, Margins).
  235list_element(ol, _, Margins, State0, State) :-
  236    margins(4, 4, State0, State),
  237    list_level_margins(State, Margins).
  238list_element(dl, _, 2-2, State, State).
  239
  240list_element(ul).
  241list_element(ol).
  242list_element(dl).
  243
  244list_level_margins(State, 2-2) :-
  245    nonvar(State),
  246    State.get(list) == [],
  247    !.
  248list_level_margins(_, 0-0).
  249
  250format_list([], _, _, _).
  251format_list([H|T], Type, Nth, State) :-
  252    format_list_element(H, Type, Nth, State),
  253    (   T == []
  254    ->  true
  255    ;   Nth1 is Nth + 1,
  256        format_list(T, Type, Nth1, State)
  257    ).
  258
  259format_list_element(element(LE, Attrs, Content), Type, Nth, State) :-
  260    setup_list_element(LE, Attrs, Type, Nth, ListParProps, State, State1),
  261    block_words(Content, Blocks, Words, State1),
  262    emit_block(Words, ListParProps, State1),
  263    (   Blocks \== []
  264    ->  ask_nl(2),                              % empty line before next par
  265        update_state_par_properties(ListParProps, State1, State2),
  266        format_dom(Blocks, State2)
  267    ;   true
  268    ).
  269
  270setup_list_element(li, _Attrs, _Type, Nth, ListParProps, State, State) :-
  271    list_par_properties(State.list, Nth, ListParProps).
  272setup_list_element(dt, _Attrs, _Type, _Nth, [], State, State2) :-
  273    margins(0, 0, State, State1),
  274    update_style([bold], State1, State2).
  275setup_list_element(dd, _Attrs, _Type, _Nth, [], State, State1) :-
  276    margins(4, 0, State, State1).
  277
  278list_item_element(li).
  279list_item_element(dt).
  280list_item_element(dd).
  281
  282list_par_properties([ul|_More], _, [bullet('\u2022')]).
  283list_par_properties([ol|_More], N, [bullet(N)]).
 block_words(+Content, -RestContent, -Words, +State)
Turn Content into a list of words with attributes and spaces.
  290block_words(Content, RC, Words, State) :-
  291    phrase(bwords(Content, RC, State), Words0),
  292    join_whitespace(Words0, Words1),
  293    trim_line(Words1, Words).
  294
  295bwords([], [], _) -->
  296    !.
  297bwords([H|T], Rest, _State) -->
  298    { var(Rest),
  299      is_block_element(H),
  300      !,
  301      Rest = [H|T]
  302    }.
  303bwords([H|T], Rest, State) -->
  304    !,
  305    bwordsel(H, State),
  306    bwords(T, Rest, State).
  307
  308is_block_element(element(E,_,_)) :-
  309    (   block_element(E, _, _, _)
  310    ;   list_element(E)
  311    ;   list_item_element(E)
  312    ),
  313    debug(format(html), 'Found block ~q', [E]),
  314    !.
  315
  316bwordsel(element(Elem, Attrs, Content), State) -->
  317    { styled_inline(Elem, Attrs, Margins, Style),
  318      !,
  319      update_style(Style, State, State1)
  320    },
  321    left_margin(Margins),
  322    bwords(Content, [], State1),
  323    right_margin(Margins).
  324bwordsel(element(br, _, _), _State) -->
  325    [br([])].
  326bwordsel(CDATA, State) -->
  327    { atomic(CDATA),
  328      !,
  329      split_string(CDATA, " \n\t\r", "", Words)
  330    },
  331    words(Words, State).
  332bwordsel(element(Elem, _Attrs, _Content), _State) -->
  333    { debug(format(html), 'Skipped inline element ~q', [Elem]) }.
  334
  335left_margin(0-_) --> !.
  336left_margin(N-_) --> [b(N,_)].
  337
  338right_margin(_-0) --> !.
  339right_margin(_-N) --> [b(N,_)].
  340
  341styled_inline(El, Attrs, Margins, Style) :-
  342    styled_inline(El, Style0),
  343    (   nonvar(Attrs),
  344        element_css(El, Attrs, CSS)
  345    ->  css_inline_options(CSS, Margins, Style1),
  346        append(Style1, Style0, Style2),
  347        list_to_set(Style2, Style)
  348    ;   Style = Style0
  349    ).
  350
  351styled_inline(b,      [bold]).
  352styled_inline(strong, [bold]).
  353styled_inline(em,     [bold]).
  354styled_inline(span,   []).
  355styled_inline(i,      [underline]).
  356styled_inline(a,      [underline]).
  357styled_inline(var,    []).
  358styled_inline(code,   []).
 words(+Tokens, +State)//
Generate a list of w(Word,Len,Attrs) and b(Len,_) terms for words and (breakable) white space.
  365words([], _) --> [].
  366words([""|T0], State) -->
  367    !,
  368    { skip_leading_spaces(T0, T) },
  369    space,
  370    words(T, State).
  371words([H|T], State) -->
  372    word(H, State),
  373    (   {T==[]}
  374    ->  []
  375    ;   { skip_leading_spaces(T, T1) },
  376        space,
  377        words(T1, State)
  378    ).
  379
  380skip_leading_spaces([""|T0], T) :-
  381    !,
  382    skip_leading_spaces(T0, T).
  383skip_leading_spaces(L, L).
  384
  385word(W, State) -->
  386    { string_length(W, Len),
  387      (   Style = State.get(style)
  388      ->  true
  389      ;   Style = []
  390      )
  391    },
  392    [w(W, Len, Style)].
  393
  394space -->
  395    [b(1,_)].
 join_whitespace(Elements, Joined)
Join consequtive space elements into a single white space element.
  401join_whitespace([], []).
  402join_whitespace([H0|T0], [H|T]) :-
  403    join_whitespace(H0, H, T0, T1),
  404    !,
  405    join_whitespace(T1, T).
  406join_whitespace([H|T0], [H|T]) :-
  407    join_whitespace(T0, T).
  408
  409join_whitespace(b(Len0,_), b(Len,_), T0, T) :-
  410    take_whitespace(T0, T, Len0, Len).
  411
  412take_whitespace([b(Len1,_)|T0], T, Len0, Len) :-
  413    !,
  414    Len2 is max(Len1,Len0),
  415    take_whitespace(T0, T, Len2, Len).
  416take_whitespace(L, L, Len, Len).
  417
  418
  419		 /*******************************
  420		 *       STATE MANAGEMENT	*
  421		 *******************************/
 update_style(+Style:list, +State0, -State)
Add Style to the current state.
  427update_style([], State, State) :-
  428    !.
  429update_style(Extra, State0, State) :-
  430    (   get_dict(style, State0, Style0, State, Style)
  431    ->  add_style(Extra, Style0, Style)
  432    ;   add_style(Extra, [], Style),
  433        put_dict(style, State0, Style, State)
  434    ).
  435
  436add_style(Extra, Style0, Style) :-
  437    reverse(Extra, RevExtra),
  438    foldl(add1_style, RevExtra, Style0, Style).
 add1_style(+New, +Style0, -Style) is det
Modify the current text style.
  444add1_style(New, Style0, Style) :-
  445    (   style_overrides(New, Add, Overrides)
  446    ->  delete_all(Overrides, Style0, Style1),
  447        append(Add, Style1, Style)
  448    ;   Style = [New|Style0]
  449    ).
  450
  451delete_all([], List, List).
  452delete_all([H|T], List0, List) :-
  453    delete(List0, H, List1),
  454    delete_all(T, List1, List).
  455
  456style_overrides(normal,           [],      [bold]).
  457style_overrides(fg(C),            [fg(C)], [fg(_), hfg(_)]).
  458style_overrides(bg(C),            [bg(C)], [bg(_), hbg(_)]).
  459style_overrides(underline(false), [],      [underline]).
  460
  461margins(Left, Right, State0, State) :-
  462    _{ margin_left:ML0, margin_right:MR0 } >:< State0,
  463    ML is ML0 + Left,
  464    MR is MR0 + Right,
  465    State = State0.put(_{margin_left:ML, margin_right:MR}).
  466
  467open_list(Type, State0, State) :-
  468    get_dict(list, State0, Lists, State, [Type|Lists]).
  469
  470update_state_par_properties([], State, State).
  471update_state_par_properties([H|T], State0, State) :-
  472    H =.. [ Key, Value ],
  473    State1 = State0.put(Key,Value),
  474    update_state_par_properties(T, State1, State).
 state_par_properties(+State, -ParProps)
Get the paragraph shape properties from State. Eventually these two should be merged!
  481state_par_properties(State, Props) :-
  482    Props0 = [ margin_left(LM),
  483               margin_right(RM),
  484               text_align(TA),
  485               width(W),
  486               pad(Pad)
  487             ],
  488    _{margin_left:LM, margin_right:RM, text_align:TA, width:W,
  489      pad:Pad} >:< State,
  490    filled_par_props(Props0, Props).
  491
  492filled_par_props([], []).
  493filled_par_props([H|T0], [H|T]) :-
  494    arg(1, H, A),
  495    nonvar(A),
  496    !,
  497    filled_par_props(T0, T).
  498filled_par_props([_|T0], T) :-
  499    filled_par_props(T0, T).
  500
  501
  502state_par_properties(State, Options, BlockOptions) :-
  503    state_par_properties(State, Options0),
  504    foldl(merge_par_option, Options, Options0, BlockOptions).
  505
  506merge_par_option(margin_left(ML0), Options0, [margin_left(ML)|Options1]) :-
  507    !,
  508    select_option(margin_left(ML1), Options0, Options1, 0),
  509    ML is ML0+ML1.
  510merge_par_option(margin_right(MR0), Options0, [margin_right(MR)|Options1]) :-
  511    !,
  512    select_option(margin_right(MR1), Options0, Options1, 0),
  513    MR is MR0+MR1.
  514merge_par_option(Opt, Options0, Options) :-
  515    merge_options([Opt], Options0, Options).
 emit_block(+Words, +Options, +State) is det
Format a block given Words inline elements, Options and State. Calls format_paragraph/2 after finalizing the paragraph shape and using the newline logic.
  523emit_block([], _, _) :-
  524    !.
  525emit_block(Words, Options, State) :-
  526    state_par_properties(State, Options, BlockOptions),
  527    use_current_position(BlockOptions, BlockOptions1),
  528    ask_nl(1),
  529    emit_nl,
  530    format_paragraph(Words, BlockOptions1),
  531    ask_nl(1).
  532
  533use_current_position(Options0, Options) :-
  534    nb_current(nl_pending, start),
  535    line_position(current_output, Pos),
  536    Pos > 0,
  537    !,
  538    Hang is -Pos,
  539    Options = [hang(Hang)|Options0].
  540use_current_position(Options, Options).
 init_nl is det
 init_nl(-State) is det
 exit_nl(+State) is det
Initialize/finalize the newline logic.
  549init_nl :-
  550    nb_setval(nl_pending, start).
  551
  552init_nl(Old) :-
  553    (   nb_current(nl_pending, Old)
  554    ->  true
  555    ;   Old = []
  556    ),
  557    nb_setval(nl_pending, start).
  558exit_nl(Old) :-
  559    nb_setval(nl_pending, Old).
  560
  561ask_nl(N) :-
  562    (   nb_current(nl_pending, N0)
  563    ->  (   N0 == start
  564        ->  true
  565        ;   integer(N0)
  566        ->  N1 is max(N0, N),
  567            nb_setval(nl_pending, N1)
  568        ;   nb_setval(nl_pending, N)
  569        )
  570    ;   nb_setval(nl_pending, N)
  571    ).
  572
  573emit_nl :-
  574    (   nb_current(nl_pending, N),
  575        integer(N)
  576    ->  forall(between(1,N,_), nl)
  577    ;   true
  578    ),
  579    nb_setval(nl_pending, 0).
  580
  581
  582		 /*******************************
  583		 *             PRE		*
  584		 *******************************/
 emit_code(+Content, +BlockAttrs, +State)
  588emit_code(Content, BlockAttrs, State) :-
  589    Style = State.style,
  590    split_string(Content, "\n", "", Lines),
  591    option(margin_left(LM0), BlockAttrs, 4),
  592    LM is LM0+State.margin_left,
  593    ask_nl(1),
  594    emit_nl,
  595    emit_code_lines(Lines, 1, LM, Style),
  596    ask_nl(1).
  597
  598emit_code_lines([], _, _, _).
  599emit_code_lines([H|T], LineNo, LM, Style) :-
  600    emit_code_line(H, LineNo, LM, Style),
  601    LineNo1 is LineNo + 1,
  602    emit_code_lines(T, LineNo1, LM, Style).
  603
  604emit_code_line(Line, _LineNo, LM, Style) :-
  605    emit_nl,
  606    emit_indent(LM),
  607    (   Style == []
  608    ->  write(Line)
  609    ;   ansi_format(Style, '~s', [Line])
  610    ),
  611    ask_nl(1).
  612
  613emit_indent(N) :-
  614    forall(between(1, N, _),
  615           put_char(' ')).
  616
  617
  618		 /*******************************
  619		 *            TABLES		*
  620		 *******************************/
 format_table(+Content, +Attrs, +BlockAttrs, +State) is det
  624format_table(Content, Attrs, BlockAttrs, State) :-
  625    tty_state(TTY),
  626    option(margin_left(ML), BlockAttrs, 0),
  627    option(margin_right(MR), BlockAttrs, 0),
  628    MaxTableWidth is State.width - ML - MR,
  629    table_cell_state(Attrs, State, CellState),
  630    phrase(rows(Content), Rows),
  631    columns(Rows, Columns),
  632    maplist(auto_column_width(CellState.put(tty,false)), Columns, Widths),
  633    column_widths(Widths, MaxTableWidth, ColWidths),
  634    maplist(format_row(ColWidths, CellState.put(tty,TTY), ML), Rows).
  635
  636tty_state(TTY) :-
  637    stream_property(current_output, tty(true)),
  638    !,
  639    TTY = true.
  640tty_state(false).
 column_widths(+AutoWidths, +MaxTableWidth, -Widths) is det
Establish the widths of the columns. AutoWidths is a list of widths for each of the columns if no folding is applied.
  648column_widths(Widths, MaxTableWidth, Widths) :-
  649    sum_list(Widths, AutoWidth),
  650    AutoWidth =< MaxTableWidth,
  651    !.
  652column_widths(AutoWidths, MaxTableWidth, Widths) :-
  653    sort(0, >=, AutoWidths, Sorted),
  654    append(Wrapped, Keep, Sorted),
  655    sum_list(Keep, KeepWidth),
  656    KeepWidth < MaxTableWidth/2,
  657    length(Wrapped, NWrapped),
  658    WideWidth is round((MaxTableWidth-KeepWidth)/NWrapped),
  659    (   [KeepW|_] = Keep
  660    ->  true
  661    ;   KeepW = 0
  662    ),
  663    !,
  664    maplist(truncate_column(KeepW,WideWidth), AutoWidths, Widths).
  665
  666truncate_column(Keep, WideWidth, AutoWidth, Width) :-
  667    (   AutoWidth =< Keep
  668    ->  Width = AutoWidth
  669    ;   Width = WideWidth
  670    ).
  671
  672table_cell_state(Attrs, State, CellState) :-
  673    (   element_css(table, Attrs, CSS)
  674    ->  true
  675    ;   CSS = []
  676    ),
  677    option(padding_left(PL), CSS, 1),
  678    option(padding_right(PR), CSS, 1),
  679    CellState = State.put(_{margin_left:PL, margin_right:PR}).
 rows(+Content, -Rows) is det
  684rows([]) --> [].
  685rows([H|T]) --> rows(H), rows(T).
  686rows([element(tbody,_,Content)|T]) --> rows(Content), rows(T).
  687rows([element(tr,Attrs,Columns)|T]) --> [row(Columns, Attrs)], rows(T).
 columns(+Rows, -Columns) is det
Transpose the table, filling missing columns with an empty td element as needed.
  694columns(Rows, Columns) :-
  695    columns(Rows, 1, Columns).
  696
  697columns(Rows, I, Columns) :-
  698    maplist(row_column(I, Found), Rows, H),
  699    (   Found == true
  700    ->  Columns = [H|T],
  701        I2 is I + 1,
  702        columns(Rows, I2, T)
  703    ;   Columns = []
  704    ).
  705
  706row_column(I, Found, row(Columns, _Attrs), Cell) :-
  707    (   nth1(I, Columns, Cell)
  708    ->  Found = true
  709    ;   Cell = element(td,[],[])
  710    ).
  711
  712auto_column_width(State, Col, Width) :-
  713    maplist(auto_cell_width(State), Col, Widths),
  714    max_list(Widths, Width).
  715
  716auto_cell_width(State, Cell, Width) :-
  717    cell_colspan(Cell, 1),
  718    !,
  719    format_cell_to_string(Cell, 1_000, State, String),
  720    split_string(String, "\n", "", Lines),
  721    maplist(string_length, Lines, LineW),
  722    max_list(LineW, Width0),
  723    Width is Width0 + State.margin_right.
  724auto_cell_width(_, _, 0).
 format_row(+ColWidths, +State, +MarginLeft, +Row)
Format a single row.
  730format_row(ColWidths, State, MarginLeft, Row) :-
  731    hrule(Row, ColWidths, MarginLeft),
  732    format_cells(ColWidths, CWSpanned, 1, Row, State, Cells),
  733    format_row_lines(1, CWSpanned, Cells, MarginLeft).
  734
  735hrule(row(_, Attrs), ColWidths, MarginLeft) :-
  736    attrs_classes(Attrs, Classes),
  737    memberchk(hline, Classes),
  738    !,
  739    sum_list(ColWidths, RuleLen),
  740    format('~N~t~*|~`-t~*+', [MarginLeft, RuleLen]).
  741hrule(_, _, _).
  742
  743format_row_lines(LineNo, Widths, Cells, MarginLeft) :-
  744    nth_row_line(Widths, 1, LineNo, Cells, CellLines, Found),
  745    (   Found == true
  746    ->  emit_nl,
  747        emit_indent(MarginLeft),
  748        maplist(emit_cell_line, CellLines),
  749        ask_nl(1),
  750        LineNo1 is LineNo + 1,
  751        format_row_lines(LineNo1, Widths, Cells, MarginLeft)
  752    ;   true
  753    ).
  754
  755emit_cell_line(Line-Pad) :-
  756    write(Line),
  757    forall(between(1,Pad,_), put_char(' ')).
  758
  759nth_row_line([], _, _, _, [], _).
  760nth_row_line([ColW|CWT], CellNo, LineNo, Cells, [CellLine-Pad|ColLines],
  761             Found) :-
  762    nth1(CellNo, Cells, CellLines),
  763    (   nth1(LineNo, CellLines, CellLine)
  764    ->  Found = true,
  765        Pad = 0
  766    ;   CellLine = '', Pad = ColW
  767    ),
  768    CellNo1 is CellNo + 1,
  769    nth_row_line(CWT, CellNo1, LineNo, Cells, ColLines, Found).
 format_cells(+ColWidths, -CWSpanned, +Col0, +Row, +State, -Cells)
Format the cells for Row. The resulting Cells list is a list of cells, where each cell is a list of strings, each representing a line.
  778format_cells([], [], _, _, _, []) :- !.
  779format_cells(CWidths, [HW|TW], Column, Row, State, [HC|TC]) :-
  780    Row = row(Columns, _Attrs),
  781    nth1(Column, Columns, Cell),
  782    cell_colspan(Cell, CWidths, HW, TW0),
  783    cell_align(Cell, Align),
  784    format_cell_to_string(Cell, HW, State.put(_{pad:' ', text_align:Align}), String),
  785    split_string(String, "\n", "", HC),
  786    Column1 is Column+1,
  787    format_cells(TW0, TW, Column1, Row, State, TC).
  788
  789cell_colspan(Cell, CWidths, HW, TW) :-
  790    cell_colspan(Cell, Span),
  791    length(SpanW, Span),
  792    append(SpanW, TW, CWidths),
  793    sum_list(SpanW, HW).
  794
  795cell_colspan(element(_,Attrs,_), Span) :-
  796    (   memberchk(colspan=SpanA, Attrs),
  797        atom_number(SpanA, SpanN)
  798    ->  Span = SpanN
  799    ;   Span = 1
  800    ).
 cell_align(+Cell, -Align) is det
Determine the cell alignment. Currently supports the (deprecated) HTML4 align=Align possibility and very naively parsed CSS text-align:center, etc.
  808cell_align(element(_,Attrs,_), Align) :-
  809    (   memberchk(align=AlignA, Attrs)
  810    ->  Align = AlignA
  811    ;   memberchk(style=Style, Attrs),
  812        style_css_attrs(Style, Props),
  813        memberchk('text-align'(AlignA), Props)
  814    ->  Align = AlignA
  815    ;   Align = left
  816    ).
 format_cell_to_string(+Cell, +ColWidth, +State, -String) is det
Format Cell to a String, given the state and column width.
  823format_cell_to_string(element(_,_,[]), ColWidth, State, String) :-
  824    Pad = State.get(pad),
  825    !,
  826    length(Chars, ColWidth),
  827    maplist(=(Pad), Chars),
  828    atomics_to_string(Chars, String).
  829format_cell_to_string(Cell, ColWidth, State, String) :-
  830    setup_call_cleanup(
  831        init_nl(NlState),
  832        with_output_to(
  833            string(String),
  834            format_cell(Cell, ColWidth, State)),
  835        exit_nl(NlState)).
  836
  837format_cell(element(E, _Attrs, Content), ColWidth, State) :-
  838    set_stream(current_output, tty(State.tty)),
  839    cell_element(E, Style),
  840    update_style(Style, State.put(width, ColWidth), CellState),
  841    block_words(Content, Blocks, Words, CellState),
  842    emit_block(Words, [], CellState),
  843    (   Blocks \== []
  844    ->  format_dom(Blocks, CellState)
  845    ;   true
  846    ).
  847
  848cell_element(td, [normal]).
  849cell_element(th, [bold]).
 emit_hr(+Attrs, +BlockOptions, +State)
Emit a horizontal rule.
  856emit_hr(_Attrs, BlockAttrs, State) :-
  857    option(margin_left(ML), BlockAttrs, 0),
  858    option(margin_right(MR), BlockAttrs, 0),
  859    RuleWidth is State.width - ML - MR,
  860    Style = State.style,
  861    emit_indent(ML),
  862    (   Style == []
  863    ->  format('~|~*t~*+', [0'-, RuleWidth])
  864    ;   ansi_format(Style, '~|~*t~*+', [0'-, RuleWidth])
  865    )