1:- module(
    2  call_ext,
    3  [
    4    bagof/4,                % +Template, :Goal, -Bag, +Zero
    5    call_boolean/2,         % :Goal_0, ?Boolean
    6    call_det_when/2,        % :Cond_0, :Goal_0
    7    call_det_when_ground/1, % :Goal_0
    8    call_det_when_ground/2, % ?Term, :Goal_0
    9    call_if_ground/1,       % :Goal_0
   10    call_if_ground/2,       % ?Term, :Goal_0
   11    call_if_nonvar/2,       % ?Term, :Goal_0
   12    call_forall/2,          % :A_1, :B_1
   13    call_must_be/2,         % :Goal_1, @Term
   14    call_pair/3,            % :Goal_2, +Pair1, -Pair2
   15    call_statistics/3,      % :Goal_0, +Key, -Delta
   16    call_stats/3,           % :Select_1, :Goal_1, -Stats
   17    call_stats_n/3,         % +Repeats, :Goal_0, -Stats
   18    call_warning/1,         % :Goal_0
   19    call_when_ground/1,     % :Goal_0
   20    call_when_ground/2,     % ?Term, :Goal_0
   21    equal_under/3,          % :Goal_2, +A, +B
   22    is_det/1,               % :Goal_0
   23    maplist/6,              % :Goal_5, ?Args1, ?Args2, ?Args3, ?Args4, ?Args5
   24    permlist/3,             % :Goal_2, ?Args1, ?Args2
   25    true/1,                 % ?Arg1
   26    true/2,                 % ?Arg1, ?Arg2
   27    true/3                  % ?Arg1, ?Arg2, ?Arg3
   28  ]
   29).   30:- reexport(library(apply)).

Call extensions

*/

   36:- use_module(library(dif)).   37:- use_module(library(plunit)).   38:- use_module(library(when)).   39
   40:- use_module(library(dict)).   41
   42:- meta_predicate
   43    bagof(+, 0, -, +),
   44    call_boolean(0, -),
   45    call_det_when(0, 0),
   46    call_det_when_ground(0),
   47    call_det_when_ground(?, 0),
   48    call_forall(1, 1),
   49    call_if_ground(0),
   50    call_if_ground(?, 0),
   51    call_if_nonvar(?, 0),
   52    call_must_be(1, +),
   53    call_pair(2, +, -),
   54    call_statistics(0, +, -),
   55    call_stats(1, 1, -),
   56    call_stats_n(+, 0, -),
   57    call_warning(0),
   58    call_when_ground(0),
   59    call_when_ground(?, 0),
   60    equal_under(2, +, +),
   61    is_det(0),
   62    maplist(5, ?, ?, ?, ?, ?),
   63    permlist(2, ?, ?),
   64    permlist1_(2, ?, ?),
   65    permlist2_(2, ?, ?).
 bagof(+Template:T, :Goal_0, -Bag:list(T), +Zero:list(T)) is det
   71bagof(Template, Goal_0, Bag, _) :-
   72  bagof(Template, Goal_0, Bag), !.
   73bagof(_, _, Zero, Zero).
 call_boolean(:Goal_0, +Boolean:boolean) is semidet
call_boolean(:Goal_0, -Boolean:boolean) is det
Returns whether Goal_0 succeeded once as a Boolean.
   82call_boolean(Goal_0, Boolean) :-
   83  (Goal_0 -> Boolean = true ; Boolean = false).
   84
   85:- begin_tests(call_boolean).   86
   87test('call_boolean(:,+)', [forall(test_call_boolean(Goal_1,Boolean))]) :-
   88  call_boolean(Goal_1, Boolean).
   89test('call_boolean(:,-)', [forall(test_call_boolean(Goal_1,Boolean))]) :-
   90  call_boolean(Goal_1, Boolean0),
   91  assertion(Boolean == Boolean0).
   92
   93test_call_boolean(false, false).
   94test_call_boolean(member(_,[]), false).
   95test_call_boolean(member(_,[_]), true).
   96test_call_boolean(true, true).
   97
   98:- end_tests(call_boolean).
 call_det_when(:Cond_0, :Goal_0)
Calls Goal_0 once when Cond_0 succeeds; otherwise calls Goal_0 normally.
  107call_det_when(Cond_0, Goal_0) :-
  108  Cond_0, !,
  109  once(Goal_0).
  110call_det_when(_, Goal_0) :-
  111  Goal_0.
 call_det_when_ground(:Goal_0)
 call_det_when_ground(?Term:term, :Goal_0)
