Skip to content

Commit

Permalink
Merge pull request #2218 from bakaq/when
Browse files Browse the repository at this point in the history
Add when/2 and when_si/2
  • Loading branch information
mthom authored Dec 20, 2023
2 parents 299df50 + f411fb1 commit 44a61fa
Show file tree
Hide file tree
Showing 6 changed files with 283 additions and 1 deletion.
31 changes: 30 additions & 1 deletion src/lib/si.pl
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,8 @@
character_si/1,
term_si/1,
chars_si/1,
dif_si/2]).
dif_si/2,
when_si/2]).

:- use_module(library(lists)).

Expand Down Expand Up @@ -98,3 +99,31 @@
( X \= Y -> true
; throw(error(instantiation_error,dif_si/2))
).

:- meta_predicate(when_si(+, 0)).

%% when_si(Condition, Goal).
%
% Executes Goal when Condition becomes true. Throws an instantiation error if
% it can't decide.
when_si(Condition, Goal) :-
% Taken from https://stackoverflow.com/a/40449516
( when_condition_si(Condition) ->
( Condition ->
Goal
; throw(error(instantiation_error,when_si/2))
)
; throw(error(domain_error(when_condition_si, Condition),_))
).

when_condition_si(Cond) :-
var(Cond), !, throw(error(instantiation_error,when_condition_si/2)).
when_condition_si(ground(_)).
when_condition_si(nonvar(_)).
when_condition_si((A, B)) :-
when_condition_si(A),
when_condition_si(B).
when_condition_si((A ; B)) :-
when_condition_si(A),
when_condition_si(B).

106 changes: 106 additions & 0 deletions src/lib/when.pl
Original file line number Diff line number Diff line change
@@ -0,0 +1,106 @@
/**
Provides the predicate `when/2`.
*/

:- module(when, [when/2]).

:- use_module(library(atts)).
:- use_module(library(dcgs)).
:- use_module(library(lists)).
:- use_module(library(lambda)).

:- use_module(library(format)).
:- use_module(library(debug)).

:- attribute when_list/1.

:- meta_predicate(when(+, 0)).

%% when(Condition, Goal).
%
% Executes Goal when Condition becomes true.
when(Condition, Goal) :-
( when_condition(Condition) ->
( Condition ->
Goal
; term_variables(Condition, Vars),
maplist(
[Goal, Condition]+\Var^(
get_atts(Var, when_list(Whens0)) ->
Whens = [when(Condition, Goal) | Whens0],
put_atts(Var, when_list(Whens))
; put_atts(Var, when_list([when(Condition, Goal)]))
),
Vars
)
)
; throw(error(domain_error(when_condition, Condition),_))
).

when_condition(Cond) :-
% Should this be delayed?
var(Cond), !, throw(error(instantiation_error,when_condition/1)).
when_condition(ground(_)).
when_condition(nonvar(_)).
when_condition((A, B)) :-
when_condition(A),
when_condition(B).
when_condition((A ; B)) :-
when_condition(A),
when_condition(B).

remove_goal([], _, []).
remove_goal([G0|G0s], Goal, Goals) :-
( G0 == Goal ->
remove_goal(G0s, Goal, Goals)
; Goals = [G0|Goals1],
remove_goal(G0s, Goal, Goals1)
).

vars_remove_goal(Vars, Goal) :-
maplist(
Goal+\Var^(
get_atts(Var, when_list(Whens0)) ->
remove_goal(Whens0, Goal, Whens),
( Whens = [] ->
put_atts(Var, -when_list(_))
; put_atts(Var, when_list(Whens))
)
; true
),
Vars
).

reinforce_goal(Goal0, Goal) :-
Goal = (
term_variables(Goal0, Vars),
when:vars_remove_goal(Vars, Goal0),
Goal0
).

verify_attributes(Var, Value, Goals) :-
( get_atts(Var, when_list(Whens)) ->
( var(Value) ->
( get_atts(Value, when_list(WhensValue)) ->
append(Whens, WhensValue, WhensNew),
put_atts(Value, when_list(WhensNew))
; put_atts(Value, when_list(Whens))
),
Goals = []
; maplist(reinforce_goal, Whens, Goals)
)
; Goals = []
).

gather_when_goals([], _) --> [].
gather_when_goals([When|Whens], Var) -->
( { term_variables(When, [V0|_]), Var == V0 } ->
[when:When]
; []
),
gather_when_goals(Whens, Var).

