Skip to content

Commit

Permalink
Additional indexing tests.
Browse files Browse the repository at this point in the history
  • Loading branch information
JanWielemaker committed Jan 13, 2025
1 parent 39a7ab8 commit 4cbc978
Showing 1 changed file with 128 additions and 89 deletions.
217 changes: 128 additions & 89 deletions src/Tests/db/test_jit.pl
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,9 @@
Author: Jan Wielemaker
E-mail: [email protected]
WWW: www.swi-prolog.org
Copyright (c) 2011-2017, University of Amsterdam
Copyright (c) 2011-2025, University of Amsterdam
VU University Amsterdam
SWI-Prolog Solutions b.v.
All rights reserved.
Redistribution and use in source and binary forms, with or without
Expand Down Expand Up @@ -34,14 +35,17 @@
*/

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

test_jit :-
run_tests([ jit
]).
run_tests([ jit,
jit_static
]).

/** <module> Test unit for Just-In-Time indexing
Expand All @@ -51,127 +55,127 @@
:- begin_tests(jit).

:- dynamic
d/2.
d/2.

:- meta_predicate
has_hashes(:, ?),
not_hashed(:).
has_hashes(:, ?),
not_hashed(:).

has_hashes(P, Hashes) :-
maplist(index, Hashes, RIndexed),
predicate_property(P, indexed(Indexed)),
maplist(pindex, Indexed, PIndexed),
msort(PIndexed, RIndexed).
maplist(index, Hashes, RIndexed),
predicate_property(P, indexed(Indexed)),
maplist(pindex, Indexed, PIndexed),
msort(PIndexed, RIndexed).

index(N, [N]-_) :- integer(N), !.
index(L, L-_).

pindex(single(I)-Hash, [I]-Hash).
pindex(multi(List)-Hash, List-Hash).
pindex(deep(_)-_, _) :-
assertion(fail).
assertion(fail).

not_hashed(P) :-
\+ predicate_property(P, indexed(_)).
\+ predicate_property(P, indexed(_)).


test(remove, [cleanup(retractall(d(_,_)))]) :-
forall(between(1,50,X), assertz(d(X,X))),
d(_,30),
assertion(has_hashes(d(_,_), [2])),
forall(between(51,125,X), assertz(d(X,X))),
assertion(not_hashed(p(_,_))),
d(30,_),
assertion(has_hashes(d(_,_), [1])).
forall(between(1,50,X), assertz(d(X,X))),
d(_,30),
assertion(has_hashes(d(_,_), [2])),
forall(between(51,125,X), assertz(d(X,X))),
assertion(not_hashed(p(_,_))),
d(30,_),
assertion(has_hashes(d(_,_), [1])).
test(remove, [cleanup(retractall(d(_,_)))]) :-
forall(between(1,40,X), assertz(d(X,a))),
forall(between(41,50,X), assertz(d(X,X))),
d(30,a),
assertion(has_hashes(d(_,_), [1])),
retractall(d(_,a)),
assertion(not_hashed(p(_,_))),
d(_,45),
assertion(has_hashes(d(_,_), [2])).
forall(between(1,40,X), assertz(d(X,a))),
forall(between(41,50,X), assertz(d(X,X))),
d(30,a),
assertion(has_hashes(d(_,_), [1])),
retractall(d(_,a)),
assertion(not_hashed(p(_,_))),
d(_,45),
assertion(has_hashes(d(_,_), [2])).
test(retract, [cleanup(retractall(d(_,_))), Xs == Xsok]) :-
forall(between(1,10,X), assertz(d(X,X))),
forall(between(11,100,X), assertz(d(a,X))),
findall(X, retract(d(a,X)), Xs),
numlist(11, 100, Xsok).
forall(between(1,10,X), assertz(d(X,X))),
forall(between(11,100,X), assertz(d(a,X))),
findall(X, retract(d(a,X)), Xs),
numlist(11, 100, Xsok).
test(retract2, [cleanup(retractall(d(_,_))), Xs == Xsok]) :-
forall(between(1,10,X), assertz(d(X,X))),
forall(between(11,100,X), assertz(d(a,X))),
findall(X, rmd(a,X), Xs),
numlist(11, 100, Xsok).
forall(between(1,10,X), assertz(d(X,X))),
forall(between(11,100,X), assertz(d(a,X))),
findall(X, rmd(a,X), Xs),
numlist(11, 100, Xsok).
test(clause, [cleanup(retractall(d(_,_))), Xs == Xsok]) :-
forall(between(1,10,X), assertz(d(X,X))),
forall(between(11,100,X), assertz(d(a,X))),
findall(X, claused(a,X), Xs),
numlist(11, 100, Xsok).
forall(between(1,10,X), assertz(d(X,X))),
forall(between(11,100,X), assertz(d(a,X))),
findall(X, claused(a,X), Xs),
numlist(11, 100, Xsok).
test(string, [cleanup(retractall(d(_,_)))]) :-
test_index_1(string_concat("a")).
test_index_1(string_concat("a")).
test(bigint, [condition(current_prolog_flag(bounded, false)),
cleanup(retractall(d(_,_)))]) :-
test_index_1(mkbigint(100)).
cleanup(retractall(d(_,_)))]) :-
test_index_1(mkbigint(100)).
test(midint, [cleanup(retractall(d(_,_)))]) :-
test_index_1(mkbigint(60)).
test_index_1(mkbigint(60)).
test(float, [cleanup(retractall(d(_,_)))]) :-
test_index_1(mkfloat).
test_index_1(mkfloat).
test(string, [cleanup(retractall(d(_,_)))]) :-
test_index_2(string_concat("a")).
test_index_2(string_concat("a")).
test(bigint, [condition(current_prolog_flag(bounded, false)),
cleanup(retractall(d(_,_)))]) :-
test_index_2(mkbigint(100)).
cleanup(retractall(d(_,_)))]) :-
test_index_2(mkbigint(100)).
test(midint, [cleanup(retractall(d(_,_)))]) :-
test_index_2(mkbigint(60)).
test_index_2(mkbigint(60)).
test(float, [cleanup(retractall(d(_,_)))]) :-
test_index_2(mkfloat).
test_index_2(mkfloat).

rmd(X,Y) :-
retract(d(X, Y)),
( Y == 89
-> garbage_collect_clauses
; true
).
retract(d(X, Y)),
( Y == 89
-> garbage_collect_clauses
; true
).

claused(X,Y) :-
clause(d(X, Y), true),
( Y == 89
-> garbage_collect_clauses
; true
).
clause(d(X, Y), true),
( Y == 89
-> garbage_collect_clauses
; true
).

mkbigint(Shift, I, Big) :-
Big is 1<<Shift+I.
Big is 1<<Shift+I.
mkfloat(I, Float) :-
Float is float(I).
Float is float(I).

:- meta_predicate
test_index_1(2),
test_index_2(2).
test_index_1(2),
test_index_2(2).

test_index_1(Convert) :-
retractall(d(_,_)),
forall(between(1, 1000, I),
( call(Convert, I, D),
assertz(d(D, I))
)),
forall(between(1, 1000, I),
( call(Convert, I, D),
assertion((d(D, I2), I2 == I))
)),
assertion(has_hashes(d(_,_), [1])).
retractall(d(_,_)),
forall(between(1, 1000, I),
( call(Convert, I, D),
assertz(d(D, I))
)),
forall(between(1, 1000, I),
( call(Convert, I, D),
assertion((d(D, I2), I2 == I))
)),
assertion(has_hashes(d(_,_), [1])).

test_index_2(Convert) :-
retractall(d(_,_)),
forall(between(1, 1000, I),
( call(Convert, I, D),
assertz(d(I, D))
)),
forall(between(1, 1000, I),
( call(Convert, I, D),
assertion((d(I2, D), I2 == I))
)),
assertion(has_hashes(d(_,_), [2])).
retractall(d(_,_)),
forall(between(1, 1000, I),
( call(Convert, I, D),
assertz(d(I, D))
)),
forall(between(1, 1000, I),
( call(Convert, I, D),
assertion((d(I2, D), I2 == I))
)),
assertion(has_hashes(d(_,_), [2])).

p1(a(b(c(d(e(f(g(1)))))))).
p1(a(b(c(d(e(f(g(2)))))))).
Expand All @@ -180,10 +184,45 @@
p2(a(b(c(d(e(f(g(h(2))))))))).

test(depth) :-
p1(a(b(c(d(e(f(g(1)))))))),
p1(a(b(c(d(e(f(g(2)))))))).
p1(a(b(c(d(e(f(g(1)))))))),
p1(a(b(c(d(e(f(g(2)))))))).
test(depth_exceeded, nondet) :-
p2(a(b(c(d(e(f(g(h(1))))))))),
p2(a(b(c(d(e(f(g(h(2))))))))).
p2(a(b(c(d(e(f(g(h(1))))))))),
p2(a(b(c(d(e(f(g(h(2))))))))).

:- end_tests(jit).

:- begin_tests(jit_static).

x(x,x,x,x,[]).
x(x,x,x,x,[_|_]).

a(_,_,_,_,[]).
a(_,_,_,_,[_|_]).

:- mode(m(?,?,?,?,-)).
m(_,_,_,_,[]).
m(_,_,_,_,[_|_]).

b(_,_,_,_,[]).
b(_,_,_,[_|_],_).

pa(_, _).
pa(_, x).

test(x) :- % must use S_LIST
x(_,_,_,_,[]).
test(a) :- % must use S_LIST (test H_VOID_N)
a(_,_,_,_,[]).
test(b) :- % may not use S_LIST (test H_VOID_N)
call_cleanup(b(_,_,_,_,[]), Det=true),
assertion(var(Det)),
!.
test(m) :- % may not use S_LIST (test mode/1)
call_cleanup(m(_,_,_,_,[]), Det=true),
assertion(var(Det)),
!.
test(pa) :- % primary index should be on arg 2
pa(_,y).

:- end_tests(jit_static).

0 comments on commit 4cbc978

Please sign in to comment.