Skip to content

Commit

Permalink
Add support for generated headers
Browse files Browse the repository at this point in the history
Signed-off-by: Andrey Mokhov <[email protected]>
  • Loading branch information
snowleopard committed Oct 11, 2019
1 parent aef3fba commit 5562ce9
Show file tree
Hide file tree
Showing 8 changed files with 152 additions and 92 deletions.
10 changes: 5 additions & 5 deletions src/dune/exe.ml
Original file line number Diff line number Diff line change
Expand Up @@ -119,7 +119,8 @@ let exe_path_from_name cctx ~name ~(linkage : Linkage.t) =
Path.Build.relative (CC.dir cctx) (name ^ linkage.ext)

let link_exe ~loc ~name ~(linkage : Linkage.t) ~cm_files ~link_time_code_gen
~promote ?(link_flags = Build.return []) ?(o_files = []) cctx =
~promote ?(link_args = Build.return Command.Args.empty) ?(o_files = [])
cctx =
let sctx = CC.super_context cctx in
let ctx = SC.context sctx in
let dir = CC.dir cctx in
Expand Down Expand Up @@ -151,7 +152,7 @@ let link_exe ~loc ~name ~(linkage : Linkage.t) ~cm_files ~link_time_code_gen
; A "-o"
; Target exe
; As linkage.flags
; Command.Args.dyn link_flags
; Command.Args.Dyn link_args
; Command.of_result_map link_time_code_gen
~f:(fun { Link_time_code_gen.to_link; force_linkall } ->
S
Expand Down Expand Up @@ -182,8 +183,7 @@ let link_js ~name ~cm_files ~promote cctx =
Js_of_ocaml_rules.build_exe cctx ~js_of_ocaml ~src ~cm:top_sorted_cms
~flags:(Command.Args.dyn flags) ~promote

let build_and_link_many ~programs ~linkages ~promote ?link_flags ?o_files cctx
=
let build_and_link_many ~programs ~linkages ~promote ?link_args ?o_files cctx =
let modules = Compilation_context.modules cctx in
let dep_graphs = Dep_rules.rules cctx ~modules in
Module_compilation.build_all cctx ~dep_graphs;
Expand All @@ -207,7 +207,7 @@ let build_and_link_many ~programs ~linkages ~promote ?link_flags ?o_files cctx
link_js ~name ~cm_files ~promote cctx
else
link_exe cctx ~loc ~name ~linkage ~cm_files ~link_time_code_gen
~promote ?link_flags ?o_files))
~promote ?link_args ?o_files))

let build_and_link ~program = build_and_link_many ~programs:[ program ]

