Skip to content

Commit

Permalink
feature: add --prefix to configure script
Browse files Browse the repository at this point in the history
In symmetric with --prefix in the install command.

Fix #10229

Signed-off-by: Rudi Grinberg <[email protected]>

<!-- ps-id: 0a9b3e1e-91d9-4ccf-8780-2210fe3d656c -->

Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Dec 8, 2024
1 parent 832acca commit 7229d34
Show file tree
Hide file tree
Showing 4 changed files with 20 additions and 2 deletions.
5 changes: 4 additions & 1 deletion boot/configure.ml
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,7 @@ let toggle =

let () =
let bad fmt = ksprintf (fun s -> raise (Arg.Bad s)) fmt in
let prefix = ref None in
let library_path = ref [] in
let library_destdir = ref None in
let mandir = ref None in
Expand All @@ -58,7 +59,8 @@ let () =
v := Some dir
in
let args =
[ ( "--libdir"
[ "--prefix", Arg.String (set_dir prefix), "DIR where files are copied"
; ( "--libdir"
, Arg.String set_libdir
, "DIR where public libraries are looked up in the default build context. Can be \
specified multiple times new one taking precedence. The last is used as default \
Expand Down Expand Up @@ -120,6 +122,7 @@ let () =
pr " ; libexec_root = %s" (option string !libexecdir);
pr " }";
pr "";
pr "let prefix : string option = %s" (option string !prefix);
List.iter !toggles ~f:(fun (name, value) ->
pr
"let %s = `%s"
Expand Down
15 changes: 14 additions & 1 deletion src/dune_rules/context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -743,6 +743,19 @@ let map_exe (context : t) =
| _ -> exe)
;;

let roots =
lazy
(let open Setup in
match prefix with
| None -> roots
| Some prefix ->
let prefix = Install.Roots.make prefix ~relative:Filename.concat in
Install.Roots.map2 roots prefix ~f:(fun root prefix ->
match root with
| None -> Some prefix
| Some _ -> root))
;;

let roots t =
let module Roots = Install.Roots in
let+ prefix_roots =
Expand All @@ -756,7 +769,7 @@ let roots t =
in
match t.kind with
| Lock _ | Default ->
let setup_roots = Roots.map ~f:(Option.map ~f:Path.of_string) Setup.roots in
let setup_roots = Roots.map ~f:(Option.map ~f:Path.of_string) (Lazy.force roots) in
Roots.first_has_priority setup_roots prefix_roots
| Opam _ -> prefix_roots
;;
1 change: 1 addition & 0 deletions src/dune_rules/setup.mli
Original file line number Diff line number Diff line change
Expand Up @@ -13,3 +13,4 @@ val roots : string option Install.Roots.t
val toolchains : Dune_config.Config.Toggle.t
val pkg_build_progress : Dune_config.Config.Toggle.t
val lock_dev_tool : Dune_config.Config.Toggle.t
val prefix : string option
1 change: 1 addition & 0 deletions src/install/roots.mli
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@ val opam_from_prefix : 'a -> relative:('a -> string -> 'a) -> 'a t
val complete : 'a option t -> 'a option t

val map : f:('a -> 'b) -> 'a t -> 'b t
val map2 : f:('a -> 'b -> 'c) -> 'a t -> 'b t -> 'c t

(** return the roots of the first argument if present *)
val first_has_priority : 'a option t -> 'a option t -> 'a option t
Expand Down

0 comments on commit 7229d34

Please sign in to comment.