Skip to content

Commit

Permalink
Add a "trust cache" repository option
Browse files Browse the repository at this point in the history
  • Loading branch information
AltGr committed Jan 22, 2025
1 parent f80c027 commit 279aaac
Show file tree
Hide file tree
Showing 5 changed files with 18 additions and 1 deletion.
4 changes: 4 additions & 0 deletions src/client/opamArg.ml
Original file line number Diff line number Diff line change
Expand Up @@ -224,6 +224,10 @@ let environment_variables =
"VALIDATIONHOOK", cli_original, (fun v -> VALIDATIONHOOK (env_string v)),
"if set, uses the `%{hook%}' command to validate \
an opam repository update.";
"TRUSTCACHE", cli_from cli2_2, (fun v -> TRUSTCACHE (env_bool v)),
"If this is set, the local opam cache is trusted and no double-checking \
is done. This is for specific purposes, normally you want to detect \
corruptions, typically due to truncated files.";
] in
let state =
let open OpamStateConfig.E in [
Expand Down
1 change: 1 addition & 0 deletions src/client/opamClientConfig.mli
Original file line number Diff line number Diff line change
Expand Up @@ -153,6 +153,7 @@ val opam_init:
?version_lag_power:int ->
?download_tool:(OpamTypes.arg list * OpamRepositoryConfig.dl_tool_kind) Lazy.t ->
?validation_hook:OpamTypes.arg list option ->
?trust_cache:bool ->
?retries:int ->
?force_checksums:bool option ->
?repo_tarring:bool ->
Expand Down
3 changes: 2 additions & 1 deletion src/repository/opamRepository.ml
Original file line number Diff line number Diff line change
Expand Up @@ -108,7 +108,8 @@ let fetch_from_cache =
with
| None, _ -> raise Not_found
| Some hit_file, miss_files ->
if List.for_all
if OpamRepositoryConfig.(!r.trust_cache) ||
List.for_all
(fun ck -> OpamHash.check_file (OpamFilename.to_string hit_file) ck)
checksums
then begin
Expand Down
8 changes: 8 additions & 0 deletions src/repository/opamRepositoryConfig.ml
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@ module E = struct
| REQUIRECHECKSUMS of bool option
| RETRIES of int option
| VALIDATIONHOOK of string option
| TRUSTCACHE of bool option

open OpamStd.Config.E
let curl = value (function CURL s -> s | _ -> None)
Expand All @@ -29,6 +30,7 @@ module E = struct
let requirechecksums = value (function REQUIRECHECKSUMS b -> b | _ -> None)
let retries = value (function RETRIES i -> i | _ -> None)
let validationhook = value (function VALIDATIONHOOK s -> s | _ -> None)
let trustcache = value (function TRUSTCACHE b -> b | _ -> None)

let curl_t () = value_t (function CURL s -> s | _ -> None)
let fetch_t () = value_t (function FETCH s -> s | _ -> None)
Expand All @@ -39,6 +41,7 @@ type dl_tool_kind = [ `Curl | `Default ]
type t = {
download_tool: (arg list * dl_tool_kind) Lazy.t;
validation_hook: arg list option;
trust_cache: bool;
retries: int;
force_checksums: bool option;
repo_tarring : bool;
Expand All @@ -47,6 +50,7 @@ type t = {
type 'a options_fun =
?download_tool:(OpamTypes.arg list * dl_tool_kind) Lazy.t ->
?validation_hook:arg list option ->
?trust_cache:bool ->
?retries:int ->
?force_checksums:bool option ->
?repo_tarring:bool ->
Expand Down Expand Up @@ -80,6 +84,7 @@ let default = {
| _ -> "either \"curl\" or \"wget\"")
);
validation_hook = None;
trust_cache = false;
retries = 3;
force_checksums = None;
repo_tarring = false;
Expand All @@ -88,6 +93,7 @@ let default = {
let setk k t
?download_tool
?validation_hook
?trust_cache
?retries
?force_checksums
?repo_tarring
Expand All @@ -96,6 +102,7 @@ let setk k t
k {
download_tool = t.download_tool + download_tool;
validation_hook = t.validation_hook + validation_hook;
trust_cache = t.trust_cache + trust_cache;
retries = t.retries + retries;
force_checksums = t.force_checksums + force_checksums;
repo_tarring = t.repo_tarring + repo_tarring;
Expand Down Expand Up @@ -153,6 +160,7 @@ let initk k =
setk (setk (fun c -> r := c; k)) !r
?download_tool
?validation_hook
?trust_cache:(E.trustcache ())
?retries:(E.retries ())
?force_checksums
?repo_tarring:(E.repositorytarring ())
Expand Down
3 changes: 3 additions & 0 deletions src/repository/opamRepositoryConfig.mli
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@ module E : sig
| REQUIRECHECKSUMS of bool option
| RETRIES of int option
| VALIDATIONHOOK of string option
| TRUSTCACHE of bool option

val curl: unit -> string option
val fetch: unit -> string option
Expand All @@ -36,6 +37,7 @@ type dl_tool_kind = [ `Curl | `Default ]
type t = {
download_tool: (OpamTypes.arg list * dl_tool_kind) Lazy.t;
validation_hook: OpamTypes.arg list option;
trust_cache: bool;
retries: int;
force_checksums: bool option;
repo_tarring : bool;
Expand All @@ -44,6 +46,7 @@ type t = {
type 'a options_fun =
?download_tool:(OpamTypes.arg list * dl_tool_kind) Lazy.t ->
?validation_hook:OpamTypes.arg list option ->
?trust_cache:bool ->
?retries:int ->
?force_checksums:bool option ->
?repo_tarring:bool ->
Expand Down

0 comments on commit 279aaac

Please sign in to comment.