Skip to content

Commit

Permalink
Explicitly load dependencies for many tests
Browse files Browse the repository at this point in the history
  • Loading branch information
JanWielemaker committed Oct 13, 2023
1 parent 7d2e721 commit 9b43b01
Show file tree
Hide file tree
Showing 13 changed files with 35 additions and 6 deletions.
1 change: 1 addition & 0 deletions src/Tests/GC/test_agc_copyterm.pl
Original file line number Diff line number Diff line change
Expand Up @@ -36,6 +36,7 @@
[ test_agc_copyterm/0
]).
:- use_module(library(plunit)).
:- use_module(library(debug)).

test_agc_copyterm :-
run_tests([ agc_copyterm
Expand Down
4 changes: 4 additions & 0 deletions src/Tests/core/test_code_type.pl
Original file line number Diff line number Diff line change
Expand Up @@ -36,6 +36,10 @@
:- module(test_code_type, [test_code_type/0]).
:- use_module(library(plunit)).
:- use_module(library(apply)).
:- use_module(library(aggregate)).
:- use_module(library(debug)).
:- use_module(library(ordsets)).
:- use_module(library(varnumbers)).

/** <module> Test Prolog text code_typeting primitives
Expand Down
1 change: 1 addition & 0 deletions src/Tests/core/test_text.pl
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,7 @@

:- module(test_text, [test_text/0]).
:- use_module(library(plunit)).
:- use_module(library(debug)).

/** <module> Test Prolog core text processing primitives
Expand Down
3 changes: 3 additions & 0 deletions src/Tests/db/test_db.pl
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,9 @@

:- module(test_db, [test_db/0]).
:- use_module(library(plunit)).
:- use_module(library(debug)).
:- use_module(library(gensym)).
:- use_module(library(lists)).

/** <module> Test Prolog core database functions
Expand Down
1 change: 1 addition & 0 deletions src/Tests/library/test_aggregate.pl
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,7 @@
:- use_module(library(dif)).
:- use_module(library(hashtable)).
:- use_module(library(lists)).
:- use_module(library(debug)).

test_aggregate :-
run_tests([ foreach,
Expand Down
3 changes: 3 additions & 0 deletions src/Tests/library/test_apply.pl
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,9 @@
[ test_apply/0
]).
:- use_module(library(apply)).
:- use_module(library(plunit)).
:- use_module(library(solution_sequences)).
:- use_module(library(yall)).

% Test foldl of library(apply)
% Author: David Tonhofer Dec 2020
Expand Down
1 change: 1 addition & 0 deletions src/Tests/library/test_date.pl
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,7 @@
:- use_module(library(lists)).
:- use_module(library(plunit)).
:- use_module(library(date)).
:- use_module(library(debug)).

:- dynamic
error/1.
Expand Down
1 change: 1 addition & 0 deletions src/Tests/library/test_evaluable_property.pl
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,7 @@
]).
:- use_module(library(plunit)).
:- use_module(library(prolog_evaluable)).
:- use_module(library(debug)).

test_evaluable_property :-
run_tests(evaluable_property).
Expand Down
2 changes: 1 addition & 1 deletion src/Tests/library/test_intercept.pl
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@
]).
:- use_module(library(plunit)).
:- use_module(library(intercept)).

:- use_module(library(debug)).

test_intercept :-
run_tests([ intercept
Expand Down
3 changes: 3 additions & 0 deletions src/Tests/tabling/test_incr_answer_subsumption.pl
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,9 @@
:- use_module(library(plunit)).
:- use_module(library(increval)).
:- use_module(library(tables)).
:- use_module(library(apply)).
:- use_module(library(debug)).
:- use_module(library(prolog_code)).

%! test_incr_answer_subsumption
%
Expand Down
2 changes: 2 additions & 0 deletions src/Tests/tabling/test_shared_units.pl
Original file line number Diff line number Diff line change
Expand Up @@ -38,6 +38,8 @@
[ test_shared_units/0
]).
:- use_module(library(plunit)).
:- use_module(library(debug)).
:- use_module(library(time)).

test_shared_units :-
run_tests([ shared_reeval
Expand Down
3 changes: 3 additions & 0 deletions src/Tests/thread/thr_local_1.pl
Original file line number Diff line number Diff line change
Expand Up @@ -36,6 +36,9 @@
[ thr_local_1/0
]).
:- use_module(library(apply)).
:- use_module(library(debug)).
:- use_module(library(lists)).
:- use_module(library(ordsets)).

/** <module> Test thread local predicates
Expand Down
16 changes: 11 additions & 5 deletions src/Tests/transaction/test_transactions.pl
Original file line number Diff line number Diff line change
Expand Up @@ -43,6 +43,7 @@
:- use_module(library(apply)).
:- use_module(library(error)).
:- use_module(library(debug)).
:- use_module(library(ordsets)).

:- meta_predicate
test_transaction(:).
Expand Down Expand Up @@ -201,9 +202,10 @@

test_transaction(M:List) :-
must_be(list, List),
anon_threads(Initial),
test(List, 1, _{module:M}, State),
cleanup(State),
assertion(no_more_threads).
assertion(no_more_threads(Initial)).

test([], _, State, State).
test([discard|More], _, State, _) :-
Expand Down Expand Up @@ -378,12 +380,16 @@
thread_send_message(Thread, done),
thread_join(Thread).

no_more_threads :-
anon_threads(Threads) :-
current_prolog_flag(threads, true),
!,
findall(T, anon_thread(T), Anon),
Anon == [].
no_more_threads.
findall(T, anon_thread(T), List),
sort(List, Threads).
anon_threads([]).

no_more_threads(Initial) :-
anon_threads(Now),
ord_subtract(Now, Initial, []).

anon_thread(T) :-
thread_property(T, id(_)),
Expand Down

0 comments on commit 9b43b01

Please sign in to comment.