Skip to content

Commit

Permalink
Prefer findlib configuration by default
Browse files Browse the repository at this point in the history
Currently, dune prefers ocamlc, ocamlopt, etc. from PATH

9106b31

Signed-off-by: Antonio Nuno Monteiro <[email protected]>

Co-authored-by: Rudi Grinberg <[email protected]>
  • Loading branch information
anmonteiro and rgrinberg committed Mar 28, 2023
1 parent a2d8cf7 commit 524fb75
Show file tree
Hide file tree
Showing 3 changed files with 180 additions and 120 deletions.
194 changes: 74 additions & 120 deletions src/dune_rules/context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -266,24 +266,6 @@ end = struct
fun ~env ~root ~switch -> Memo.exec memo (env, root, switch)
end

let ocamlpath_sep =
if Sys.cygwin then (* because that's what ocamlfind expects *)
';'
else Bin.path_sep

let ocamlfind_printconf_path ~env ~ocamlfind ~toolchain =
let args =
let args = [ "printconf"; "path" ] in
match toolchain with
| None -> args
| Some s -> "-toolchain" :: Context_name.to_string s :: args
in
let+ l =
Memo.of_reproducible_fiber
(Process.run_capture_lines ~display:Quiet ~env Strict ocamlfind args)
in
List.map l ~f:Path.of_filename_relative_to_initial_cwd

module Build_environment_kind = struct
(* Heuristics to detect the current environment *)

Expand Down Expand Up @@ -316,19 +298,27 @@ module Build_environment_kind = struct
| Some s -> Opam2_environment s
| None -> Unknown)))

let findlib_paths ~kind ~findlib_toolchain ~env ~which_exn ~dir =
let findlib_paths ocamlfind ~kind ~context ~findlib_toolchain ~env ~dir =
match query ~kind ~findlib_toolchain ~env with
| Cross_compilation_using_findlib_toolchain toolchain ->
let* ocamlfind = which_exn "ocamlfind" in
let env = Env.remove env ~var:"OCAMLPATH" in
ocamlfind_printconf_path ~env ~ocamlfind ~toolchain:(Some toolchain)
| Hardcoded_path l ->
Memo.return (List.map l ~f:Path.of_filename_relative_to_initial_cwd)
| Cross_compilation_using_findlib_toolchain _toolchain -> (
match ocamlfind with
| None ->
Code_error.raise
"Could not find ocamlfind in PATH or an environment variable \
OCAMLFIND_CONF"
[ ("context", Context_name.to_dyn context) ]
| Some ocamlfind -> Ocamlfind.conf_path ocamlfind)
| Hardcoded_path l -> List.map l ~f:Path.of_filename_relative_to_initial_cwd
| Opam2_environment opam_prefix ->
let p = Path.of_filename_relative_to_initial_cwd opam_prefix in
let p = Path.relative p "lib" in
Memo.return [ p ]
| Unknown -> Memo.return [ Path.relative (Path.parent_exn dir) "lib" ]
[ p ]
| Unknown -> (
match ocamlfind with
| None ->
(* TODO? *)
[ Path.relative (Path.parent_exn dir) "lib" ]
| Some ocamlfind -> Ocamlfind.conf_path ocamlfind)
end

let check_fdo_support has_native ocfg ~name =
Expand Down Expand Up @@ -366,70 +356,53 @@ type instance =
; targets : t list
}

let get_tool_using_findlib_config findlib_config prog ~which =
match
Option.bind findlib_config ~f:(fun conf -> Findlib.Config.get conf prog)
with
| None -> Memo.return None
| Some s -> (
match Filename.analyze_program_name s with
| In_path -> which s
| Relative_to_current_dir ->
User_error.raise
[ Pp.textf
"The effective Findlib configuration specifies the relative path \
%S for the program %S. This is currently not supported."
s prog
]
| Absolute ->
Memo.return (Some (Path.of_filename_relative_to_initial_cwd s)))

let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
~host_context ~host_toolchain ~profile ~fdo_target_exe
~dynamically_linked_foreign_archives ~instrument_with =
let prog_not_found_in_path prog =
Utils.program_not_found prog ~context:name ~loc:None
in
let which = Program.which ~path in
let which_exn x =
which x >>| function
| None -> prog_not_found_in_path x
| Some x -> x
in
let findlib_config_path =
Memo.lazy_ ~cutoff:Path.External.equal (fun () ->
let* fn = which_exn "ocamlfind" in
(* When OCAMLFIND_CONF is set, "ocamlfind printconf" does print the
contents of the variable, but "ocamlfind printconf conf" still prints
the configuration file set at the configuration time of ocamlfind,
sigh... *)
(match Env.get env "OCAMLFIND_CONF" with
| Some s -> Memo.return s
| None ->
Memo.of_reproducible_fiber
(Process.run_capture_line ~display:Quiet ~env Strict fn
[ "printconf"; "conf" ]))
>>| Path.External.of_filename_relative_to_initial_cwd)

