Skip to content

Commit

Permalink
Remove ?ext arg from the Module.cm_file family of functions
Browse files Browse the repository at this point in the history
The ?ext is only set for .o files. This isn't strong enough justification to
keep this argument around.

Signed-off-by: Rudi Grinberg <rudi.grinberg@gmail.com>
  • Loading branch information
rgrinberg committed Jun 5, 2019
1 parent 7d9a251 commit e9e71d1
Show file tree
Hide file tree
Showing 3 changed files with 22 additions and 19 deletions.
16 changes: 8 additions & 8 deletions src/module.ml
Original file line number Diff line number Diff line change
Expand Up @@ -269,25 +269,25 @@ let obj_name t = t.obj_name

let cm_source t kind = file t (Cm_kind.source kind)

let cm_file_unsafe t ?ext kind =
let ext = Option.value ext ~default:(Cm_kind.ext kind) in
let cm_file_unsafe t kind =
let ext = Cm_kind.ext kind in
obj_file t ~kind ~ext

let cm_file t ?ext (kind : Cm_kind.t) =
let cm_file t (kind : Cm_kind.t) =
match kind with
| (Cmx | Cmo) when not (has_impl t) -> None
| _ -> Some (cm_file_unsafe t ?ext kind)
| _ -> Some (cm_file_unsafe t kind)

let cm_public_file_unsafe t ?ext kind =
let ext = Option.value ext ~default:(Cm_kind.ext kind) in
let cm_public_file_unsafe t kind =
let ext = Cm_kind.ext kind in
let base = Obj_dir.cm_public_dir t.obj_dir kind in
Path.relative base (t.obj_name ^ ext)

let cm_public_file t ?ext (kind : Cm_kind.t) =
let cm_public_file t (kind : Cm_kind.t) =
match kind with
| (Cmx | Cmo) when not (has_impl t) -> None
| Cmi when is_private t -> None
| _ -> Some (cm_public_file_unsafe t ?ext kind)
| _ -> Some (cm_public_file_unsafe t kind)

let cmt_file t (kind : Ml_kind.t) =
match kind with
Expand Down
9 changes: 4 additions & 5 deletions src/module.mli
Original file line number Diff line number Diff line change
Expand Up @@ -113,8 +113,8 @@ val pp_flags : t -> (unit, string list) Build.t option

val file : t -> Ml_kind.t -> Path.t option
val cm_source : t -> Cm_kind.t -> Path.t option
val cm_file : t -> ?ext:string -> Cm_kind.t -> Path.t option
val cm_public_file : t -> ?ext:string -> Cm_kind.t -> Path.t option
val cm_file : t -> Cm_kind.t -> Path.t option
val cm_public_file : t -> Cm_kind.t -> Path.t option
val cmt_file : t -> Ml_kind.t -> Path.t option

val obj_file : t -> kind:Cm_kind.t -> ext:string -> Path.t
Expand All @@ -123,10 +123,9 @@ val obj_name : t -> string

(** Same as [cm_file] but doesn't raise if [cm_kind] is [Cmo] or [Cmx]
and the module has no implementation.
If present [ext] replace the extension of the kind
*)
val cm_file_unsafe : t -> ?ext:string -> Cm_kind.t -> Path.t
val cm_public_file_unsafe : t -> ?ext:string -> Cm_kind.t -> Path.t
val cm_file_unsafe : t -> Cm_kind.t -> Path.t
val cm_public_file_unsafe : t -> Cm_kind.t -> Path.t

val odoc_file : t -> doc_dir:Path.Build.t -> Path.Build.t

Expand Down
16 changes: 10 additions & 6 deletions src/virtual_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -45,9 +45,9 @@ let setup_copy_rules_for_impl ~sctx ~dir vimpl =
let modes =
Dune_file.Mode_conf.Set.eval impl.modes
~has_native:(Option.is_some ctx.ocamlopt) in
let copy_obj_file ~src ~dst ?ext kind =
let src = Module.cm_file_unsafe src ?ext kind in
let dst = Module.cm_file_unsafe dst ?ext kind in
let copy_obj_file ~src ~dst kind =
let src = Module.cm_file_unsafe src kind in
let dst = Module.cm_file_unsafe dst kind in
copy_to_obj_dir ~src ~dst:(Path.as_in_build_dir_exn dst) in
let copy_objs src =
let dst = Module.set_obj_dir ~obj_dir:(Obj_dir.of_local impl_obj_dir) src in
Expand All @@ -62,9 +62,13 @@ let setup_copy_rules_for_impl ~sctx ~dir vimpl =
if Module.has_impl src then begin
if modes.byte then
copy_obj_file ~src ~dst Cmo;
if modes.native then
List.iter [Cm_kind.ext Cmx; ctx.ext_obj]
~f:(fun ext -> copy_obj_file ~src ~dst ~ext Cmx)
if modes.native then begin
copy_obj_file ~src ~dst Cmx;
(let object_file = Module.obj_file ~kind:Cmx ~ext:ctx.ext_obj in
copy_to_obj_dir
~src:(object_file src)
~dst:(Path.as_in_build_dir_exn (object_file dst)))
end
end
in
let copy_all_deps =
Expand Down

0 comments on commit e9e71d1

Please sign in to comment.