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 28, 2023
1 parent 524fb75 commit 12395d2
Show file tree
Hide file tree
Showing 6 changed files with 48 additions and 45 deletions.
48 changes: 19 additions & 29 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,7 +379,6 @@ 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
Expand All @@ -400,17 +390,17 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
let toolchain = Context_name.to_string toolchain in
Ocamlfind.set_toolchain ocamlfind ~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
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/byte-code-only.t/run.t
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
$ export OCAMLFIND_CONF="/fake"
$ env ORIG_PATH="$PATH" PATH="$PWD/ocaml-bin:$PATH" dune build @all --display short
ocamlc bin/.toto.eobjs/byte/dune__exe__Toto.{cmi,cmo,cmt}
ocamlc src/.foo.objs/byte/foo.{cmi,cmo,cmt}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ But is supported with Dune >= 3.0.0:
> (display verbose)
> EOF
$ dune build -f 2>&1 | grep Hello | sed 's/&&.*echo/\&\& echo/'
Running[1]: (cd _build/default && echo 'Hello, world!')
Running[2]: (cd _build/default && echo 'Hello, world!')
Hello, world!

Make sure errors related to fields other than the ones allowed in the
Expand Down
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
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/trace-file.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@
This captures the commands that are being run:

$ <trace.json grep '"X"' | cut -c 2- | sed -E 's/:[0-9]+/:.../g'
{"args":{"process_args":["printconf","conf"],"pid":...},"ph":"X","dur":...,"name":"ocamlfind","cat":"process","ts":...,"pid":...,"tid":...}
{"args":{"process_args":["-config"],"pid":...},"ph":"X","dur":...,"name":"ocamlc.opt","cat":"process","ts":...,"pid":...,"tid":...}
{"args":{"process_args":["-modules","-impl","prog.ml"],"pid":...},"ph":"X","dur":...,"name":"ocamldep.opt","cat":"process","ts":...,"pid":...,"tid":...}
{"args":{"process_args":["-w","@[email protected]@30..39@[email protected]@[email protected]","-strict-sequence","-strict-formats","-short-paths","-keep-locs","-g","-bin-annot","-I",".prog.eobjs/byte","-no-alias-deps","-opaque","-o",".prog.eobjs/byte/prog.cmo","-c","-impl","prog.ml"],"pid":...},"ph":"X","dur":...,"name":"ocamlc.opt","cat":"process","ts":...,"pid":...,"tid":...}
Expand Down

0 comments on commit 12395d2

Please sign in to comment.