diff --git a/src/gen_rules.ml b/src/gen_rules.ml index 46cc34aa8fa..385881a28d8 100644 --- a/src/gen_rules.ml +++ b/src/gen_rules.ml @@ -412,16 +412,27 @@ module Gen(P : Params) = struct | Executables stuff | +-----------------------------------------------------------------+ *) - let build_exe ~js_of_ocaml ~flags ~dir ~requires ~name ~mode ~modules ~dep_graph + let build_exe ~js_of_ocaml ~flags ~dir ~requires ~name ~mode ~binary_kind ~modules ~dep_graph ~link_flags ~force_custom_bytecode = - let exe_ext = Mode.exe_ext mode in let mode, link_flags, compiler = match force_custom_bytecode, Context.compiler ctx mode with | false, Some compiler -> (mode, link_flags, compiler) | _ -> (Byte, "-custom" :: link_flags, ctx.ocamlc) in let dep_graph = Ml_kind.Dict.get dep_graph Impl in - let exe = Path.relative dir (name ^ exe_ext) in + let extension= + match binary_kind with + | Mode.Dict.Binary_Kind_Set.Executable -> Mode.exe_ext mode + | Object -> (Mode.exe_ext mode) ^ ".o" + | Shared_object -> (if mode = Byte then ".bc" else "") ^ ctx.ext_dll + in + let specific_flags = + match binary_kind with + | Mode.Dict.Binary_Kind_Set.Executable -> [] + | Object -> ["-output-complete-obj"] + | Shared_object -> ["-output-complete-obj";"-runtime-variant";"_pic"] + in + let target = Path.relative dir (name ^ extension) in let libs_and_cm = Build.fanout (requires @@ -440,13 +451,14 @@ module Gen(P : Params) = struct Build.run ~context:ctx (Dep compiler) [ Ocaml_flags.get flags mode - ; A "-o"; Target exe + ; As specific_flags + ; A "-o"; Target target ; As link_flags ; Dyn (fun (libs, _) -> Lib.link_flags libs ~mode) ; Dyn (fun (_, cm_files) -> Deps cm_files) ]); - if mode = Mode.Byte then - let rules = Js_of_ocaml_rules.build_exe sctx ~dir ~js_of_ocaml ~src:exe in + if mode = Byte && binary_kind = Mode.Dict.Binary_Kind_Set.Executable then + let rules = Js_of_ocaml_rules.build_exe sctx ~dir ~js_of_ocaml ~src:target in SC.add_rules sctx (List.map rules ~f:(fun r -> libs_and_cm >>> r)) let executables_rules (exes : Executables.t) ~dir ~all_modules ~scope = @@ -492,10 +504,12 @@ module Gen(P : Params) = struct ~requires ~alias_module:None; List.iter exes.names ~f:(fun name -> - List.iter Mode.all ~f:(fun mode -> - build_exe ~js_of_ocaml:exes.buildable.js_of_ocaml ~flags ~dir ~requires ~name - ~mode ~modules ~dep_graph ~link_flags:exes.link_flags - ~force_custom_bytecode:(mode = Native && not exes.modes.native))); + List.iter (Mode.Dict.Binary_Kind_Set.to_list exes.modes) + ~f:(fun (mode,binary_kind) -> + build_exe ~js_of_ocaml:exes.buildable.js_of_ocaml ~flags ~dir ~requires ~name + ~mode ~binary_kind ~modules ~dep_graph ~link_flags:exes.link_flags + ~force_custom_bytecode:false (* mode = Native && not exes.modes.native *))); + { Merlin. requires = real_requires ; flags = flags.common diff --git a/src/jbuild.ml b/src/jbuild.ml index e3b102b10fc..0dbd613326a 100644 --- a/src/jbuild.ml +++ b/src/jbuild.ml @@ -632,11 +632,12 @@ module Install_conf = struct end module Executables = struct + type t = { names : string list ; link_executables : bool ; link_flags : string list - ; modes : Mode.Dict.Set.t + ; modes : Mode.Dict.Binary_Kind_Set.t ; buildable : Buildable.t } @@ -644,9 +645,10 @@ module Executables = struct Buildable.v1 >>= fun buildable -> field "link_executables" bool ~default:true >>= fun link_executables -> field "link_flags" (list string) ~default:[] >>= fun link_flags -> - map_validate (field "modes" Mode.Dict.Set.t ~default:Mode.Dict.Set.all) + map_validate (field "modes" Mode.Dict.Binary_Kind_Set.t + ~default:Mode.Dict.Binary_Kind_Set.default) ~f:(fun modes -> - if Mode.Dict.Set.is_empty modes then + if Mode.Dict.Binary_Kind_Set.is_empty modes then Error "No compilation mode defined." else Ok modes) @@ -660,13 +662,16 @@ module Executables = struct } in let to_install = - let ext = if modes.native then ".exe" else ".bc" in - List.map2 names public_names - ~f:(fun name pub -> - match pub with - | None -> None - | Some pub -> Some ({ Install_conf. src = name ^ ext; dst = Some pub })) - |> List.filter_map ~f:(fun x -> x) + match Mode.Dict.Binary_Kind_Set.best_executable_mode t.modes with + | None -> [] + | Some best_mode -> + let ext = if best_mode = Native then ".exe" else ".bc" in + List.map2 names public_names + ~f:(fun name pub -> + match pub with + | None -> None + | Some pub -> Some ({ Install_conf. src = name ^ ext; dst = Some pub })) + |> List.filter_map ~f:(fun x -> x) in match to_install with | [] -> diff --git a/src/jbuild.mli b/src/jbuild.mli index 711aa064b3d..f5ec75b65f9 100644 --- a/src/jbuild.mli +++ b/src/jbuild.mli @@ -171,7 +171,7 @@ module Executables : sig { names : string list ; link_executables : bool ; link_flags : string list - ; modes : Mode.Dict.Set.t + ; modes : Mode.Dict.Binary_Kind_Set.t ; buildable : Buildable.t } end diff --git a/src/mode.ml b/src/mode.ml index af929064b48..1985962824a 100644 --- a/src/mode.ml +++ b/src/mode.ml @@ -75,4 +75,56 @@ module Dict = struct if t.byte then f Byte; if t.native then f Native end + + module Binary_Kind_Set = struct + type binary_kind = + | Executable + | Object + | Shared_object + + let binary_kind = + let open Sexp.Of_sexp in + enum + [ "executable" , Executable + ; "object" , Object + ; "shared_object" , Shared_object + ] + + type nonrec t = binary_kind list t + + let default = + { byte = [Executable] + ; native = [Executable] + } + + let all_binary_kind = [Executable; Object; Shared_object] + let all = + { byte = all_binary_kind + ; native = all_binary_kind + } + + let to_list t = + (List.map t.native ~f:(fun x -> Native,x)) @ + (List.map t.byte ~f:(fun x -> Byte,x)) + + let of_list l = + let byte, native = List.partition_map ~f:(fun (m,x) -> if m=Byte then Inr x else Inl x) l in + { byte + ; native + } + + let t : t Sexp.Of_sexp.t = fun sexp -> of_list (Sexp.Of_sexp.list (Sexp.Of_sexp.pair t binary_kind) sexp) + + let is_empty t = t.byte = [] && t.native = [] + + let iter t ~f = + List.iter ~f (to_list t) + + let best_executable_mode t = + if List.mem ~set:t.native Executable then Some Native + else if List.mem ~set:t.byte Executable then Some Byte + else None + end + + end diff --git a/src/mode.mli b/src/mode.mli index e37ec9b7994..8ac5dacc9f7 100644 --- a/src/mode.mli +++ b/src/mode.mli @@ -30,6 +30,7 @@ module Dict : sig val map2 : 'a t -> 'b t -> f:('a -> 'b -> 'c) -> 'c t module Set : sig + type nonrec t = bool t val t : t Sexp.Of_sexp.t val all : t @@ -38,4 +39,24 @@ module Dict : sig val of_list : mode list -> t val iter : t -> f:(mode -> unit) -> unit end + + module Binary_Kind_Set : sig + + type binary_kind = + | Executable + | Object + | Shared_object + + type nonrec t = binary_kind list t + val t : t Sexp.Of_sexp.t + val default : t + val all : t + val is_empty : t -> bool + val to_list : t -> (mode * binary_kind) list + val of_list : (mode * binary_kind) list -> t + val iter : t -> f:((mode * binary_kind) -> unit) -> unit + val best_executable_mode : t -> mode option + end + + end with type mode := t diff --git a/test/jbuild b/test/jbuild index 0265ed506b7..30a4e63807d 100644 --- a/test/jbuild +++ b/test/jbuild @@ -104,3 +104,12 @@ (deps ((alias sleep5) (alias sleep4-and-fail) (alias sleep1-and-fail))))) + + +(alias + ((name runtest) + (deps ((files_recursively_in workspaces/output_obj))) + (action + (chdir workspaces/output_obj + (run ${exe:run.exe} -- + ${bin:jbuilder} build -j1 --root . @all ))))) diff --git a/test/workspaces/output_obj/jbuild b/test/workspaces/output_obj/jbuild new file mode 100644 index 00000000000..d015b98b0a9 --- /dev/null +++ b/test/workspaces/output_obj/jbuild @@ -0,0 +1,17 @@ +(alias ( + (name all) + (deps (test.exe test.bc test.exe.o test.so stub)) +)) + +(executable ( + (name test) + (modes ((byte executable)(native executable) + (byte object)(native object) + (byte shared_object)(native shared_object))) +)) + +(rule ( + (targets (stub)) + (deps (stub.c test.exe.o test.so)) + (action (run cc -o stub -I ${ocaml_where} -I . -ltest stub.c)) +)) diff --git a/test/workspaces/output_obj/stub.c b/test/workspaces/output_obj/stub.c new file mode 100644 index 00000000000..e2115895a2f --- /dev/null +++ b/test/workspaces/output_obj/stub.c @@ -0,0 +1,10 @@ +#include +#include +#include +#include + +int main(char ** argv){ + + caml_startup(argv); + return 0; +} diff --git a/test/workspaces/output_obj/test.ml b/test/workspaces/output_obj/test.ml new file mode 100644 index 00000000000..b2106fd5051 --- /dev/null +++ b/test/workspaces/output_obj/test.ml @@ -0,0 +1 @@ +let () = print_string "Test!!"