View source with raw comments or as raw
    1/*  Part of sCASP
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        jan@swi-prolog.org
    5    Copyright (c)  2021, SWI-Prolog Solutions b.v.
    6    All rights reserved.
    7
    8    Redistribution and use in source and binary forms, with or without
    9    modification, are permitted provided that the following conditions
   10    are met:
   11
   12    1. Redistributions of source code must retain the above copyright
   13       notice, this list of conditions and the following disclaimer.
   14
   15    2. Redistributions in binary form must reproduce the above copyright
   16       notice, this list of conditions and the following disclaimer in
   17       the documentation and/or other materials provided with the
   18       distribution.
   19
   20    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   21    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   22    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   23    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   24    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   25    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   26    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   27    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   28    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   29    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   30    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   31    POSSIBILITY OF SUCH DAMAGE.
   32*/
   33
   34:- module(scasp_html_text,
   35          [ emit_as//2,
   36            emitting_as/1,
   37            emit//1,
   38            fixup_layout/2              % +Tokens,-Final
   39          ]).   40:- use_module(library(dcg/high_order)).   41:- use_module(library(http/html_write)).   42:- use_module(library(apply)).   43:- use_module(library(error)).   44:- use_module(library(lists)).   45
   46:- html_meta
   47    emit_as(html, +, ?, ?),
   48    emit(html, ?, ?).

Switch between HTML and plain text output

Allow generating plain (colored) text from html//1 compatible calls. We do this in two steps, first creating a token list and next deal with state using fixup_layout/2. It would be nicer if we could avoid the latter step, but we need to maintain state such as indentation and attributes and we cannot pass that around in an additional argument as there are calls that do not know about this transformation in between.

The translation is highly specific for the calls done in html.pl. If you change CSS classes or the HTML DOM produced you likely have to make changes here as well.

To be done
- It might be better to maintain a stack of parent DOM nodes in a backtrackable global variable to deal with the state. */
 emit_as(+HTML, +Mode)//
Causes all emit//1 calls to either behave as html//1 or convert the commands to output for print_message_lines/3.
   72emit_as(Goal, Mode) -->
   73    { must_be(oneof([plain,html]), Mode) },
   74    html(Goal),
   75    {no_lco(Mode)}.
   76
   77no_lco(_).
 emitting_as(-Mode)
Current emit mode. One of plain or html
   83emitting_as(Mode) :-
   84    prolog_current_frame(F),
   85    prolog_frame_attribute(F, parent_goal, emit_as(_, Mode, _, _)).
 emit(:HTML)
Emits HTML or message line elements depending on emit_as//2.
   91emit(M:Spec) -->
   92    { emitting_as(plain)
   93    },
   94    !,
   95    emit(Spec, M).
   96emit(Spec) -->
   97    html(Spec).
   98
   99emit(Var, _) -->
  100    { var(Var) },
  101    !,
  102    [ '~p'-[Var] ].
  103emit(List, M) -->
  104    { is_list(List) },
  105    !,
  106    sequence(emit_r(M), List).
  107emit(\Goal, M) -->
  108    { callable(Goal) },
  109    !,
  110    call(M:Goal).
  111emit(Element, _M) -->
  112    { is_machine(Element)
  113    },
  114    !.
  115emit(var(Name), _M) -->
  116    !,
  117    [ ansi(fg(magenta), '~w', [Name]) ].
  118emit(span(Content), M) -->
  119    !,
  120    emit(Content, M).
  121emit(span(Attrs, Content), M) -->
  122    !,
  123    (   classes_ansi(Attrs)
  124    ->  emit(Content, M),
  125        [pop_ansi]
  126    ;   emit(Content, M)
  127    ).
  128emit(div(Attrs, Content), M) -->
  129    { has_class(Attrs, 'scasp-query-literal') },
  130    !,
  131    [indent(3)],
  132    emit(Content, M),
  133    [indent(-3), nl(1)].
  134emit(div(Attrs, Content), M) -->
  135    !,
  136    classes_pre_lines(Attrs),
  137    (   classes_bullet(Attrs)
  138    ->  emit(Content, M),
  139        [bullet(pop)]
  140    ;   emit(Content, M)
  141    ),
  142    [nl(1)].
  143emit(div(Content), M) -->
  144    !,
  145    emit(Content, M),
  146    [nl(1)].
  147emit(ul(_Attrs, LIs), M) -->
  148    !,
  149    [indent(3)],
  150    emit(LIs, M),
  151    [indent(-3)].
  152emit(li(_Attrs, Content), M) -->
  153    !,
  154    [bullet],
  155    emit(Content, M),
  156    [nl(1)].
  157emit(li(Content), M) -->
  158    !,
  159    [bullet],
  160    emit(Content, M),
  161    [nl(1)].
  162emit(Fmt-Args, _M) -->
  163    !,
  164    [ Fmt-Args ].
  165emit(Atomic, _M) -->
  166    !,
  167    [ '~w'-[Atomic] ].
  168
  169emit_r(M, Spec) -->
  170    emit(Spec, M).
  171
  172is_machine(Element) :-
  173    compound(Element),
  174    functor(Element, _, 2),
  175    arg(1, Element, Attrs),
  176    has_class(Attrs, machine).
  177
  178classes_ansi(Attrs) -->
  179    { classes(Attrs, Classes),
  180      include(truth_class, Classes, TClasses),
  181      sort(TClasses, TClassesS),
  182      classes_ansi_map(TClassesS, Ansi)
  183    },
  184    !,
  185    [ansi(Ansi)].
  186
  187classes_bullet(Attrs) -->
  188    { has_class(Attrs, 'scasp-justification') },
  189    !,
  190    [ bullet('') ].
  191
  192classes_pre_lines(Attrs) -->
  193    { has_class(Attrs, 'scasp-predicate') },
  194    !,
  195    [ nl(1) ].
  196classes_pre_lines(_) -->
  197    [].
  198
  199has_class(Attrs, Class) :-
  200    classes(Attrs, Classes),
  201    memberchk(Class, Classes).
  202
  203classes(Attrs, Classes) :-
  204    (   is_list(Attrs)
  205    ->  include(is_class, Attrs, ClassAttrs),
  206        maplist(arg(1), ClassAttrs, Classes0),
  207        flatten(Classes0, Classes)
  208    ;   Attrs = class(Classes0),
  209        (   is_list(Classes0)
  210        ->  Classes = Classes0
  211        ;   Classes = [Classes0]
  212        )
  213    ).
  214
  215is_class(class(_)).
  216
  217truth_class(pos).
  218truth_class(not).
  219truth_class(neg).
  220
  221classes_ansi_map([neg],     [fg(red), bold]).
  222%classes_ansi_map([neg,not], []).
  223classes_ansi_map([not],     [fg(red)]).
  224classes_ansi_map([pos],     [bold]).
 fixup_layout(+Tokens, -Final)