Call Goal_0 deterministically in case Term is ground. Otherwise call Goal_0 normally.
  121call_det_when_ground(Mod:Goal_0) :-
  122  call_det_when_ground(Goal_0, Mod:Goal_0).
  123
  124
  125call_det_when_ground(Term, Goal_0) :-
  126  ground(Term), !,
  127  once(Goal_0).
  128call_det_when_ground(_, Goal_0) :-
  129  Goal_0.
 call_forall(:A_1, :B_1)
  135call_forall(A_1, B_1) :-
  136  forall(
  137    call(A_1, X),
  138    call(B_1, X)
  139  ).
 call_if_ground(:Goal_0) is det
 call_if_ground(?Term:term, :Goal_0) is det
  146call_if_ground(Mod:Goal_0) :-
  147  call_if_ground(Goal_0, Mod:Goal_0).
  148
  149
  150call_if_ground(Term, Goal_0) :-
  151  ground(Term), !,
  152  Goal_0.
  153call_if_ground(_, _).
 call_if_nonvar(?Term:term, :Goal_0) is det
  159call_if_nonvar(Term, _) :-
  160  var(Term), !.
  161call_if_nonvar(_, Goal_0) :-
  162  Goal_0.
 call_must_be(:Goal_1, @Term) is det
Checks whether Term belongs to the set of terms denoted by Goal_1.

