Skip to content

Commit

Permalink
fix(x-compilation): take the default findlib path context into account
Browse files Browse the repository at this point in the history
Signed-off-by: Antonio Nuno Monteiro <[email protected]>
  • Loading branch information
anmonteiro committed Mar 29, 2023
1 parent ff22822 commit 5e5fd76
Show file tree
Hide file tree
Showing 5 changed files with 83 additions and 84 deletions.
58 changes: 20 additions & 38 deletions src/dune_rules/context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -299,26 +299,23 @@ module Build_environment_kind = struct
| None -> Unknown)))

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

let check_fdo_support has_native ocfg ~name =
Expand Down Expand Up @@ -359,20 +356,14 @@ type instance =
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 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
| [], _ :: _ -> initial_ocamlpath
| _, _ -> (
match
List.compare ~compare:Path.compare env_ocamlpath initial_ocamlpath
Expand All @@ -388,29 +379,20 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
| 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)
Ocamlfind.discover_from_env ~env ~which ~ocamlpath ~findlib_toolchain
in

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
let ocamlc = "ocamlc" in
get_tool_using_findlib_config ocamlc >>= function
| Some x -> Memo.return x
| None -> (
which "ocamlc" >>| function
which ocamlc >>| function
| Some x -> x
| None -> prog_not_found_in_path "ocamlc")
| None -> Utils.program_not_found ocamlc ~context:name ~loc:None)
in
let dir = Path.parent_exn ocamlc in
let get_ocaml_tool prog =
Expand Down
10 changes: 7 additions & 3 deletions src/dune_rules/findlib/findlib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -100,7 +100,7 @@ module Vars = struct

let empty = String.Map.empty

let superpose = String.Map.superpose
let union = String.Map.union
end

module Config = struct
Expand All @@ -116,7 +116,6 @@ module Config = struct
; ("preds", Ps.to_dyn preds)
]


let load config_file =
let load p =
let+ meta = Meta.load ~name:None p in
Expand All @@ -141,7 +140,12 @@ module Config = struct
let p = Path.Outside_build_dir.relative config_dir p in
load p)
in
List.fold_left all_vars ~init:vars ~f:Vars.superpose
List.fold_left all_vars ~init:vars ~f:(fun acc vars ->
Vars.union acc vars ~f:(fun _ (x : Rules.t) y ->
Some
{ Rules.set_rules = x.set_rules @ y.set_rules
; add_rules = x.add_rules @ y.add_rules
}))
| Error _ -> Memo.return vars)
| Ok false | Error _ -> Memo.return vars
in
Expand Down
51 changes: 30 additions & 21 deletions src/dune_rules/findlib/ocamlfind.ml
Original file line number Diff line number Diff line change
Expand Up @@ -19,8 +19,6 @@ let ocamlpath env =
| None -> []
| Some s -> path_var s

let toolchain t = t.toolchain

let set_toolchain t ~toolchain =
match t.toolchain with
| None ->
Expand Down Expand Up @@ -55,29 +53,40 @@ let tool t ~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 ocamlfind_config_path ~env ~which ~findlib_toolchain =
let open Memo.O in
let+ path =
match Env.get env "OCAMLFIND_CONF" with
| Some s -> Memo.return (Some s)
| None -> (
match findlib_toolchain with
| None -> Memo.return None
| Some _ -> (
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
(* From http://projects.camlcity.org/projects/dl/findlib-1.9.6/doc/ref-html/r865.html
This variable overrides the location of the configuration file
findlib.conf. It must contain the absolute path name of this file. *)
Option.map path ~f:Path.External.of_string

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

let extra_env t = Findlib.Config.env t.config
17 changes: 7 additions & 10 deletions src/dune_rules/findlib/ocamlfind.mli
Original file line number Diff line number Diff line change
Expand Up @@ -4,20 +4,17 @@ 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

val discover_from_env :
env:Env.t
-> which:(string -> Path.t option Memo.t)
-> ocamlpath:Path.t list
-> findlib_toolchain:Dune_engine.Context_name.t option
-> t option Memo.t
Original file line number Diff line number Diff line change
Expand Up @@ -63,17 +63,24 @@ Dune should be able to find it too

$ dune build --root=app @install -x foo
Entering directory 'app'
File "dune", line 6, characters 12-18:
6 | (libraries libdep))
^^^^^^
Error: Library "libdep" not found.
-> required by _build/default/.gen.eobjs/byte/dune__exe__Gen.cmi
-> required by _build/default/.gen.eobjs/native/dune__exe__Gen.cmx
-> required by _build/default/gen.exe
-> required by _build/default.foo/foo.ml
-> required by _build/install/default.foo/lib/repro/foo.ml
-> required by _build/default.foo/repro-foo.install
-> required by alias install (context default.foo)
Leaving directory 'app'
[1]

Library is built in the target context

$ ls app/_build/default.foo
META.repro
foo.ml
repro-foo.install
repro.a
repro.cma
repro.cmxa
repro.cmxs
repro.dune-package
repro.ml-gen

Executable was built in the host context

$ ls app/_build/default
gen.exe
gen.ml
gen.mli

0 comments on commit 5e5fd76

Please sign in to comment.