Skip to content

Commit

Permalink
review
Browse files Browse the repository at this point in the history
Signed-off-by: Arseniy Alekseyev <aalekseyev@janestreet.com>
  • Loading branch information
aalekseyev committed Oct 15, 2019
1 parent 94e607d commit a40146e
Show file tree
Hide file tree
Showing 3 changed files with 24 additions and 7 deletions.
4 changes: 2 additions & 2 deletions src/dune/foreign.ml
Original file line number Diff line number Diff line change
Expand Up @@ -230,8 +230,8 @@ module Sources = struct
Raising in [Not_allowed_until] can break backwards compatibility
when we change a file from [Unrecognized] to [Not_allowed_until].
One way could be to instead pass the dune language version here
and interpret those as [Unrecognized]. *)
An easy fix would be to treat [Not_allowed_until] as
[Unrecognized], but the error messages are not good then. *)
let loc = Loc.in_dir (Path.build dir) in
User_error.raise ~loc
[ Pp.textf
Expand Down
16 changes: 12 additions & 4 deletions src/dune/foreign_sources.ml
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,9 @@ let eval_foreign_sources (d : _ Dir_with_dune.t) foreign_stubs
let osl = stubs.names in
Ordered_set_lang.Unordered_string.eval_loc osl
~key:(fun x -> x)
(* CR-someday aalekseyev:
Might be a good idea to change [standard] to mean
"all files with the relevant extension". *)
~standard:String.Map.empty
~parse:(fun ~loc s ->
let name = valid_name language ~loc s in
Expand All @@ -53,8 +56,13 @@ let eval_foreign_sources (d : _ Dir_with_dune.t) foreign_stubs
];
name)
|> String.Map.map ~f:(fun (loc, name) ->
match String.Map.find sources name with
| Some paths when List.length paths > 1 ->
match String.Map.find sources name with
| Some (_ :: _ :: _ as paths) ->
(* CR aalekseyev:
This looks suspicious to me.
If the user writes foo.c and foo.cpp and only declares a foreign
library that uses foo.cpp, will that be an error?
I think it shouldn't be. *)
User_error.raise ~loc
[ Pp.textf "Multiple sources map to the same object name %S:"
name
Expand All @@ -77,13 +85,13 @@ let eval_foreign_sources (d : _ Dir_with_dune.t) foreign_stubs
]
| Some [ (l, path) ] when l = language ->
(loc, Foreign.Source.make ~stubs ~path)
| _ ->
| Some [] | None | [ (_wrong_lang, _) ] ->
User_error.raise ~loc
[ Pp.textf "Object %S has no source; %s must be present." name
(String.enumerate_one_of
( Foreign.Language.possible_fns language name
~dune_version:d.dune_version
|> List.map ~f:(fun s -> "\"" ^ s ^ "\"") ))
|> List.map ~f:(fun s -> sprintf "%S" s) ))
])
in
let stub_maps = List.map foreign_stubs ~f:eval in
Expand Down
11 changes: 10 additions & 1 deletion src/dune/lib_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -136,12 +136,17 @@ let ocamlmklib ~path ~loc ~c_library_flags ~sctx ~dir ~expander ~o_files
; Hidden_targets targets
])

(* Add a rule calling [ocamlmklib] to build an OCaml library. *)
(* Add a rule calling [ocamlmklib] to build a stubs archive for an OCaml
library. *)
let ocamlmklib_ocaml (lib : Library.t) ~sctx ~dir ~expander ~o_files ~sandbox
~custom ~targets =
let path =
Path.build (Path.Build.relative dir (Library.stubs_archive_name lib))
in
(* CR-someday aalekseyev:
I'm not sure why [c_library_flags] is needed here. I think it's unused
at least when building a static archive. But maybe it's used for
dynamic libraries. It would be nice to clarify that somewhere. *)
ocamlmklib ~path ~loc:lib.buildable.loc ~c_library_flags:lib.c_library_flags
~sctx ~dir ~expander ~o_files ~sandbox ~custom ~targets

Expand Down Expand Up @@ -194,6 +199,10 @@ let include_dir_flags ~expander ~dir (stubs : Foreign.Stubs.t) =
Command.Args.Hidden_deps deps :: args))
] )))

(* CR aalekseyev:
Maybe we'll need to support the case when dynamic library can't be
built for some reason. It seems that the OCaml library code path has to deal
with that case. *)
(* Build a static and a dynamic archive for a foreign library. *)
let foreign_rules (library : Foreign.Library.t) ~sctx ~expander ~dir
~dir_contents =
Expand Down

0 comments on commit a40146e

Please sign in to comment.