attribute_goals(Var) -->
{ get_atts(Var, when_list(Whens)) },
gather_when_goals(Whens, Var),
{ put_atts(Var, -when_list(_)) }.
145 changes: 145 additions & 0 deletions src/tests/when.pl
Original file line number Diff line number Diff line change
@@ -0,0 +1,145 @@
/**/

:- use_module(library(format)).
:- use_module(library(dcgs)).
:- use_module(library(lists)).
:- use_module(library(debug)).
:- use_module(library(atts)).

:- use_module(library(when)).

test("condition true before ground/1",(
A = 1,
when(ground(A), Run = true),
Run == true
)).

test("condition true before nonvar/1",(
A = a(_),
when(nonvar(A), Run = true),
Run == true
)).

test("condition true before ','/2",(
A = 1,
B = a(_),
when((ground(A), nonvar(B)), Run = true),
Run == true
)).

test("condition true before (;)/2",(
A = 1,
when((ground(A) ; nonvar(_)), Run1 = true),
Run1 == true,

B = a(_),
when((ground(_) ; nonvar(B)), Run2 = true),
Run2 == true
)).

test("condition true after ground/1",(
when(ground(A), Run = true),
var(Run),
A = 1,
Run == true
)).

test("condition true after nonvar/1",(
when(nonvar(A), Run = true),
var(Run),
A = a(_),
Run == true
)).

test("condition true after ','/2",(
when((ground(A), nonvar(B)), Run = true),
var(Run),
A = 1,
var(Run),
B = a(_),
Run == true
)).

test("condition true after (;)/2",(
when((ground(A) ; nonvar(_)), Run1 = true),
var(Run1),
A = 1,
Run1 == true,

when((ground(_) ; nonvar(B)), Run2 = true),
var(Run2),
B = a(_),
Run2 == true
)).

test("multiple when/2 on same variable",(
when(nonvar(A), Run1 = true),
when(ground(A), Run2 = true),
var(Run1), var(Run2),
A = a(B),
Run1 == true, var(Run2),
B = 1,
Run2 == true
)).

main :-
findall(test(Name, Goal), test(Name, Goal), Tests),
run_tests(Tests, Failed),
show_failed(Failed),
halt.

main_quiet :-
findall(test(Name, Goal), test(Name, Goal), Tests),
run_tests_quiet(Tests, Failed),
( Failed = [] ->
format("All tests passed", [])
; format("Some tests failed", [])
),
halt.

portray_failed_([]) --> [].
portray_failed_([F|Fs]) -->
"\"", F, "\"", "\n", portray_failed_(Fs).

portray_failed([]) --> [].
portray_failed([F|Fs]) -->
"\n", "Failed tests:", "\n", portray_failed_([F|Fs]).

show_failed(Failed) :-
phrase(portray_failed(Failed), F),
format("~s", [F]).

run_tests([], []).
run_tests([test(Name, Goal)|Tests], Failed) :-
format("Running test \"~s\"~n", [Name]),
( call(Goal) ->
Failed = Failed1
; format("Failed test \"~s\"~n", [Name]),
Failed = [Name|Failed1]
),
run_tests(Tests, Failed1).

run_tests_quiet([], []).
run_tests_quiet([test(Name, Goal)|Tests], Failed) :-
( call(Goal) ->
Failed = Failed1
; Failed = [Name|Failed1]
),
run_tests_quiet(Tests, Failed1).

assert_p(A, B) :-
phrase(portray_clause_(A), Portrayed),
phrase((B, ".\n"), Portrayed).

call_residual_goals(Goal, ResidualGoals) :-
call_residue_vars(Goal, Vars),
variables_residual_goals(Vars, ResidualGoals).

variables_residual_goals(Vars, Goals) :-
phrase(variables_residual_goals(Vars), Goals).

variables_residual_goals([]) --> [].
variables_residual_goals([Var|Vars]) -->
dif_:attribute_goals(Var),
variables_residual_goals(Vars).

Empty file.
1 change: 1 addition & 0 deletions tests/scryer/cli/src_tests/when_tests.stdout
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
All tests passed
1 change: 1 addition & 0 deletions tests/scryer/cli/src_tests/when_tests.toml
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
args = ["-f", "--no-add-history", "src/tests/when.pl", "-f", "-g", "main_quiet"]

0 comments on commit 44a61fa

Please sign in to comment.