Skip to content

Commit

Permalink
Merge pull request #5068 from rjbou/lint-repo-pkg
Browse files Browse the repository at this point in the history
lint: Fix repository package lint with tarred repositories, and update filename display
  • Loading branch information
rjbou committed May 10, 2022
2 parents 59c6cbb + 906a895 commit e36650b
Show file tree
Hide file tree
Showing 3 changed files with 46 additions and 20 deletions.
2 changes: 2 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -96,6 +96,8 @@ users)
* W68: add warning for missing license field [#4766 @kit-ty-kate - partial fix #4598]
* W62: use the spdx_licenses library to check for valid licenses. This allows to use compound expressions such as "MIT AND (GPL-2.0-only OR LGPL-2.0-only)", as well as user defined licenses e.g. "LicenseRef-my-custom-license" [#4768 @kit-ty-kate - fixes #4598]
* E57 (capital on synopsis) not trigger W47 (empty descr) [#5070 @rjbou]
* [BUG] Fix linting packages from repository with tarred repositories, the file in temporary repository was no more avaiable when lint is done [#5068 @rjbou]
* Update repository package filename display [#5068 @rjbou]

## Repository
* When several checksums are specified, instead of adding in the cache only the archive by first checksum, name by best one and link others to this archive [#4696 rjbou]
Expand Down
57 changes: 40 additions & 17 deletions src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3570,18 +3570,18 @@ let lint cli =
(OpamFilename.Dir.to_string d);
[]
| l ->
List.map (fun (_name,f,_) -> Some f) l
List.map (fun (_name,f,_) -> `file f) l
in
let files = match files, package with
| [], None -> (* Lookup in cwd if nothing was specified *)
opam_files_in_dir (OpamFilename.cwd ())
| files, None ->
List.map (function
| None -> [None] (* this means '-' was specified for stdin *)
| None -> [`stdin] (* this means '-' was specified for stdin *)
| Some (OpamFilename.D d) ->
opam_files_in_dir d
| Some (OpamFilename.F f) ->
[Some (OpamFile.make f)])
[`file (OpamFile.make f)])
files
|> List.flatten
| [], Some pkg ->
Expand All @@ -3595,7 +3595,25 @@ let lint cli =
let opam = OpamSwitchState.opam st nv in
match OpamPinned.orig_opam_file st (OpamPackage.name nv) opam with
| None -> raise Not_found
| some -> [some]
| Some f ->
let filename =
match OpamFile.OPAM.metadata_dir opam with
| None -> None
| Some (None, abs) ->
let filename =
if OpamFilename.starts_with
(OpamPath.Switch.Overlay.dir gt.root st.switch)
(OpamFilename.of_string abs) then
Printf.sprintf "<pinned>/%s" (OpamPackage.to_string nv)
else abs
in
Some filename
| Some (Some repo, _rel) ->
Some (Printf.sprintf "<%s>/%s"
(OpamRepositoryName.to_string repo)
(OpamPackage.to_string nv))
in
[`pkg (OpamFilename.read (OpamFile.filename f), filename)]
with Not_found ->
OpamConsole.error_and_exit `Not_found "No opam file found for %s%s"
(OpamPackage.Name.to_string (fst pkg))
Expand All @@ -3614,13 +3632,23 @@ let lint cli =
let err,json =
List.fold_left (fun (err,json) opam_f ->
try
let warnings,opam =
let (warnings, opam), opam_f =
let to_file f = OpamFile.make (OpamFilename.of_string f) in
let stdin_f = to_file "-" in
match opam_f with
| Some f ->
OpamFileTools.lint_file ~check_upstream ~handle_dirname:true f
| None ->
| `file f ->
OpamFileTools.lint_file ~check_upstream ~handle_dirname:true f,
Some (OpamFile.to_string f)
| `pkg (content, filename) ->
OpamFileTools.lint_string
~check_upstream ~handle_dirname:false
OpamStd.Option.(default stdin_f (map to_file filename))
content,
filename
| `stdin ->
OpamFileTools.lint_channel ~check_upstream ~handle_dirname:false
(OpamFile.make (OpamFilename.of_string "-")) stdin
stdin_f stdin,
None
in
let enabled =
let default = match warnings_sel with
Expand All @@ -3646,14 +3674,11 @@ let lint cli =
else if warnings = [] then
(if not normalise then
msg "%s%s\n"
(OpamStd.Option.to_string
(fun f -> OpamFile.to_string f ^ ": ")
opam_f)
(OpamStd.Option.to_string (Printf.sprintf "%s: ") opam_f)
(OpamConsole.colorise `green "Passed."))
else
msg "%s%s\n%s\n"
(OpamStd.Option.to_string (fun f -> OpamFile.to_string f ^ ": ")
opam_f)
(OpamStd.Option.to_string (Printf.sprintf "%s: ") opam_f)
(if failed then OpamConsole.colorise `red "Errors."
else OpamConsole.colorise `yellow "Warnings.")
(OpamFileTools.warns_to_string warnings);
Expand All @@ -3662,9 +3687,7 @@ let lint cli =
let json =
OpamStd.Option.map
(OpamStd.List.cons
(OpamFileTools.warns_to_json
?filename:(OpamStd.Option.map OpamFile.to_string opam_f)
warnings))
(OpamFileTools.warns_to_json ?filename:opam_f warnings))
json
in
(err || failed), json
Expand Down
7 changes: 4 additions & 3 deletions tests/reftests/lint.test
Original file line number Diff line number Diff line change
Expand Up @@ -534,7 +534,7 @@ ${BASEDIR}/lint.opam: Errors.
# Return code 1 #
### : E53: Mismatching 'extra-files:' field
### opam lint --package lint
${BASEDIR}/OPAM/repo/default/packages/lint/lint.1/opam: Errors.
<default>/lint.1: Errors.
error 53: Mismatching 'extra-files:' field: "more-file"
# Return code 1 #
### OPAMREPOSITORYTARRING=1
Expand All @@ -543,8 +543,9 @@ ${BASEDIR}/OPAM/repo/default/packages/lint/lint.1/opam: Errors.
<><> Updating package repositories ><><><><><><><><><><><><><><><><><><><><><><>
[default] no changes from file://${BASEDIR}/REPO
### opam lint --package lint
[ERROR] File ${OPAMTMP}/default/packages/lint/lint.1/opam not found
# Return code 2 #
<default>/lint.1: Errors.
error 53: Mismatching 'extra-files:' field: "more-file"
# Return code 1 #
### : W54: External dependencies should not contain spaces nor empty string
### <lint.opam>
opam-version: "2.0"
Expand Down

0 comments on commit e36650b

Please sign in to comment.