Skip to content

Commit 4dd2fe9

Browse files
authored
Merge pull request #6199 from dra27/format-warning
Return parse errors for 2.2/2.3 formats
2 parents 21bb251 + a216344 commit 4dd2fe9

File tree

4 files changed

+188
-4
lines changed

4 files changed

+188
-4
lines changed

master_changes.md

+3
Original file line numberDiff line numberDiff line change
@@ -93,6 +93,8 @@ users)
9393

9494
## Opamfile
9595
* Make all writes atomic [#5489 @kit-ty-kate]
96+
* Propagate future opamfile parse errors correctly [#6199 @dra27]
97+
* Ensure future syntax errors are only reported when the syntax version is greater than the client, not the format library [#6199 @dra27 - fix #6188]
9698

9799
## External dependencies
98100
* Always pass --no-version-check and --no-write-registry to Cygwin setup [#6046 @dra27]
@@ -209,6 +211,7 @@ users)
209211
* lint: add more test cases for E59: special cases (conf, git url), with and without option `--with-check-upstream` [#5561 @rjbou]
210212
* lint: add more test cases for W59: special cases (conf, git url), with and without `--with-check-upstream` [#5561 @rjbou]
211213
* Add a test showing an unhelpful conflict message [#5210 @kit-ty-kate]
214+
* Add test in pin and lint for future opam version parse error [#6199 @dra27]
212215

213216
### Engine
214217
* Add a test filtering mechanism [#6105 @Keryan-dev]

src/format/opamFile.ml

+13-4
Original file line numberDiff line numberDiff line change
@@ -874,9 +874,17 @@ module Syntax = struct
874874
let filename = OpamFilename.to_string filename in
875875
lexbuf.Lexing.lex_curr_p <- { lexbuf.Lexing.lex_curr_p with
876876
Lexing.pos_fname = filename };
877-
try OpamParser.main OpamLexer.token lexbuf filename with
878-
| OpamLexer.Error msg -> error msg
879-
| Parsing.Parse_error -> error "Parse error"
877+
match OpamParser.main OpamLexer.token lexbuf filename with
878+
| {file_contents =
879+
[{pelem = Variable({pelem = "opam-version"; _},
880+
{pelem = String ver; _}); _ };
881+
{pelem = Section {section_kind = {pelem = "#"; _}; _}; _}]; _}
882+
when OpamVersion.(compare (nopatch (of_string ver))
883+
(nopatch OpamVersion.current)) <= 0 ->
884+
error "Parse error"
885+
| opamfile -> opamfile
886+
| exception OpamLexer.Error msg -> error msg
887+
| exception Parsing.Parse_error -> error "Parse error"
880888

881889

882890
let pp_channel filename ic oc =
@@ -1171,7 +1179,8 @@ module SyntaxFile(X: SyntaxFileArg) : IO_FILE with type t := X.t = struct
11711179
let catch_future_syntax_error = function
11721180
| {file_contents = [{pelem = Variable({pelem = "opam-version"; _}, {pelem = String ver; _}); _ };
11731181
{pelem = Section {section_kind = {pelem = "#"; _}; _}; pos}]; _}
1174-
when OpamVersion.(compare (nopatch (of_string ver)) (nopatch X.format_version)) <= 0 ->
1182+
when OpamVersion.(compare (nopatch (of_string ver))
1183+
(nopatch OpamVersion.current)) <= 0 ->
11751184
raise (OpamPp.Bad_version (Some pos, "Parse error"))
11761185
| opamfile -> opamfile
11771186

tests/reftests/lint.test

+51
Original file line numberDiff line numberDiff line change
@@ -1226,3 +1226,54 @@ ${BASEDIR}/lint.opam: Errors.
12261226
error 53: Mismatching 'extra-files:' field: "./relative/path", "/absolute/../relative/path", "/absolute/path", "extra-files..patch.patch"
12271227
error 73: Field 'extra-files' contains path with '..': "/absolute/../relative/path"
12281228
# Return code 1 #
1229+
### :::::::::::::::::::::
1230+
### : Test parse errors :
1231+
### :::::::::::::::::::::
1232+
### :1: future opam versions
1233+
### <pin:future/pin-at-two-one.opam>
1234+
opam-version: "2.1"
1235+
### <pin:future/pin-at-two-two.opam>
1236+
opam-version: "2.2"
1237+
### <pin:future/pin-at-two-three.opam>
1238+
opam-version: "2.3"
1239+
### <pin:future/pin-at-future.opam>
1240+
opam-version: "50.0"
1241+
### opam lint future/pin-at-two-one.opam
1242+
${BASEDIR}/future/pin-at-two-one.opam: Errors.
1243+
error 2: File format error: unsupported or missing file format version; should be 2.0 or older
1244+
# Return code 1 #
1245+
### opam lint future/pin-at-two-two.opam
1246+
${BASEDIR}/future/pin-at-two-two.opam: Errors.
1247+
error 2: File format error: unsupported or missing file format version; should be 2.0 or older
1248+
# Return code 1 #
1249+
### opam lint future/pin-at-two-three.opam
1250+
${BASEDIR}/future/pin-at-two-three.opam: Errors.
1251+
error 2: File format error: unsupported or missing file format version; should be 2.0 or older
1252+
# Return code 1 #
1253+
### opam lint future/pin-at-future.opam
1254+
${BASEDIR}/future/pin-at-future.opam: Errors.
1255+
error 2: File format error: unsupported or missing file format version; should be 2.0 or older
1256+
# Return code 1 #
1257+
### :2: future opam versions with parse error
1258+
### <junk.sh>
1259+
echo GARBAGE>>"$1"
1260+
### sh junk.sh future/pin-at-two-one.opam
1261+
### sh junk.sh future/pin-at-two-two.opam
1262+
### sh junk.sh future/pin-at-two-three.opam
1263+
### sh junk.sh future/pin-at-future.opam
1264+
### opam lint future/pin-at-two-one.opam
1265+
${BASEDIR}/future/pin-at-two-one.opam: Errors.
1266+
error 2: File format error at line 11, column 0: Parse error
1267+
# Return code 1 #
1268+
### opam lint future/pin-at-two-two.opam
1269+
${BASEDIR}/future/pin-at-two-two.opam: Errors.
1270+
error 2: File format error at line 11, column 0: Parse error
1271+
# Return code 1 #
1272+
### opam lint future/pin-at-two-three.opam
1273+
${BASEDIR}/future/pin-at-two-three.opam: Errors.
1274+
error 2: File format error at line 11, column 0: Parse error
1275+
# Return code 1 #
1276+
### opam lint future/pin-at-future.opam
1277+
${BASEDIR}/future/pin-at-future.opam: Errors.
1278+
error 2: File format error: unsupported or missing file format version; should be 2.0 or older
1279+
# Return code 1 #

tests/reftests/pin.test

+121
Original file line numberDiff line numberDiff line change
@@ -263,3 +263,124 @@ Could not retrieve some package sources, they will not be pinned nor installed:
263263

264264
Continue anyway? [y/n] y
265265
### opam pin
266+
### : Parse error with future opam version field on pin
267+
### :: just the opam version that is a future
268+
### <pin:pin-at-two-one/pin-at-two-one.opam>
269+
opam-version: "2.1"
270+
### opam install ./pin-at-two-one
271+
[ERROR] In ${BASEDIR}/pin-at-two-one/pin-at-two-one.opam:
272+
unsupported or missing file format version; should be 2.0 or older
273+
[ERROR] Strict mode: aborting
274+
# Return code 30 #
275+
### OPAMSTRICT=0 opam install ./pin-at-two-one
276+
[ERROR] In ${BASEDIR}/pin-at-two-one/pin-at-two-one.opam:
277+
unsupported or missing file format version; should be 2.0 or older [skipped]
278+
279+
[ERROR] Invalid opam file in pin-at-two-one source from file://${BASEDIR}/pin-at-two-one:
280+
error 2: File format error: unsupported or missing file format version; should be 2.0 or older
281+
[ERROR] No package named pin-at-two-one found.
282+
# Return code 5 #
283+
### <pin:pin-at-two-two/pin-at-two-two.opam>
284+
opam-version: "2.2"
285+
### opam install ./pin-at-two-two
286+
[ERROR] In ${BASEDIR}/pin-at-two-two/pin-at-two-two.opam:
287+
unsupported or missing file format version; should be 2.0 or older
288+
[ERROR] Strict mode: aborting
289+
# Return code 30 #
290+
### OPAMSTRICT=0 opam install ./pin-at-two-two
291+
[ERROR] In ${BASEDIR}/pin-at-two-two/pin-at-two-two.opam:
292+
unsupported or missing file format version; should be 2.0 or older [skipped]
293+
294+
[ERROR] Invalid opam file in pin-at-two-two source from file://${BASEDIR}/pin-at-two-two:
295+
error 2: File format error: unsupported or missing file format version; should be 2.0 or older
296+
[ERROR] No package named pin-at-two-two found.
297+
# Return code 5 #
298+
### <pin:pin-at-two-three/pin-at-two-three.opam>
299+
opam-version: "2.3"
300+
### opam install ./pin-at-two-three
301+
[ERROR] In ${BASEDIR}/pin-at-two-three/pin-at-two-three.opam:
302+
unsupported or missing file format version; should be 2.0 or older
303+
[ERROR] Strict mode: aborting
304+
# Return code 30 #
305+
### OPAMSTRICT=0 opam install ./pin-at-two-three
306+
[ERROR] In ${BASEDIR}/pin-at-two-three/pin-at-two-three.opam:
307+
unsupported or missing file format version; should be 2.0 or older [skipped]
308+
309+
[ERROR] Invalid opam file in pin-at-two-three source from file://${BASEDIR}/pin-at-two-three:
310+
error 2: File format error: unsupported or missing file format version; should be 2.0 or older
311+
[ERROR] No package named pin-at-two-three found.
312+
# Return code 5 #
313+
### <pin:pin-at-future/pin-at-future.opam>
314+
opam-version: "50.0"
315+
### opam install ./pin-at-future
316+
[ERROR] In ${BASEDIR}/pin-at-future/pin-at-future.opam:
317+
unsupported or missing file format version; should be 2.0 or older
318+
[ERROR] Strict mode: aborting
319+
# Return code 30 #
320+
### OPAMSTRICT=0 opam install ./pin-at-future
321+
[ERROR] In ${BASEDIR}/pin-at-future/pin-at-future.opam:
322+
unsupported or missing file format version; should be 2.0 or older [skipped]
323+
324+
[ERROR] Invalid opam file in pin-at-future source from file://${BASEDIR}/pin-at-future:
325+
error 2: File format error: unsupported or missing file format version; should be 2.0 or older
326+
[ERROR] No package named pin-at-future found.
327+
# Return code 5 #
328+
### :: opam version is a future and there is a parse error
329+
### <junk.sh>
330+
echo GARBAGE>>"$1"
331+
### sh junk.sh pin-at-two-one/pin-at-two-one.opam
332+
### opam install ./pin-at-two-one
333+
[ERROR] At ${BASEDIR}/pin-at-two-one/pin-at-two-one.opam:11:0-11:0::
334+
Parse error
335+
[ERROR] Strict mode: aborting
336+
# Return code 30 #
337+
### OPAMSTRICT=0 opam install ./pin-at-two-one
338+
[ERROR] At ${BASEDIR}/pin-at-two-one/pin-at-two-one.opam:11:0-11:0::
339+
Parse error [skipped]
340+
341+
[ERROR] Invalid opam file in pin-at-two-one source from file://${BASEDIR}/pin-at-two-one:
342+
error 2: File format error at line 11, column 0: Parse error
343+
[ERROR] No package named pin-at-two-one found.
344+
# Return code 5 #
345+
### sh junk.sh pin-at-two-two/pin-at-two-two.opam
346+
### opam install ./pin-at-two-two
347+
[ERROR] At ${BASEDIR}/pin-at-two-two/pin-at-two-two.opam:11:0-11:0::
348+
Parse error
349+
[ERROR] Strict mode: aborting
350+
# Return code 30 #
351+
### OPAMSTRICT=0 opam install ./pin-at-two-two
352+
[ERROR] At ${BASEDIR}/pin-at-two-two/pin-at-two-two.opam:11:0-11:0::
353+
Parse error [skipped]
354+
355+
[ERROR] Invalid opam file in pin-at-two-two source from file://${BASEDIR}/pin-at-two-two:
356+
error 2: File format error at line 11, column 0: Parse error
357+
[ERROR] No package named pin-at-two-two found.
358+
# Return code 5 #
359+
### sh junk.sh pin-at-two-three/pin-at-two-three.opam
360+
### opam install ./pin-at-two-three
361+
[ERROR] At ${BASEDIR}/pin-at-two-three/pin-at-two-three.opam:11:0-11:0::
362+
Parse error
363+
[ERROR] Strict mode: aborting
364+
# Return code 30 #
365+
### OPAMSTRICT=0 opam install ./pin-at-two-three
366+
[ERROR] At ${BASEDIR}/pin-at-two-three/pin-at-two-three.opam:11:0-11:0::
367+
Parse error [skipped]
368+
369+
[ERROR] Invalid opam file in pin-at-two-three source from file://${BASEDIR}/pin-at-two-three:
370+
error 2: File format error at line 11, column 0: Parse error
371+
[ERROR] No package named pin-at-two-three found.
372+
# Return code 5 #
373+
### sh junk.sh pin-at-future/pin-at-future.opam
374+
### opam install ./pin-at-future
375+
[ERROR] In ${BASEDIR}/pin-at-future/pin-at-future.opam:
376+
unsupported or missing file format version; should be 2.0 or older
377+
[ERROR] Strict mode: aborting
378+
# Return code 30 #
379+
### OPAMSTRICT=0 opam install ./pin-at-future
380+
[ERROR] In ${BASEDIR}/pin-at-future/pin-at-future.opam:
381+
unsupported or missing file format version; should be 2.0 or older [skipped]
382+
383+
[ERROR] Invalid opam file in pin-at-future source from file://${BASEDIR}/pin-at-future:
384+
error 2: File format error: unsupported or missing file format version; should be 2.0 or older
385+
[ERROR] No package named pin-at-future found.
386+
# Return code 5 #

0 commit comments

Comments
 (0)