Skip to content

Commit

Permalink
Silently mark packages requiring an unsupported version of opam as un…
Browse files Browse the repository at this point in the history
…available
  • Loading branch information
kit-ty-kate committed Sep 18, 2024
1 parent 6126c2b commit 03296d2
Show file tree
Hide file tree
Showing 6 changed files with 121 additions and 52 deletions.
1 change: 1 addition & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -82,6 +82,7 @@ users)

## Repository
* Mitigate curl/curl#13845 by falling back from --write-out to --fail if exit code 43 is returned by curl [#6168 @dra27 - fix #6120]
* Silently mark packages requiring an unsupported version of opam as unavailable [#5665 @kit-ty-kate - fix #5631]

## Lock

Expand Down
8 changes: 5 additions & 3 deletions src/format/opamFile.ml
Original file line number Diff line number Diff line change
Expand Up @@ -130,7 +130,7 @@ module MakeIO (F : IO_Arg) = struct
with
| OpamSystem.File_not_found _ ->
None
| e ->
| Pp.Bad_format _ as e ->
OpamStd.Exn.fatal e;
if OpamFormatConfig.(!r.strict) then
(OpamConsole.error "%s"
Expand Down Expand Up @@ -160,7 +160,7 @@ module MakeIO (F : IO_Arg) = struct

let read_from_f f input =
try f input with
| (Pp.Bad_version _ | Pp.Bad_format _) as e->
| Pp.Bad_format _ as e ->
if OpamFormatConfig.(!r.strict) then
(OpamConsole.error "%s" (Pp.string_of_bad_format e);
OpamConsole.error_and_exit `File_error "Strict mode: aborting")
Expand Down Expand Up @@ -1181,7 +1181,9 @@ module SyntaxFile(X: SyntaxFileArg) : IO_FILE with type t := X.t = struct
{pelem = Section {section_kind = {pelem = "#"; _}; _}; pos}]; _}
when OpamVersion.(compare (nopatch (of_string ver))
(nopatch OpamVersion.current)) <= 0 ->
raise (OpamPp.Bad_version (Some pos, "Parse error"))
raise
(OpamPp.Bad_version ((Some pos, "Parse error"),
Some (OpamVersion.of_string ver)))
| opamfile -> opamfile

let of_channel filename (ic:in_channel) =
Expand Down
22 changes: 11 additions & 11 deletions src/format/opamPp.ml
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ open OpamStd.Op

type bad_format = pos option * string

exception Bad_version of bad_format
exception Bad_version of bad_format * OpamVersion.t option
exception Bad_format of bad_format
exception Bad_format_list of bad_format list

Expand All @@ -25,35 +25,35 @@ let bad_format ?pos fmt =
raise (Bad_format (pos,str)))
fmt

let bad_version ?pos fmt =
let bad_version v ?pos fmt =
Printf.ksprintf
(fun str ->
raise (Bad_version (pos,str)))
raise (Bad_version ((pos,str), v)))
fmt

let add_pos pos = function
| Bad_format (pos_opt,msg) as e ->
if pos_opt = None || pos_opt = Some pos_null
then Bad_format (Some pos, msg)
else e
| Bad_version (pos_opt,msg) as e ->
| Bad_version ((pos_opt,msg),v) as e ->
if pos_opt = None || pos_opt = Some pos_null
then Bad_version (Some pos, msg)
then Bad_version ((Some pos, msg),v)
else e

| e -> e

let rec string_of_bad_format ?file e =
match e, file with
| Bad_version (None, msg), Some filename
| Bad_version ((None, msg), _), Some filename
| Bad_format (None, msg), Some filename
| Bad_version (Some {filename; start = -1, -1 ; stop = -1,-1 }, msg), _
| Bad_version ((Some {filename; start = -1, -1 ; stop = -1,-1 }, msg), _), _
| Bad_format (Some {filename; start = -1, -1 ; stop = -1,-1 }, msg), _ ->
Printf.sprintf "In %s:\n%s" filename msg
| Bad_version (Some pos, msg), _
| Bad_version ((Some pos, msg), _), _
| Bad_format (Some pos, msg), _ ->
Printf.sprintf "At %s:\n%s" (string_of_pos pos) msg
| Bad_version (None, msg), None
| Bad_version ((None, msg), _), None
| Bad_format (None, msg), None ->
Printf.sprintf "Input error:\n%s" msg
| Bad_format_list bfl, _ ->
Expand Down Expand Up @@ -137,13 +137,13 @@ let ignore = {
name_constr = (fun _ -> "<ignored>");
}

let check ?name ?(raise=bad_format) ?errmsg f =
let check ?name ?(raise=fun _ ?pos fmt -> bad_format ?pos fmt) ?errmsg f =
pp
?name
(fun ~pos x ->
if not (f x) then
match errmsg with
| Some m -> raise ~pos "%s" m
| Some m -> raise x ~pos "%s" m
| None -> unexpected ()
else x)
(fun x ->
Expand Down
6 changes: 3 additions & 3 deletions src/format/opamPp.mli
Original file line number Diff line number Diff line change
Expand Up @@ -22,13 +22,13 @@ type bad_format = pos option * string
input does not have the right format. *)
exception Bad_format of bad_format
exception Bad_format_list of bad_format list
exception Bad_version of bad_format
exception Bad_version of bad_format * OpamVersion.t option

(** Raise [Bad_format]. *)
val bad_format: ?pos:pos -> ('a, unit, string, 'b) format4 -> 'a

(** Raise [Bad_version]. *)
val bad_version: ?pos:pos -> ('a, unit, string, 'b) format4 -> 'a
val bad_version: OpamVersion.t option -> ?pos:pos -> ('a, unit, string, 'b) format4 -> 'a

val string_of_bad_format: ?file:string -> exn -> string

Expand Down Expand Up @@ -101,7 +101,7 @@ val ignore : ('a, 'b option) t
[Bad_format]. *)
val check :
?name:string ->
?raise:(?pos:pos -> (string -> 'a, unit, string, 'a) format4
?raise:('a -> ?pos:pos -> (string -> 'a, unit, string, 'a) format4
-> string -> 'a) ->
?errmsg:string -> ('a -> bool) -> ('a, 'a) t

Expand Down
19 changes: 18 additions & 1 deletion src/state/opamFileTools.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1176,7 +1176,7 @@ let lint_gen ?check_extra_files ?check_upstream ?(handle_dirname=false)
[0, `Error, "File does not exist"], None
| OpamLexer.Error _ | Parsing.Parse_error ->
[1, `Error, "File does not parse"], None
| OpamPp.Bad_version bf | OpamPp.Bad_format bf -> [warn_of_bad_format bf], None
| OpamPp.Bad_version (bf, _) | OpamPp.Bad_format bf -> [warn_of_bad_format bf], None
| OpamPp.Bad_format_list bfl -> List.map warn_of_bad_format bfl, None
in
let check_extra_files = match check_extra_files with
Expand Down Expand Up @@ -1409,6 +1409,23 @@ let read_opam dir =
(OpamPp.string_of_bad_format (OpamPp.Bad_format (snd err)));
None
| None, None -> None
| exception OpamPp.Bad_version ((_, _errmsg), Some version) ->
let sversion = OpamVersion.to_string version in
let scurrent = OpamVersion.to_string OpamVersion.current_nopatch in
log "opam-version %S unsupported on %s. Added as dummy unavailable package."
sversion (OpamFile.to_string opam_file);
Some
(OpamFile.OPAM.empty
|> OpamFile.OPAM.with_available
(FOp (FIdent ([], OpamVariable.of_string "opam-version", None),
`Geq, FString sversion))
|> OpamFile.OPAM.with_descr_body
(Printf.sprintf
"This package uses opam %s file format which opam %s cannot \
read.\n\n\
In order to install or view information on this package, please \
upgrade your opam installation to at least version %s."
sversion scurrent sversion))

