Skip to content

Commit

Permalink
Drop code duplication, simplify API
Browse files Browse the repository at this point in the history
Signed-off-by: Andrey Mokhov <amokhov@janestreet.com>
  • Loading branch information
snowleopard committed Oct 9, 2019
1 parent c480f9e commit 9315526
Show file tree
Hide file tree
Showing 3 changed files with 15 additions and 32 deletions.
23 changes: 6 additions & 17 deletions src/dune/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -958,33 +958,22 @@ module Library = struct
List.is_non_empty t.buildable.foreign_stubs
|| List.is_non_empty t.buildable.foreign_archives

let default_archive_name t = Lib_name.Local.to_string (snd t.name) ^ "_stubs"

let default_lib_file t ~dir ~ext_lib =
Path.Build.relative dir
(sprintf "lib%s%s" (default_archive_name t) ext_lib)

let default_dll_file t ~dir ~ext_dll =
Path.Build.relative dir
(sprintf "dll%s%s" (default_archive_name t) ext_dll)
let stubs_archive_name t = Lib_name.Local.to_string (snd t.name) ^ "_stubs"

let archive_names t =
( if List.is_empty t.buildable.foreign_stubs then
[]
else
[ default_archive_name t ] )
[ stubs_archive_name t ] )
@ List.map ~f:snd t.buildable.foreign_archives

(* TODO_AM: Code duplication. *)
let lib_files t ~dir ~ext_lib =
List.map (archive_names t) ~f:(fun name ->
Path.Build.relative dir (sprintf "lib%s%s" name ext_lib))
List.map (archive_names t) ~f:(fun archive_name ->
Foreign.lib_file ~archive_name ~dir ~ext_lib)

let dll_files t ~dir ~ext_dll =
List.map (archive_names t) ~f:(fun name ->
Path.Build.relative dir (sprintf "dll%s%s" name ext_dll))

let stubs_path t ~dir = Path.Build.relative dir (default_archive_name t)
List.map (archive_names t) ~f:(fun archive_name ->
Foreign.dll_file ~archive_name ~dir ~ext_dll)

let archive t ~dir ~ext =
Path.Build.relative dir (Lib_name.Local.to_string (snd t.name) ^ ext)
Expand Down
10 changes: 1 addition & 9 deletions src/dune/dune_file.mli
Original file line number Diff line number Diff line change
Expand Up @@ -202,22 +202,14 @@ module Library : sig

val has_stubs : t -> bool

val default_archive_name : t -> string

val default_lib_file :
t -> dir:Path.Build.t -> ext_lib:string -> Path.Build.t

val default_dll_file :
t -> dir:Path.Build.t -> ext_dll:string -> Path.Build.t
val stubs_archive_name : t -> string

val archive_names : t -> string list

val lib_files : t -> dir:Path.Build.t -> ext_lib:string -> Path.Build.t list

val dll_files : t -> dir:Path.Build.t -> ext_dll:string -> Path.Build.t list

val stubs_path : t -> dir:Path.Build.t -> Path.Build.t

val archive : t -> dir:Path.Build.t -> ext:string -> Path.Build.t

val best_name : t -> Lib_name.t
Expand Down
14 changes: 8 additions & 6 deletions src/dune/lib_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -136,10 +136,11 @@ let ocamlmklib ~path ~loc ~c_library_flags ~sctx ~dir ~expander ~o_files
(* Add a rule calling [ocamlmklib] to build an OCaml library. *)
let ocamlmklib_ocaml (lib : Library.t) ~sctx ~dir ~expander ~o_files ~sandbox
~custom ~targets =
ocamlmklib
~path:(Path.build (Library.stubs_path lib ~dir))
~loc:lib.buildable.loc ~c_library_flags:lib.c_library_flags ~sctx ~dir
~expander ~o_files ~sandbox ~custom ~targets
let path =
Path.build (Path.Build.relative dir (Library.stubs_archive_name lib))
in
ocamlmklib ~path ~loc:lib.buildable.loc ~c_library_flags:lib.c_library_flags
~sctx ~dir ~expander ~o_files ~sandbox ~custom ~targets

(* Build a static and a dynamic archive for a foreign library. *)
let build_foreign_library (library : Foreign.Library.t) ~sctx ~expander ~dir
Expand Down Expand Up @@ -226,8 +227,9 @@ let build_self_stubs lib ~cctx ~expander ~dir ~o_files =
let sctx = Compilation_context.super_context cctx in
let ctx = Super_context.context sctx in
let { Lib_config.ext_lib; ext_dll; _ } = ctx.lib_config in
let static = Library.default_lib_file lib ~dir ~ext_lib in
let dynamic = Library.default_dll_file lib ~dir ~ext_dll in
let archive_name = Library.stubs_archive_name lib in
let static = Foreign.lib_file ~archive_name ~dir ~ext_lib in
let dynamic = Foreign.dll_file ~archive_name ~dir ~ext_dll in
let modes = Compilation_context.modes cctx in
let ocamlmklib = ocamlmklib_ocaml lib ~sctx ~expander ~dir ~o_files in
if
Expand Down

0 comments on commit 9315526

Please sign in to comment.