File: bench.pl

package info (click to toggle)
swi-prolog 9.0.4%2Bdfsg-2
  • links: PTS, VCS
  • area: main
  • in suites: bookworm
  • size: 82,408 kB
  • sloc: ansic: 387,503; perl: 359,326; cpp: 6,613; lisp: 6,247; java: 5,540; sh: 3,147; javascript: 2,668; python: 1,900; ruby: 1,594; yacc: 845; makefile: 428; xml: 317; sed: 12; sql: 6
file content (120 lines) | stat: -rw-r--r-- 2,645 bytes parent folder | download | duplicates (4)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
:- module(bench,
          [ bench/0,
            bench_first/1,
            create/1,                   % +Triples
            remove_p/1,                 % +Fraction
            stress/2                    % SizeM, Threads
          ]).
:- include(local_test).
:- use_module(library(semweb/rdf_db)).
:- use_module(library(apply_macros)).
:- use_module(library(statistics)).
:- use_module(library(random)).

:- if(\+current_predicate(rdf_resource/1)).
rdf_resource(S) :-
    rdf_subject(S).
rdf_resource(S) :-
    rdf_current_predicate(S).
:- endif.

:- initialization set_random(seed(111)).

bench :-
    time(create(100000)),
    bench_first(100).

%!  bench_first
%
%   Query the first triple of all resources

bench_first(N) :-
    findall(Q, rdf_resource(Q), Resources),
    length(Resources, Len),
    format('~D resources~n', [Len]),
    time(forall(between(1, N, _),
                forall(member(Q,Resources),
                       first_triple(Q)))).

first_triple(Q) :-
    rdf(Q,_,_),
    !.
first_triple(_).

%!  create(N)
%
%   Create an RDF DB with N triples

create(N) :-
    flag(offset, Off, Off+N),
    create(N,Off).

create(N,Off) :-
    forall(between(1, N, I),
           add_random(N, I, Off)).

add_random(N, I, Off) :-
    random_triple(N,I,Off, S,P,O),
    rdf_assert(S, P, O).

random_triple(N,I,Off, S,P,O) :-
    random_subject(N, I, Off, S),
    random_predicate(N, I, Off, P),
    random_object(N, I, Off, O).

random_subject(N,_I,Off,S) :-
    I is random(N//10)+Off,
    atom_concat(s,I,S).

random_predicate(_N,_I,_Off,S) :-
    I is random(10),
    atom_concat(p,I,S).

random_object(N,I,Off,O) :-
    (   maybe(0.3),fail
    ->  R is random(N//30),
        atom_concat(l,R,L),
        O = literal(L)
    ;   random_subject(N,I,Off,O)
    ).

%!  remove_p(+P)
%
%   Remove a fraction of the DB.  E.g., remove_p(0.1) removes
%   10% of the DB.

remove_p(Prob) :-
    (   rdf(S,P,O),
        maybe(Prob),
        rdf_retractall(S,P,O),
        fail
    ;   true
    ).


%!  stress(SizeM, FillerThreads)
%
%   Start threads that fill, remove and GC the DB.

stress(SizeM, Fillers) :-
    MaxCount = round(SizeM*1000000),
    forall(between(1, Fillers, FI),
           (   atom_concat(filler_, FI, Alias),
               thread_create(filler(MaxCount), _, [alias(Alias)])
           )),
    thread_create(emptier, _, [alias(emptier)]).

filler(MaxCount) :-
    rdf_statistics(triples(Count)),
    (   Count > MaxCount
    ->  sleep(1)
    ;   Bunch = 100000,
        Offset is random(MaxCount-Bunch),
        time(create(Bunch,Offset))
    ),
    filler(MaxCount).

emptier :-
    remove_p(0.1),
    emptier.