Skip to content

Commit

Permalink
Obj_dir: rename has_public_cmi_dir to need_dedicated_public_dir
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Mar 28, 2019
1 parent a063572 commit d135f68
Show file tree
Hide file tree
Showing 4 changed files with 9 additions and 9 deletions.
2 changes: 1 addition & 1 deletion src/module_compilation.ml
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ let build_cm cctx ?sandbox ?(dynlink=true) ~dep_graphs
let copy_interface () =
(* symlink the .cmi into the public interface directory *)
if not (Module.is_private m)
&& (Obj_dir.has_public_cmi_dir obj_dir) then
&& (Obj_dir.need_dedicated_public_dir obj_dir) then
SC.add_rule sctx ~sandbox:false ~dir
(Build.symlink
~src:(Module.cm_file_unsafe m Cmi)
Expand Down
12 changes: 6 additions & 6 deletions src/obj_dir.ml
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ module External = struct
; private_dir
}

let has_public_cmi_dir t = Option.is_some t.private_dir
let need_dedicated_public_dir t = Option.is_some t.private_dir

let public_cmi_dir t = t.public_dir

Expand Down Expand Up @@ -105,7 +105,7 @@ module Local = struct
; public_cmi_dir
}

let has_public_cmi_dir t = Option.is_some t.public_cmi_dir
let need_dedicated_public_dir t = Option.is_some t.public_cmi_dir

let public_cmi_dir t =
Option.value ~default:t.byte_dir t.public_cmi_dir
Expand Down Expand Up @@ -156,9 +156,9 @@ type t =
| External of External.t
| Local of Local.t

let has_public_cmi_dir = function
| External e -> External.has_public_cmi_dir e
| Local e -> Local.has_public_cmi_dir e
let need_dedicated_public_dir = function
| External e -> External.need_dedicated_public_dir e
| Local e -> Local.need_dedicated_public_dir e

let encode = function
| Local obj_dir ->
Expand Down Expand Up @@ -216,7 +216,7 @@ let pp fmt t = Dyn.pp fmt (to_dyn t)
let convert_to_external t ~dir =
match t with
| Local e ->
let has_private_modules = Local.has_public_cmi_dir e in
let has_private_modules = Local.need_dedicated_public_dir e in
External (External.make ~dir ~has_private_modules)
| External obj_dir ->
Exn.code_error
Expand Down
2 changes: 1 addition & 1 deletion src/obj_dir.mli
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ val all_cmis: t -> Path.t list
(** The public compiled cmi file directory *)
val public_cmi_dir: t -> Path.t

val has_public_cmi_dir : t -> bool
val need_dedicated_public_dir : t -> bool

val pp: t Fmt.t
val to_sexp: t -> Sexp.t
Expand Down
2 changes: 1 addition & 1 deletion src/virtual_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -51,7 +51,7 @@ let setup_copy_rules_for_impl ~sctx ~dir vimpl =
let copy_objs src =
let dst = Module.set_obj_dir ~obj_dir:impl_obj_dir src in
copy_obj_file ~src ~dst Cmi;
if Module.is_public dst && Obj_dir.has_public_cmi_dir impl_obj_dir
if Module.is_public dst && Obj_dir.need_dedicated_public_dir impl_obj_dir
then begin
let src = Module.cm_public_file_unsafe src Cmi in
let dst = Module.cm_public_file_unsafe dst Cmi in
Expand Down

0 comments on commit d135f68

Please sign in to comment.