diff --git a/master_changes.md b/master_changes.md index 84a08da01a4..dfd9ed3b1e3 100644 --- a/master_changes.md +++ b/master_changes.md @@ -46,6 +46,8 @@ Possibly scripts breaking changes are prefixed with ✘ ## Internal * Disable chrono when timestamps are disables [#4206 @rjbou] + * Expose some functionality in the `OpamAction`, `OpamPath` and `OpamSwitchState` + modules for use without a `switch` value [#4147] ## Test * Add show cram test [#4206 @rjbou] diff --git a/src/client/opamAction.ml b/src/client/opamAction.ml index 61af4913fd0..6ba26423b78 100644 --- a/src/client/opamAction.ml +++ b/src/client/opamAction.ml @@ -240,15 +240,13 @@ let download_package st nv = (* Prepare the package build: * apply the patches * substitute the files *) -let prepare_package_build st nv dir = - let opam = OpamSwitchState.opam st nv in - +let prepare_package_build env opam nv dir = let patches = OpamFile.OPAM.patches opam in let rec iter_patches f = function | [] -> Done [] | (patchname,filter)::rest -> - if OpamFilter.opt_eval_to_bool (OpamPackageVar.resolve ~opam st) filter + if OpamFilter.opt_eval_to_bool env filter then OpamFilename.patch (dir // OpamFilename.Base.to_string patchname) dir @@+ function @@ -278,8 +276,7 @@ let prepare_package_build st nv dir = OpamFilename.in_dir dir @@ fun () -> List.fold_left (fun errs f -> try - OpamFilter.expand_interpolations_in_file - (OpamPackageVar.resolve ~opam st) f; + OpamFilter.expand_interpolations_in_file env f; errs with e -> (f, e)::errs) [] subst_patches @@ -306,8 +303,7 @@ let prepare_package_build st nv dir = OpamFilename.in_dir dir @@ fun () -> List.fold_left (fun errs f -> try - OpamFilter.expand_interpolations_in_file - (OpamPackageVar.resolve ~opam st) f; + OpamFilter.expand_interpolations_in_file env f; errs with e -> (f, e)::errs) subst_errs subst_others @@ -404,7 +400,8 @@ let prepare_package_source st nv dir = OpamFilename.mkdir dir; get_extra_sources_job @@+ function Some _ as err -> Done err | None -> check_extra_files |> function Some _ as err -> Done err | None -> - prepare_package_build st nv dir + let opam = OpamSwitchState.opam st nv in + prepare_package_build (OpamPackageVar.resolve ~opam st) opam nv dir let compilation_env t opam = OpamEnv.get_full ~force_path:true t ~updates:([ diff --git a/src/client/opamAction.mli b/src/client/opamAction.mli index ebf847fadbe..fc4ce0fdfe6 100644 --- a/src/client/opamAction.mli +++ b/src/client/opamAction.mli @@ -29,6 +29,12 @@ val download_package: val prepare_package_source: rw switch_state -> package -> dirname -> exn option OpamProcess.job +(** [prepare_package_build env opam pkg dir] is a lower level version + of `prepare_package_source`, without requiring a switch and + without handling extra downloads. *) +val prepare_package_build: + OpamFilter.env -> OpamFile.OPAM.t -> package -> dirname -> exn option OpamProcess.job + (** [build_package t build_dir pkg] builds the package [pkg] within [build_dir]. Returns [None] on success, [Some exn] on error. See {!download_package} and {!prepare_package_source} for the previous diff --git a/src/format/opamPath.ml b/src/format/opamPath.ml index fc8ce0addfa..dd04ab870c8 100644 --- a/src/format/opamPath.ml +++ b/src/format/opamPath.ml @@ -74,6 +74,12 @@ let plugin t name = assert (sname <> "bin"); plugins t / sname +module type LAYOUT = sig + type ctx + val root : dirname -> ctx -> dirname + val lib_dir : dirname -> ctx -> dirname +end + module Switch = struct let root t a = OpamSwitch.get_root t a @@ -142,39 +148,45 @@ module Switch = struct let installed_opam_files_dir t a nv = installed_package_dir t a nv / "files" - module Default = struct - - (** Visible files that can be redirected using - [config/global-config.config] *) + module DefaultF(L:LAYOUT) = struct + let lib_dir = L.lib_dir - let lib_dir t a = root t a / "lib" + let lib t a n = L.lib_dir t a / OpamPackage.Name.to_string n - let lib t a n = lib_dir t a / OpamPackage.Name.to_string n + let stublibs t a = L.lib_dir t a / "stublibs" - let stublibs t a = lib_dir t a / "stublibs" + let toplevel t a = L.lib_dir t a / "toplevel" - let toplevel t a = lib_dir t a / "toplevel" - - let doc_dir t a = root t a / "doc" + let doc_dir t a = L.root t a / "doc" let man_dir ?num t a = match num with - | None -> root t a / "man" - | Some n -> root t a / "man" / ("man" ^ n) + | None -> L.root t a / "man" + | Some n -> L.root t a / "man" / ("man" ^ n) - let share_dir t a = root t a / "share" + let share_dir t a = L.root t a / "share" let share t a n = share_dir t a / OpamPackage.Name.to_string n - let etc_dir t a = root t a / "etc" + let etc_dir t a = L.root t a / "etc" let etc t a n = etc_dir t a / OpamPackage.Name.to_string n let doc t a n = doc_dir t a / OpamPackage.Name.to_string n - let bin t a = root t a / "bin" + let bin t a = L.root t a / "bin" + + let sbin t a = L.root t a / "sbin" + end - let sbin t a = root t a / "sbin" + (** Visible files that can be redirected using + [config/global-config.config] *) + module Default = struct + include DefaultF(struct + type ctx = switch + let root = root + let lib_dir t a = root t a / "lib" + end) end diff --git a/src/format/opamPath.mli b/src/format/opamPath.mli index c6e74362245..1c06fc41a1f 100644 --- a/src/format/opamPath.mli +++ b/src/format/opamPath.mli @@ -78,6 +78,12 @@ val plugin_bin: t -> name -> filename forbidden. *) val plugin: t -> name -> dirname +module type LAYOUT = sig + type ctx + val root : dirname -> ctx -> dirname + val lib_dir : dirname -> ctx -> dirname +end + (** Switch related paths *) module Switch: sig @@ -237,6 +243,37 @@ module Switch: sig val sbin: t -> switch -> dirname end + (** Fuctorised version of Default, for replicating + a switch's layout in non-switch contexts *) + module DefaultF : functor (L:LAYOUT) -> sig + val lib: t -> L.ctx -> name -> dirname + + val lib_dir: t -> L.ctx -> dirname + + val stublibs: t -> L.ctx -> dirname + + val toplevel: t -> L.ctx -> dirname + + val doc: t -> L.ctx -> name -> dirname + + val doc_dir: t -> L.ctx -> dirname + + val share_dir: t -> L.ctx -> dirname + + val share: t -> L.ctx -> name -> dirname + + val etc_dir: t -> L.ctx -> dirname + + val etc: t -> L.ctx -> name -> dirname + + val man_dir: ?num:string -> t -> L.ctx -> dirname + + val bin: t -> L.ctx -> dirname + + val sbin: t -> L.ctx -> dirname + end + + (** Actual config handling the global-config.config indirections *) (** Package-independent dirs *) diff --git a/src/state/opamSwitchState.ml b/src/state/opamSwitchState.ml index aaa68bb8c13..4d92fb0ab1f 100644 --- a/src/state/opamSwitchState.ml +++ b/src/state/opamSwitchState.ml @@ -723,7 +723,7 @@ let conflicts_with st subset = let remove_conflicts st subset pkgs = pkgs -- conflicts_with st subset pkgs -let get_conflicts st packages opams_map = +let get_conflicts_t env packages opams_map = let conflict_classes = OpamPackage.Map.fold (fun nv opam acc -> List.fold_left (fun acc cc -> @@ -750,7 +750,7 @@ let get_conflicts st packages opams_map = OpamPackage.Map.fold (fun nv opam acc -> let conflicts = OpamFilter.filter_formula ~default:false - (OpamPackageVar.resolve_switch ~package:nv st) + (env nv) (OpamFile.OPAM.conflicts opam) in let conflicts = @@ -770,6 +770,11 @@ let get_conflicts st packages opams_map = opams_map OpamPackage.Map.empty +let get_conflicts st packages opams_map = + get_conflicts_t + (fun package -> OpamPackageVar.resolve_switch ~package st) + packages opams_map + let universe st ?(test=OpamStateConfig.(!r.build_test)) ?(doc=OpamStateConfig.(!r.build_doc)) diff --git a/src/state/opamSwitchState.mli b/src/state/opamSwitchState.mli index 2dacefb867b..a1c903966b4 100644 --- a/src/state/opamSwitchState.mli +++ b/src/state/opamSwitchState.mli @@ -54,6 +54,14 @@ val compute_available_packages: pinned:package_set -> opams:OpamFile.OPAM.t package_map -> package_set +(** Raw function to compute the conflicts for all packages, given + the set of available packages and the corresponding opam files. + This is useful to populate the `u_conflicts` field when building + a universe manually. *) +val get_conflicts_t: + (package -> OpamFilter.env) -> package_set -> + OpamFile.OPAM.t package_map -> formula package_map + (** Infer a switch invariant from a switch state with compiler_packages and roots set, using some heuristics. Useful for migration from pre-2.1 opam *) val infer_switch_invariant: 'a switch_state -> OpamFormula.t