From 855b085d889389e17dc914d094617090321fbfa5 Mon Sep 17 00:00:00 2001 From: Ulysse <5031221+voodoos@users.noreply.github.com> Date: Tue, 23 Nov 2021 17:38:05 +0100 Subject: [PATCH] Add default cxx link flags to `ocamlmklib` and `ocamlc` calls (#5185) MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit * Split cxx flags by phase * Add link flags when building libraries * Add default cxx link flags for exe with cxx stubs * Update tests Signed-off-by: Ulysse GĂ©rard --- src/dune_rules/cxx_flags.ml | 19 ++-- src/dune_rules/cxx_flags.mli | 6 +- src/dune_rules/dune_file.ml | 9 ++ src/dune_rules/dune_file.mli | 9 ++ src/dune_rules/exe_rules.ml | 21 +++-- src/dune_rules/foreign.ml | 4 + src/dune_rules/foreign.mli | 2 + src/dune_rules/lib_rules.ml | 86 ++++++++++++------- src/dune_rules/super_context.ml | 2 +- .../test-cases/cxx-flags.t/baz.cpp | 10 +++ .../test-cases/cxx-flags.t/bazexe.cpp | 11 +++ .../test-cases/cxx-flags.t/dune | 2 +- .../test-cases/cxx-flags.t/main.ml | 10 ++- .../test-cases/cxx-flags.t/quad.ml | 4 + .../test-cases/cxx-flags.t/run.t | 71 ++++++++++++--- 15 files changed, 210 insertions(+), 56 deletions(-) create mode 100644 test/blackbox-tests/test-cases/cxx-flags.t/bazexe.cpp diff --git a/src/dune_rules/cxx_flags.ml b/src/dune_rules/cxx_flags.ml index 404aa69f0dc..a67ff4277de 100644 --- a/src/dune_rules/cxx_flags.ml +++ b/src/dune_rules/cxx_flags.ml @@ -1,16 +1,23 @@ open! Stdune open Dune_engine +type phase = + | Compile + | Link + type ccomp_type = | Gcc | Msvc | Clang | Other of string -let base_cxx_flags = function - | Gcc -> [ "-x"; "c++"; "-lstdc++"; "-shared-libgcc" ] - | Clang -> [ "-x"; "c++" ] - | Msvc -> [ "/TP" ] +let base_cxx_flags ~for_ cc = + match (cc, for_) with + | Gcc, Compile -> [ "-x"; "c++" ] + | Gcc, Link -> [ "-lstdc++"; "-shared-libgcc" ] + | Clang, Compile -> [ "-x"; "c++" ] + | Clang, Link -> [ "-lc++" ] + | Msvc, Compile -> [ "/TP" ] | _ -> [] let preprocessed_filename = "ccomp" @@ -38,8 +45,8 @@ let check_warn = function ] | _ -> () -let get_flags dir = +let get_flags ~for_ dir = let open Action_builder.O in let+ ccomp_type = ccomp_type dir in check_warn ccomp_type; - base_cxx_flags ccomp_type + base_cxx_flags ~for_ ccomp_type diff --git a/src/dune_rules/cxx_flags.mli b/src/dune_rules/cxx_flags.mli index 8fcf68bc129..e9b61cc5b3a 100644 --- a/src/dune_rules/cxx_flags.mli +++ b/src/dune_rules/cxx_flags.mli @@ -4,10 +4,14 @@ open! Stdune open Dune_engine +type phase = + | Compile + | Link + (** The name of the file created in the .dune folder after calling the C preprocessor *) val preprocessed_filename : string (** [get_flags c_compiler] returns the necessary flags to turn this compiler into a c++ compiler for some of the most common compilers *) -val get_flags : Path.Build.t -> string list Action_builder.t +val get_flags : for_:phase -> Path.Build.t -> string list Action_builder.t diff --git a/src/dune_rules/dune_file.ml b/src/dune_rules/dune_file.ml index b0e4ee23e3e..81c5129b13e 100644 --- a/src/dune_rules/dune_file.ml +++ b/src/dune_rules/dune_file.ml @@ -341,6 +341,11 @@ module Buildable = struct let has_foreign t = List.is_non_empty t.foreign_stubs || List.is_non_empty t.foreign_archives + + let has_foreign_cxx t = + List.exists + ~f:(fun stub -> Foreign_language.(equal Cxx stub.Foreign.Stubs.language)) + t.foreign_stubs end module Public_lib = struct @@ -778,6 +783,8 @@ module Library = struct let has_foreign t = Buildable.has_foreign t.buildable + let has_foreign_cxx t = Buildable.has_foreign_cxx t.buildable + let foreign_archives t = (if List.is_empty t.buildable.foreign_stubs then [] @@ -1526,6 +1533,8 @@ module Executables = struct let has_foreign t = Buildable.has_foreign t.buildable + let has_foreign_cxx t = Buildable.has_foreign_cxx t.buildable + let obj_dir t ~dir = Obj_dir.make_exe ~dir ~name:(snd (List.hd t.names)) end diff --git a/src/dune_rules/dune_file.mli b/src/dune_rules/dune_file.mli index 6a0f16eb778..5e7d23630e3 100644 --- a/src/dune_rules/dune_file.mli +++ b/src/dune_rules/dune_file.mli @@ -49,6 +49,9 @@ module Buildable : sig (** Check if the buildable has any foreign stubs or archives. *) val has_foreign : t -> bool + + (** Check if the buildable has any c++ foreign stubs. *) + val has_foreign_cxx : t -> bool end module Public_lib : sig @@ -162,6 +165,9 @@ module Library : sig (** Check if the library has any foreign stubs or archives. *) val has_foreign : t -> bool + (** Check if the library has any c++ foreign stubs. *) + val has_foreign_cxx : t -> bool + (** The list of all foreign archives, including the foreign stubs archive. *) val foreign_archives : t -> Foreign.Archive.t list @@ -262,6 +268,9 @@ module Executables : sig (** Check if the executables have any foreign stubs or archives. *) val has_foreign : t -> bool + (** Check if the executables have any c++ foreign stubs. *) + val has_foreign_cxx : t -> bool + val obj_dir : t -> dir:Path.Build.t -> Path.Build.t Obj_dir.t end diff --git a/src/dune_rules/exe_rules.ml b/src/dune_rules/exe_rules.ml index a591af2f243..d789560dd26 100644 --- a/src/dune_rules/exe_rules.ml +++ b/src/dune_rules/exe_rules.ml @@ -104,6 +104,7 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info in let* () = Check_rules.add_obj_dir sctx ~obj_dir in let ctx = Super_context.context sctx in + let project = Scope.project scope in let* pp = let instrumentation_backend = Lib.DB.instrumentation_backend (Scope.libs scope) @@ -132,10 +133,8 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info let* m = Pp_spec.pp_module_as pp name m in let add_empty_intf = (add_empty_intf - || - let project = Scope.project scope in - Dune_project.executables_implicit_empty_intf project - && List.mem executable_names name ~equal:Module_name.equal) + || Dune_project.executables_implicit_empty_intf project + && List.mem executable_names name ~equal:Module_name.equal) && not (Module.has m ~ml_kind:Intf) in if add_empty_intf then @@ -144,7 +143,7 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info Memo.Build.return m) in let programs = programs ~modules ~exes in - let explicit_js_mode = Dune_project.explicit_js_mode (Scope.project scope) in + let explicit_js_mode = Dune_project.explicit_js_mode project in let linkages = linkages ctx ~exes ~explicit_js_mode in let* flags = Super_context.ocaml_flags sctx ~dir exes.buildable.flags in let cctx = @@ -174,7 +173,14 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info files directly to improve perf. *) let link_deps, sandbox = Dep_conf_eval.unnamed ~expander exes.link_deps in let link_args = - let standard = Action_builder.return [] in + let standard = + match Dune_project.use_standard_c_and_cxx_flags project with + | Some true when Buildable.has_foreign_cxx exes.buildable -> + let open Action_builder.O in + let+ flags = Cxx_flags.get_flags ~for_:Link dir in + List.concat_map flags ~f:(fun f -> [ "-cclib"; f ]) + | _ -> Action_builder.return [] + in let open Action_builder.O in let link_flags = link_deps @@ -182,7 +188,8 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info in let+ flags = link_flags and+ ctypes_cclib_flags = - Ctypes_rules.ctypes_cclib_flags ~scope ~standard ~expander + Ctypes_rules.ctypes_cclib_flags ~scope + ~standard:(Action_builder.return []) ~expander ~buildable:exes.buildable in Command.Args.S diff --git a/src/dune_rules/foreign.ml b/src/dune_rules/foreign.ml index 2e8d50c2de9..e6f4f57318b 100644 --- a/src/dune_rules/foreign.ml +++ b/src/dune_rules/foreign.ml @@ -191,6 +191,10 @@ module Sources = struct String.Map.keys t |> List.map ~f:(fun c -> Path.Build.relative dir (c ^ ext_obj)) + let has_cxx_sources (t : t) = + String.Map.exists t ~f:(fun (_loc, source) -> + Foreign_language.(equal Cxx source.stubs.language)) + module Unresolved = struct type t = (Foreign_language.t * Path.Build.t) String.Map.Multi.t diff --git a/src/dune_rules/foreign.mli b/src/dune_rules/foreign.mli index 0e06dbb9797..1e5bff57f27 100644 --- a/src/dune_rules/foreign.mli +++ b/src/dune_rules/foreign.mli @@ -166,6 +166,8 @@ module Sources : sig val object_files : t -> dir:Path.Build.t -> ext_obj:string -> Path.Build.t list + val has_cxx_sources : t -> bool + (** A map from object names to lists of possible language/path combinations. *) module Unresolved : sig type t = (Foreign_language.t * Path.Build.t) String.Map.Multi.t diff --git a/src/dune_rules/lib_rules.ml b/src/dune_rules/lib_rules.ml index e161f8f66ae..e3a22bae598 100644 --- a/src/dune_rules/lib_rules.ml +++ b/src/dune_rules/lib_rules.ml @@ -43,10 +43,19 @@ let build_lib (lib : Library.t) ~native_archives ~sctx ~expander ~flags ~dir Action_builder.paths (Cm_files.unsorted_objects_and_cms cm_files ~mode) in let ocaml_flags = Ocaml_flags.get flags mode in - let standard = Action_builder.return [] in + let standard = + let project = + Super_context.find_scope_by_dir sctx dir |> Scope.project + in + match Dune_project.use_standard_c_and_cxx_flags project with + | Some true when Buildable.has_foreign_cxx lib.buildable -> + Cxx_flags.get_flags ~for_:Link dir + | _ -> Action_builder.return [] + in let cclibs = Expander.expand_and_eval_set expander lib.c_library_flags ~standard in + let standard = Action_builder.return [] in let library_flags = Expander.expand_and_eval_set expander lib.library_flags ~standard in @@ -115,20 +124,26 @@ let gen_wrapped_compat_modules (lib : Library.t) cctx = |> Super_context.add_rule sctx ~loc ~dir:(Compilation_context.dir cctx)) (* Rules for building static and dynamic libraries using [ocamlmklib]. *) -let ocamlmklib ~loc ~c_library_flags ~sctx ~dir ~expander ~o_files ~archive_name +let ocamlmklib ~loc ~c_library_flags ~sctx ~dir ~o_files ~archive_name ~build_targets_together = let ctx = Super_context.context sctx in let { Lib_config.ext_lib; ext_dll; _ } = ctx.lib_config in let static_target = Foreign.Archive.Name.lib_file archive_name ~dir ~ext_lib in + let cclibs = + Action_builder.map c_library_flags ~f:(fun cclibs -> + (* https://github.com/ocaml/dune/issues/119 *) + let cclibs = + match ctx.lib_config.ccomp_type with + | Msvc -> msvc_hack_cclibs cclibs + | Other _ -> cclibs + in + Command.quote_args "-ldopt" cclibs) + in let build ~custom ~sandbox targets = Super_context.add_rule sctx ~dir ~loc (let open Action_builder.With_targets.O in - let cclibs_args = - Expander.expand_and_eval_set expander c_library_flags - ~standard:(Action_builder.return []) - in let ctx = Super_context.context sctx in Command.run ~dir:(Path.build ctx.build_dir) ctx.ocamlmklib [ A "-g" @@ -139,16 +154,9 @@ let ocamlmklib ~loc ~c_library_flags ~sctx ~dir ~expander ~o_files ~archive_name ; A "-o" ; Path (Path.build (Foreign.Archive.Name.path ~dir archive_name)) ; Deps o_files - ; Dyn - (* The [c_library_flags] is needed only for the [dynamic_target] - case, but we pass them unconditionally for simplicity. *) - (Action_builder.map cclibs_args ~f:(fun cclibs -> - (* https://github.com/ocaml/dune/issues/119 *) - match ctx.lib_config.ccomp_type with - | Msvc -> - let cclibs = msvc_hack_cclibs cclibs in - Command.quote_args "-ldopt" cclibs - | Other _ -> As cclibs)) + (* The [c_library_flags] is needed only for the [dynamic_target] case, + but we pass them unconditionally for simplicity. *) + ; Dyn cclibs ; Hidden_targets targets ] >>| Action.Full.add_sandbox sandbox) @@ -192,30 +200,40 @@ let ocamlmklib ~loc ~c_library_flags ~sctx ~dir ~expander ~o_files ~archive_name let foreign_rules (library : Foreign.Library.t) ~sctx ~expander ~dir ~dir_contents = let archive_name = library.archive_name in + let* foreign_sources = + Dir_contents.foreign_sources dir_contents + >>| Foreign_sources.for_archive ~archive_name + in let* o_files = - let* foreign_sources = - Dir_contents.foreign_sources dir_contents - >>| Foreign_sources.for_archive ~archive_name - in Foreign_rules.build_o_files ~sctx ~dir ~expander ~requires:(Resolve.return []) ~dir_contents ~foreign_sources |> Memo.Build.parallel_map ~f:(Memo.Build.map ~f:Path.build) in let* () = Check_rules.add_files sctx ~dir o_files in - ocamlmklib ~archive_name ~loc:library.stubs.loc - ~c_library_flags:Ordered_set_lang.Unexpanded.standard ~sctx ~dir ~expander + let standard = + let project = Super_context.find_scope_by_dir sctx dir |> Scope.project in + match Dune_project.use_standard_c_and_cxx_flags project with + | Some true when Foreign.Sources.has_cxx_sources foreign_sources -> + Cxx_flags.get_flags ~for_:Link dir + | _ -> Action_builder.return [] + in + let c_library_flags = + Expander.expand_and_eval_set expander Ordered_set_lang.Unexpanded.standard + ~standard + in + ocamlmklib ~archive_name ~loc:library.stubs.loc ~c_library_flags ~sctx ~dir ~o_files ~build_targets_together:false (* Build a required set of archives for an OCaml library. *) let build_stubs lib ~cctx ~dir ~expander ~requires ~dir_contents ~vlib_stubs_o_files = let sctx = Compilation_context.super_context cctx in + let* foreign_sources = + let+ foreign_sources = Dir_contents.foreign_sources dir_contents in + let name = Library.best_name lib in + Foreign_sources.for_lib foreign_sources ~name + in let* lib_o_files = - let* foreign_sources = - let+ foreign_sources = Dir_contents.foreign_sources dir_contents in - let name = Library.best_name lib in - Foreign_sources.for_lib foreign_sources ~name - in Foreign_rules.build_o_files ~sctx ~dir ~expander ~requires ~dir_contents ~foreign_sources |> Memo.Build.parallel_map ~f:(Memo.Build.map ~f:Path.build) @@ -232,8 +250,18 @@ let build_stubs lib ~cctx ~dir ~expander ~requires ~dir_contents modes.native && modes.byte && Dynlink_supported.get lib.dynlink ctx.supports_shared_libraries in - ocamlmklib ~archive_name ~loc:lib.buildable.loc ~sctx ~expander ~dir - ~o_files ~c_library_flags:lib.c_library_flags ~build_targets_together + let standard = + let project = Super_context.find_scope_by_dir sctx dir |> Scope.project in + match Dune_project.use_standard_c_and_cxx_flags project with + | Some true when Foreign.Sources.has_cxx_sources foreign_sources -> + Cxx_flags.get_flags ~for_:Link dir + | _ -> Action_builder.return [] + in + let c_library_flags = + Expander.expand_and_eval_set expander lib.c_library_flags ~standard + in + ocamlmklib ~archive_name ~loc:lib.buildable.loc ~sctx ~dir ~o_files + ~c_library_flags ~build_targets_together let build_shared lib ~native_archives ~sctx ~dir ~flags = let ctx = Super_context.context sctx in diff --git a/src/dune_rules/super_context.ml b/src/dune_rules/super_context.ml index 9dc0cfa0774..b28a6fee34d 100644 --- a/src/dune_rules/super_context.ml +++ b/src/dune_rules/super_context.ml @@ -16,7 +16,7 @@ let default_context_flags (ctx : Context.t) ~project = let c = cflags @ Ocaml_config.ocamlc_cppflags ctx.ocaml_config in let cxx = let open Action_builder.O in - let+ db_flags = Cxx_flags.get_flags ctx.build_dir in + let+ db_flags = Cxx_flags.get_flags ~for_:Compile ctx.build_dir in db_flags @ cxxflags in (Action_builder.return c, cxx) diff --git a/test/blackbox-tests/test-cases/cxx-flags.t/baz.cpp b/test/blackbox-tests/test-cases/cxx-flags.t/baz.cpp index 9fbd06bf4fd..5cbbc00c0c7 100644 --- a/test/blackbox-tests/test-cases/cxx-flags.t/baz.cpp +++ b/test/blackbox-tests/test-cases/cxx-flags.t/baz.cpp @@ -1,2 +1,12 @@ #include +#include +#include + extern "C" value baz(value unit) { return Val_int(2046); } + +extern "C" void hello_world_baz (); + +void hello_world_baz () +{ + std::cout << "Hello World Baz!\n"; +} diff --git a/test/blackbox-tests/test-cases/cxx-flags.t/bazexe.cpp b/test/blackbox-tests/test-cases/cxx-flags.t/bazexe.cpp new file mode 100644 index 00000000000..c44efd5cc3e --- /dev/null +++ b/test/blackbox-tests/test-cases/cxx-flags.t/bazexe.cpp @@ -0,0 +1,11 @@ +#include +#include + +extern "C" value bazexe(value unit) { return Val_int(4096); } + +extern "C" void hello_world_bazexe (); + +void hello_world_bazexe () +{ + std::cout << "Hello World Bazexe!"; +} diff --git a/test/blackbox-tests/test-cases/cxx-flags.t/dune b/test/blackbox-tests/test-cases/cxx-flags.t/dune index 56b17d50b04..6f4cc7ca904 100644 --- a/test/blackbox-tests/test-cases/cxx-flags.t/dune +++ b/test/blackbox-tests/test-cases/cxx-flags.t/dune @@ -6,5 +6,5 @@ (executable (name main) (libraries quad) + (foreign_stubs (language cxx) (names bazexe)) (modules main)) - diff --git a/test/blackbox-tests/test-cases/cxx-flags.t/main.ml b/test/blackbox-tests/test-cases/cxx-flags.t/main.ml index 782f3f1b49c..33d67253f52 100644 --- a/test/blackbox-tests/test-cases/cxx-flags.t/main.ml +++ b/test/blackbox-tests/test-cases/cxx-flags.t/main.ml @@ -1 +1,9 @@ -let () = Printf.printf "%d" (Quad.quad ()) +external bazexe : unit -> int = "bazexe" +external hello_world_bazexe : unit -> unit = "hello_world_bazexe" + +let () = Quad.hello (); hello_world_bazexe () + + +let () = Printf.printf "%d\n%d\n" + (Quad.quad ()) + (bazexe ()) diff --git a/test/blackbox-tests/test-cases/cxx-flags.t/quad.ml b/test/blackbox-tests/test-cases/cxx-flags.t/quad.ml index 49a7e910809..1334cfe4f56 100644 --- a/test/blackbox-tests/test-cases/cxx-flags.t/quad.ml +++ b/test/blackbox-tests/test-cases/cxx-flags.t/quad.ml @@ -1,2 +1,6 @@ external baz : unit -> int = "baz" + +external hello_world_baz : unit -> unit = "hello_world_baz" + let quad x = baz x +let hello () = hello_world_baz () diff --git a/test/blackbox-tests/test-cases/cxx-flags.t/run.t b/test/blackbox-tests/test-cases/cxx-flags.t/run.t index 5d0ab42d0b4..b6511d61458 100644 --- a/test/blackbox-tests/test-cases/cxx-flags.t/run.t +++ b/test/blackbox-tests/test-cases/cxx-flags.t/run.t @@ -5,10 +5,18 @@ Default: use_standard_c_and_cxx_flags = false > (lang dune 2.8) > EOF -> The flags that Dune should use - $ GCCF="-x c++ -lstdc++ -shared-libgcc" - $ ClangF="-x c++" - $ MsvcF="/TP" +> The flags that Dune should use for compilation + $ GCC_CF="-x c++" + $ Clang_CF="-x c++" + $ Msvc_CF="/TP" + +> And linking + $ GCC_LF_OPT=" -ldopt -lstdc++ -ldopt -shared-libgcc" + $ Clang_LF_OPT=" -ldopt -lc++" + $ Msvc_LF_OPT="" + $ GCC_LF_LIB=" -cclib -lstdc++ -cclib -shared-libgcc" + $ Clang_LF_LIB=" -cclib -lc++" + $ Msvc_LF_LIB="" > Check that compiler detection is done $ dune build .dune/ccomp/ccomp @@ -17,12 +25,25 @@ Default: use_standard_c_and_cxx_flags = false > grep -ce "clang\|gcc\|msvc" 1 -> No specific flags added +> No specific flags added for compilation... $ dune rules baz.o | tr -s '\n' ' ' | - > grep -ce "$GCCF\|$ClangF|$MsvcF" + > grep -ce "$GCC_CF\|$Clang_CF|$Msvc_CF" 0 [1] + $ dune rules bazexe.o | tr -s '\n' ' ' | + > grep -ce "$GCC_CF\|$Clang_CF\|$Msvc_CF" + 0 + [1] + +> ...nor linking + $ dune rules libquad_stubs.a | tr -s '\n' ' ' | + > grep -ce "quad_stubs baz.o)" + 1 + + $ dune rules main.exe | tr -s '\n' ' ' | + > grep -ce "Main.cmx)" + 1 With use_standard_c_and_cxx_flags = false ========================================= @@ -32,12 +53,26 @@ With use_standard_c_and_cxx_flags = false > (use_standard_c_and_cxx_flags false) > EOF -> No specific flags added +> No specific flags added for compilation... $ dune rules baz.o | tr -s '\n' ' ' | - > grep -ce "$GCCF\|$ClangF|$MsvcF" + > grep -ce "$GCC_CF\|$Clang_CF|$Msvc_CF" + 0 + [1] + + $ dune rules bazexe.o | tr -s '\n' ' ' | + > grep -ce "$GCC_CF\|$Clang_CF\|$Msvc_CF" 0 [1] +> ...nor linking + $ dune rules libquad_stubs.a | tr -s '\n' ' ' | + > grep -ce "quad_stubs baz.o)" + 1 + + $ dune rules main.exe | tr -s '\n' ' ' | + > grep -ce "Main.cmx)" + 1 + With use_standard_c_and_cxx_flags = true ======================================== @@ -53,10 +88,26 @@ With use_standard_c_and_cxx_flags = true > grep -ce "clang\|gcc\|msvc" 1 -> Specific flags added +> Specific flags added for compilation... $ dune rules baz.o | tr -s '\n' ' ' | - > grep -ce "$GCCF\|$ClangF\|$MsvcF" + > grep -ce "$GCC_CF\|$Clang_CF\|$Msvc_CF" + 1 + + $ dune rules bazexe.o | tr -s '\n' ' ' | + > grep -ce "$GCC_CF\|$Clang_CF\|$Msvc_CF" + 1 + +> ..and link + $ dune rules libquad_stubs.a | tr -s '\n' ' ' | + > grep -ce "quad_stubs baz.o$GCC_LF_OPT)\|quad_stubs baz.o$Clang_LF_OPT)\|quad_stubs baz.o$Msvc_LF_OPT)" + 1 + + $ dune rules main.exe | tr -s '\n' ' ' | + > grep -ce "Main.cmx$GCC_LF)\|Main.cmx$Clang_LF)\|Main.cmx$Msvc_LF)" 1 $ dune exec ./main.exe 2046 + 4096 + Hello World Baz! + Hello World Bazexe!