diff --git a/src/opam_create.ml b/src/opam_create.ml index 23476e4c1564..958290c47a92 100644 --- a/src/opam_create.ml +++ b/src/opam_create.ml @@ -13,6 +13,7 @@ let correct_specific ; opam = _ } = let open Opam_file.Mutator in + let open Opam_file.Mutator.No_overwrite in (opt synopsis) (set_string "synopsis") >>> (opt description) (set_string "description") >>> list depends @@ -24,6 +25,7 @@ let correct_specific let correct project (package : Package.t) = let open Opam_file.Mutator in + let open Opam_file.Mutator.No_overwrite in correct_specific package >>> opt (Dune_project.maintainer project) (set_string "maintainer") >>> opt (Dune_project.bug_reports project) (set_string "bug-reports") >>> @@ -89,6 +91,7 @@ let add_rule sctx ~project ~pkg = let aliases = [ Alias.install ~dir ; Alias.runtest ~dir + ; Alias.check ~dir (* check doesn't pick up the promote target? *) ] in let deps = Path.Set.singleton opam_path in diff --git a/src/opam_file.ml b/src/opam_file.ml index 2c953afdaf1f..c94cd36ee784 100644 --- a/src/opam_file.ml +++ b/src/opam_file.ml @@ -108,9 +108,9 @@ module Mutator = struct let remap x f = List.filter_map ~f:(function | Variable (_, v, y) when v = x -> begin - match f (Some y) with - | Some y' -> Some (Variable (nopos, v, y')) - | None -> None + match f (Some y) with + | Some y' -> Some (Variable (nopos, v, y')) + | None -> None end | z -> Some z) @@ -136,9 +136,22 @@ module Mutator = struct let mkstring x = String (nopos, x) let mklist f xs = List (nopos, List.map ~f xs) - let set_string x y = set_var x (mkstring y) + module Make_set(Set_var : sig + val set_var : string -> value -> t + end) = struct + open Set_var + let set_string x y = set_var x (mkstring y) + let set_list x conv l = set_var x (mklist conv l) + end + include Make_set(struct let set_var = set_var end) + + module No_overwrite = Make_set(struct + let set_var x y zs = + if binding_present x zs + then zs + else add_var x y zs + end) - let set_list x conv l = set_var x (mklist conv l) let id x = x let opt opt f : t = match opt with | None -> id | Some x -> f x diff --git a/src/opam_file.mli b/src/opam_file.mli index a506bfcb771c..979e4f0a2ab9 100644 --- a/src/opam_file.mli +++ b/src/opam_file.mli @@ -57,6 +57,12 @@ module Mutator : sig file it is inserted at the top of the file. *) val set_list : string -> ('a -> value) -> 'a list -> t + module No_overwrite : sig + (** Same functions but will not modify existing keys *) + val set_string : string -> string -> t + val set_list : string -> ('a -> value) -> 'a list -> t + end + (** [opt v f] returns an identity transformer if [v] is None and if it is [Some x] applies [f] to [x] to return a transformer. Useful for constructing a mutator that is only applied if an optional value has been