let env_ocamlpath = Ocamlfind.ocamlpath env in
let ocamlpath =
let initial_ocamlpath = Ocamlfind.ocamlpath Env.initial in
match (env_ocamlpath, initial_ocamlpath) with
| [], [] -> []
| _ :: _, [] -> env_ocamlpath
| [], _ :: _ ->
(* TODO? *)
initial_ocamlpath
| _, _ -> (
match
List.compare ~compare:Path.compare env_ocamlpath initial_ocamlpath
with
| Eq -> []
| _ -> env_ocamlpath)
in

let create_one ~(name : Context_name.t) ~implicit ~findlib_toolchain ~host
~merlin =
let* findlib_config =
match findlib_toolchain with
| None -> Memo.return None
| Some toolchain ->
let+ findlib_config =
let* path = Memo.Lazy.force findlib_config_path in
Findlib.Config.load (External path)
in
let toolchain =
let toolchain = Context_name.to_string toolchain in
Findlib.Config.toolchain findlib_config ~toolchain
in
Some toolchain
let ocamlpath =
match (kind, findlib_toolchain) with
| Default, None -> env_ocamlpath
| _, _ -> ocamlpath
in

let* ocamlfind =
Ocamlfind.discover_from_env ~env ~ocamlpath ~which >>| function
| None -> None
| Some ocamlfind ->
Some
(match findlib_toolchain with
| None -> ocamlfind
| Some toolchain ->
let toolchain = Context_name.to_string toolchain in
Ocamlfind.set_toolchain ocamlfind ~toolchain)
in

let get_tool_using_findlib_config =
get_tool_using_findlib_config findlib_config ~which
let get_tool_using_findlib_config prog =
Memo.Option.bind ocamlfind ~f:(Ocamlfind.tool ~prog)
in
let* ocamlc =
get_tool_using_findlib_config "ocamlc" >>= function
Expand Down Expand Up @@ -457,28 +430,9 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
~hint ()))
in
let build_dir = Context_name.build_dir name in
let ocamlpath =
match
let var = "OCAMLPATH" in
match (kind, findlib_toolchain) with
| Default, None -> Env.get env var
| _ -> (
(* If we are not in the default context, we can only use the OCAMLPATH
variable if it is specific to this build context *)
(* CR-someday diml: maybe we should actually clear OCAMLPATH in other
build contexts *)
match (Env.get env var, Env.get Env.initial var) with
| None, None -> None
| Some s, None -> Some s
| None, Some _ -> None
| Some x, Some y -> Option.some_if (x <> y) x)
with
| None -> []
| Some s -> Bin.parse_path s ~sep:ocamlpath_sep
in
let default_library_search_path () =
Build_environment_kind.findlib_paths ~kind ~findlib_toolchain ~env
~which_exn ~dir
let default_ocamlpath =
Build_environment_kind.findlib_paths ocamlfind ~kind ~context:name ~env
~findlib_toolchain ~dir
in
let ocaml_config_ok_exn = function
| Ok x -> x
Expand All @@ -491,20 +445,19 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
| Error (Makefile_config file, msg) ->
User_error.raise ~loc:(Loc.in_file file) [ Pp.text msg ]
in
let* default_ocamlpath, (ocaml_config_vars, ocfg) =
Memo.fork_and_join default_library_search_path (fun () ->
let+ lines =
Memo.of_reproducible_fiber
(Process.run_capture_lines ~display:Quiet ~env Strict ocamlc
[ "-config" ])
in
ocaml_config_ok_exn
(match Ocaml_config.Vars.of_lines lines with
| Ok vars ->
let open Result.O in
let+ ocfg = Ocaml_config.make vars in
(vars, ocfg)
| Error msg -> Error (Ocamlc_config, msg)))
let* ocaml_config_vars, ocfg =
let+ lines =
Memo.of_reproducible_fiber
(Process.run_capture_lines ~display:Quiet ~env Strict ocamlc
[ "-config" ])
in
ocaml_config_ok_exn
(match Ocaml_config.Vars.of_lines lines with
| Ok vars ->
let open Result.O in
let+ ocfg = Ocaml_config.make vars in
(vars, ocfg)
| Error msg -> Error (Ocamlc_config, msg))
in
let stdlib_dir = Path.of_string (Ocaml_config.standard_library ocfg) in
let version = Ocaml.Version.of_ocaml_config ocfg in
Expand Down Expand Up @@ -546,16 +499,17 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
(Path.Build.relative
(Local_install_path.dir ~context:name)
"lib/stublibs")
; extend_var "OCAMLPATH" ~path_sep:ocamlpath_sep local_lib_root
; extend_var "OCAMLPATH" ~path_sep:Ocamlfind.ocamlpath_sep
local_lib_root
; ("DUNE_OCAML_STDLIB", Ocaml_config.standard_library ocfg)
; ( "DUNE_OCAML_HARDCODED"
, String.concat
~sep:(Char.escaped ocamlpath_sep)
~sep:(Char.escaped Ocamlfind.ocamlpath_sep)
(List.map ~f:Path.to_string default_ocamlpath) )
; extend_var "OCAMLTOP_INCLUDE_PATH"
(Path.Build.relative local_lib_root "toplevel")
; extend_var "OCAMLFIND_IGNORE_DUPS_IN" ~path_sep:ocamlpath_sep
local_lib_root
; extend_var "OCAMLFIND_IGNORE_DUPS_IN"
~path_sep:Ocamlfind.ocamlpath_sep local_lib_root
; extend_var "MANPATH" (Local_install_path.man_dir ~context:name)
; ("INSIDE_DUNE", Path.to_absolute_filename (Path.build build_dir))
; ( "DUNE_SOURCEROOT"
Expand All @@ -573,7 +527,7 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
| Some host -> Env.get host.env "PATH")
|> Env.extend_env
(Option.value ~default:Env.empty
(Option.map findlib_config ~f:Findlib.Config.env))
(Option.map ocamlfind ~f:Ocamlfind.extra_env))
|> Env.extend_env (Env_nodes.extra_env ~profile env_nodes)
in
let natdynlink_supported = Ocaml_config.natdynlink_supported ocfg in
Expand Down
83 changes: 83 additions & 0 deletions src/dune_rules/findlib/ocamlfind.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,83 @@
open Import