Fixup layout instructions in the token list.
  230:- det(fixup_layout/2).  231
  232fixup_layout(Tokens, Final) :-
  233    fixup_layout(Tokens, Final,
  234                 #{ indent:0,
  235                    ansi:[], ansi_stack:[],
  236                    bullet:['\u2022']
  237                  }).
  238
  239fixup_layout([], [], _).
  240fixup_layout([nl(Lines0)|T0], Final, State) :-
  241    !,
  242    Indent0 = State.indent,
  243    join_blank_lines(T0, T1, Indent0, Indent, Lines0, Lines),
  244    skip_lines(Lines, Final, T),
  245    (   T1 == []
  246    ->  T = []
  247    ;   Indent > 0
  248    ->  format(atom(I), '~t~*|', [Indent]),
  249        T = [I|T2]
  250    ;   T = T2
  251    ),
  252    fixup_layout(T1, T2, State.put(indent, Indent)).
  253fixup_layout([indent(N)|T0], T, State) :-
  254    !,
  255    Indent is State.indent+N,
  256    indent(Indent, T, T1),
  257    fixup_layout(T0, T1, State.put(indent, Indent)).
  258fixup_layout([bullet|T0], T, State) :-
  259    !,
  260    [Bullet|_] = State.bullet,
  261    (   Bullet == ''
  262    ->  fixup_layout(T0, T, State)
  263    ;   T = ['~w '-[Bullet]|T1],
  264        fixup_layout(T0, T1, State)
  265    ).
  266fixup_layout([bullet(Bullet)|T0], T, State) :-
  267    !,
  268    Stack = State.bullet,
  269    (   Bullet == pop
  270    ->  Stack = [_|NewStack]
  271    ;   NewStack = [Bullet|Stack]
  272    ),
  273    fixup_layout(T0, T, State.put(bullet, NewStack)).
  274fixup_layout([ansi(Attrs)|T0], T, State) :-
  275    !,
  276    Old = State.ansi,
  277    Stack = State.ansi_stack,
  278    append(Attrs, Old, New),
  279    fixup_layout(T0, T, State.put(#{ansi:New, ansi_stack:[Old|Stack]})).
  280fixup_layout([pop_ansi|T0], T, State) :-
  281    !,
  282    [Old|Stack] = State.ansi_stack,
  283    fixup_layout(T0, T, State.put(#{ansi:Old, ansi_stack:Stack})).
  284fixup_layout([H0|T0], [H|T], State) :-
  285    fixup_element(H0, H, State.ansi),
  286    fixup_layout(T0, T, State).
  287
  288fixup_element(E, E, []) :-
  289    !.
  290fixup_element(Fmt-Args, ansi(Ansi, Fmt, Args), Ansi) :-
  291    !.
  292fixup_element(E, E, _).
 join_blank_lines(+Tokens, -RestTokens, +Indent0, -Indent, +Lines0, -Lines) is det
Deal with a sequence of nl(N) and indent(Incr) tokens, computing the next relevant indentation and the number of newlines to insert.
  300join_blank_lines([nl(N)|T0], T, I0, I, Lines0, Lines) :-
  301    !,
  302    Lines1 is max(N, Lines0),
  303    join_blank_lines(T0, T, I0, I, Lines1, Lines).
  304join_blank_lines([indent(N)|T0], T, I0, I, Lines0, Lines) :-
  305    !,
  306    I1 is I0+N,
  307    join_blank_lines(T0, T, I1, I, Lines0, Lines).
  308join_blank_lines(L, L, I, I, Lines, Lines).
  309
  310indent(I, [Spaces|T], T) :-
  311    I > 0,
  312    !,
  313    format(atom(Spaces), '~t~*|', [I]).
  314indent(_, L, L).
  315
  316skip_lines(N, [nl|L0], L) :-
  317    succ(N1, N),
  318    !,
  319    skip_lines(N1, L0, L).
  320skip_lines(_, L, L)