blob: 407e5d62f1889b20b23263409341ffc51348f0e6 [file] [log] [blame]
Shawn O. Pearce9f253522011-06-06 13:49:06 -07001%% Copyright (C) 2011 The Android Open Source Project
2%%
3%% Licensed under the Apache License, Version 2.0 (the "License");
4%% you may not use this file except in compliance with the License.
5%% You may obtain a copy of the License at
6%%
7%% http://www.apache.org/licenses/LICENSE-2.0
8%%
9%% Unless required by applicable law or agreed to in writing, software
10%% distributed under the License is distributed on an "AS IS" BASIS,
11%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
12%% See the License for the specific language governing permissions and
13%% limitations under the License.
14
Shawn O. Pearce62628812011-06-16 13:56:25 -070015:- package gerrit.
Shawn O. Pearce9f253522011-06-06 13:49:06 -070016'$init' :- init.
17
18
19%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
20%%
21%% init:
22%%
23%% Initialize the module's private state. These typically take the form of global
24%% aliased hashes carrying "constant" data about the current change for any
25%% predicate that needs to obtain it.
26%%
27init :-
Shawn O. Pearced0df1692012-05-02 15:20:07 -070028 define_hash(commit_labels).
Shawn O. Pearce9f253522011-06-06 13:49:06 -070029
30define_hash(A) :- hash_exists(A), !, hash_clear(A).
31define_hash(A) :- atom(A), !, new_hash(_, [alias(A)]).
32
33
34%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
35%%
36%% commit_label/2:
37%%
38%% During rule evaluation of a change, this predicate is defined to
39%% be a table of labels that pertain to the commit of interest.
40%%
41%% commit_label( label('Code-Review', 2), user(12345789) ).
42%% commit_label( label('Verified', -1), user(8181) ).
43%%
44:- public commit_label/2.
45%%
46commit_label(L, User) :- L = label(H, _),
47 atom(H),
48 !,
49 hash_get(commit_labels, H, Cached),
50 ( [] == Cached ->
51 get_commit_labels(_),
52 hash_get(commit_labels, H, Rs), !
53 ;
54 Rs = Cached
55 ),
56 scan_commit_labels(Rs, L, User)
57 .
58commit_label(Label, User) :-
59 get_commit_labels(Rs),
60 scan_commit_labels(Rs, Label, User).
61
62scan_commit_labels([R | Rs], L, U) :- R = commit_label(L, U).
63scan_commit_labels([_ | Rs], L, U) :- scan_commit_labels(Rs, L, U).
64scan_commit_labels([], _, _) :- fail.
65
66get_commit_labels(Rs) :-
67 hash_contains_key(commit_labels, '$all'),
68 !,
69 hash_get(commit_labels, '$all', Rs)
70 .
71get_commit_labels(Rs) :-
Dave Borowitz808ee992012-01-18 15:36:23 -080072 '_load_commit_labels'(Rs),
Shawn O. Pearce9f253522011-06-06 13:49:06 -070073 set_commit_labels(Rs).
74
75set_commit_labels(Rs) :-
76 define_hash(commit_labels),
77 hash_put(commit_labels, '$all', Rs),
78 index_commit_labels(Rs).
79
80index_commit_labels([]).
81index_commit_labels([R | Rs]) :-
82 R = commit_label(label(H, _), _),
83 atom(H),
84 !,
85 hash_get(commit_labels, H, Tmp),
86 hash_put(commit_labels, H, [R | Tmp]),
87 index_commit_labels(Rs)
88 .
89index_commit_labels([_ | Rs]) :-
90 index_commit_labels(Rs).
91
92
93%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
94%%
Shawn O. Pearce9f253522011-06-06 13:49:06 -070095%% not_same/2:
96%%
97:- public not_same/2.
98%%
99not_same(ok(A), ok(B)) :- !, A \= B.
100not_same(label(_, ok(A)), label(_, ok(B))) :- !, A \= B.
101not_same(_, _).
102
103
104%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
105%%
106%% can_submit/2:
107%%
Jason Tsayf93796c2011-06-09 16:17:01 -0700108%% Executes the SubmitRule for each solution until one where all of the
Shawn O. Pearce9f253522011-06-06 13:49:06 -0700109%% states has the format label(_, ok(_)) is found, then cut away any
110%% remaining choice points leaving this as the last solution.
111%%
112:- public can_submit/2.
113%%
114can_submit(SubmitRule, S) :-
Sasa Zivkov680a5f82012-08-13 10:46:08 +0200115 call_rule(SubmitRule, Tmp),
Shawn O. Pearce9f253522011-06-06 13:49:06 -0700116 Tmp =.. [submit | Ls],
117 ( is_all_ok(Ls) -> S = ok(Tmp), ! ; S = not_ready(Tmp) ).
118
Sasa Zivkov680a5f82012-08-13 10:46:08 +0200119call_rule(P:X, Arg) :- !, F =.. [X, Arg], P:F.
120call_rule(X, Arg) :- !, F =.. [X, Arg], F.
Shawn O. Pearce9f253522011-06-06 13:49:06 -0700121
122is_all_ok([]).
123is_all_ok([label(_, ok(__)) | Ls]) :- is_all_ok(Ls).
Magnus Bäcka6ce9602012-05-10 11:33:47 -0700124is_all_ok([label(_, may(__)) | Ls]) :- is_all_ok(Ls).
Shawn O. Pearce9f253522011-06-06 13:49:06 -0700125is_all_ok(_) :- fail.
126
127
128%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
129%%
Sasa Zivkov3531ca42012-10-10 14:05:03 +0200130%% locate_helper
131%%
132%% Returns user:Func if it exists otherwise returns gerrit:Default
133
134locate_helper(Func, Default, Arity, user:Func) :-
135 '$compiled_predicate'(user, Func, Arity), !.
136locate_helper(Func, Default, Arity, user:Func) :-
137 listN(Arity, P), C =.. [Func | P], clause(user:C, _), !.
138locate_helper(Func, Default, _, gerrit:Default).
139
140listN(0, []).
141listN(N, [_|T]) :- N > 0, N1 is N - 1, listN(N1, T).
142
143%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
144%%
Jason Tsayf93796c2011-06-09 16:17:01 -0700145%% locate_submit_rule/1:
146%%
147%% Finds a submit_rule depending on what rules are available.
148%% If none are available, use default_submit/1.
149%%
150:- public locate_submit_rule/1.
151%%
152
153locate_submit_rule(RuleName) :-
Sasa Zivkov3531ca42012-10-10 14:05:03 +0200154 locate_helper(submit_rule, default_submit, 1, RuleName).
Jason Tsayf93796c2011-06-09 16:17:01 -0700155
156
157%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
158%%
Sasa Zivkov680a5f82012-08-13 10:46:08 +0200159%% get_submit_type/2:
160%%
161%% Executes the SubmitTypeRule and return the first solution
162%%
163:- public get_submit_type/2.
164%%
165get_submit_type(SubmitTypeRule, A) :-
166 call_rule(SubmitTypeRule, A), !.
167
168
169%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
170%%
171%% locate_submit_type/1:
172%%
173%% Finds a submit_type_rule depending on what rules are available.
174%% If none are available, use project_default_submit_type/1.
175%%
176:- public locate_submit_type/1.
177%%
178locate_submit_type(RuleName) :-
179 locate_helper(submit_type, project_default_submit_type, 1, RuleName).
180
181
182%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
183%%
Shawn O. Pearce9f253522011-06-06 13:49:06 -0700184%% default_submit/1:
185%%
186:- public default_submit/1.
187%%
188default_submit(P) :-
Dave Borowitz03fbaf82013-02-15 17:34:31 -0800189 get_legacy_label_types(LabelTypes),
190 default_submit(LabelTypes, P).
Shawn O. Pearce9f253522011-06-06 13:49:06 -0700191
192% Apply the old "all approval categories must be satisfied"
Dave Borowitz03fbaf82013-02-15 17:34:31 -0800193% loop by scanning over all of the label types to build up the
194% submit record.
Shawn O. Pearce9f253522011-06-06 13:49:06 -0700195%
Dave Borowitz03fbaf82013-02-15 17:34:31 -0800196default_submit(LabelTypes, P) :-
197 default_submit(LabelTypes, [], Tmp),
Shawn O. Pearce9f253522011-06-06 13:49:06 -0700198 reverse(Tmp, Ls),
199 P =.. [ submit | Ls].
200
201default_submit([], Out, Out).
202default_submit([Type | Types], Tmp, Out) :-
Dave Borowitz8e5de822013-02-18 14:53:57 -0800203 label_type(Label, Fun, Min, Max) = Type,
204 legacy_submit_rule(Fun, Label, Min, Max, Status),
Shawn O. Pearce9f253522011-06-06 13:49:06 -0700205 R = label(Label, Status),
206 default_submit(Types, [R | Tmp], Out).
207
208
209%% legacy_submit_rule:
210%%
211%% Apply the old -2..+2 style logic.
212%%
Dave Borowitz8e5de822013-02-18 14:53:57 -0800213legacy_submit_rule('MaxWithBlock', Label, Min, Max, T) :- !, max_with_block(Label, Min, Max, T).
Khai Dod44ea942013-07-31 07:45:17 -0700214legacy_submit_rule('AnyWithBlock', Label, Min, Max, T) :- !, any_with_block(Label, Min, T).
Dave Borowitz8e5de822013-02-18 14:53:57 -0800215legacy_submit_rule('MaxNoBlock', Label, Min, Max, T) :- !, max_no_block(Label, Max, T).
216legacy_submit_rule('NoBlock', Label, Min, Max, T) :- !, T = may(_).
217legacy_submit_rule('NoOp', Label, Min, Max, T) :- !, T = may(_).
Nasser Grainawi240ea292015-11-09 09:56:56 -0800218legacy_submit_rule('PatchSetLock', Label, Min, Max, T) :- !, T = may(_).
Dave Borowitz8e5de822013-02-18 14:53:57 -0800219legacy_submit_rule(Fun, Label, Min, Max, T) :- T = impossible(unsupported(Fun)).
Shawn O. Pearce9f253522011-06-06 13:49:06 -0700220
Shawn O. Pearce9f253522011-06-06 13:49:06 -0700221%% max_with_block:
222%%
223%% - The minimum is never used.
224%% - At least one maximum is used.
225%%
Shawn O. Pearce849a0a52011-06-20 17:39:07 -0700226:- public max_with_block/4.
227%%
Sasa Zivkovc73ea622013-01-30 13:56:15 +0100228max_with_block(Min, Max, Label, label(Label, S)) :-
229 number(Min), number(Max), atom(Label),
230 !,
231 max_with_block(Label, Min, Max, S).
Shawn O. Pearce9f253522011-06-06 13:49:06 -0700232max_with_block(Label, Min, Max, reject(Who)) :-
Changcheng Xiao6071c4e2017-07-21 16:10:23 +0200233 commit_label(label(Label, Min), Who),
Shawn O. Pearce9f253522011-06-06 13:49:06 -0700234 !
235 .
236max_with_block(Label, Min, Max, ok(Who)) :-
Changcheng Xiao6071c4e2017-07-21 16:10:23 +0200237 \+ commit_label(label(Label, Min), _),
238 commit_label(label(Label, Max), Who),
Shawn O. Pearce9f253522011-06-06 13:49:06 -0700239 !
240 .
241max_with_block(Label, Min, Max, need(Max)) :-
242 true
243 .
Khai Dod44ea942013-07-31 07:45:17 -0700244
Khai Dod44ea942013-07-31 07:45:17 -0700245%% any_with_block:
246%%
247%% - The maximum is never used.
248%%
249any_with_block(Label, Min, reject(Who)) :-
Simon Hwangd7fa6e382015-09-17 16:26:46 -0400250 Min < 0,
Changcheng Xiao6071c4e2017-07-21 16:10:23 +0200251 commit_label(label(Label, Min), Who),
Khai Dod44ea942013-07-31 07:45:17 -0700252 !
253 .
254any_with_block(Label, Min, may(_)).
255
Shawn O. Pearce9f253522011-06-06 13:49:06 -0700256
257%% max_no_block:
258%%
259%% - At least one maximum is used.
260%%
Nasser Grainawica444d02015-11-12 18:38:29 -0800261max_no_block(Max, Label, label(Label, S)) :-
262 number(Max), atom(Label),
263 !,
264 max_no_block(Label, Max, S).
Shawn O. Pearce9f253522011-06-06 13:49:06 -0700265max_no_block(Label, Max, ok(Who)) :-
Changcheng Xiao6071c4e2017-07-21 16:10:23 +0200266 commit_label(label(Label, Max), Who),
Shawn O. Pearce9f253522011-06-06 13:49:06 -0700267 !
268 .
269max_no_block(Label, Max, need(Max)) :-
270 true
271 .
Jason Tsay6c6700f2011-06-21 13:25:52 -0700272
Jason Tsay82c088e2011-06-30 15:42:37 -0700273%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
274%%
275%% filter_submit_results/3:
276%%
277%% Executes the submit_filter against the given list of results,
278%% returns a list of filtered results.
279%%
280:- public filter_submit_results/3.
281%%
282filter_submit_results(Filter, In, Out) :-
283 filter_submit_results(Filter, In, [], Tmp),
284 reverse(Tmp, Out).
285filter_submit_results(Filter, [I | In], Tmp, Out) :-
286 arg(1, I, R),
287 call_submit_filter(Filter, R, S),
288 !,
289 S =.. [submit | Ls],
290 ( is_all_ok(Ls) -> T = ok(S) ; T = not_ready(S) ),
291 filter_submit_results(Filter, In, [T | Tmp], Out).
292filter_submit_results(Filter, [_ | In], Tmp, Out) :-
Gustaf Lundh70209472014-12-18 16:05:30 +0100293 filter_submit_results(Filter, In, Tmp, Out),
Jason Tsay82c088e2011-06-30 15:42:37 -0700294 !
295 .
296filter_submit_results(Filter, [], Out, Out).
297
298call_submit_filter(P:X, R, S) :- !, F =.. [X, R, S], P:F.
299call_submit_filter(X, R, S) :- F =.. [X, R, S], F.
300
Sasa Zivkov680a5f82012-08-13 10:46:08 +0200301%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
302%%
303%% filter_submit_type_results/3:
304%%
305%% Executes the submit_type_filter against the result,
306%% returns the filtered result.
307%%
308:- public filter_submit_type_results/3.
309%%
310filter_submit_type_results(Filter, In, Out) :- call_submit_filter(Filter, In, Out).
311
Jason Tsay82c088e2011-06-30 15:42:37 -0700312
313%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
314%%
315%% locate_submit_filter/1:
316%%
317%% Finds a submit_filter if available.
318%%
319:- public locate_submit_filter/1.
320%%
321locate_submit_filter(FilterName) :-
Sasa Zivkov3531ca42012-10-10 14:05:03 +0200322 locate_helper(submit_filter, noop_filter, 2, FilterName).
323
324%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
325%%
326%% noop_filter/2:
327%%
328:- public noop_filter/2.
329%%
330noop_filter(In, In).
Jason Tsay82c088e2011-06-30 15:42:37 -0700331
Sasa Zivkov680a5f82012-08-13 10:46:08 +0200332%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
333%%
334%% locate_submit_type_filter/1:
335%%
336%% Finds a submit_type_filter if available.
337%%
338:- public locate_submit_type_filter/1.
339%%
340locate_submit_type_filter(FilterName) :-
341 locate_helper(submit_type_filter, noop_filter, 2, FilterName).
Jason Tsay82c088e2011-06-30 15:42:37 -0700342
343%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
344%%
345%% find_label/3:
346%%
347%% Finds labels successively and fails when there are no more results.
348%%
349:- public find_label/3.
350%%
351find_label([], _, _) :- !, fail.
352find_label(List, Name, Label) :-
353 List = [_ | _],
354 !,
355 find_label2(List, Name, Label).
356find_label(S, Name, Label) :-
357 S =.. [submit | Ls],
358 find_label2(Ls, Name, Label).
359
360find_label2([L | _ ], Name, L) :- L = label(Name, _).
361find_label2([_ | Ls], Name, L) :- find_label2(Ls, Name, L).
362
363
364%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
365%%
366%% remove_label/3:
367%%
368%% Removes all occurances of label(Name, Status).
369%%
370:- public remove_label/3.
371%%
372remove_label([], _, []) :- !.
373remove_label(List, Label, Out) :-
374 List = [_ | _],
375 !,
376 subtract1(List, Label, Out).
377remove_label(S, Label, Out) :-
378 S =.. [submit | Ls],
379 subtract1(Ls, Label, Tmp),
380 Out =.. [submit | Tmp].
381
382subtract1([], _, []) :- !.
383subtract1([E | L], E, R) :- !, subtract1(L, E, R).
384subtract1([H | L], E, [H | R]) :- subtract1(L, E, R).
385
386
Jason Tsay6c6700f2011-06-21 13:25:52 -0700387%% commit_author/1:
388%%
389:- public commit_author/1.
390%%
391commit_author(Author) :-
392 commit_author(Author, _, _).
393
394
395%% commit_committer/1:
396%%
397:- public commit_committer/1.
398%%
399commit_committer(Committer) :-
400 commit_committer(Committer, _, _).
Jason Tsay93f4de92011-06-27 11:25:07 -0700401
402
403%% commit_delta/1:
404%%
405:- public commit_delta/1.
406%%
407commit_delta(Regex) :-
408 once(commit_delta(Regex, _, _, _)).
409
410
411%% commit_delta/3:
412%%
413:- public commit_delta/3.
414%%
415commit_delta(Regex, Type, Path) :-
416 commit_delta(Regex, TmpType, NewPath, OldPath),
417 split_commit_delta(TmpType, NewPath, OldPath, Type, Path).
418
419split_commit_delta(rename, NewPath, OldPath, delete, OldPath).
420split_commit_delta(rename, NewPath, OldPath, add, NewPath) :- !.
421split_commit_delta(copy, NewPath, OldPath, add, NewPath) :- !.
422split_commit_delta(Type, Path, _, Type, Path).
Jason Tsayac7d2f32011-07-15 12:26:36 -0700423
424
425%% commit_message_matches/1:
426%%
427:- public commit_message_matches/1.
428%%
429commit_message_matches(Pattern) :-
430 commit_message(Msg),
431 regex_matches(Pattern, Msg).
Gal Paikin1226ce62020-07-24 20:58:45 +0300432
433
434%% member/2:
435%%
436:- public member/2.
437%%
438member(X,[X|_]).
439member(X,[Y|T]) :- member(X,T).
440
441%% includes_file/1:
442%%
443:- public includes_file/1.
444%%
445includes_file(File) :-
446 files(List),
447 member(File, List).