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)  2006-2016, University of Amsterdam
   7                              VU University Amsterdam
   8    All rights reserved.
   9
  10    Redistribution and use in source and binary forms, with or without
  11    modification, are permitted provided that the following conditions
  12    are met:
  13
  14    1. Redistributions of source code must retain the above copyright
  15       notice, this list of conditions and the following disclaimer.
  16
  17    2. Redistributions in binary form must reproduce the above copyright
  18       notice, this list of conditions and the following disclaimer in
  19       the documentation and/or other materials provided with the
  20       distribution.
  21
  22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
  23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
  24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
  25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
  26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
  27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
  28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
  29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
  30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
  31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
  32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
  33    POSSIBILITY OF SUCH DAMAGE.
  34*/
  35
  36:- module(prolog_cover,
  37          [ show_coverage/1             % :Goal
  38          ]).
  39:- use_module(library(ordsets)).
  40
  41:- set_prolog_flag(generate_debug_info, false).
  42
  43/** <module> Clause cover analysis
  44
  45The purpose of this module is to find which part of the program has been
  46use by a certain goal. Usage is defined   in  terms of clauses that have
  47fired, seperated in clauses that  succeeded   at  least once and clauses
  48that failed on each occasion.
  49
  50This module relies on the  SWI-Prolog   tracer  hooks. It modifies these
  51hooks and collects the results, after   which  it restores the debugging
  52environment.  This has some limitations:
  53
  54        * The performance degrades significantly (about 10 times)
  55        * It is not possible to use the debugger during coverage analysis
  56        * The cover analysis tool is currently not thread-safe.
  57
  58The result is  represented  as  a   list  of  clause-references.  As the
  59references to clauses of dynamic predicates  cannot be guaranteed, these
  60are omitted from the result.
  61
  62@bug    Relies heavily on SWI-Prolog internals. We have considered using
  63        a meta-interpreter for this purpose, but it is nearly impossible
  64        to do 100% complete meta-interpretation of Prolog.  Example
  65        problem areas include handling cuts in control-structures
  66        and calls from non-interpreted meta-predicates.
  67@tbd    Provide detailed information organised by predicate.  Possibly
  68        annotate the source with coverage information.
  69*/
  70
  71
  72:- dynamic
  73    entered/1,                      % clauses entered
  74    exited/1.                       % clauses completed
  75
  76:- meta_predicate
  77    show_coverage(0).
  78
  79%!  show_coverage(:Goal)
  80%
  81%   Report on coverage by Goal.  Goal is executed as in once/1.
  82
  83show_coverage(Goal) :-
  84    setup_call_cleanup(
  85        setup_trace(State),
  86        once(Goal),
  87        cleanup_trace(State)).
  88
  89setup_trace(state(Visible, Leash, Ref)) :-
  90    asserta((user:prolog_trace_interception(Port, Frame, _, continue) :-
  91                    prolog_cover:assert_cover(Port, Frame)), Ref),
  92    port_mask([unify,exit], Mask),
  93    '$visible'(Visible, Mask),
  94    '$leash'(Leash, Mask),
  95    trace.
  96
  97port_mask([], 0).
  98port_mask([H|T], Mask) :-
  99    port_mask(T, M0),
 100    '$syspreds':port_name(H, Bit),
 101    Mask is M0 \/ Bit.
 102
 103cleanup_trace(state(Visible, Leash, Ref)) :-
 104    nodebug,
 105    '$visible'(_, Visible),
 106    '$leash'(_, Leash),
 107    erase(Ref),
 108    covered(Succeeded, Failed),
 109    file_coverage(Succeeded, Failed).
 110
 111
 112%!  assert_cover(+Port, +Frame) is det.
 113%
 114%   Assert coverage of the current clause. We monitor two ports: the
 115%   _unify_ port to see which  clauses   we  entered, and the _exit_
 116%   port to see which completed successfully.
 117
 118assert_cover(unify, Frame) :-
 119    running_static_pred(Frame),
 120    prolog_frame_attribute(Frame, clause, Cl),
 121    !,
 122    assert_entered(Cl).
 123assert_cover(exit, Frame) :-
 124    running_static_pred(Frame),
 125    prolog_frame_attribute(Frame, clause, Cl),
 126    !,
 127    assert_exited(Cl).
 128assert_cover(_, _).
 129
 130%!  running_static_pred(+Frame) is semidet.
 131%
 132%   True if Frame is not running a dynamic predicate.
 133
 134running_static_pred(Frame) :-
 135    prolog_frame_attribute(Frame, goal, Goal),
 136    \+ predicate_property(Goal, dynamic).
 137
 138%!  assert_entered(+Ref) is det.
 139%!  assert_exited(+Ref) is det.
 140%
 141%   Add Ref to the set of entered or exited clauses.
 142
 143assert_entered(Cl) :-
 144    entered(Cl),
 145    !.
 146assert_entered(Cl) :-
 147    assert(entered(Cl)).
 148
 149assert_exited(Cl) :-
 150    exited(Cl),
 151    !.
 152assert_exited(Cl) :-
 153    assert(exited(Cl)).
 154
 155%!  covered(+Ref, +VisibleMask, +LeashMask, -Succeeded, -Failed) is det.
 156%
 157%   Restore state and collect failed and succeeded clauses.
 158
 159covered(Succeeded, Failed) :-
 160    findall(Cl, (entered(Cl), \+exited(Cl)), Failed0),
 161    findall(Cl, retract(exited(Cl)), Succeeded0),
 162    retractall(entered(Cl)),
 163    sort(Failed0, Failed),
 164    sort(Succeeded0, Succeeded).
 165
 166
 167                 /*******************************
 168                 *           REPORTING          *
 169                 *******************************/
 170
 171%!  file_coverage(+Succeeded, +Failed) is det.
 172%
 173%   Write a report on  the  clauses   covered  organised  by file to
 174%   current output.
 175
 176file_coverage(Succeeded, Failed) :-
 177    format('~N~n~`=t~78|~n'),
 178    format('~tCoverage by File~t~78|~n'),
 179    format('~`=t~78|~n'),
 180    format('~w~t~w~64|~t~w~72|~t~w~78|~n',
 181           ['File', 'Clauses', '%Cov', '%Fail']),
 182    format('~`=t~78|~n'),
 183    forall(source_file(File),
 184           file_coverage(File, Succeeded, Failed)),
 185    format('~`=t~78|~n').
 186
 187file_coverage(File, Succeeded, Failed) :-
 188    findall(Cl, clause_source(Cl, File, _), Clauses),
 189    sort(Clauses, All),
 190    (   ord_intersect(All, Succeeded)
 191    ->  true
 192    ;   ord_intersect(All, Failed)
 193    ),
 194    !,
 195    ord_intersection(All, Failed, FailedInFile),
 196    ord_intersection(All, Succeeded, SucceededInFile),
 197    ord_subtract(All, SucceededInFile, UnCov1),
 198    ord_subtract(UnCov1, FailedInFile, Uncovered),
 199    length(All, AC),
 200    length(Uncovered, UC),
 201    length(FailedInFile, FC),
 202    CP is 100-100*UC/AC,
 203    FCP is 100*FC/AC,
 204    summary(File, 56, SFile),
 205    format('~w~t ~D~64| ~t~1f~72| ~t~1f~78|~n', [SFile, AC, CP, FCP]).
 206file_coverage(_,_,_).
 207
 208
 209summary(Atom, MaxLen, Summary) :-
 210    atom_length(Atom, Len),
 211    (   Len < MaxLen
 212    ->  Summary = Atom
 213    ;   SLen is MaxLen - 5,
 214        sub_atom(Atom, _, SLen, 0, End),
 215        atom_concat('...', End, Summary)
 216    ).
 217
 218
 219%!  clause_source(+Clause, -File, -Line) is det.
 220%!  clause_source(-Clause, +File, -Line) is det.
 221
 222clause_source(Clause, File, Line) :-
 223    nonvar(Clause),
 224    !,
 225    clause_property(Clause, file(File)),
 226    clause_property(Clause, line_count(Line)).
 227clause_source(Clause, File, Line) :-
 228    Pred = _:_,
 229    source_file(Pred, File),
 230    \+ predicate_property(Pred, multifile),
 231    nth_clause(Pred, _Index, Clause),
 232    clause_property(Clause, line_count(Line)).
 233clause_source(Clause, File, Line) :-
 234    Pred = _:_,
 235    predicate_property(Pred, multifile),
 236    nth_clause(Pred, _Index, Clause),
 237    clause_property(Clause, file(File)),
 238    clause_property(Clause, line_count(Line)).