Skip to content

Commit

Permalink
Merge pull request #5561 from rjbou/lint-security
Browse files Browse the repository at this point in the history
lint: add errors about duplicated extra-files and checksums & when extra-file paths contains '..'
  • Loading branch information
kit-ty-kate authored Sep 3, 2024
2 parents a7fcf1e + 0e4b791 commit 4a3c545
Show file tree
Hide file tree
Showing 10 changed files with 412 additions and 31 deletions.
21 changes: 21 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -71,6 +71,11 @@ users)
## Source

## Lint
* Add E70 to check `extra-files:` duplicated fields [#5561 @rjbou]
* Add E71 to check if the same checksum algorithm is used several times for a given url in `url` section [#5561 @rjbou]
* Add E72 to check if the same checksum algorithm is used several times for a given url in `extra-sources` section [#5561 @rjbou]
* Add E73 to check that paths in `extra-files:` are not escapable [#5561 @rjbou]
* Update W59 (no checksum in `url`) to always display a warning, untying it from `--check-upstream` [#5561 @rjbou]

## 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]
Expand Down Expand Up @@ -180,6 +185,20 @@ users)
* Add a test showing the behaviour of `opam switch list-available` [#6098 @kit-ty-kate]
* Add a test for git packages with submodules [#6132 @kit-ty-kate]
* Add basic test for `install --check` [#6122 @rjbou]
* lint: add an additional test case for W37 [#5561 @rjbou]
* lint: update W37 to test other urls scheme [#5561 @rjbou]
* lint: update W37 to test other url schemes [#5561 @rjbou]
* lint: add E70 test [#5561 @rjbou]
* lint: add E71 test [#5561 @rjbou]
* lint: add E72 test [#5561 @rjbou]
* lint: add E73 test [#5561 @rjbou]
* lint: add more test cases for E59: special cases (conf, git url), with and without option `--with-check-upstream` [#5561 @rjbou]
* lint: add E70 test [#5561 @rjbou]
* lint: add E71 test [#5561 @rjbou]
* lint: add E72 test [#5561 @rjbou]
* lint: add E73 test [#5561 @rjbou]
* lint: add more test cases for E59: special cases (conf, git url), with and without option `--with-check-upstream` [#5561 @rjbou]
* lint: add more test cases for W59: special cases (conf, git url), with and without `--with-check-upstream` [#5561 @rjbou]

### Engine
* Add a test filtering mechanism [#6105 @Keryan-dev]
Expand Down Expand Up @@ -240,3 +259,5 @@ users)

## opam-core
* `OpamStd.Env`: add `env_string_list` for parsing string list environment variables (comma separated) [#5682 @desumn]
* `OpamHash`: export `compare_kind` [#5561 @rjbou]
* `OpamFilename`: add `might_escape` to check if a path is escapable, ie contains `<sep>..<sep>` [#5561 @rjbou]
10 changes: 10 additions & 0 deletions src/core/opamFilename.ml
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,16 @@
(* *)
(**************************************************************************)

let might_escape ~sep path =
let sep =
match sep with
| `Unix -> Re.char '/'
| `Windows -> Re.alt Re.[ char '\\'; char '/' ]
| `Unspecified -> Re.str Filename.dir_sep
in
List.exists (String.equal Filename.parent_dir_name)
Re.(split (compile sep) path)

module Base = struct
include OpamStd.AbstractString

Expand Down
3 changes: 3 additions & 0 deletions src/core/opamFilename.mli
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,9 @@
(** Higher level file and directory name manipulation AND file operations,
wrappers on OpamSystem using the filename type *)

(* Returns [true] if string contains '..' between directory separators *)
val might_escape: sep:[`Unix | `Windows | `Unspecified ] -> string -> bool

(** Basenames *)
module Base: sig
include OpamStd.ABSTRACT
Expand Down
1 change: 1 addition & 0 deletions src/core/opamHash.mli
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@ val sha512: string -> t
include OpamStd.ABSTRACT with type t := t

val of_string_opt: string -> t option
val compare_kind: kind -> kind -> int

(** Check if [hash] contains only 0 *)
val is_null: t -> bool
Expand Down
89 changes: 85 additions & 4 deletions src/state/opamFileTools.ml
Original file line number Diff line number Diff line change
Expand Up @@ -396,11 +396,32 @@ let t_lint ?check_extra_files ?(check_upstream=false) ?(all=false) t =
| #OpamUrl.version_control -> true
| _ -> false)
in
let check_upstream =
check_upstream &&
let is_url_archive =
not (OpamFile.OPAM.has_flag Pkgflag_Conf t) &&
url_vcs = Some false
in
let check_upstream = check_upstream && is_url_archive in
let check_double compare to_str lst =
let double =
List.sort compare lst
|> List.fold_left (fun (last, dbl) elem ->
match last with
| Some last ->
if compare last elem = 0 then
Some elem, OpamStd.String.Map.update (to_str elem) ((+) 1) 1 dbl
else
Some elem, dbl
| None -> Some elem, dbl)
(None, OpamStd.String.Map.empty)
|> snd
in
if OpamStd.String.Map.is_empty double then false, None else
true,
Some (List.map (fun (elem, occ) ->
Printf.sprintf "%s: %d occurence%s"
elem occ (if occ = 1 then "" else "s"))
(OpamStd.String.Map.bindings double))
in
let warnings = [
cond 20 `Warning
"Field 'opam-version' refers to the patch version of opam, it \
Expand Down Expand Up @@ -790,7 +811,7 @@ let t_lint ?check_extra_files ?(check_upstream=false) ?(all=false) t =
Printf.sprintf "Found %s variable%s, predefined one%s" var s_ nvar)
(rem_test || rem_doc));
cond 59 `Warning "url doesn't contain a checksum"
(check_upstream &&
(is_url_archive &&
OpamStd.Option.map OpamFile.URL.checksum t.url = Some []);
(let upstream_error =
if not check_upstream then None else
Expand Down Expand Up @@ -909,7 +930,7 @@ let t_lint ?check_extra_files ?(check_upstream=false) ?(all=false) t =
("file" | "path" | "local" | "rsync") -> true
| _, _ -> false)
&& (Filename.is_relative u.path
|| OpamStd.String.contains ~sub:".." u.path))
|| OpamFilename.might_escape ~sep:`Unix u.path))
(all_urls t)
in
cond 65 `Error
Expand Down Expand Up @@ -1011,6 +1032,66 @@ let t_lint ?check_extra_files ?(check_upstream=false) ?(all=false) t =
p v p v)
vars)
(vars <> []));
(let has_double, detail =
check_double OpamFilename.Base.compare OpamFilename.Base.to_string
(match OpamFile.OPAM.extra_files t with
| Some extra_files -> List.map fst extra_files
| None -> [])
in
cond 70 `Error
"Field 'extra-files' contains duplicated files"
?detail
has_double);
(let has_double, detail =
check_double OpamHash.compare_kind OpamHash.string_of_kind
(match OpamFile.OPAM.url t with
| Some url ->
List.map OpamHash.kind (OpamFile.URL.checksum url)
| None -> [])
in
cond 71 `Error
"Field 'url.checksum' contains duplicated checksums"
?detail has_double);
(let has_double, detail =
OpamFile.OPAM.extra_sources t
|> List.rev_map (fun (basename, url) ->
basename,
OpamFile.URL.checksum url
|> List.rev_map OpamHash.kind
|> check_double
OpamHash.compare_kind
OpamHash.string_of_kind)
|> List.fold_left (fun (has_double, details) (basename, (double, detail)) ->
let has_double = has_double || double in
let details =
match detail with
| None -> details
| Some detail ->
Printf.sprintf "%s have %s"
(OpamFilename.Base.to_string basename)
(OpamStd.Format.pretty_list detail)
:: details
in
has_double, details) (false, [])
|> (function hd, [] -> hd, None | hd, d -> hd, Some d)
in
cond 72 `Error
"Field 'extra-sources' contains duplicated checksums"
?detail has_double);
(let relative =
match t.extra_files with
| None -> []
| Some extra_files ->
List.filter_map (fun (base, _) ->
let path = OpamFilename.Base.to_string base in
if OpamFilename.might_escape ~sep:`Unix path then
Some path else None)
extra_files
in
cond 73 `Error
"Field 'extra-files' contains path with '..'"
~detail:relative
(relative <> []));
]
in
format_errors @
Expand Down
13 changes: 10 additions & 3 deletions tests/reftests/archive.test
Original file line number Diff line number Diff line change
Expand Up @@ -430,7 +430,8 @@ Successfully extracted to ${BASEDIR}/good-sha256-good-md5.1
Clearing cache of downloaded files
### :I:5: no checksum
### opam lint --package no-checksum
<default>/no-checksum.1: Passed.
<default>/no-checksum.1: Warnings.
warning 59: url doesn't contain a checksum
### opam lint --package no-checksum --check-upstream
<default>/no-checksum.1: Warnings.
warning 59: url doesn't contain a checksum
Expand Down Expand Up @@ -475,12 +476,15 @@ Successfully extracted to ${BASEDIR}/no-checksum.1
Clearing cache of downloaded files
### :I:6: multiple md5
### opam lint --package multiple-md5
<default>/multiple-md5.1: Passed.
<default>/multiple-md5.1: Errors.
error 71: Field 'url.checksum' contains duplicated checksums: "md5: 2 occurences"
# Return code 1 #
### opam lint --package multiple-md5 --check-upstream | '[0-9a-z]{32}' -> 'hash'
<default>/multiple-md5.1: Errors.
error 60: Upstream check failed: "The archive doesn't match checksum:
- archive: md5=hash, in opam file: md5=hash
."
error 71: Field 'url.checksum' contains duplicated checksums: "md5: 2 occurences"
# Return code 1 #
### opam install multiple-md5 | '[0-9a-z]{32}' -> 'hash'
The following actions will be performed:
Expand Down Expand Up @@ -781,7 +785,9 @@ OpamSolution.Fetch_fail("Checksum mismatch")
Clearing cache of downloaded files
### :I:10: clash with all md5
### opam lint --package clash-with-all-md5s
<default>/clash-with-all-md5s.666: Passed.
<default>/clash-with-all-md5s.666: Errors.
error 71: Field 'url.checksum' contains duplicated checksums: "md5: 17 occurences"
# Return code 1 #
### opam lint --package clash-with-all-md5s --check-upstream | '[0-9a-z]{32,64}' -> 'hash'
<default>/clash-with-all-md5s.666: Errors.
error 60: Upstream check failed: "The archive doesn't match checksums:
Expand All @@ -803,6 +809,7 @@ Clearing cache of downloaded files
- archive: md5=hash, in opam file: md5=hash
- archive: sha256=hash, in opam file: sha256=hash
."
error 71: Field 'url.checksum' contains duplicated checksums: "md5: 17 occurences"
# Return code 1 #
### opam install clash-with-all-md5s | '[0-9a-z]{32}' -> 'hash'
The following actions will be performed:
Expand Down
18 changes: 14 additions & 4 deletions tests/reftests/extrafile.test
Original file line number Diff line number Diff line change
Expand Up @@ -200,9 +200,13 @@ Successfully extracted to ${BASEDIR}/good-md5.1
Clearing cache of downloaded files
### :I:2: good md5 & sha256
### opam lint --package good-md5-good-sha256
<default>/good-md5-good-sha256.1: Passed.
<default>/good-md5-good-sha256.1: Errors.
error 70: Field 'extra-files' contains duplicated files: "p.patch: 2 occurences"
# Return code 1 #
### opam lint --package good-md5-good-sha256 --check-upstream
<default>/good-md5-good-sha256.1: Passed.
<default>/good-md5-good-sha256.1: Errors.
error 70: Field 'extra-files' contains duplicated files: "p.patch: 2 occurences"
# Return code 1 #
### opam install good-md5-good-sha256
The following actions will be performed:
=== install 1 package
Expand Down Expand Up @@ -284,9 +288,13 @@ Bad hash for - ${BASEDIR}/OPAM/repo/default/packages/bad-md5/bad-md5.1/files/p
Clearing cache of downloaded files
### :I:4: good md5 & bad sha256
### opam lint --package good-md5-bad-sha256
<default>/good-md5-bad-sha256.1: Passed.
<default>/good-md5-bad-sha256.1: Errors.
error 70: Field 'extra-files' contains duplicated files: "p.patch: 2 occurences"
# Return code 1 #
### opam lint --package good-md5-bad-sha256 --check-upstream
<default>/good-md5-bad-sha256.1: Passed.
<default>/good-md5-bad-sha256.1: Errors.
error 70: Field 'extra-files' contains duplicated files: "p.patch: 2 occurences"
# Return code 1 #
### opam install good-md5-bad-sha256
The following actions will be performed:
=== install 1 package
Expand Down Expand Up @@ -520,10 +528,12 @@ Clearing cache of downloaded files
### opam lint --package escape-good-md5
<default>/escape-good-md5.1: Errors.
error 53: Mismatching 'extra-files:' field: "../../../no-checksum/no-checksum.1/files/p.patch"
error 73: Field 'extra-files' contains path with '..': "../../../no-checksum/no-checksum.1/files/p.patch"
# Return code 1 #
### opam lint --package escape-good-md5 --check-upstream
<default>/escape-good-md5.1: Errors.
error 53: Mismatching 'extra-files:' field: "../../../no-checksum/no-checksum.1/files/p.patch"
error 73: Field 'extra-files' contains path with '..': "../../../no-checksum/no-checksum.1/files/p.patch"
# Return code 1 #
### # ERROR it copies it to build dir ^ relative path -> escape!!!!
### # currently writing in /tmp as a common it copies in
Expand Down
16 changes: 12 additions & 4 deletions tests/reftests/extrasource.test
Original file line number Diff line number Diff line change
Expand Up @@ -549,9 +549,13 @@ Successfully extracted to ${BASEDIR}/no-checksum.1
Clearing cache of downloaded files
### :I:6: multiple md5
### opam lint --package multiple-md5
<default>/multiple-md5.1: Passed.
<default>/multiple-md5.1: Errors.
error 72: Field 'extra-sources' contains duplicated checksums: "i-am-a-patch have md5: 2 occurences"
# Return code 1 #
### opam lint --package multiple-md5 --check-upstream
<default>/multiple-md5.1: Passed.
<default>/multiple-md5.1: Errors.
error 72: Field 'extra-sources' contains duplicated checksums: "i-am-a-patch have md5: 2 occurences"
# Return code 1 #
### opam install multiple-md5 | '[0-9a-z]{32}' -> 'hash'
The following actions will be performed:
=== install 1 package
Expand Down Expand Up @@ -839,9 +843,13 @@ OpamSolution.Fetch_fail("Checksum mismatch")
Clearing cache of downloaded files
### :I:10: clash with all md5
### opam lint --package clash-with-all-md5s
<default>/clash-with-all-md5s.666: Passed.
<default>/clash-with-all-md5s.666: Errors.
error 72: Field 'extra-sources' contains duplicated checksums: "i-am-a-patch have md5: 17 occurences"
# Return code 1 #
### opam lint --package clash-with-all-md5s --check-upstream
<default>/clash-with-all-md5s.666: Passed.
<default>/clash-with-all-md5s.666: Errors.
error 72: Field 'extra-sources' contains duplicated checksums: "i-am-a-patch have md5: 17 occurences"
# Return code 1 #
### opam install clash-with-all-md5s | '[0-9a-z]{32}' -> 'hash'
The following actions will be performed:
=== install 1 package
Expand Down
Loading

0 comments on commit 4a3c545

Please sign in to comment.