diff --git a/src/dune_rules/cm_files.ml b/src/dune_rules/cm_files.ml index 113955fc74a0..8b6013915259 100644 --- a/src/dune_rules/cm_files.ml +++ b/src/dune_rules/cm_files.ml @@ -40,6 +40,11 @@ let top_sorted_cms t ~mode = Obj_dir.Module.L.cm_files t.obj_dir ~kind:(Ocaml kind) modules) ;; +let top_sorted_modules t = + Action_builder.map t.top_sorted_modules ~f:(fun modules -> + filter_excluded_modules t modules) +;; + let top_sorted_objects_and_cms t ~mode = Action_builder.map t.top_sorted_modules ~f:(fun modules -> let modules = filter_excluded_modules t modules in diff --git a/src/dune_rules/cm_files.mli b/src/dune_rules/cm_files.mli index be3cc69b33d6..62ea0f532399 100644 --- a/src/dune_rules/cm_files.mli +++ b/src/dune_rules/cm_files.mli @@ -17,4 +17,5 @@ val make val unsorted_objects_and_cms : t -> mode:Mode.t -> Path.t list val top_sorted_cms : t -> mode:Mode.t -> Path.t list Action_builder.t +val top_sorted_modules : t -> Module.t list Action_builder.t val top_sorted_objects_and_cms : t -> mode:Mode.t -> Path.t list Action_builder.t diff --git a/src/dune_rules/dune_file.mli b/src/dune_rules/dune_file.mli index 11a27a76c725..d0ac3c108629 100644 --- a/src/dune_rules/dune_file.mli +++ b/src/dune_rules/dune_file.mli @@ -200,6 +200,7 @@ module Library : sig declared in. *) val archive : t -> dir:Path.Build.t -> ext:string -> Path.Build.t + val archive_basename : t -> ext:string -> string val best_name : t -> Lib_name.t val is_virtual : t -> bool val is_impl : t -> bool diff --git a/src/dune_rules/jsoo/jsoo_rules.ml b/src/dune_rules/jsoo/jsoo_rules.ml index 2b5cf0c82137..c004506d5280 100644 --- a/src/dune_rules/jsoo/jsoo_rules.ml +++ b/src/dune_rules/jsoo/jsoo_rules.ml @@ -7,7 +7,7 @@ module Config : sig val path : t -> string val of_string : string -> t val of_flags : string list -> t - val to_flags : t -> string list + val to_flags : current:string list -> t -> string list end = struct type t = { js_string : bool option @@ -80,12 +80,15 @@ end = struct loop default l ;; - let to_flags t = - List.concat_map (get t) ~f:(function - | "toplevel", true -> [ "--toplevel" ] + let to_flags ~current t = + current + :: List.map (get t) ~f:(function + | "toplevel", true -> + if List.mem current "--toplevel" ~equal:String.equal then [] else [ "--toplevel" ] | "toplevel", false -> [] | name, true -> [ "--enable"; name ] | name, false -> [ "--disable"; name ]) + |> List.concat ;; end @@ -191,6 +194,12 @@ let js_of_ocaml_rule let open Memo.O in let+ jsoo = jsoo ~dir sctx and+ flags = js_of_ocaml_flags sctx ~dir flags in + let flags = + match sub_command with + | Compile -> flags.compile + | Link -> flags.link + | Build_runtime -> flags.build_runtime + in Command.run ~dir:(Path.build dir) jsoo @@ -198,18 +207,17 @@ let js_of_ocaml_rule | Compile -> S [] | Link -> A "link" | Build_runtime -> A "build-runtime") - ; Command.Args.dyn - (match sub_command with - | Compile -> flags.compile - | Link -> flags.link - | Build_runtime -> flags.build_runtime) ; (match config with - | None -> S [] + | None -> + Dyn + (Action_builder.map flags ~f:(fun flags -> + Command.Args.S (List.map flags ~f:(fun x -> Command.Args.A x)))) | Some config -> Dyn - (Action_builder.map config ~f:(fun config -> + (Action_builder.map2 flags config ~f:(fun flags config -> Command.Args.S - (List.map (Config.to_flags config) ~f:(fun x -> Command.Args.A x))))) + (List.map (Config.to_flags ~current:flags config) ~f:(fun x -> + Command.Args.A x))))) ; A "-o" ; Target target ; spec @@ -315,12 +323,13 @@ let link_rule cc ~runtime ~target ~obj_dir cm ~flags ~linkall ~link_time_code_ge let special_units = List.concat_map to_link ~f:(function | Lib_flags.Lib_and_module.Lib _lib -> [] - | Module (obj_dir, m) -> [ in_obj_dir' ~obj_dir ~config:None [ mod_name m ] ]) + | Module (obj_dir, m) -> + [ in_obj_dir' ~obj_dir ~config:(Some config) [ mod_name m ] ]) in let all_libs = List.concat_map libs ~f:(jsoo_archives ctx config) in let all_other_modules = List.map cm ~f:(fun m -> - Path.build (in_obj_dir ~obj_dir ~config:None [ mod_name m ])) + Path.build (in_obj_dir ~obj_dir ~config:(Some config) [ mod_name m ])) in let std_exit = Path.build (in_build_dir ctx ~config [ "stdlib"; "std_exit" ^ Js_of_ocaml.Ext.cmo ]) @@ -361,6 +370,33 @@ let build_cm sctx ~dir ~in_context ~src ~obj_dir ~config = ~config:(Option.map config ~f:Action_builder.return) ;; +let build_cma_js sctx ~dir ~in_context ~obj_dir ~config ~linkall:_ cm_files name = + let target = in_obj_dir ~obj_dir ~config [ name ] in + let flags = in_context.Js_of_ocaml.In_context.flags in + let modules = + let open Action_builder.O in + let+ l = Cm_files.top_sorted_modules cm_files in + let l = + List.map l ~f:(fun m -> + in_obj_dir + ~obj_dir + ~config + [ Module_name.Unique.to_string (Module.obj_name m) ^ Js_of_ocaml.Ext.cmo ] + |> Path.build) + in + l + in + js_of_ocaml_rule + sctx + ~dir + ~sub_command:Link + ~config:(Option.map config ~f:Action_builder.return) + ~flags + ~spec: + (S [ A "-a"; Dyn (Action_builder.map modules ~f:(fun x -> Command.Args.Deps x)) ]) + ~target +;; + let setup_separate_compilation_rules sctx components = match components with | _ :: _ :: _ :: _ | [] | [ _ ] -> Memo.return () diff --git a/src/dune_rules/jsoo/jsoo_rules.mli b/src/dune_rules/jsoo/jsoo_rules.mli index dcb7fa414609..6cd8600a5565 100644 --- a/src/dune_rules/jsoo/jsoo_rules.mli +++ b/src/dune_rules/jsoo/jsoo_rules.mli @@ -36,6 +36,17 @@ val build_exe -> link_time_code_gen:Link_time_code_gen_type.t Resolve.t -> unit Memo.t +val build_cma_js + : Super_context.t + -> dir:Path.Build.t + -> in_context:Js_of_ocaml.In_context.t + -> obj_dir:Path.Build.t Obj_dir.t + -> config:Config.t option + -> linkall:bool Action_builder.t + -> Cm_files.t + -> string + -> Action.Full.t Action_builder.With_targets.t Memo.t + val setup_separate_compilation_rules : Super_context.t -> string list -> unit Memo.t val runner : string val js_of_ocaml_runtest_alias : Super_context.t -> dir:Path.Build.t -> Alias.Name.t Memo.t diff --git a/src/dune_rules/lib_rules.ml b/src/dune_rules/lib_rules.ml index b362c67b72a1..eb6375342386 100644 --- a/src/dune_rules/lib_rules.ml +++ b/src/dune_rules/lib_rules.ml @@ -120,6 +120,41 @@ let build_lib ])) ;; +(* Build an OCaml library. *) +let build_js_lib + (lib : Library.t) + ~sctx + ~expander + ~flags + ~dir + ~cm_files + ~in_context + ~obj_dir + config + = + let linkall = + match lib.kind with + | Ppx_deriver _ | Ppx_rewriter _ -> Action_builder.return true + | Normal -> + let standard = Action_builder.return [] in + let open Action_builder.O in + let+ library_flags = + Expander.expand_and_eval_set expander lib.library_flags ~standard + and+ ocaml_flags = Ocaml_flags.get flags (Ocaml Byte) in + List.exists library_flags ~f:(String.equal "-linkall") + || List.exists ocaml_flags ~f:(String.equal "-linkall") + in + Jsoo_rules.build_cma_js + sctx + ~dir + ~config + ~in_context + ~obj_dir + ~linkall + cm_files + (Library.archive_basename lib ~ext:".cma.js") +;; + let gen_wrapped_compat_modules (lib : Library.t) cctx = let modules = Compilation_context.modules cctx in let wrapped_compat = Modules.wrapped_compat modules in @@ -484,20 +519,39 @@ let setup_build_archives build_lib lib ~native_archives ~dir ~sctx ~expander ~flags ~mode ~cm_files) and* () = (* Build *.cma.js *) - Memo.when_ modes.ocaml.byte (fun () -> - let src = Library.archive lib ~dir ~ext:(Mode.compiled_lib_ext Mode.Byte) in - let action_with_targets = - List.map Jsoo_rules.Config.all ~f:(fun config -> - Jsoo_rules.build_cm - sctx - ~dir - ~in_context:js_of_ocaml - ~config:(Some config) - ~src:(Path.build src) - ~obj_dir) - in - Memo.parallel_iter action_with_targets ~f:(fun rule -> - rule >>= Super_context.add_rule sctx ~dir ~loc:lib.buildable.loc)) + match `From_cmos with + | `From_cma -> + Memo.when_ modes.ocaml.byte (fun () -> + let src = Library.archive lib ~dir ~ext:(Mode.compiled_lib_ext Mode.Byte) in + let action_with_targets = + List.map Jsoo_rules.Config.all ~f:(fun config -> + Jsoo_rules.build_cm + sctx + ~dir + ~in_context:js_of_ocaml + ~config:(Some config) + ~src:(Path.build src) + ~obj_dir) + in + Memo.parallel_iter action_with_targets ~f:(fun rule -> + rule >>= Super_context.add_rule sctx ~dir ~loc:lib.buildable.loc)) + | `From_cmos -> + Memo.when_ modes.ocaml.byte (fun () -> + let action_with_targets = + List.map Jsoo_rules.Config.all ~f:(fun config -> + build_js_lib + (lib : Library.t) + ~sctx + ~expander + ~flags + ~dir + ~cm_files + ~in_context:js_of_ocaml + ~obj_dir + (Some config)) + in + Memo.parallel_iter action_with_targets ~f:(fun rule -> + rule >>= Super_context.add_rule sctx ~dir ~loc:lib.buildable.loc)) in Memo.when_ (Dynlink_supported.By_the_os.get natdynlink_supported && modes.ocaml.native) diff --git a/src/dune_rules/module_compilation.ml b/src/dune_rules/module_compilation.ml index 6544ff9a0c3e..fc88d83f5aab 100644 --- a/src/dune_rules/module_compilation.ml +++ b/src/dune_rules/module_compilation.ml @@ -315,15 +315,17 @@ let build_module ?(force_write_cmi = false) ?(precompiled_cmi = false) cctx m = let sctx = Compilation_context.super_context cctx in let dir = Compilation_context.dir cctx in let action_with_targets = - Jsoo_rules.build_cm - sctx - ~dir - ~in_context - ~src:(Path.build src) - ~obj_dir - ~config:None + List.map Jsoo_rules.Config.all ~f:(fun config -> + Jsoo_rules.build_cm + sctx + ~dir + ~in_context + ~src:(Path.build src) + ~obj_dir + ~config:(Some config)) in - action_with_targets >>= Super_context.add_rule sctx ~dir)) + Memo.parallel_iter action_with_targets ~f:(fun rule -> + rule >>= Super_context.add_rule sctx ~dir))) in Memo.when_ melange (fun () -> let* () = build_cm ~cm_kind:(Melange Cmj) ~phase:None in diff --git a/test/blackbox-tests/test-cases/jsoo/explicit-js-mode-specified.t/run.t b/test/blackbox-tests/test-cases/jsoo/explicit-js-mode-specified.t/run.t index 6b9460d9b141..8924d6250573 100644 --- a/test/blackbox-tests/test-cases/jsoo/explicit-js-mode-specified.t/run.t +++ b/test/blackbox-tests/test-cases/jsoo/explicit-js-mode-specified.t/run.t @@ -11,7 +11,7 @@ Check that .bc.js rule is generated only if js mode is used. ocamlc .b.eobjs/byte/b.{cmi,cmo,cmt} js_of_ocaml .js/default/stdlib/std_exit.cmo.js js_of_ocaml .js/default/stdlib/stdlib.cma.js - js_of_ocaml .b.eobjs/jsoo/b.cmo.js + js_of_ocaml .b.eobjs/jsoo/default/b.cmo.js js_of_ocaml b.bc.js We also check that .cmo.js rules are not generated if not specified. @@ -24,10 +24,11 @@ JS compilation of libraries is always available to avoid having to annotate every dependency of an executable. $ dune build --display short _build/default/.foo.objs/jsoo/default/foo.cma.js - ocamlc .foo.objs/byte/foo.{cmi,cmo,cmt} ocamldep .foo.objs/foo__C.impl.d + ocamlc .foo.objs/byte/foo.{cmi,cmo,cmt} + js_of_ocaml .foo.objs/jsoo/default/foo.cmo.js ocamlc .foo.objs/byte/foo__C.{cmi,cmo,cmt} - ocamlc foo.cma + js_of_ocaml .foo.objs/jsoo/default/foo__C.cmo.js js_of_ocaml .foo.objs/jsoo/default/foo.cma.js Check that js targets are attached to @all, but not for tests that do not @@ -39,10 +40,12 @@ specify js mode (#1940). js_of_ocaml .e.eobjs/jsoo/e.bc.runtime.js js_of_ocaml .js/default/stdlib/std_exit.cmo.js js_of_ocaml .js/default/stdlib/stdlib.cma.js - js_of_ocaml .b.eobjs/jsoo/b.cmo.js + js_of_ocaml .foo.objs/jsoo/default/foo.cmo.js + js_of_ocaml .b.eobjs/jsoo/default/b.cmo.js + js_of_ocaml .foo.objs/jsoo/default/foo__C.cmo.js js_of_ocaml b.bc.js js_of_ocaml .foo.objs/jsoo/default/foo.cma.js - js_of_ocaml .e.eobjs/jsoo/e.cmo.js + js_of_ocaml .e.eobjs/jsoo/default/e.cmo.js js_of_ocaml e.bc.js Check that building a JS-enabled executable that depends on a library works. @@ -56,8 +59,9 @@ Check that building a JS-enabled executable that depends on a library works. js_of_ocaml .js/default/stdlib/std_exit.cmo.js js_of_ocaml .js/default/stdlib/stdlib.cma.js ocamlc .foo.objs/byte/foo__C.{cmi,cmo,cmt} + js_of_ocaml .foo.objs/jsoo/default/foo.cmo.js ocamlc .e.eobjs/byte/e.{cmi,cmo,cmt} - ocamlc foo.cma - js_of_ocaml .e.eobjs/jsoo/e.cmo.js + js_of_ocaml .foo.objs/jsoo/default/foo__C.cmo.js + js_of_ocaml .e.eobjs/jsoo/default/e.cmo.js js_of_ocaml .foo.objs/jsoo/default/foo.cma.js js_of_ocaml e.bc.js diff --git a/test/blackbox-tests/test-cases/jsoo/jsoo-config.t/run.t b/test/blackbox-tests/test-cases/jsoo/jsoo-config.t/run.t index 95d85a917c1e..f6b532dc84a2 100644 --- a/test/blackbox-tests/test-cases/jsoo/jsoo-config.t/run.t +++ b/test/blackbox-tests/test-cases/jsoo/jsoo-config.t/run.t @@ -1,6 +1,34 @@ tests js_of_ocaml conigs - $ dune build bin/bin1.bc.js bin/bin2.bc.js bin/bin3.bc.js + $ dune build bin/bin1.bc.js bin/bin2.bc.js bin/bin3.bc.js --display short + js_of_ocaml bin/.bin1.eobjs/jsoo/bin1.bc.runtime.js + js_of_ocaml bin/.bin2.eobjs/jsoo/bin2.bc.runtime.js + js_of_ocaml bin/.bin3.eobjs/jsoo/bin3.bc.runtime.js + js_of_ocaml .js/use-js-string/stdlib/std_exit.cmo.js + js_of_ocaml .js/use-js-string/stdlib/stdlib.cma.js + ocamlc lib/.library1.objs/byte/library1.{cmi,cmo,cmt} + js_of_ocaml .js/!use-js-string/stdlib/std_exit.cmo.js + js_of_ocaml .js/!use-js-string/stdlib/stdlib.cma.js + js_of_ocaml .js/default/stdlib/std_exit.cmo.js + js_of_ocaml .js/default/stdlib/stdlib.cma.js + ocamlc bin/.bin1.eobjs/byte/dune__exe__Bin1.{cmi,cmti} + js_of_ocaml lib/.library1.objs/jsoo/use-js-string/library1.cmo.js + ocamlc bin/.bin2.eobjs/byte/dune__exe__Bin2.{cmi,cmti} + js_of_ocaml lib/.library1.objs/jsoo/!use-js-string/library1.cmo.js + js_of_ocaml lib/.library1.objs/jsoo/default/library1.cmo.js + ocamlc bin/.bin3.eobjs/byte/dune__exe__Bin3.{cmi,cmti} + ocamlc bin/.bin1.eobjs/byte/dune__exe__Bin1.{cmo,cmt} + js_of_ocaml lib/.library1.objs/jsoo/use-js-string/library1.cma.js + ocamlc bin/.bin2.eobjs/byte/dune__exe__Bin2.{cmo,cmt} + js_of_ocaml lib/.library1.objs/jsoo/!use-js-string/library1.cma.js + js_of_ocaml lib/.library1.objs/jsoo/default/library1.cma.js + ocamlc bin/.bin3.eobjs/byte/dune__exe__Bin3.{cmo,cmt} + js_of_ocaml bin/.bin1.eobjs/jsoo/use-js-string/dune__exe__Bin1.cmo.js + js_of_ocaml bin/.bin2.eobjs/jsoo/!use-js-string/dune__exe__Bin2.cmo.js + js_of_ocaml bin/.bin3.eobjs/jsoo/default/dune__exe__Bin3.cmo.js + js_of_ocaml bin/bin1.bc.js + js_of_ocaml bin/bin2.bc.js + js_of_ocaml bin/bin3.bc.js $ node _build/default/bin/bin1.bc.js Hello bin1 Hi library1 diff --git a/test/blackbox-tests/test-cases/jsoo/no-check-prim.t/run.t b/test/blackbox-tests/test-cases/jsoo/no-check-prim.t/run.t index 33fc4afab30e..78af37931ae7 100644 --- a/test/blackbox-tests/test-cases/jsoo/no-check-prim.t/run.t +++ b/test/blackbox-tests/test-cases/jsoo/no-check-prim.t/run.t @@ -14,17 +14,20 @@ Compilation using jsoo js_of_ocaml .js/default/js_of_ocaml/js_of_ocaml.cma.js js_of_ocaml .js/default/stdlib/std_exit.cmo.js js_of_ocaml .js/default/stdlib/stdlib.cma.js + js_of_ocaml lib/.x.objs/jsoo/default/x__.cmo.js ocamlopt lib/.x.objs/native/x__Y.{cmx,o} ocamlc lib/.x.objs/byte/x.{cmi,cmo,cmt} + js_of_ocaml lib/.x.objs/jsoo/default/x__Y.cmo.js ocamlopt lib/.x.objs/native/x.{cmx,o} ocamlc bin/.technologic.eobjs/byte/z.{cmi,cmo,cmt} ocamlc lib/x.cma + js_of_ocaml lib/.x.objs/jsoo/default/x.cmo.js ocamlopt lib/x.{a,cmxa} ocamlc bin/.technologic.eobjs/byte/technologic.{cmi,cmo,cmt} - js_of_ocaml bin/.technologic.eobjs/jsoo/z.cmo.js + js_of_ocaml bin/.technologic.eobjs/jsoo/default/z.cmo.js js_of_ocaml lib/.x.objs/jsoo/default/x.cma.js ocamlopt lib/x.cmxs - js_of_ocaml bin/.technologic.eobjs/jsoo/technologic.cmo.js + js_of_ocaml bin/.technologic.eobjs/jsoo/default/technologic.cmo.js js_of_ocaml bin/technologic.bc.js $ node ./_build/default/bin/technologic.bc.js buy it diff --git a/test/blackbox-tests/test-cases/jsoo/public-libs.t/run.t b/test/blackbox-tests/test-cases/jsoo/public-libs.t/run.t index bb44601c9c9e..c7908d2b2ed8 100644 --- a/test/blackbox-tests/test-cases/jsoo/public-libs.t/run.t +++ b/test/blackbox-tests/test-cases/jsoo/public-libs.t/run.t @@ -8,10 +8,11 @@ Compilation of libraries with pulic-names ocamlc a/a.cma js_of_ocaml .js/default/stdlib/std_exit.cmo.js js_of_ocaml .js/default/stdlib/stdlib.cma.js + js_of_ocaml a/.a.objs/jsoo/default/a.cmo.js ocamlopt a/a.{a,cmxa} ocamlc b/.main.eobjs/byte/dune__exe__Main.{cmo,cmt} js_of_ocaml a/.a.objs/jsoo/default/a.cma.js ocamlopt a/a.cmxs ocamlc b/main.bc-for-jsoo - js_of_ocaml b/.main.eobjs/jsoo/dune__exe__Main.cmo.js + js_of_ocaml b/.main.eobjs/jsoo/default/dune__exe__Main.cmo.js js_of_ocaml b/main.bc.js