Assumes that terms enumerated by `Goal_1' are ground.

  172call_must_be(Goal_1, Term) :-
  173  findall(Term0, call(Goal_1, Term0), Terms),
  174  must_be(oneof(Terms), Term).
 call_pair(:Goal_2, +Pair1:pair, -Pair2:pair) is det
Calls Goal_2 on the values of Pair1 and Pair2.
  182call_pair(Goal_2, Key-Value1, Key-Value2) :-
  183  call(Goal_2, Value1, Value2).
 call_statistics(:Goal_0, +Key, -Delta) is det
  189call_statistics(Goal_0, Key, Delta):-
  190  statistics(Key, Val1a),
  191  fix_val0(Val1a, Val1b),
  192  call(Goal_0),
  193  statistics(Key, Val2a),
  194  fix_val0(Val2a, Val2b),
  195  Delta is Val2b - Val1b.
  196
  197fix_val0([X,_], X) :- !.
  198fix_val0(X, X).
 call_stats(:Select_1, :Goal_1, -Stats:dict) is det
_{ cputime: float, inferences: nonneg, max: float, min: float, walltime: float }
  212call_stats(Select_1, Goal_1, Stats) :-
  213  % Initialize the state based on the first run.
  214  stats(Cpu1, Inf1, Wall1),
  215  once(call(Select_1, X0)),
  216  call(Goal_1, X0),
  217  stats(Cpu2, Inf2, Wall2),
  218  Cpu12 is Cpu2 - Cpu1,
  219  Inf12 is Inf2 - Inf1,
  220  Wall12 is Wall2 - Wall1,
  221  State = _{
  222    cputime: Cpu12-1,
  223    inferences: Inf12-1,
  224    maxcpu: Cpu12,
  225    mincpu: Cpu12,
  226    walltime: Wall12-1
  227  },
  228  forall(
  229    call(Select_1, X),
  230    (
  231      stats(Cpu3, Inf3, Wall3),
  232      call(Goal_1, X),
  233      stats(Cpu4, Inf4, Wall4),
  234      Cpu34 is Cpu4 - Cpu3,
  235      update_average(cputime, State, Cpu34),
  236      Inf34 is Inf4 - Inf3,
  237      update_average(inferences, State, Inf34),
  238      (   dict_get(maxcpu, State, Max),
  239          Cpu34 > Max
  240      ->  nb_set_dict(maxcpu, State, Cpu34)
  241      ;   true
  242      ),
  243      (   dict_get(mincpu, State, Min),
  244          Cpu34 < Min
  245      ->  nb_set_dict(mincpu, State, Cpu34)
  246      ;   true
  247      ),
  248      Wall34 is Wall4 - Wall3,
  249      update_average(walltime, State, Wall34)
  250    )
  251  ),
  252  _{
  253    cputime: Cpu-Repeats,
  254    inferences: Inf-Repeats,
  255    maxcpu: Max,
  256    mincpu: Min,
  257    walltime: Wall-Repeats
  258  } :< State,
  259  Stats = _{
  260    cputime: Cpu,
  261    inferences: Inf,
  262    max: Max,
  263    min: Min,
  264    walltime: Wall
  265  }.
 call_stats_n(+Repeats:positive_integer, :Goal_0, -Stats:dict) is det
_{ cputime: float, inferences: nonneg, max: float, min: float, walltime: float }
  279call_stats_n(Repeats, Goal_0, Stats) :-
  280  % Initialize the state based on the first run.
  281  stats(Cpu1, Inf1, Wall1),
  282  call(Goal_0),
  283  stats(Cpu2, Inf2, Wall2),
  284  Cpu12 is Cpu2 - Cpu1,
  285  Inf12 is Inf2 - Inf1,
  286  Wall12 is Wall2 - Wall1,
  287  State = _{
  288    cputime: Cpu12-1,
  289    inferences: Inf12-1,
  290    maxcpu: Cpu12,
  291    mincpu: Cpu12,
  292    walltime: Wall12-1
  293  },
  294  forall(
  295    between(2, Repeats, _),
  296    (
  297      stats(Cpu3, Inf3, Wall3),
  298      call(Goal_0),
  299      stats(Cpu4, Inf4, Wall4),
  300      Cpu34 is Cpu4 - Cpu3,
  301      update_average(cputime, State, Cpu34),
  302      Inf34 is Inf4 - Inf3,
  303      update_average(inferences, State, Inf34),
  304      (   dict_get(maxcpu, State, Max),
  305          Cpu34 > Max
  306      ->  nb_set_dict(maxcpu, State, Cpu34)
  307      ;   true
  308      ),
  309      (   dict_get(mincpu, State, Min),
  310          Cpu34 < Min
  311      ->  nb_set_dict(mincpu, State, Cpu34)
  312      ;   true
  313      ),
  314      Wall34 is Wall4 - Wall3,
  315      update_average(walltime, State, Wall34)
  316    )
  317  ),
  318  _{
  319    cputime: Cpu-Repeats,
  320    inferences: Inf-Repeats,
  321    maxcpu: Max,
  322    mincpu: Min,
  323    walltime: Wall-Repeats
  324  } :< State,
  325  Stats = _{
  326    cputime: Cpu,
  327    inferences: Inf,
  328    max: Max,
  329    min: Min,
  330    walltime: Wall
  331  }.
  332
  333stats(Cpu, Inf, Wall) :-
  334  statistics(inferences, Inf),
  335  statistics(cputime, Cpu),
  336  get_time(Wall).
  337
  338update_average(Key, State, Avg) :-
  339  dict_get(Key, State, M1-N1),
  340  N2 is N1 + 1,
  341  M2 is ((N1 * M1) + Avg) / N2,
  342  nb_set_dict(Key, State, M2-N2).
 call_warning(:Goal_0) is semidet
  348call_warning(Goal_0) :-
  349  catch(Goal_0, Error, true),
  350  (var(Error) -> true ; print_message(warning, Error), fail).
 call_when_ground(:Goal_0) is det
 call_when_ground(?Term:term, :Goal_0) is det
  357call_when_ground(Goal_0) :-
  358  call_when_ground(Goal_0, Goal_0).
  359
  360
  361call_when_ground(Term, Goal_0) :-
  362  when(ground(Term), Goal_0).
 equal_under(:Goal_2, +A:term, +B:term) is semidet
Succeeds iff `A' and `B' are equal under transformation `Goal_2'.
  370equal_under(Goal_2, A1, B1) :-
  371  maplist(Goal_2, [A1,B1], [A2,B2]),
  372  A2 == B2.
 is_det(:Goal_0) is semidet
  378is_det(Goal_0) :-
  379  call_cleanup(Goal_0, Det = true),
  380  (Det == true -> true ; !, fail).
 maplist(:Goal_5, ?Args1:list, ?Args2:list, ?Args3:list, ?Args4:list, ?Args5:list)
  386maplist(Goal_5, L1, L2, L3, L4, L5) :-
  387  maplist_(L1, L2, L3, L4, L5, Goal_5).
  388
  389maplist_([], [], [], [], [], _).
  390maplist_([H1|T1], [H2|T2], [H3|T3], [H4|T4], [H5|T5], Goal_5) :-
  391  call(Goal_5, H1, H2, H3, H4, H5),
  392  maplist_(T1, T2, T3, T4, T5, Goal_5).
 permlist(:Goal_2, ?Args1:list(term), ?Args2:list(term)) is det
  398permlist(Goal_2, Args1, Args2) :-
  399  permlist1_(Goal_2, Args1, Args2).
  400
  401permlist1_(_, [], _) :- !.
  402permlist1_(Goal_2, [H1|T1], L2) :-
  403  permlist2_(Goal_2, H1, L2),
  404  permlist1_(Goal_2, T1, L2).
  405
  406permlist2_(_, _, []) :- !.
  407permlist2_(Goal_2, H1, [H2|T2]) :-
  408  call(Goal_2, H1, H2),
  409  permlist2_(Goal_2, H1, T2).
 true(?Arg1) is det
 true(?Arg1, ?Arg2) is det
 true(?Arg1, ?Arg2, ?Arg3) is det
Always succeeds.
  419true(_).
  420true(_, _).
  421true(_, _, _)