Skip to content

Commit

Permalink
ADDED: cov_property/1
Browse files Browse the repository at this point in the history
Allows querying coverage collection system properties (currently
only whether coverage data collection is active).
  • Loading branch information
JanWielemaker committed Jan 18, 2024
1 parent e169c79 commit 69481a1
Show file tree
Hide file tree
Showing 2 changed files with 32 additions and 6 deletions.
16 changes: 15 additions & 1 deletion library/prolog_coverage.pl
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,8 @@
show_coverage/2, % :Goal, +Options (deprecated)
cov_save_data/2, % +File, +Options
cov_load_data/2, % +File, +Options
cov_reset/0 %
cov_reset/0, %
cov_property/1 % ?Property
]).
:- autoload(library(apply), [exclude/3, maplist/2, convlist/3]).
:- autoload(library(ordsets),
Expand Down Expand Up @@ -940,6 +941,19 @@
'$cov_reset'.


%! cov_property(?Property)
%
% True when coverage analysis satisfies Property. Currently defined
% properties are:
%
% - active(?Nesting)
% True when coverage data is being collected. Nesting expresses
% the nesting of coverage/1 calls and is normally 1 (one).

cov_property(active(Level)) :-
'$cov_active'(Level).


/*******************************
* MESSAGES *
*******************************/
Expand Down
22 changes: 17 additions & 5 deletions src/pl-coverage.c
Original file line number Diff line number Diff line change
Expand Up @@ -563,16 +563,28 @@ PRED_IMPL("$cov_stop", 1, cov_stop, 0)
}


static
PRED_IMPL("$cov_active", 1, cov_active, 0)
{ PRED_LD

if ( !LD->coverage.active )
return FALSE;

return PL_unify_integer(A1, LD->coverage.active);
}


/*******************************
* PUBLISH PREDICATES *
*******************************/

BeginPredDefs(coverage)
PRED_DEF("$cov_data", 3, cov_data, PL_FA_NONDETERMINISTIC)
PRED_DEF("$cov_add", 3, cov_add, 0)
PRED_DEF("$cov_reset", 0, cov_reset, 0)
PRED_DEF("$cov_start", 1, cov_start, 0)
PRED_DEF("$cov_stop", 1, cov_stop, 0)
PRED_DEF("$cov_data", 3, cov_data, PL_FA_NONDETERMINISTIC)
PRED_DEF("$cov_add", 3, cov_add, 0)
PRED_DEF("$cov_reset", 0, cov_reset, 0)
PRED_DEF("$cov_start", 1, cov_start, 0)
PRED_DEF("$cov_stop", 1, cov_stop, 0)
PRED_DEF("$cov_active", 1, cov_active, 0)
EndPredDefs

#endif /*O_COVERAGE*/

0 comments on commit 69481a1

Please sign in to comment.