Skip to content

Commit 2b14740

Browse files
author
Jan Wielemaker
committed
ADDED: lib/patch.pl and tests for merging conflicting edits
1 parent ae3a3a6 commit 2b14740

File tree

5 files changed

+207
-0
lines changed

5 files changed

+207
-0
lines changed

lib/patch.pl

+118
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,118 @@
1+
/* Part of SWISH
2+
3+
Author: Jan Wielemaker
4+
5+
WWW: http://www.swi-prolog.org
6+
Copyright (C): 2014-2016, VU University Amsterdam
7+
CWI Amsterdam
8+
All rights reserved.
9+
10+
Redistribution and use in source and binary forms, with or without
11+
modification, are permitted provided that the following conditions
12+
are met:
13+
14+
1. Redistributions of source code must retain the above copyright
15+
notice, this list of conditions and the following disclaimer.
16+
17+
2. Redistributions in binary form must reproduce the above copyright
18+
notice, this list of conditions and the following disclaimer in
19+
the documentation and/or other materials provided with the
20+
distribution.
21+
22+
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
23+
"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
24+
LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
25+
FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
26+
COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
27+
INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
28+
BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
29+
LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
30+
CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
31+
LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
32+
ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
33+
POSSIBILITY OF SUCH DAMAGE.
34+
*/
35+
36+
:- module(patch,
37+
[ patch/4 % +Data, +Diff, -Merged, +Options
38+
]).
39+
:- use_module(library(process)).
40+
:- use_module(library(option)).
41+
42+
/** <module> Run patch program
43+
44+
This library uses the GNU patch(1) program to merge changes.
45+
*/
46+
47+
:- predicate_options(patch/4, 4,
48+
[ status(-compound),
49+
stderr(-string)
50+
]).
51+
52+
%% patch(+Orig:string, +Diff:string, -Merged:string, +Options)
53+
%
54+
% Patch the string Orig using Diff. Options:
55+
%
56+
% - status(-Status)
57+
% Unify Status with the completion status of patch. This
58+
% is exit(0) for smooth completion and exit(1) if there are
59+
% merge conflicts.
60+
% - stderr(-String)
61+
% Unify String with the data patch(1) sent to standard error.
62+
63+
patch(Orig, Diff, Merged, Options) :-
64+
setup_call_cleanup(
65+
tmp_file_stream(utf8, TmpFile, Out),
66+
( call_cleanup(format(Out, '~s', [Orig]),
67+
close(Out)),
68+
run_patch(TmpFile, Diff, Merged, Options)
69+
),
70+
delete_file(TmpFile)).
71+
72+
run_patch(File, Diff, Merged, Options) :-
73+
thread_self(Me),
74+
setup_call_cleanup(
75+
process_create(path(patch),
76+
[ '--force', '--merge', '--silent',
77+
'--output=-', file(File) ],
78+
[ stdin(pipe(In)),
79+
stdout(pipe(Out)),
80+
stderr(pipe(Err)),
81+
process(PID)
82+
]),
83+
( set_stream(In, encoding(utf8)),
84+
set_stream(Out, encoding(utf8)),
85+
set_stream(Err, encoding(utf8)),
86+
thread_create(copy_diff(Diff, In), _, [detached(true)]),
87+
thread_create(read_stderr(Me, Err), ErrThread, []),
88+
read_string(Out, _, Merged)
89+
),
90+
( close(Out),
91+
process_wait(PID, Status)
92+
)),
93+
get_errors(ErrThread, Options),
94+
( option(status(VarStat), Options)
95+
-> VarStat = Status
96+
; true
97+
).
98+
99+
copy_diff(Diff, To) :-
100+
call_cleanup(
101+
format(To, '~s', [Diff]),
102+
close(To)).
103+
104+
read_stderr(Master, Stderr) :-
105+
read_string(Stderr, _, Errors),
106+
thread_send_message(Master, patch_errors(Errors)).
107+
108+
get_errors(Thread, Options) :-
109+
thread_join(Thread, Status),
110+
( Status == true
111+
-> thread_get_message(patch_errors(Errors))
112+
; Status == exception(Error)
113+
-> throw(Error)
114+
),
115+
( option(stderr(Var), Options)
116+
-> Var = Errors
117+
; true
118+
).

test/diff/f0.txt

+5
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
Line 10
2+
Line 20
3+
Line 30
4+
Line 40
5+
Line 50

test/diff/f1.txt

+6
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
Line 10
2+
Line 20
3+
Line 30
4+
Line 35
5+
Line 40
6+
Line 50

test/diff/f2.txt

+6
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
Line 10
2+
Line 20
3+
Line 30
4+
Line 37
5+
Line 40
6+
Line 50

test/test_patch.pl

+72
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,72 @@
1+
/* Part of SWISH
2+
3+
Author: Jan Wielemaker
4+
5+
WWW: http://www.swi-prolog.org
6+
Copyright (C): 2014-2016, VU University Amsterdam
7+
CWI Amsterdam
8+
All rights reserved.
9+
10+
Redistribution and use in source and binary forms, with or without
11+
modification, are permitted provided that the following conditions
12+
are met:
13+
14+
1. Redistributions of source code must retain the above copyright
15+
notice, this list of conditions and the following disclaimer.
16+
17+
2. Redistributions in binary form must reproduce the above copyright
18+
notice, this list of conditions and the following disclaimer in
19+
the documentation and/or other materials provided with the
20+
distribution.
21+
22+
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
23+
"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
24+
LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
25+
FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
26+
COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
27+
INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
28+
BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
29+
LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
30+
CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
31+
LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
32+
ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
33+
POSSIBILITY OF SUCH DAMAGE.
34+
*/
35+
36+
:- module(test_patch, [ test_patch/0 ]).
37+
:- use_module(library(plunit)).
38+
:- use_module(library(process)).
39+
:- use_module(library(aggregate)).
40+
:- use_module(library(debug)).
41+
:- use_module(library(readutil)).
42+
:- use_module('../lib/patch').
43+
44+
test_patch :-
45+
run_tests([patch]).
46+
47+
:- begin_tests(patch).
48+
49+
test(simple, Merged+Status == Final+exit(0)) :-
50+
run(diff('-u', file('diff/f0.txt'), file('diff/f1.txt')), Diff, _),
51+
read_file_to_string('diff/f0.txt', Orig, []),
52+
read_file_to_string('diff/f1.txt', Final, []),
53+
patch(Orig, Diff, Merged, [status(Status)]).
54+
test(conflict, Status+Failures == exit(1)+1) :-
55+
run(diff('-u', file('diff/f0.txt'), file('diff/f1.txt')), Diff, _),
56+
read_file_to_string('diff/f2.txt', Orig, []),
57+
patch(Orig, Diff, Merged, [status(Status), stderr(Errors)]),
58+
aggregate_all(count, sub_string(Errors, _,_,_, 'Hunk #'), Failures),
59+
assertion(sub_string(Merged, _, _, _, "<<<<<")),
60+
assertion(sub_string(Merged, _, _, _, ">>>>>")),
61+
debug(patch,
62+
'Diff:~n~s~nMerged:~n~s~nStatus: ~p', [Diff, Merged, Status]).
63+
64+
:- end_tests(patch).
65+
66+
run(Command, Output, Status) :-
67+
Command =.. [Exe|Argv],
68+
setup_call_cleanup(
69+
process_create(path(Exe), Argv, [stdout(pipe(Out)), process(Pid)]),
70+
read_string(Out, _, Output),
71+
close(Out)),
72+
process_wait(Pid, Status).

0 commit comments

Comments
 (0)