1/*  Part of Extended Tools for SWI-Prolog
    2
    3    Author:        Edison Mera
    4    E-mail:        efmera@gmail.com
    5    WWW:           https://github.com/edisonm/xtools
    6    Copyright (C): 2015, Process Design Center, Breda, The Netherlands.
    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(ws_cover, [cache_file_lines/0]).   36
   37:- reexport(library(ws_browser)).   38:- use_module(library(ntabling)).   39:- use_module(library(apply)).   40:- use_module(library(gcover)).   41:- use_module(library(lists)).   42:- use_module(library(pairs)).   43:- use_module(library(solution_sequences)).   44:- use_module(library(http/html_write)).   45:- use_module(library(module_files)).   46:- use_module(library(pldoc/doc_htmlsrc)).   47
   48ws_browser:provides_method(gcover).
   49
   50:- table
   51       cov_source_file/1,
   52       source_file_line/4.   53
   54ws_browser:fetch_files_properties_hook(gcover, [ccov, clss, lcov, lits], FileMG) :-
   55    findall(File-[CCov, Clss, LCov, Lits],
   56            ( source_file(File),
   57              cover_info(File, CCov, Clss, LCov, Lits)
   58            ), FileMU),
   59    sort(FileMU, FileML),
   60    group_pairs_by_key(FileML, FileMG).
   61
   62cov_source_file(File) :-
   63    distinct(File, covered_db(File, _, _, _, _, _)).
   64
   65cache_file_lines :-
   66    findall(File, cov_source_file(File), FileL),
   67    length(FileL, N),
   68    forall(nth1(I, FileL, File),
   69           ( format(user_error, "Caching ~w of ~w files\r", [I, N]),
   70             ignore(source_file_line(File, _, _, _))
   71           )),
   72    nl(user_error).
   73
   74cover_info(File, CCov, Clss, LCov, Lits) :-
   75    CountC = count(0, 0),
   76    CountL = count(0, 0),
   77    ( source_file_line(File, L1, L2, Scope),
   78      ( Scope = cl(_)
   79      ->Count = CountC
   80      ; Count = CountL
   81      ),
   82      Count = count(C1, N1),
   83      succ(N1, N),
   84      nb_setarg(2, Count, N),
   85      ( covered_db(File, L1, L2, _, _, _)
   86      ->succ(C1, C),
   87        nb_setarg(1, Count, C)
   88      ; true
   89      ),
   90      fail
   91    ; true
   92    ),
   93    CountC = count(CCov, Clss),
   94    CountL = count(LCov, Lits).
 ports_color(List:list(pair), Color:atm)
Convention: the color that affects the clause should be darker than those that affects only literals.

Keep the order since it is the priority.

  103ports_color([(success)-_, failure-_, multi-_], lightpink).
  104ports_color([(success)-_, multi-_],            yellowgreen).
  105ports_color([(success)-_, failure-_],          orange).
  106ports_color([uncovered-[cl(_)-_]],             bisque).
  107ports_color([(exit)-_,    fail-_],             yellow).
  108ports_color([(exit)-_,    call-_],             lime).
  109ports_color([Port-_], Color) :- port_color(Port, Color).
  110
  111port_color(exception,    red).
  112port_color(exception(_), red).
  113port_color(failure,      orangered).
  114port_color(success,      greenyellow).
  115port_color(multi,        green).
  116port_color(fail,         fuchsia).
  117port_color(redo,         lightblue).
  118port_color(redoi,        cyan).
  119port_color(exit,         greenyellow).
  120port_color(call,         darkgreen).
  121% Note that exitcl and unify are converted to failure and success:
  122port_color(exitcl,       orchid).
  123port_color(unify,        orange).
  124port_color(uncovered,    white).
  125
  126ws_browser:show_source_hook(gcover, File) :-
  127    format('Content-type: text/html~n~n', []),
  128    source_to_html(File, stream(current_output),
  129                   [format_comments(true), skin(coverage_js(File))]).
  130
  131source_file_line(File, L1, L2, Scope) :-
  132    file_clause(File, Ref),
  133    source_clause_line(File, Ref, L1, L2, Scope).
  134
  135clause_id(Ref, File, CI) :-
  136    nth_clause(M:H, I, Ref),
  137    functor(H, F, A),
  138    ( module_file(M, File)
  139    ->CI = F/A-I
  140    ; CI = M:F/A-I
  141    ).
  142
  143source_clause_line(File, Ref, L1, L2, cl(CI)) :-
  144    clause_id(Ref, File, CI),
  145    clause_property(Ref, line_count(L1)),
  146    loc_file_line(clause(Ref), File, L1, L2).
  147source_clause_line(File, Ref, L1, L2, lt(TInstr)) :-
  148    '$break_pc'(Ref, PC1, _NextPC1),
  149    '$fetch_vm'(Ref, PC1, PC, TInstr),
  150    \+ skip_instr(TInstr),
  151    loc_file_line(clause_pc(Ref, PC), File, L1, L2).
  152
  153skip_instr(i_cut).
  154skip_instr(i_enter).
  155skip_instr(i_exit).
  156
  157file_clause(File, Ref) :-
  158    current_predicate(M:F/A),
  159    functor(H, F, A),
  160    \+ predicate_property(M:H, imported_from(_)),
  161    \+ predicate_property(M:H, dynamic),
  162    nth_clause(M:H, _, Ref),
  163    clause_property(Ref, file(File)).
 covered(+File, -L1, -L2, -Port, -Tag, -Count)
Get on backtracking coverage information per each line, and the Port that has been tried in the program point specified by File, L1 and L2, including uncovered which is used to detect if such code has been covered or not, in such case the Tag can be clause or literal, depending if is the clause or the literal that has not been covered. Note that could happend that a covered line does not have an 'uncovered' entry, for instance if at some late point the system was unable to get the program point.
  175covered(File, L1, L2, Port, Tag, Count) :-
  176    covered_db(File, L1, L2, Port, Tag, Count).
  177covered(File, L1, L2, uncovered, Scope, 0) :-
  178    source_file_line(File, L1, L2, Scope).
  179
  180property_lines(File, List, Tail) :-
  181    findall((L1-L2)-(Port-(Tag-Count)),
  182            covered(File, L1, L2, Port, Tag, Count),
  183            Pairs),
  184    sort(Pairs, Sorted),
  185    group_pairs_by_key(Sorted, Grouped),
  186    foldl(property_lines_each, Grouped, List, Tail).
  187
  188porttags_color(Pairs, Color) :-
  189    ports_color(Ports, Color),
  190    subset(Ports, Pairs).
  191
  192property_lines_each((L1-L2)-PortTagCL) -->
  193    { group_pairs_by_key(PortTagCL, PortTagCGU),
  194      ( subtract(PortTagCGU, [uncovered-_], PortTagCG),
  195        PortTagCG \= []
  196      ->true
  197      ; PortTagCG = PortTagCGU
  198      ),
  199      once(porttags_color(PortTagCG, Color)),
  200      findall(L, between(L1, L2, L), LineL)
  201    },
  202    foldl(line_color(Color), LineL),
  203    ['  tT["', L1, '"]="'],
  204    foldl(port_tags_text, PortTagCG),
  205    ['";\n'].
  206
  207line_color(Color, Line) --> ['  lC["', Line, '"]="', Color, '";\n'].
  208
  209port_tags_text(Port-TagCL) -->
  210    { group_pairs_by_key(TagCL, TagCG),
  211      maplist(tag_count, TagCG, TagC)
  212    },
  213    [Port, ":", TagC,"\\n"].
  214
  215tag_count(Tag-L, Tag:S) :-
  216    sum_list(L, S).
  217
  218:- public coverage_js/3.  219
  220coverage_js(File, header, Out) :-
  221    phrase(html([script([type('text/javascript')
  222                        ],
  223                        ['function updateColorLine(){\n',
  224                         '  var lC={};\n',
  225                         '  var tT={};\n',
  226                         \property_lines(File),
  227                         '  elements=document.getElementsByClassName("line-no");\n',
  228                         '  for (var i=0; i < elements.length; i++) {\n',
  229                         '    var key=elements[i].innerText.trim();\n',
  230                         '    if (typeof lC[key] !== \'undefined\') {\n',
  231                         '      elements[i].style.backgroundColor=lC[key];\n',
  232                         '    };\n',
  233                         '    if (typeof tT[key] !== \'undefined\') {\n',
  234                         '      elements[i].style.textDecoration="underline";\n',
  235                         '      elements[i].classList.add("tooltip");\n',
  236                         '      var t=document.createElement("span");\n',
  237                         '      t.classList.add("tooltiptext");\n',
  238                         '      t.classList.add("tooltiptext::after");\n',
  239                         '      t.classList.add("tooltip-right");\n',
  240                         '      var content=document.createTextNode(tT[key]);\n',
  241                         '      t.appendChild(content);\n',
  242                         '      elements[i].appendChild(t);\n',
  243                         '    }\n',
  244                         '  }\n',
  245                         '}\n'
  246                        ]),
  247                 style([],
  248                       [
  249"
  250span.directive {
  251    display: inline;
  252}
  253
  254.tooltip {
  255    position: relative;
  256    display: inline-block;
  257    border-bottom: 1px dotted #ccc;
  258    color: #006080;
  259}
  260
  261.tooltip .tooltiptext {
  262    visibility: hidden;
  263    position: absolute;
  264    //width: 120px;
  265    background-color: dimgray;
  266    color: white;
  267    text-align: center;
  268    padding: 5px 0;
  269    border-radius: 6px;
  270    z-index: 1;
  271    opacity: 0;
  272    transition: opacity 1s;
  273}
  274
  275.tooltip:hover .tooltiptext {
  276    visibility: visible;
  277    opacity: 1;
  278}
  279
  280.tooltip-right {
  281  top: -5px;
  282  left: 125%;  
  283}
  284
  285.tooltip-right::after {
  286    content: "";
  287    position: absolute;
  288    top: 50%;
  289    right: 100%;
  290    margin-top: -5px;
  291    border-width: 5px;
  292    border-style: solid;
  293    border-color: transparent #555 transparent transparent;
  294}
  295
  296.tooltip-bottom {
  297  top: 135%;
  298  left: 50%;  
  299  margin-left: -60px;
  300}
  301
  302.tooltip-bottom::after {
  303    content: "";
  304    position: absolute;
  305    bottom: 100%;
  306    left: 50%;
  307    margin-left: -5px;
  308    border-width: 5px;
  309    border-style: solid;
  310    border-color: transparent transparent #555 transparent;
  311}
  312
  313.tooltip-top {
  314  bottom: 125%;
  315  left: 50%;  
  316  margin-left: -60px;
  317}
  318
  319.tooltip-top::after {
  320    content: "";
  321    position: absolute;
  322    top: 100%;
  323    left: 50%;
  324    margin-left: -5px;
  325    border-width: 5px;
  326    border-style: solid;
  327    border-color: #555 transparent transparent transparent;
  328}
  329
  330.tooltip-left {
  331  top: -5px;
  332  bottom:auto;
  333  right: 128%;  
  334}
  335.tooltip-left::after {
  336    content: "";
  337    position: absolute;
  338    top: 50%;
  339    left: 100%;
  340    margin-top: -5px;
  341    border-width: 5px;
  342    border-style: solid;
  343    border-color: transparent transparent transparent #555;
  344}
  345"
  346                       ])
  347                ]), Tokens),
  348    print_html(Out, Tokens).
  349coverage_js(_, footer, Out) :-
  350    phrase(html(script([type('text/javascript')
  351                       ],
  352                       ['updateColorLine();'])
  353               ), Tokens),
  354    print_html(Out, Tokens)