let read_repo_opam ~repo_name ~repo_root dir =
let open OpamStd.Option.Op in
Expand Down
117 changes: 83 additions & 34 deletions tests/reftests/repository.test
Original file line number Diff line number Diff line change
Expand Up @@ -637,12 +637,10 @@ some-field-that-do-not-exist: true
<><> Updating package repositories ><><><><><><><><><><><><><><><><><><><><><><>
[repo] no changes from file://${BASEDIR}/REPO
[versions] synchronised from file://${BASEDIR}/VRS
[ERROR] In ${BASEDIR}/OPAM/repo/versions/packages/bad-opam-version/bad-opam-version.1/opam:
unsupported or missing file format version; should be 2.0 or older
[ERROR] Strict mode: aborting
[ERROR] Could not update repository "versions": OpamStd.OpamSys.Exit(30)
# Return code 40 #
opam-file opam-version "5.0" unsupported on ${BASEDIR}/OPAM/repo/versions/packages/bad-opam-version/bad-opam-version.1/opam. Added as dummy unavailable package.
Now run 'opam upgrade' to apply any package updates.
### opam list -A --all-versions -s
bad-opam-version.1
foo.1
foo.2
foo.3
Expand All @@ -651,8 +649,15 @@ foo.5
foo.6
good-opam-version.1
### opam show --raw bad-opam-version.1 | "${OPAMMAJORVERSION}" -> "CURRENTMAJOR"
[ERROR] No package matching bad-opam-version.1 found
# Return code 5 #
opam-version: "2.0"
name: "bad-opam-version"
version: "1"
synopsis: ""
description: """\
This package uses opam 5.0 file format which opam CURRENTMAJOR cannot read.

In order to install or view information on this package, please upgrade your opam installation to at least version 5.0."""
available: opam-version >= "5.0"
### :: without opam strict
### OPAMSTRICT=0
### <REPO/packages/bad-opam-version/bad-opam-version.2/opam>
Expand All @@ -667,13 +672,16 @@ opam-version: "2.0"