type t =
{ config : Findlib.Config.t
; ocamlpath : Path.t list
; which : string -> Path.t option Memo.t
; toolchain : string option
}

let ocamlpath_sep =
if Sys.cygwin then (* because that's what ocamlfind expects *)
';'
else Bin.path_sep

let path_var = Bin.parse_path ~sep:ocamlpath_sep

let ocamlpath env =
match Env.get env "OCAMLPATH" with
| None -> []
| Some s -> path_var s

let toolchain t = t.toolchain

let set_toolchain t ~toolchain =
match t.toolchain with
| None ->
{ t with
config = Findlib.Config.toolchain t.config ~toolchain
; toolchain = Some toolchain
}
| Some old_toolchain ->
Code_error.raise "Ocamlfind.set_toolchain: cannot set toolchain twice"
[ ("old_toolchain", Dyn.string old_toolchain)
; ("toolchain", Dyn.string toolchain)
]

let conf_path t =
match Findlib.Config.get t.config "path" with
| None -> t.ocamlpath
| Some p -> t.ocamlpath @ path_var p

let tool t ~prog =
match Findlib.Config.get t.config prog with
| None -> Memo.return None
| Some s -> (
match Filename.analyze_program_name s with
| In_path -> t.which s
| Relative_to_current_dir ->
User_error.raise
[ Pp.textf
"The effective Findlib configuration specifies the relative path \
%S for the program %S. This is currently not supported."
s prog
]
| Absolute ->
Memo.return (Some (Path.of_filename_relative_to_initial_cwd s)))

let ocamlfind_config_path ~env ~which =
Memo.lazy_ ~cutoff:(Option.equal Path.External.equal) (fun () ->
let open Memo.O in
let+ path =
match Env.get env "OCAMLFIND_CONF" with
| Some s -> Memo.return (Some s)
| None -> (
which "ocamlfind" >>= function
| None -> Memo.return None
| Some fn ->
Memo.of_reproducible_fiber
(Process.run_capture_line ~display:Quiet ~env Strict fn
[ "printconf"; "conf" ])
|> Memo.map ~f:Option.some)
in
Option.map path ~f:Path.External.of_filename_relative_to_initial_cwd)

let discover_from_env ~env ~ocamlpath ~which =
let open Memo.O in
Memo.Lazy.force (ocamlfind_config_path ~env ~which) >>= function
| None -> Memo.return None
| Some config ->
let+ config = Findlib.Config.load (External config) in
Some { config; ocamlpath; which; toolchain = None }

let extra_env t = Findlib.Config.env t.config
23 changes: 23 additions & 0 deletions src/dune_rules/findlib/ocamlfind.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1,23 @@
open Stdune

type t

val conf_path : t -> Path.t list

val discover_from_env :
env:Env.t
-> ocamlpath:Path.t list
-> which:(string -> Path.t option Memo.t)
-> t option Memo.t

val tool : t -> prog:string -> Path.t option Memo.t

val ocamlpath_sep : char

val ocamlpath : Env.t -> Path.t list

val toolchain : t -> string option

val set_toolchain : t -> toolchain:string -> t

val extra_env : t -> Env.t

0 comments on commit 524fb75

Please sign in to comment.