Expand Down
4 changes: 2 additions & 2 deletions src/dune/exe.mli
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ val build_and_link :
program:Program.t
-> linkages:Linkage.t list
-> promote:Dune_file.Promote.t option
-> ?link_flags:string list Build.t
-> ?link_args:Command.Args.static Command.Args.t Build.t
-> ?o_files:Path.t list
-> Compilation_context.t
-> unit
Expand All @@ -50,7 +50,7 @@ val build_and_link_many :
programs:Program.t list
-> linkages:Linkage.t list
-> promote:Dune_file.Promote.t option
-> ?link_flags:string list Build.t
-> ?link_args:Command.Args.static Command.Args.t Build.t
-> ?o_files:Path.t list
-> Compilation_context.t
-> unit
Expand Down
23 changes: 17 additions & 6 deletions src/dune/exe_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -43,10 +43,10 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info
(Module_name.to_string mod_name)
])
in
let ctx = SC.context sctx in
let explicit_js_mode = Dune_project.explicit_js_mode (Scope.project scope) in
let linkages =
let module L = Dune_file.Executables.Link_mode in
let ctx = SC.context sctx in
let l =
let has_native = Option.is_some ctx.ocamlopt in
let modes =
Expand Down Expand Up @@ -85,11 +85,22 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info
>>> Expander.expand_and_eval_set expander exes.link_flags
~standard:(Build.return [])
in
let link_flags =
(* TODO_AM: Implement the same approach in lib_rules. *)
let link_args =
let+ flags = link_flags in
flags
@ List.concat_map archive_names ~f:(fun archive_name ->
[ "-cclib"; "-l" ^ archive_name ])
Command.Args.S
[ Command.Args.As flags
; Command.Args.S
(List.map archive_names ~f:(fun archive_name ->
let ext_lib = ctx.lib_config.ext_lib in
let dir =
Path.Build.relative dir (Filename.dirname archive_name)
in
let archive_name = Filename.basename archive_name in
let lib = Foreign.lib_file ~archive_name ~dir ~ext_lib in
Command.Args.S
[ Command.Args.A "-cclib"; Command.Args.Dep (Path.build lib) ]))
]
in
let requires_compile = Lib.Compile.direct_requires compile_info in
let cctx =
Expand Down Expand Up @@ -146,7 +157,7 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info
o_files
in
let requires_compile = Compilation_context.requires_compile cctx in
Exe.build_and_link_many cctx ~programs ~linkages ~link_flags ~o_files
Exe.build_and_link_many cctx ~programs ~linkages ~link_args ~o_files
~promote:exes.promote;
( cctx
, Merlin.make () ~requires:requires_compile ~flags ~modules
Expand Down
1 change: 1 addition & 0 deletions src/dune/foreign_sources.ml
Original file line number Diff line number Diff line change
Expand Up @@ -126,6 +126,7 @@ let make (d : _ Dir_with_dune.t) ~(object_map : Foreign.Object_map.t) =
])
|> String.Map.map ~f:snd
in
(* TODO: Make this more type-safe by switching to non-empty lists. *)
let executables =
String.Map.of_list_map_exn exes ~f:(fun (exes, m) ->
(snd (List.hd exes.names), m))
Expand Down
2 changes: 1 addition & 1 deletion src/dune/inline_tests.ml
Original file line number Diff line number Diff line change
Expand Up @@ -313,7 +313,7 @@ include Sub_system.Register_end_point (struct
Exe.build_and_link cctx
~program:{ name; main_module_name = Module.name main_module; loc }
~linkages
~link_flags:(Build.return [ "-linkall" ])
~link_args:(Build.return (Command.Args.A "-linkall" ))
~promote:None;
let flags =
let flags =
Expand Down
27 changes: 18 additions & 9 deletions src/dune/lib_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -179,17 +179,26 @@ let include_dir_flags ~expander ~dir (stubs : Foreign.Stubs.t) =
; Command.Args.S
(File_tree.Dir.fold dir ~traverse:Sub_dirs.Status.Set.all
~init:[] ~f:(fun t args ->
(* let dir = Path.append_source build_dir
(File_tree.Dir.path t) and deps = Dep.Set.paths
(File_selector.create ~dir (Predicate.create
~id:("files_in_" ^ Path.to_string dir) ~f:(fun _ ->
true))) in *)
let local_dir =
Path.Source.to_local (File_tree.Dir.path t)
in
let dir =
Path.relative build_dir
(Path.Local.to_string local_dir)
in
let deps =
Path.Source.Set.to_list (File_tree.Dir.file_paths t)
|> List.map ~f:(Path.append_source build_dir)
Dep.Set.singleton
(Dep.file_selector
(File_selector.create ~dir
(Predicate.create
~id:
( lazy
(String
("files_in_" ^ Path.to_string dir))
)
~f:(fun _ -> true))))
in
Command.Args.Hidden_deps (Dep.Set.of_files deps)
:: args))
Command.Args.Hidden_deps deps :: args))
] )))

(* Build a static and a dynamic archive for a foreign library. *)
Expand Down
2 changes: 1 addition & 1 deletion src/dune/toplevel.ml
Original file line number Diff line number Diff line change
Expand Up @@ -84,7 +84,7 @@ let setup_rules t =
let program = Source.program t.source in
let sctx = Compilation_context.super_context t.cctx in
Exe.build_and_link t.cctx ~program ~linkages:[ linkage ]
~link_flags:(Build.return [ "-linkall"; "-warn-error"; "-31" ])
~link_args:(Build.return (Command.Args.As [ "-linkall"; "-warn-error"; "-31" ]))
~promote:None;
let src = Exe.exe_path t.cctx ~program ~linkage in
let dir = Source.stanza_dir t.source in
Expand Down
Loading

0 comments on commit 5562ce9

Please sign in to comment.