<><> Updating package repositories ><><><><><><><><><><><><><><><><><><><><><><>
[repo] synchronised from file://${BASEDIR}/REPO
[ERROR] Could not update repository "repo": In ${BASEDIR}/OPAM/repo/repo/packages/bad-opam-version/bad-opam-version.2/opam:
unsupported or missing file format version; should be 2.0 or older
opam-file opam-version "5.0" unsupported on ${BASEDIR}/OPAM/repo/repo/packages/bad-opam-version/bad-opam-version.2/opam. Added as dummy unavailable package.
opam-file opam-version "5.0" unsupported on ${BASEDIR}/OPAM/repo/repo/packages/bad-opam-version/bad-opam-version.3/opam. Added as dummy unavailable package.
[versions] synchronised from file://${BASEDIR}/VRS
[ERROR] Could not update repository "versions": In ${BASEDIR}/OPAM/repo/versions/packages/bad-opam-version/bad-opam-version.1/opam:
unsupported or missing file format version; should be 2.0 or older
# Return code 40 #
opam-file opam-version "5.0" unsupported on ${BASEDIR}/OPAM/repo/versions/packages/bad-opam-version/bad-opam-version.1/opam. Added as dummy unavailable package.
Now run 'opam upgrade' to apply any package updates.
### opam list -A --all-versions -s
a.1
bad-opam-version.1
bad-opam-version.2
bad-opam-version.3
foo.1
foo.2
foo.3
Expand All @@ -686,33 +694,61 @@ good-opam-version.1
### opam list -A --all-versions -s
### opam repository --this-switch add repo ./REPO
[repo] Initialised
[ERROR] Could not update repository "repo": In ${BASEDIR}/OPAM/repo/repo/packages/bad-opam-version/bad-opam-version.3/opam:
unsupported or missing file format version; should be 2.0 or older
[ERROR] Initial repository fetch failed
# Return code 40 #
### opam repository --this-switch add versions ./VRS
[versions] Initialised
[ERROR] Could not update repository "versions": In ${BASEDIR}/OPAM/repo/versions/packages/bad-opam-version/bad-opam-version.1/opam:
unsupported or missing file format version; should be 2.0 or older
[ERROR] Initial repository fetch failed
# Return code 40 #
### opam list -A --all-versions -s
a.1
bad-opam-version.1
bad-opam-version.2
bad-opam-version.3
foo.1
foo.2
foo.3
foo.4
foo.5
foo.6
good-opam-version.1
### opam show --raw bad-opam-version.1 | "${OPAMMAJORVERSION}" -> "CURRENTMAJOR"
[ERROR] No package matching bad-opam-version.1 found
# Return code 5 #
opam-version: "2.0"
name: "bad-opam-version"
version: "1"
synopsis: ""
description: """\
This package uses opam 5.0 file format which opam CURRENTMAJOR cannot read.

In order to install or view information on this package, please upgrade your opam installation to at least version 5.0."""
available: opam-version >= "5.0"
### opam show --raw bad-opam-version.2 | "${OPAMMAJORVERSION}" -> "CURRENTMAJOR"
[ERROR] No package matching bad-opam-version.2 found
# Return code 5 #
opam-version: "2.0"
name: "bad-opam-version"
version: "2"
synopsis: ""
description: """\
This package uses opam 5.0 file format which opam CURRENTMAJOR cannot read.

In order to install or view information on this package, please upgrade your opam installation to at least version 5.0."""
available: opam-version >= "5.0"
### opam show --raw bad-opam-version.3 | "${OPAMMAJORVERSION}" -> "CURRENTMAJOR"
[ERROR] No package matching bad-opam-version.3 found
# Return code 5 #
opam-version: "2.0"
name: "bad-opam-version"
version: "3"
synopsis: ""
description: """\
This package uses opam 5.0 file format which opam CURRENTMAJOR cannot read.

In order to install or view information on this package, please upgrade your opam installation to at least version 5.0."""
available: opam-version >= "5.0"
### :: Parse errors
### <VRS/packages/two-zero/two-zero.1/opam>
opam-version: "2.0"
GARBAGE
### opam update versions
[ERROR] Unknown repositories or installed packages: versions
# Return code 40 #

