View source with formatted comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        jan@swi-prolog.org
    5    WWW:           https://www.swi-prolog.org
    6    Copyright (c)  2006-2024, University of Amsterdam
    7                              VU University Amsterdam
    8                              SWI-Prolog Solutions b.v.
    9    All rights reserved.
   10
   11    Redistribution and use in source and binary forms, with or without
   12    modification, are permitted provided that the following conditions
   13    are met:
   14
   15    1. Redistributions of source code must retain the above copyright
   16       notice, this list of conditions and the following disclaimer.
   17
   18    2. Redistributions in binary form must reproduce the above copyright
   19       notice, this list of conditions and the following disclaimer in
   20       the documentation and/or other materials provided with the
   21       distribution.
   22
   23    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   24    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   25    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   26    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   27    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   28    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   29    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   30    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   31    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   32    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   33    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   34    POSSIBILITY OF SUCH DAMAGE.
   35*/
   36
   37:- module(prolog_coverage,
   38          [ coverage/1,                 % :Goal
   39            coverage/2,                 % :Goal, +Options
   40            show_coverage/1,            % :Options
   41            show_coverage/2,            % :Goal, +Options (deprecated)
   42            cov_save_data/2,            % +File, +Options
   43            cov_load_data/2,            % +File, +Options
   44            cov_reset/0,                %
   45            cov_property/1              % ?Property
   46          ]).   47:- autoload(library(apply),
   48            [exclude/3, maplist/2, convlist/3, maplist/3, maplist/4]).   49:- autoload(library(ordsets), [ord_intersection/3, ord_subtract/3, ord_union/3]).   50:- autoload(library(pairs),
   51            [ group_pairs_by_key/2,
   52              pairs_keys_values/3,
   53              pairs_values/2,
   54              map_list_to_pairs/3
   55            ]).   56:- autoload(library(ansi_term), [ansi_format/3]).   57:- autoload(library(filesex), [directory_file_path/3, make_directory_path/1]).   58:- autoload(library(lists),
   59            [append/3, flatten/2, max_list/2, member/2, append/2, sum_list/2]).   60:- autoload(library(option), [option/2, option/3]).   61:- autoload(library(readutil), [read_line_to_string/2]).   62:- use_module(library(prolog_breakpoints), []).   63:- autoload(library(prolog_clause), [clause_info/4]).   64:- autoload(library(solution_sequences), [call_nth/2, distinct/2]).   65:- use_module(library(debug), [debug/3, assertion/1]).   66:- autoload(library(error), [must_be/2]).   67:- autoload(library(prolog_code), [pi_head/2]).   68:- autoload(library(terms), [mapsubterms/3]).   69
   70:- set_prolog_flag(generate_debug_info, false).   71
   72/** <module> Coverage analysis tool
   73
   74The purpose of this module is to find which part of the program has been
   75used by a certain goal. Usage is defined   in terms of clauses for which
   76the _head unification_ succeeded. For each clause  we count how often it
   77succeeded and how often it  failed.  In   addition  we  track  all _call
   78sites_, creating goal-by-goal annotated clauses.
   79
   80The result is  represented  as  a   list  of  clause-references.  As the
   81references to clauses of dynamic predicates  cannot be guaranteed, these
   82are omitted from the result.
   83
   84Using coverage/2 with the option annotate(true),  implied by ext(Ext) or
   85dir(Dir), the analysis creates a line-by-line   copy of the source files
   86that is annotated with how many times   this  line was executed and with
   87what logical results. These annotations rely on relating executable code
   88to source locations which is shared by the source level debugger. Source
   89level rewrites due to term or goal expansion may harm the results.
   90
   91The typical usage is to load the program  and run the query below to get
   92a report by  file  with  percentages   and  a  directory  `cov`  holding
   93annotated   files   that   provide     line-by-line   annotations.   See
   94show_coverage/1 for details.
   95
   96   ?- coverage(Goal, [dir(cov)]).
   97
   98## Coverage collection and threads {#coverage-threads}
   99
  100The coverage collect data structure is   shared  by threads created from
  101the thread that is collecting  coverage   data.  Currently,  this thread
  102should be _joined_ before we can operate on the coverage data.
  103
  104## Combining coverage data from multiple runs {#coverage-merge}
  105
  106The coverage tools allow  both  combining   data  from  running multiple
  107queries as combining data from multiple Prolog processes.
  108
  109For multiple queries in the same process, coverage data may be collected
  110using  coverage/1  which,  unlike  coverage/2,    does  not  change  the
  111non-deterministic semantics of the  `Goal`  and   adds  to  the  already
  112collected data. If no current collection   is in progress, the currently
  113collected data can be displayed using show_coverage/1.
  114
  115Coverage data may be saved to a   file using cov_save_data/2. Saved data
  116can be reloaded using cov_load_data/2. Data   from  multiple Prolog runs
  117can be combined  in  the  same   file  using  cov_save_data/2  with  the
  118append(true) option. When possible, file locking  is used to ensure that
  119concurrect processes can safely use the same   data file. The result can
  120be shown by loading  the  code  that   was  relevant  to  all  runs, use
  121cov_load_data/2 and show the result using show_coverage/1.
  122
  123Note that saving  an  loading  the   coverage  data  saves  and restores
  124references to the clauses as the Nth clause  of a predicate defined in a
  125specific file. This implies that the program   must be loaded in exactly
  126the same way, including  optimization   level,  term/goal  expansion and
  127order of _multifile_ predicates.
  128
  129## Predicate reference {#coverage-predicates}
  130*/
  131
  132:- meta_predicate
  133    coverage(0),
  134    coverage(0,+),                      % :Goal, +Options
  135    show_coverage(:),                   % +Options
  136    show_coverage(0,+).                 % :Goal, +Options (deprecated)
  137
  138:- predicate_options(show_coverage/1, 1,
  139                     [ all(boolean),
  140                       modules(list(atom)),
  141                       roots(list),
  142                       annotate(boolean),
  143                       ext(atom),
  144                       dir(atom),
  145                       line_numbers(boolean),
  146                       color(boolean)
  147                     ]).  148:- predicate_options(coverage/2, 2,
  149                     [ show(boolean),
  150                       pass_to(prolog_coverage:show_coverage/1,1)
  151                     ]).  152:- predicate_options(cov_save_data/2, 2,
  153                     [ append(boolean)
  154                     ]).  155:- predicate_options(cov_load_data/2, 2,
  156                     [ load(boolean),
  157                       silent(boolean)
  158                     ]).  159
  160
  161%!  coverage(:Goal)
  162%
  163%   As  call(Goal),  collecting  coverage  information   while  Goal  is
  164%   running. If Goal succeeds with a   choice point, coverage collection
  165%   is suspended and  resumed  if  we   backtrack  into  Goal.  Calls to
  166%   coverage/1 may be nested.
  167
  168coverage(Goal) :-
  169    setup_call_cleanup(
  170        '$cov_start'(Level),
  171        cov_run(Goal, Level),
  172        '$cov_stop'(Level)).
  173
  174cov_run(Goal, Level) :-
  175    call(Goal),
  176    deterministic(Det),
  177    (   Det == true
  178    ->  true
  179    ;   (   '$cov_stop'(Level)
  180        ;   '$cov_start'(Level),
  181            fail
  182        )
  183    ).
  184
  185%!  coverage(:Goal, +Options) is semidet.
  186%
  187%   Collect and optionally report coverage by  Goal. Goal is executed as
  188%   in once/1. Options processed:
  189%
  190%     - show(+Boolean)
  191%       When `true` (default), call show_coverage/1 passing Options
  192%       to show the collected coverage data and reset the data.  When
  193%       `false`, collect the data but do not reset it.  If there is
  194%       already existing data the new data is added.
  195
  196coverage(Goal, Options) :-
  197    clean_output(Options),
  198    setup_call_cleanup(
  199        '$cov_start'(Level),
  200        once(Goal),
  201        cov_finish(Level, Options)).
  202
  203show_coverage(Goal, Options) :-
  204    print_message(warning, coverage(deprecated(show_coverage/2))),
  205    coverage(Goal, Options).
  206
  207cov_finish(Level, Options) :-
  208    option(show(true), Options, true),
  209    !,
  210    '$cov_stop'(Level),
  211    (   Level == 1
  212    ->  show_coverage(Options),
  213        cov_reset
  214    ;   true
  215    ).
  216cov_finish(Level, _) :-
  217    '$cov_stop'(Level).
  218
  219
  220%!  show_coverage(+Options) is det.
  221%
  222%   Show collected coverage data. By default   it reports the percentage
  223%   of called and  failed  clauses  related   to  covered  files.  Using
  224%   dir(Dir), detailed line-by-line annotated files   are created in the
  225%   directory Dir.  Other options control the level of detail.
  226%
  227%     - all(+Boolean)
  228%       When true, report on any file in which some predicate was
  229%       called.
  230%     - modules(+Modules)
  231%       Only report on files that implement one of the given Modules.
  232%     - roots(+Directories)
  233%       Only report on files below one of the given roots.  Each
  234%       directory in Directories can be a specification for
  235%       absolute_file_name/3.
  236%     - annotate(+Bool)
  237%       Create an annotated file for the detailed results.
  238%       This is implied if the `ext` or `dir` option are
  239%       specified.
  240%     - ext(+Ext)
  241%       Extension to use for the annotated file. Default is
  242%       `.cov`.
  243%     - dir(+Dir)
  244%       Dump the annotations in the given directory.  If not
  245%       given, the annotated files are created in the same
  246%       directory as the source file.   Each clause that is
  247%       related to a physical line in the file is annotated
  248%       with one of:
  249%
  250%         | ###  | Clause was never executed.                       |
  251%         | ++N  | Clause was entered N times and always succeeded  |
  252%         | --N  | Clause was entered N times and never succeeded   |
  253%         | +N-M | Clause has succeeded N times and failed M times  |
  254%         | +N*M | Clause was entered N times and succeeded M times |
  255%
  256%       All _call sites_ are annotated using the same conventions,
  257%       except that `---` is used to annotate subgoals that were
  258%       never called.
  259%     - line_numbers(Boolean)
  260%       If `true` (default), add line numbers to the annotated file.
  261%     - color(Boolean)
  262%       Controls using ANSI escape sequences to color the output
  263%       in the annotated source.  Default is `true`.
  264%     - width(+Columns)
  265%       Presumed width of the output window.  A value of 40 is
  266%       considered the minimum.  Smaller values are handled as 40.
  267%
  268%   For example, run a goal and create   annotated  files in a directory
  269%   `cov` using:
  270%
  271%       ?- show_coverage([dir(cov)]).
  272%
  273%   @bug Color annotations are created using   ANSI escape sequences. On
  274%   most systems these are displayed  if  the   file  is  printed on the
  275%   terminal. On most systems `less` may be   used with the ``-r`` flag.
  276%   Alternatively, programs such as `ansi2html` (Linux)   may be used to
  277%   convert the files to HTML. It would  probably be better to integrate
  278%   the output generation with library(pldoc/doc_htmlsrc).
  279
  280show_coverage(_:Options), is_list(Options) =>
  281    covered(Succeeded, Failed),
  282    (   report_hook(Succeeded, Failed)
  283    ->  true
  284    ;   file_coverage(Succeeded, Failed, Options)
  285    ).
  286show_coverage(_:Goal), Goal=_:Call, callable(Call) =>
  287    print_message(warning, cov_deprecated(show_coverage)),
  288    coverage(Goal, []).
  289show_coverage(_:Options) =>
  290    must_be(list, Options).
  291
  292%!  covered(-Succeeded, -Failed) is det.
  293%
  294%   Collect failed and succeeded clauses.
  295
  296covered(Succeeded, Failed) :-
  297    findall(Cl, ('$cov_data'(clause(Cl), Enter, 0), Enter > 0), Failed0),
  298    findall(Cl, ('$cov_data'(clause(Cl), _, Exit), Exit > 0), Succeeded0),
  299    sort(Failed0, Failed),
  300    sort(Succeeded0, Succeeded).
  301
  302
  303                 /*******************************
  304                 *           REPORTING          *
  305                 *******************************/
  306
  307%!  file_coverage(+Succeeded, +Failed, +Options) is det.
  308%
  309%   Write a report on the clauses covered   organised by file to current
  310%   output. Show detailed information about   the  non-coverered clauses
  311%   defined in the modules Modules.
  312
  313file_coverage(Succeeded, Failed, Options) :-
  314    abolish_module_tables(prolog_coverage),
  315    findall(File-PrintFile,
  316            report_file(File, PrintFile, Succeeded, Failed, Options),
  317            Pairs),
  318    Pairs \== [],
  319    !,
  320
  321    (   option(width(W0), Options)
  322    ->  W is max(40, W0)
  323    ;   pairs_values(Pairs, PrintFiles),
  324        maplist(atom_length, PrintFiles, Lengths),
  325        max_list(Lengths, Longest),
  326        IdealWidth is Longest+21,
  327
  328        tty_width(Width, Options),
  329        W is min(IdealWidth, Width - 2)
  330    ),
  331    CovCol is W - 6,
  332    ClausesCol is CovCol - 6,
  333
  334    header('Coverage by File', W),
  335    ansi_format(bold, '~w~t~w~*|~t~w~*|~t~w~*|~n',
  336                ['File', 'Clauses', ClausesCol, '%Cov', CovCol, '%Fail', W]),
  337    hr(W),
  338    forall(member(File-_, Pairs),
  339           file_summary(File, Succeeded, Failed,
  340                        W, CovCol, ClausesCol,
  341                        Options)),
  342    hr(W),
  343
  344    (   annotate_files(Options)
  345    ->  forall(member(File-_, Pairs),
  346               file_details(File, Succeeded, Failed, Options)),
  347        progress_done('done', [])
  348    ;   true
  349    ).
  350file_coverage(_Succeeded, _Failed, _Options) :-
  351    print_message(warning, coverage(no_files_to_report)).
  352
  353%!  report_file(?File, -PrintFile, -Succeeded, -Failed, +Options) is semidet
  354
  355report_file(File, PrintFile, Succeeded, Failed, Options) :-
  356    (   nonvar(File)
  357    ->  true
  358    ;   (   source_file(File)
  359        ;   distinct(File, source_includes(_, File))
  360        )
  361    ),
  362    cov_report_file(File, PrintFile, Options),
  363    cov_clause_sets(File, Succeeded, Failed, Sets),
  364    \+ ( Sets.failed == [],
  365         Sets.succeeded == []
  366       ).
  367
  368%!  source_includes(?Main, ?Included) is nondet.
  369%
  370%   True when Included is (recursively) included in the "true" source
  371%   fine Main.
  372
  373:- table source_includes/2.  374
  375source_includes(Main, Included) :-
  376    nonvar(Main),
  377    !,
  378    source_file_property(Main, includes(File, _Time)),
  379    (   Included = File
  380    ;   source_includes(File, Included)
  381    ).
  382source_includes(Main, Included) :-
  383    nonvar(Included),
  384    !,
  385    source_file_property(Included, included_in(Parent, _Time)),
  386    (   no_included_file(Parent)
  387    ->  Main = Parent
  388    ;   source_includes(Main, Parent)
  389    ).
  390source_includes(Main, Included) :-
  391    source_file(Main),			% generator
  392    source_includes(Main, Included).
  393
  394main_source(File, Main) :-
  395    no_included_file(File),
  396    !,
  397    Main = File.
  398main_source(File, Main) :-
  399    source_includes(Main, File).
  400
  401%!  file_summary(+File, +Succeeded, +Failed,
  402%!               +Width, +CovCol, +ClausesCol, +Options) is det.
  403%
  404%   Write a summary with the file  and   clause  percentages on a single
  405%   line.
  406
  407file_summary(File, Succeeded, Failed, W, CovCol, ClausesCol, Options) :-
  408    cov_report_file(File, PrintFile, Options),
  409    cov_clause_sets(File, Succeeded, Failed, Sets0),
  410    \+ ( Sets0.failed == [],
  411         Sets0.succeeded == []
  412       ),
  413    !,
  414    deduplicate_clauses(File, Sets0, Sets),
  415
  416    length(Sets.clauses, AC),
  417    length(Sets.uncovered, UC),
  418    length(Sets.failed, FC),
  419
  420    CP is 100-100*UC/AC,
  421    FCP is 100*FC/AC,
  422    summary(PrintFile, ClausesCol-8, SFile),
  423    format('~w ~`.t ~D~*| ~t~1f~*| ~t~1f~*|~n',
  424           [SFile, AC, ClausesCol, CP, CovCol, FCP, W]).
  425file_summary(_,_,_,_,_,_,_).
  426
  427file_details(File, Succeeded, Failed, Options) :-
  428    cov_report_file(File, _PrintFile, Options),
  429    cov_clause_sets(File, Succeeded, Failed, Sets0),
  430    \+ ( Sets0.failed == [],
  431         Sets0.succeeded == []
  432       ),
  433    !,
  434    deduplicate_clauses(File, Sets0, Sets),
  435    ord_union(Sets.failed, Sets.succeeded, Covered),
  436    detailed_report(Sets.uncovered, Covered, File, Options).
  437file_details(_,_,_,_).
  438
  439%!  cov_clause_sets(+File, +Succeeded, +Failed, -Sets) is det.
  440
  441cov_clause_sets(File, Succeeded, Failed,
  442                #{ clauses: All_wo_system,
  443                   succeeded: Succeeded_wo_system,
  444                   failed: Failed_wo_system,
  445                   uncovered: Uncovered_wo_system
  446                 }) :-
  447    file_clauses(File, FileClauses),
  448    ord_intersection(FileClauses, Failed, FailedInFile),
  449    ord_intersection(FileClauses, Succeeded, SucceededInFile),
  450    ord_subtract(FileClauses, SucceededInFile, UnCov1),
  451    ord_subtract(UnCov1, FailedInFile, Uncovered),
  452
  453    clean_set(FileClauses, All_wo_system),
  454    clean_set(SucceededInFile, Succeeded_wo_system),
  455    clean_set(FailedInFile, Failed_wo_system),
  456    clean_set(Uncovered, Uncovered_wo_system).
  457
  458clean_set(Clauses, UserClauses) :-
  459    exclude(is_pldoc, Clauses, Clauses_wo_pldoc),
  460    exclude(is_system_clause, Clauses_wo_pldoc, UserClauses).
  461
  462is_system_clause(Clause) :-
  463    clause_pi(Clause, Name),
  464    Name = system:_.
  465
  466is_pldoc(Clause) :-
  467    clause_pi(Clause, _Module:Name2/_Arity),
  468    pldoc_predicate(Name2).
  469
  470pldoc_predicate('$pldoc').
  471pldoc_predicate('$mode').
  472pldoc_predicate('$pred_option').
  473pldoc_predicate('$exported_op').        % not really PlDoc ...
  474
  475summary(String, MaxLen, Summary) :-
  476    string_length(String, Len),
  477    (   Len < MaxLen
  478    ->  Summary = String
  479    ;   SLen is MaxLen - 5,
  480        sub_string(String, _, SLen, 0, End),
  481        string_concat('...', End, Summary)
  482    ).
  483
  484%!  file_clauses(+File, -Set) is det.
  485%
  486%   Set are all clauses in File as an ordered set.
  487
  488file_clauses(File, Set) :-
  489    findall(Cl, clause_source(Cl, File, _), Clauses),
  490    sort(Clauses, Set).
  491
  492%!  clause_source(+Clause, -File, -Line) is semidet.
  493%!  clause_source(-Clause, +File, -Line) is semidet.
  494
  495clause_source(Clause, File, Line) :-
  496    nonvar(Clause),
  497    !,
  498    clause_property(Clause, file(File)),
  499    clause_property(Clause, line_count(Line)).
  500clause_source(Clause, File, Line) :-
  501    clause_in_file(File, File, Clause, Line).
  502clause_source(Clause, File, Line) :-
  503    source_includes(Main, File),
  504    clause_in_file(Main, File, Clause, Line).
  505
  506clause_in_file(Main, Source, Clause, Line) :-
  507    Pred = _:_,
  508    source_file(Pred, Main),
  509    \+ predicate_property(Pred, multifile),
  510    nth_clause(Pred, _Index, Clause),
  511    clause_property(Clause, file(Source)),
  512    clause_property(Clause, line_count(Line)).
  513clause_in_file(_Main, Source, Clause, Line) :-
  514    Pred = _:_,
  515    predicate_property(Pred, multifile),
  516    nth_clause(Pred, _Index, Clause),
  517    clause_property(Clause, file(Source)),
  518    clause_property(Clause, line_count(Line)).
  519
  520%!  deduplicate_clauses(+File, +ClauseSetsIn, -ClauseSetsOut) is det.
  521%
  522%   @arg ClauseSetsIn is a dict   with  `clauses`, `uncovered`, `failed`
  523%   and `succeeded`.
  524
  525deduplicate_clauses(File, Set, Set) :-
  526    no_included_file(File),
  527    !.
  528deduplicate_clauses(_File, SetIn, SetOut) :-
  529    _{clauses:AC, uncovered:UC, failed:FC, succeeded:FS} :< SetIn,
  530    clause_duplicates(AC, AC1),
  531    clause_duplicates(UC, UC1),
  532    clause_duplicates(FC, FC1),
  533    clause_duplicates(FS, FS1),
  534    exclude(covered_in_some_file(AC1, FC, FS), UC1, UC2),
  535    exclude(succeeded_in_some_file(AC1, FS), FC1, FC2),
  536    SetOut = SetIn.put(_{clauses:AC1, uncovered:UC2, failed:FC2, succeeded:FS1}).
  537
  538no_included_file(File) :-
  539    source_file(File).
  540
  541%!  clause_duplicates(+Clauses, -Sets) is det.
  542%
  543%   Assuming Clauses is a list of clauses   associated  with a file that
  544%   was included multiple times, get  the   equivalent  clauses as sets.
  545%   Note that we know all Clauses come from the same file.
  546%
  547%   @arg Sets is an ordered set  of   ordered  sets of clause references
  548%   that form an equivalence group.
  549
  550clause_duplicates(Clauses, Sets) :-
  551    maplist(clause_dedup_data, Clauses, Dedups),
  552    sort(2, @=<, Dedups, ByMain),       % first my line
  553    sort(1, @=<, ByMain, ByLine),       % then by main
  554    clause_sets(ByLine, Sets0),
  555    sort(Sets0, Sets).
  556
  557clause_dedup_data(Clause, dd(Line, Main, Clause)) :-
  558    clause_property(Clause, line_count(Line)),
  559    clause_property(Clause, source(Main)).
  560
  561clause_sets([], []).
  562clause_sets([H|T0], Sets) :-
  563    same_line_clauses(H, SameL, T0, T1),
  564    same_line_clause_sets([H|SameL], Sets, More),
  565    clause_sets(T1, More).
  566
  567same_line_clauses(CRef, [H|TS], [H|T0], T) :-
  568    arg(1, CRef, Line),
  569    arg(1, H, Line),
  570    !,
  571    same_line_clauses(CRef, TS, T0, T).
  572same_line_clauses(_, [], L, L).
  573
  574%!  same_line_clause_sets(+DDClauses, -Sets, ?Tail) is det.
  575%
  576%   Given that DDClauses is a list of   dd(Line, File, Clause) each with
  577%   the same `Line` and ordered on File,  compute the sets of equivalent
  578%   clauses.
  579%
  580%   First we deal with the common case where there is at most one clause
  581%   per file.  Then we consider them all the same.
  582
  583same_line_clause_sets([], Sets, Sets) :-
  584    !.
  585same_line_clause_sets(SameL, Sets, More) :-
  586    map_list_to_pairs(arg(2), SameL, Pairs),
  587    group_pairs_by_key(Pairs, ByFile),
  588    pairs_values(ByFile, FileSets),
  589    \+ member([_,_|_], FileSets),
  590    !,
  591    maplist(arg(3), SameL, Clauses0),
  592    sort(Clauses0, Clauses),
  593    Sets = [Clauses|More].
  594same_line_clause_sets([H|T0], [Clauses|Sets], More) :-
  595    same_clauses(H, Same, T0, T),
  596    maplist(arg(3), [H|Same], Clauses0),
  597    sort(Clauses0, Clauses),
  598    same_line_clause_sets(T, Sets, More).
  599
  600same_clauses(CRef, [Same|TS], L0, L) :-
  601    select(Same, L0, L1),
  602    same_clause(CRef, Same),
  603    !,
  604    same_clauses(CRef, TS, L1, L).
  605same_clauses(_, [], L, L).
  606
  607same_clause(dd(L1, F1, C1), dd(L2, F2, C2)) :-
  608    assertion(L1 == L2),
  609    F1 \== F2,
  610    clause_property(C1, size(Size)),
  611    clause_property(C2, size(Size)),
  612    clause(Head0, Body1, C1),
  613    clause(Head1, Body2, C2),
  614    mapsubterms(unqualify, (Head0:-Body1), Clause1),
  615    mapsubterms(unqualify, (Head1:-Body2), Clause2),
  616    Clause1 =@= Clause2.
  617
  618unqualify(_:X, X).
  619
  620covered_in_some_file(AllEQ, Failed, Succeeded, UncoveredSet) :-
  621    member(Clause, UncoveredSet),
  622    member(EQSet, AllEQ),
  623    memberchk(Clause, EQSet),
  624    !,
  625    member(Cl2, EQSet),
  626    (   memberchk(Cl2, Succeeded)
  627    ;   memberchk(Cl2, Failed)
  628    ),
  629    !.
  630covered_in_some_file(_AllEQ, _Failed, _Succeeded, _UncoveredSet) :-
  631    assertion(fail).
  632
  633succeeded_in_some_file(AllEQ, Succeeded, FailedSet) :-
  634    member(Clause, FailedSet),
  635    member(EQSet, AllEQ),
  636    memberchk(Clause, EQSet),
  637    !,
  638    member(Cl2, EQSet),
  639    memberchk(Cl2, Succeeded),
  640    !.
  641succeeded_in_some_file(_AllEQ, _Succeeded, _FailedSet) :-
  642    assertion(fail).
  643
  644%!  cov_report_file(+File, -PrintFile, +Options) is semidet.
  645%
  646%   Whether or not to report on File.   Scenarios:
  647%
  648%     - all(true)
  649%       Report on every file.
  650%     - modules(List)
  651%       Report of the file implements one of the modules in List.
  652%     - roots(+Dirs)
  653%       Report if the file appears below one of Dirs.
  654%     - (default)
  655%       Report if the file implements a `user` or `test` module.
  656
  657cov_report_file(File, _, _) :-
  658    source_file(cov_report_file(_,_,_), File),
  659    !,
  660    fail.                               % do not report on myself
  661cov_report_file(File, File, Options) :-
  662    option(all(true), Options),
  663    !.
  664cov_report_file(File, File, Options) :-
  665    option(modules(Modules), Options),
  666    file_module(File, M),
  667    memberchk(M, Modules),
  668    !.
  669cov_report_file(File, PrintFile, Options) :-
  670    option(roots(Roots), Options),
  671    !,
  672    must_be(list, Roots),
  673    member(Root, Roots),
  674    absolute_file_name(Root, Path,
  675                       [ file_type(directory),
  676                         solutions(all),
  677                         file_errors(fail)
  678                       ]),
  679    ensure_slash(Path, Path1),
  680    atom_concat(Path1, PrintFile, File),
  681    !.
  682cov_report_file(File, File, _Options) :-
  683    (   file_module(File, M),
  684        module_property(M, class(user))
  685    ->  true
  686    ;   forall(source_file_property(File, module(M)),
  687               module_property(M, class(test)))
  688    ).
  689
  690file_module(File, Module) :-
  691    source_file_property(File, module(Module)).
  692file_module(File, Module) :-
  693    source_includes(Main, File),
  694    file_module(Main, Module).
  695
  696ensure_slash(Path, Path) :-
  697    sub_atom(Path, _, _, 0, /),
  698    !.
  699ensure_slash(Path, Path1) :-
  700    atom_concat(Path, /, Path1).
  701
  702%!  annotate_files(+Options) is semidet.
  703
  704annotate_files(Options) :-
  705    (   option(annotate(true), Options)
  706    ;   option(dir(_), Options)
  707    ;   option(ext(_), Options)
  708    ),
  709    !.
  710
  711%!  detailed_report(+Uncovered, +Covered, +File:atom, +Options) is det
  712%
  713%   Generate a detailed report for  File.   Depending  on  Options, this
  714%   either creates an annotated version of File   or  it generates a per
  715%   clause report of non-covered clauses.
  716%
  717%   @arg Uncovered is a list of uncovered clauses.  If File is an
  718%   included file, it is a list of sets of clause references that
  719%   represent the same clause.
  720%   @arg Covered is a list of covered clauses.  As with Uncovered,
  721%   this is a list of sets for an included File
  722
  723detailed_report(Uncovered, Covered, File, Options):-
  724    annotate_files(Options),
  725    !,
  726    convlist(line_annotation(File, uncovered), Uncovered, Annot1),
  727    convlist(line_annotation(File, covered),   Covered,   Annot20),
  728    flatten(Annot20, Annot2),
  729    append(Annot1, Annot2, AnnotationsLen),
  730    pairs_keys_values(AnnotationsLen, Annotations, Lens),
  731    max_list(Lens, MaxLen),
  732    Margin is MaxLen+1,
  733    annotate_file(File, Annotations, [margin(Margin)|Options]).
  734detailed_report(Uncovered, _, File, _Options):-
  735    convlist(uncovered_clause_line(File), Uncovered, Pairs),
  736    sort(Pairs, Pairs_sorted),
  737    group_pairs_by_key(Pairs_sorted, Compact_pairs),
  738    nl,
  739    file_base_name(File, Base),
  740    format('~2|Clauses not covered from file ~p~n', [Base]),
  741    format('~4|Predicate ~59|Clauses at lines ~n', []),
  742    maplist(print_clause_line, Compact_pairs),
  743    nl.
  744
  745line_annotation(File, uncovered, Clause, Annotation) :-
  746    !,
  747    clause_or_set_source_location(Clause, File, Line),
  748    Annotation = (Line-ansi(error,###))-3.
  749line_annotation(File, covered, ClauseOrSet, [HeadAllot|CallSites]) :-
  750    clause_or_set_source_location(ClauseOrSet, File, Line),
  751    clause_or_set_cov_data(ClauseOrSet, Entered, Exited),
  752    line_annotation_msg(line_anot(Line, 0, Entered, Exited), HeadAllot),
  753    flatten([ClauseOrSet], Clauses),
  754    maplist(clause_call_site_annotations, Clauses, AnnotSets),
  755    append(AnnotSets, Annots),
  756    join_annots(Annots, Joined),
  757    maplist(line_annotation_msg, Joined, CallSites),
  758    check_correct_offsets(Clauses, AnnotSets).
  759
  760clause_or_set_source_location([Clause|_], File, Line) =>
  761    clause_property(Clause, file(File)),
  762    clause_property(Clause, line_count(Line)).
  763clause_or_set_source_location(Clause, File, Line) =>
  764    clause_property(Clause, file(File)),
  765    clause_property(Clause, line_count(Line)).
  766
  767clause_or_set_cov_data(Clause, Entered, Exited),
  768    blob(Clause, clause) =>
  769    '$cov_data'(clause(Clause), Entered, Exited).
  770clause_or_set_cov_data(Clauses, Entered, Exited) =>
  771    maplist(clause_or_set_cov_data, Clauses, LEntered, LExited),
  772    sum_list(LEntered, Entered),
  773    sum_list(LExited, Exited).
  774
  775line_annotation_msg(line_anot(Line, _PC, Entered, Exited), (Line-Annot)-Len) :-
  776    (   Exited == Entered
  777    ->  format(string(Text), '++~D', [Entered]),
  778        Annot = ansi(comment, Text)
  779    ;   Exited == 0
  780    ->  format(string(Text), '--~D', [Entered]),
  781        Annot = ansi(warning, Text)
  782    ;   Exited < Entered
  783    ->  Failed is Entered - Exited,
  784        format(string(Text), '+~D-~D', [Exited, Failed]),
  785        Annot = ansi(comment, Text)
  786    ;   format(string(Text), '+~D*~D', [Entered, Exited]),
  787        Annot = ansi(fg(cyan), Text)
  788    ),
  789    string_length(Text, Len).
  790
  791uncovered_clause_line(File, Code, Name-Line) :-
  792    clause_or_set_source_location(Clause, File, Line),
  793    (   Code = [Clause|_]                % included file; omit module
  794    ->  clause_pi(Clause, _:Name)
  795    ;   clause_pi(Code, Name)
  796    ).
  797
  798%!  clause_pi(+Clause, -Name) is det.
  799%
  800%   Return the clause predicate indicator as Module:Name/Arity.
  801
  802clause_pi(Clause, Name) :-
  803    clause(Module:Head, _, Clause),
  804    functor(Head,F,A),
  805    Name=Module:F/A.
  806
  807print_clause_line((Module:Name/Arity)-Lines):-
  808    term_string(Module:Name, Complete_name),
  809    summary(Complete_name, 54, SName),
  810    format('~4|~w~t~59|~p~n', [SName/Arity, Lines]).
  811
  812
  813		 /*******************************
  814		 *     LINE LEVEL CALL SITES	*
  815		 *******************************/
  816
  817join_annots(Annots, Joined) :-
  818    sort(2, @=<, Annots, ByPC),
  819    join_annots_(ByPC, Joined0),
  820    sort(1, @=<, Joined0, Joined).
  821
  822join_annots_([], []).
  823join_annots_([H0|T0], [H|T]) :-
  824    sum_annot_counts(H0, H, T0, T1),
  825    join_annots_(T1, T).
  826
  827sum_annot_counts(line_anot(Line, PC, Enter1, Exit1),
  828                 Final,
  829                 [line_anot(Line, PC, Enter2, Exit2)|T0],
  830                 T) :-
  831    !,
  832    Enter is Enter1 + Enter2,
  833    Exit  is Exit1 + Exit2,
  834    sum_annot_counts(line_anot(Line, PC, Enter, Exit),
  835                     Final, T0, T).
  836sum_annot_counts(Sum, Sum, T, T).
  837
  838%!  clause_call_site_annotations(+Clause, -Annotations) is det.
  839%
  840%   @arg Annotations is a list line_anot(Line, PC, Entered, Exited)
  841
  842clause_call_site_annotations(Clause, Annots) :-
  843    findall(Annot,
  844            clause_call_site_annotation(Clause, Annot),
  845            Annots).
  846
  847clause_call_site_annotation(ClauseRef,
  848                            line_anot(Line, NextPC, Entered, Exited)) :-
  849    clause_call_site(ClauseRef, PC-NextPC, Line:_LPos),
  850    (   '$cov_data'(call_site(ClauseRef, NextPC), Entered, Exited)
  851    ->  true
  852    ;   '$fetch_vm'(ClauseRef, PC, _, VMI),
  853        \+ no_annotate_call_site(VMI)
  854    ->  Entered = 0, Exited = 0
  855    ).
  856
  857no_annotate_call_site(i_enter).
  858no_annotate_call_site(i_exit).
  859no_annotate_call_site(i_cut).
  860
  861clause_call_site(ClauseRef, PC-NextPC, Pos) :-
  862    clause_info(ClauseRef, File, TermPos, _NameOffset),
  863    '$break_pc'(ClauseRef, PC, NextPC),
  864    '$clause_term_position'(ClauseRef, NextPC, List),
  865    catch(prolog_breakpoints:range(List, TermPos, SubPos), E, true),
  866    (   var(E)
  867    ->  arg(1, SubPos, A),
  868        file_offset_pos(File, A, Pos)
  869    ;   print_message(warning, coverage(clause_info(ClauseRef))),
  870        fail
  871    ).
  872
  873file_offset_pos(File, A, Line:LPos) :-
  874    file_text(File, String),
  875    State = start(1, 0),
  876    call_nth(sub_string(String, S, _, _, "\n"), NLine),
  877    (   S >= A
  878    ->  !,
  879        State = start(Line, SLine),
  880        LPos is A-SLine
  881    ;   NS is S+1,
  882        NLine1 is NLine+1,
  883        nb_setarg(1, State, NLine1),
  884        nb_setarg(2, State, NS),
  885        fail
  886    ).
  887
  888file_text(File, String) :-
  889    setup_call_cleanup(
  890        open(File, read, In),
  891        read_string(In, _, String),
  892        close(In)).
  893
  894%!  check_correct_offsets(+Clauses, +Annotations) is det.
  895%
  896%   Verify that all PC's that  were   annotated  have  been generated as
  897%   possible call sites.
  898
  899check_correct_offsets([Clause|_], [Annots|_]) :-
  900    maplist(arg(2), Annots, PCs),
  901    check_covered_call_sites(Clause, PCs).
  902
  903check_covered_call_sites(Clause, Reported) :-
  904    findall(PC, ('$cov_data'(call_site(Clause,PC), Enter, _), Enter > 0), Seen),
  905    sort(Reported, SReported),
  906    sort(Seen, SSeen),
  907    ord_subtract(SSeen, SReported, Missed),
  908    (   Missed == []
  909    ->  true
  910    ;   print_message(warning, coverage(unreported_call_sites(Clause, Missed)))
  911    ).
  912
  913
  914		 /*******************************
  915		 *           ANNOTATE		*
  916		 *******************************/
  917
  918clean_output(Options) :-
  919    option(dir(Dir), Options),
  920    !,
  921    option(ext(Ext), Options, cov),
  922    format(atom(Pattern), '~w/*.~w', [Dir, Ext]),
  923    expand_file_name(Pattern, Files),
  924    maplist(delete_file, Files).
  925clean_output(Options) :-
  926    forall(source_file(File),
  927           clean_output(File, Options)).
  928
  929clean_output(File, Options) :-
  930    option(ext(Ext), Options, cov),
  931    file_name_extension(File, Ext, CovFile),
  932    (   exists_file(CovFile)
  933    ->  E = error(_,_),
  934        catch(delete_file(CovFile), E,
  935              print_message(warning, E))
  936    ;   true
  937    ).
  938
  939
  940%!  annotate_file(+File, +Annotations, +Options) is det.
  941%
  942%   Create  an  annotated  copy  of  File.  Annotations  is  a  list  of
  943%   `LineNo-Annotation`,  where  `Annotation`  is  atomic    or  a  term
  944%   Format-Args,  optionally  embedded   in    ansi(Code,   Annotation).
  945
  946annotate_file(Source, Annotations, Options) :-
  947    option(ext(Ext), Options, cov),
  948    (   option(dir(Dir), Options)
  949    ->  file_base_name(Source, Base),
  950        file_name_extension(Base, Ext, CovFile),
  951        directory_file_path(Dir, CovFile, CovPath),
  952        make_directory_path(Dir)
  953    ;   file_name_extension(Source, Ext, CovPath)
  954    ),
  955    summary(Source, 30, SSource),
  956    progress('Annotating ~w in ~w ... ', [SSource,CovPath]),
  957    keysort(Annotations, SortedAnnotations),
  958    setup_call_cleanup(
  959        open(Source, read, In),
  960        setup_call_cleanup(
  961            open(CovPath, write, Out),
  962            annotate(In, Out, SortedAnnotations, Options),
  963            close(Out)),
  964        close(In)).
  965
  966annotate(In, Out, Annotations, Options) :-
  967    (   option(color(true), Options, true)
  968    ->  set_stream(Out, tty(true))
  969    ;   true
  970    ),
  971    annotate(In, Out, Annotations, 0, Options).
  972
  973annotate(In, Out, Annotations, LineNo0, Options) :-
  974    read_line_to_string(In, Line),
  975    (   Line == end_of_file
  976    ->  true
  977    ;   succ(LineNo0, LineNo),
  978        margins(LMargin, CMargin, Options),
  979        line_no(LineNo, Out, LMargin),
  980        annotations(LineNo, Out, LMargin, Annotations, Annotations1),
  981        format(Out, '~t~*|~s~n', [CMargin, Line]),
  982        annotate(In, Out, Annotations1, LineNo, Options)
  983    ).
  984
  985annotations(Line, Out, LMargin, [Line-Annot|T0], T) :-
  986    !,
  987    write_annotation(Out, Annot),
  988    (   T0 = [Line-_|_]
  989    ->  with_output_to(Out, ansi_format(bold, ' \u2bb0~n~t~*|', [LMargin])),
  990        annotations(Line, Out, LMargin, T0, T)
  991    ;   T = T0
  992    ).
  993annotations(_, _, _, Annots, Annots).
  994
  995write_annotation(Out, ansi(Code, Fmt-Args)) =>
  996    with_output_to(Out, ansi_format(Code, Fmt, Args)).
  997write_annotation(Out, ansi(Code, Fmt)) =>
  998    with_output_to(Out, ansi_format(Code, Fmt, [])).
  999write_annotation(Out, Fmt-Args) =>
 1000    format(Out, Fmt, Args).
 1001write_annotation(Out, Fmt) =>
 1002    format(Out, Fmt, []).
 1003
 1004line_no(_, _, 0) :- !.
 1005line_no(Line, Out, LMargin) :-
 1006    with_output_to(Out, ansi_format(fg(127,127,127), '~t~d ~*|',
 1007                                    [Line, LMargin])).
 1008
 1009margins(LMargin, Margin, Options) :-
 1010    option(line_numbers(true), Options, true),
 1011    !,
 1012    option(line_number_margin(LMargin), Options, 6),
 1013    option(margin(AMargin), Options, 4),
 1014    Margin is LMargin+AMargin.
 1015margins(0, Margin, Options) :-
 1016    option(margin(Margin), Options, 4).
 1017
 1018%!  report_hook(+Succeeded, +Failed) is semidet.
 1019%
 1020%   This hook is called after the data   collection. It is passed a list
 1021%   of objects that have succeeded as  well   as  a list of objects that
 1022%   have failed.  The objects are one of
 1023%
 1024%     - ClauseRef
 1025%       The specified clause
 1026%     - call_site(ClauseRef, PC)
 1027%       A call was make in ClauseRef at the given program counter.
 1028
 1029:- multifile
 1030    report_hook/2. 1031
 1032		 /*******************************
 1033		 *          SAVE/RELOAD		*
 1034		 *******************************/
 1035
 1036%!  cov_save_data(+File, +Options) is det.
 1037%
 1038%   Save the coverage information to File.  Options:
 1039%
 1040%     - append(true)
 1041%       Append to File rather than truncating the data if the file
 1042%       exists.
 1043%
 1044%   The File is  opened  using   lock(exclusive),  which  implies  that,
 1045%   provided the OS and file system   implements  file locking, multiple
 1046%   processes may save coverage data to the same file.
 1047%
 1048%   The saved data is highly specific to the  setup in which it has been
 1049%   created. It can typically only be  reloaded using cov_load_data/2 in
 1050%   the same Prolog executable  using  the   same  options  and with all
 1051%   relevant source file unmodified at the same location.
 1052%
 1053%   Reproducibility can be improved by  using   `.qlf`  files  or _saved
 1054%   states_.
 1055
 1056:- thread_local
 1057    saved_clause/2.                     % Clause, Ref
 1058
 1059cov_save_data(File, Options) :-
 1060    (   option(append(true), Options)
 1061    ->  Mode = append
 1062    ;   Mode = write
 1063    ),
 1064    absolute_file_name(File, Path, [ access(write) ]),
 1065    setup_call_cleanup(
 1066        open(Path, Mode, Out,
 1067             [ encoding(utf8),
 1068               lock(exclusive)
 1069             ]),
 1070        cov_save_to_stream(Out),
 1071        ( retractall(saved_clause(_,_)),
 1072          close(Out))).
 1073
 1074cov_save_to_stream(Out) :-
 1075    get_time(Now),
 1076    format(Out, 'cov_begin_data(~1f).~n', [Now]),
 1077    forall('$cov_data'(Site, Enter, Exit),
 1078           cov_save_entry(Out, Site, Enter, Exit)),
 1079    format(Out, 'cov_end_data.~n', []).
 1080
 1081:- det(cov_save_entry/4). 1082cov_save_entry(Out, call_site(Clause, PC), Enter, Exit) =>
 1083    save_clause(Out, Clause, Ref),
 1084    (   nonvar(Ref)
 1085    ->  format(Out, '~q.~n', [cs(Ref, PC, Enter, Exit)])
 1086    ;   true
 1087    ).
 1088cov_save_entry(Out, clause(Clause), Enter, Exit) =>
 1089    save_clause(Out, Clause, Ref),
 1090    (   nonvar(Ref)
 1091    ->  format(Out, '~q.~n', [cs(Ref, Enter, Exit)])
 1092    ;   true
 1093    ).
 1094
 1095save_clause(_Out, Clause, Ref) :-
 1096    saved_clause(Clause, Ref),
 1097    !.
 1098save_clause(Out, Clause, Ref) :-
 1099    clause_property(Clause, file(File)),
 1100    clause_property(Clause, line_count(Line)),
 1101    clause_property(Clause, size(Bytes)),
 1102    clause_property(Clause, predicate(PI)),
 1103    main_source(File, Main),
 1104    source_file_property(Main, load_context(Module, Location, Options)),
 1105    nth_clause(_, Nth, Clause),
 1106    !,
 1107    (   predicate_property(saved_clause(_,_), number_of_clauses(N))
 1108    ->  Ref is N+1
 1109    ;   Ref = 1
 1110    ),
 1111    format(Out, '~q.~n', [cl(PI, Nth, Bytes, Main, File:Line, Module, Location, Options, Ref)]),
 1112    assertz(saved_clause(Clause, Ref)).
 1113save_clause(_Out, Clause, _Ref) :-
 1114    debug(cov(save), 'Could not save clause ~p', [Clause]).
 1115
 1116%!  cov_load_data(+File, +Options) is det.
 1117%
 1118%   Reload coverage data from File.  Options:
 1119%
 1120%     - load(true)
 1121%       If specified and the file in which a clauses is expected to
 1122%       exist, load the file using load_files/2 with the same options
 1123%       as used to initially load the file.
 1124%     - silent(+Boolean)
 1125%       When `true`, do not emit messages on not loaded source files.
 1126%
 1127%   Data is assumed to be reliable if   the Nth-clause of a predicate is
 1128%   loaded from the same file at the same   line number and has the same
 1129%   size. Unreliable data is ignored, silently if silent(true) is used.
 1130
 1131:- thread_local
 1132    warned/1. 1133
 1134cov_load_data(File, Options) :-
 1135    absolute_file_name(File, Path, [ access(read) ]),
 1136    setup_call_cleanup(
 1137        open(Path, read, In, [encoding(utf8)]),
 1138        cov_load_data_from_stream(In, Options),
 1139        ( retractall(saved_clause(_,_)),
 1140          retractall(warned(_)),
 1141          close(In))).
 1142
 1143cov_load_data_from_stream(In, Options) :-
 1144    read_term(In, Term, []),
 1145    cov_load_data_from_stream(Term, In, Options).
 1146
 1147cov_load_data_from_stream(end_of_file, _, _) :-
 1148    !.
 1149cov_load_data_from_stream(Term, In, Options) :-
 1150    cov_restore_data(Term, Options),
 1151    read_term(In, Term2, []),
 1152    cov_load_data_from_stream(Term2, In, Options).
 1153
 1154cov_restore_data(cov_begin_data(_), _Options) =>
 1155    true.
 1156cov_restore_data(cl(PI, Nth,
 1157                    Bytes, Main, File:Line, Module, _Location, LoadOptions,
 1158                    Ref), Options) =>
 1159    (   restore_clause(PI, Nth, Bytes, File, Line, Ref)
 1160    ->  true
 1161    ;   source_file(File)
 1162    ->  warn(File, coverage(source_changed(File, PI)))
 1163    ;   option(load(true), Options)
 1164    ->  load_files(Module:Main, [if(not_loaded)|LoadOptions]),
 1165        (   restore_clause(PI, Nth, Bytes, File, Line, Ref)
 1166        ->  true
 1167        ;   warn(File, coverage(source_changed(File, PI)))
 1168        )
 1169    ;   option(silent(true), Options)
 1170    ->  true
 1171    ;   warn(File, coverage(no_source(File)))
 1172    ).
 1173cov_restore_data(cs(Ref, PC, Enter, Exit), _Options) =>
 1174    (   saved_clause(Clause, Ref)
 1175    ->  '$cov_add'(call_site(Clause, PC), Enter, Exit)
 1176    ;   true
 1177    ).
 1178cov_restore_data(cs(Ref, Enter, Exit), _Options) =>
 1179    (   saved_clause(Clause, Ref)
 1180    ->  '$cov_add'(clause(Clause), Enter, Exit)
 1181    ;   true
 1182    ).
 1183cov_restore_data(cov_end_data, _Options) =>
 1184    retractall(saved_clause(_,_)).
 1185
 1186restore_clause(PI, _Nth, Bytes, File, Line, Ref) :-
 1187    pi_head(PI, Head),
 1188    predicate_property(Head, multifile),
 1189    !,
 1190    (   nth_clause(Head, _, Clause),
 1191        clause_property(Clause, file(File)),
 1192        clause_property(Clause, line_count(Line)),
 1193        clause_property(Clause, size(Bytes))
 1194    ->  assertz(saved_clause(Clause, Ref))
 1195    ;   warn(File, coverage(no_multifile_source(File:Line, PI)))
 1196    ).
 1197restore_clause(PI, Nth, Bytes, File, Line, Ref) :-
 1198    pi_head(PI, Head),
 1199    (   nth_clause(Head, Nth, Clause)
 1200    ->  (   clause_property(Clause, file(File)),
 1201            clause_property(Clause, line_count(Line)),
 1202            clause_property(Clause, size(Bytes))
 1203        ->  assertz(saved_clause(Clause, Ref))
 1204        ;   warn(File, coverage(source_changed(File:Line, PI, Nth)))
 1205        )
 1206    ).
 1207
 1208warn(Term, _Msg) :-
 1209    warned(Term),
 1210    !.
 1211warn(Term, Msg) :-
 1212    assertz(warned(Term)),
 1213    print_message(warning, Msg).
 1214
 1215
 1216%!  cov_reset is det.
 1217%
 1218%   Discard  all  collected  coverage  data.  This  predicate  raises  a
 1219%   permission error if coverage collection is in progress.
 1220
 1221cov_reset :-
 1222    '$cov_reset'.
 1223
 1224
 1225%!  cov_property(?Property)
 1226%
 1227%   True when coverage analysis satisfies   Property.  Currently defined
 1228%   properties are:
 1229%
 1230%     - active(?Nesting)
 1231%       True when coverage data is   being  collected. Nesting expresses
 1232%       the nesting of coverage/1 calls and is normally 1 (one).
 1233
 1234cov_property(active(Level)) :-
 1235    '$cov_active'(Level).
 1236
 1237
 1238		 /*******************************
 1239		 *             MESSAGES		*
 1240		 *******************************/
 1241
 1242:- multifile
 1243    prolog:message//1. 1244
 1245prolog:message(coverage(Msg)) -->
 1246    message(Msg).
 1247
 1248message(no_files_to_report) -->
 1249    [ 'No coverage events in selected files'-[] ].
 1250message(clause_info(ClauseRef)) -->
 1251    [ 'Inconsistent clause info for '-[] ],
 1252    clause_msg(ClauseRef).
 1253message(unreported_call_sites(ClauseRef, PCList)) -->
 1254    [ 'Failed to report call sites for '-[] ],
 1255    clause_msg(ClauseRef),
 1256    [ nl, '  Missed at these PC offsets: ~p'-[PCList] ].
 1257message(source_changed(File, PI)) -->
 1258    [ 'Predicate ', ansi(code, '~p', [PI]), ' cannot be found while file ',
 1259      url(File), ' is loaded.'
 1260    ].
 1261message(no_source(File)) -->
 1262    [ 'File ', url(File), ' is not loaded.  Please re-run with ', nl,
 1263      'file loaded or use the ', ansi(code, 'load(true)', []), ' option.'
 1264    ].
 1265message(no_multifile_source(Location, PI)) -->
 1266    [ 'Could not find matching clause for multifile predicate ',
 1267      ansi(code, '~p', [PI]), ' at ', url(Location)
 1268    ].
 1269message(source_changed(File:Line, PI, Nth)) -->
 1270    [ '~D-th clause for '-[Nth], ansi(code, '~p', [PI]),
 1271      ' cannot be found at ', url(File:Line), '.'
 1272    ].
 1273message(deprecated(show_coverage/2)) -->
 1274    [ 'show_coverage/2 is deprecated.  Please use coverage/2', nl,
 1275      'with the same arguments.'
 1276    ].
 1277
 1278
 1279clause_msg(ClauseRef) -->
 1280    { clause_pi(ClauseRef, PI),
 1281      clause_property(ClauseRef, file(File)),
 1282      clause_property(ClauseRef, line_count(Line))
 1283    },
 1284    [ '~p at'-[PI], nl, '  ', url(File:Line) ].
 1285
 1286
 1287		 /*******************************
 1288		 *      TTY PRINT SUPPORT	*
 1289		 *******************************/
 1290
 1291progress(_, _) :-
 1292    current_prolog_flag(verbose, silent),
 1293    !.
 1294progress(Format, Args) :-
 1295    stream_property(user_output, tty(true)),
 1296    !,
 1297    format(user_output, '\r\e[2K', []),
 1298    ansi_format(comment, Format, Args),
 1299    flush_output(user_output).
 1300progress(Format, Args) :-
 1301    format(Format, Args),
 1302    nl.
 1303
 1304progress_done(_,_) :-
 1305    current_prolog_flag(verbose, silent),
 1306    !.
 1307progress_done(Format, Args) :-
 1308    stream_property(user_output, tty(true)),
 1309    !,
 1310    ansi_format(comment, Format, Args),
 1311    nl.
 1312progress_done(_, _).
 1313
 1314header(Title, Width) :-
 1315    hr(Width),
 1316    ansi_format([bold], '~t~w~t~*|', [Title,Width]),
 1317    nl.
 1318
 1319hr(Width) :-
 1320    format('~N~`\u2015t~*|~n', [Width]).
 1321
 1322%!  tty_width(-Width, +Options) is det.
 1323
 1324tty_width(W, Options) :-
 1325    option(width(W), Options),
 1326    !.
 1327:- if(current_predicate(tty_size/2)). 1328tty_width(W, _Options) :-
 1329    catch(tty_size(_, TtyW), _, fail),
 1330    !,
 1331    W is max(60, TtyW).
 1332:- endif. 1333tty_width(78, _)