<><> Updating package repositories ><><><><><><><><><><><><><><><><><><><><><><>
[versions] synchronised from file://${BASEDIR}/VRS
[WARNING] Could not read file ${BASEDIR}/OPAM/repo/versions/packages/two-zero/two-zero.1/opam. skipping:
At ${BASEDIR}/OPAM/repo/versions/packages/two-zero/two-zero.1/opam:3:0-3:0::
Parse error
### opam show two-zero --raw
[ERROR] No package matching two-zero found
# Return code 5 #
Expand All @@ -721,8 +757,13 @@ GARBAGE
opam-version: "2.1"
GARBAGE
### opam update versions
[ERROR] Unknown repositories or installed packages: versions
# Return code 40 #

<><> Updating package repositories ><><><><><><><><><><><><><><><><><><><><><><>
[versions] synchronised from file://${BASEDIR}/VRS
[WARNING] Could not read file ${BASEDIR}/OPAM/repo/versions/packages/two-one/two-one.1/opam. skipping:
At ${BASEDIR}/OPAM/repo/versions/packages/two-one/two-one.1/opam:3:0-3:0::
Parse error
Now run 'opam upgrade' to apply any package updates.
### opam show two-one --raw
[ERROR] No package matching two-one found
# Return code 5 #
Expand All @@ -731,8 +772,12 @@ GARBAGE
opam-version: "2.2"
GARBAGE
### opam update versions
[ERROR] Unknown repositories or installed packages: versions
# Return code 40 #

<><> Updating package repositories ><><><><><><><><><><><><><><><><><><><><><><>
[versions] synchronised from file://${BASEDIR}/VRS
[WARNING] Could not read file ${BASEDIR}/OPAM/repo/versions/packages/two-two/two-two.1/opam. skipping:
At ${BASEDIR}/OPAM/repo/versions/packages/two-two/two-two.1/opam:3:0-3:0::
Parse error
### opam show two-two --raw
[ERROR] No package matching two-two found
# Return code 5 #
Expand All @@ -741,8 +786,12 @@ GARBAGE
opam-version: "2.3"
GARBAGE
### opam update versions
[ERROR] Unknown repositories or installed packages: versions
# Return code 40 #

<><> Updating package repositories ><><><><><><><><><><><><><><><><><><><><><><>
[versions] synchronised from file://${BASEDIR}/VRS
[WARNING] Could not read file ${BASEDIR}/OPAM/repo/versions/packages/two-three/two-three.1/opam. skipping:
At ${BASEDIR}/OPAM/repo/versions/packages/two-three/two-three.1/opam:3:0-3:0::
Parse error
### opam show two-three --raw
[ERROR] No package matching two-three found
# Return code 5 #

0 comments on commit 03296d2

Please sign in to comment.