Skip to content

Commit 231bc20

Browse files
committed
refactor
1 parent a7dfc66 commit 231bc20

File tree

3 files changed

+59
-83
lines changed
  • src/dune_rules/jsoo
  • test/blackbox-tests/test-cases/jsoo
    • explicit-js-mode-specified.t
    • no-check-prim.t

3 files changed

+59
-83
lines changed

src/dune_rules/jsoo/jsoo_rules.ml

Lines changed: 47 additions & 71 deletions
Original file line numberDiff line numberDiff line change
@@ -316,25 +316,14 @@ let wasmoo ~dir sctx =
316316
"wasm_of_ocaml"
317317
;;
318318

319-
let jsoo_memo ~dir sctx =
320-
Super_context.resolve_program_memo
321-
sctx
322-
~dir
323-
~loc:None
324-
~where:Original_path
325-
~hint:install_jsoo_hint
326-
"js_of_ocaml"
327-
;;
328-
329-
let jsoo_has_shapes ~dir sctx =
330-
let* jsoo = jsoo_memo ~dir sctx in
331-
let+ jsoo_version = Version.jsoo_version jsoo in
332-
match jsoo_version with
333-
| Some version ->
334-
(match Version.compare version (6, 0) with
319+
let jsoo_has_shapes (mode : Js_of_ocaml.Mode.t) jsoo_version =
320+
match mode, jsoo_version with
321+
| JS, Some version ->
322+
(match Version.compare version (6, 1) with
335323
| Lt -> false
336324
| Gt | Eq -> true)
337-
| None -> false
325+
| Wasm, Some _version -> false
326+
| _, None -> false
338327
;;
339328

340329
type sub_command =
@@ -632,22 +621,18 @@ let build_cm' sctx ~dir ~in_context ~mode ~src ~target ~config ~shapes ~sourcema
632621
Command.Args.(
633622
S
634623
[ Dep src
635-
; (match shapes with
636-
| Some shapes ->
637-
S
638-
[ Dyn
639-
(let open Action_builder.O in
640-
let* has_shape = Action_builder.of_memo (jsoo_has_shapes ~dir sctx) in
641-
match has_shape with
642-
| false -> Action_builder.return (S [])
643-
| true ->
644-
let+ shapes = shapes in
645-
S
646-
[ S [ A "--write-shape" ]
647-
; S (List.map shapes ~f:(fun s -> S [ A "--load-shape"; Dep s ]))
648-
])
649-
]
650-
| None -> S [])
624+
; Dyn
625+
(let open Action_builder.O in
626+
let* jsoo_version =
627+
let* jsoo = jsoo ~dir sctx in
628+
Action_builder.of_memo @@ Version.jsoo_version jsoo
629+
in
630+
let+ shapes =
631+
match jsoo_has_shapes mode jsoo_version with
632+
| false -> Action_builder.return []
633+
| true -> shapes
634+
in
635+
S (List.map shapes ~f:(fun s -> S [ A "--load-shape"; Dep s ])))
651636
])
652637
in
653638
let flags = in_context.Js_of_ocaml.In_context.flags in
@@ -670,24 +655,19 @@ let build_cm cctx ~dir ~in_context ~mode ~src ~obj_dir ~config:config_opt =
670655
let sctx = Compilation_context.super_context cctx in
671656
let ctx = Super_context.context sctx |> Context.build_context in
672657
let shapes =
673-
match mode with
674-
| JS ->
675-
Some
676-
(let open Action_builder.O in
677-
let+ libs = Resolve.Memo.read (Compilation_context.requires_link cctx)
678-
and+ config =
679-
match config_opt with
680-
| None ->
681-
let flags = in_context.Js_of_ocaml.In_context.flags in
682-
js_of_ocaml_flags sctx ~dir ~mode flags
683-
|> Action_builder.bind ~f:(fun (x : _ Js_of_ocaml.Flags.t) -> x.compile)
684-
|> Action_builder.map ~f:Config.of_flags
685-
| Some config -> Action_builder.return config
686-
in
687-
Path.build
688-
(in_build_dir ctx ~config [ "stdlib"; with_js_ext ~mode "stdlib.cma" ])
689-
:: List.concat_map libs ~f:(fun lib -> jsoo_archives ~mode ctx config lib))
690-
| Wasm -> None
658+
let open Action_builder.O in
659+
let+ libs = Resolve.Memo.read (Compilation_context.requires_link cctx)
660+
and+ config =
661+
match config_opt with
662+
| None ->
663+
let flags = in_context.Js_of_ocaml.In_context.flags in
664+
js_of_ocaml_flags sctx ~dir ~mode flags
665+
|> Action_builder.bind ~f:(fun (x : _ Js_of_ocaml.Flags.t) -> x.compile)
666+
|> Action_builder.map ~f:Config.of_flags
667+
| Some config -> Action_builder.return config
668+
in
669+
Path.build (in_build_dir ctx ~config [ "stdlib"; with_js_ext ~mode "stdlib.cma" ])
670+
:: List.concat_map libs ~f:(fun lib -> jsoo_archives ~mode ctx config lib)
691671
in
692672
build_cm'
693673
sctx
@@ -736,7 +716,7 @@ let setup_separate_compilation_rules sctx components =
736716
in
737717
archive "stdlib.cma" :: archive "std_exit.cmo" :: archives
738718
| _ -> Memo.return archives
739-
and* requires = Resolve.Memo.read_memo requires in
719+
in
740720
Memo.parallel_iter Js_of_ocaml.Mode.all ~f:(fun mode ->
741721
Memo.parallel_iter archives ~f:(fun fn ->
742722
let build_context = Context.build_context ctx in
@@ -750,25 +730,21 @@ let setup_separate_compilation_rules sctx components =
750730
in_build_dir build_context ~config [ lib_name; with_js_ext ~mode name ]
751731
in
752732
let shapes =
753-
match mode with
754-
| JS ->
755-
let l =
756-
List.concat_map requires ~f:(fun lib ->
757-
jsoo_archives ~mode build_context config lib)
758-
in
759-
let l =
760-
match lib_name with
761-
| "stdlib" -> l
762-
| _ ->
763-
Path.build
764-
(in_build_dir
765-
build_context
766-
~config
767-
[ "stdlib"; with_js_ext ~mode "stdlib.cma" ])
768-
:: l
769-
in
770-
Some (Action_builder.return l)
771-
| Wasm -> None
733+
let open Action_builder.O in
734+
let+ requires = Resolve.Memo.read requires in
735+
let l =
736+
List.concat_map requires ~f:(fun lib ->
737+
jsoo_archives ~mode build_context config lib)
738+
in
739+
match lib_name with
740+
| "stdlib" -> l
741+
| _ ->
742+
Path.build
743+
(in_build_dir
744+
build_context
745+
~config
746+
[ "stdlib"; with_js_ext ~mode "stdlib.cma" ])
747+
:: l
772748
in
773749
build_cm'
774750
sctx

test/blackbox-tests/test-cases/jsoo/explicit-js-mode-specified.t/run.t

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -25,12 +25,12 @@ specify js mode (#1940).
2525
$ dune build --display short @@all 2>&1 | grep js_of_ocaml
2626
js_of_ocaml .b.eobjs/jsoo/b.bc.runtime.js
2727
js_of_ocaml .e.eobjs/jsoo/e.bc.runtime.js
28-
js_of_ocaml .js/default/stdlib/stdlib.cma.{js,jsoo-shape}
29-
js_of_ocaml .js/default/stdlib/std_exit.cmo.{js,jsoo-shape}
30-
js_of_ocaml .b.eobjs/jsoo/b.cmo.{js,jsoo-shape}
28+
js_of_ocaml .js/default/stdlib/std_exit.cmo.js
29+
js_of_ocaml .js/default/stdlib/stdlib.cma.js
30+
js_of_ocaml .b.eobjs/jsoo/b.cmo.js
3131
js_of_ocaml b.bc.js
32-
js_of_ocaml .foo.objs/jsoo/default/foo.cma.{js,jsoo-shape}
33-
js_of_ocaml .e.eobjs/jsoo/e.cmo.{js,jsoo-shape}
32+
js_of_ocaml .e.eobjs/jsoo/e.cmo.js
33+
js_of_ocaml .foo.objs/jsoo/default/foo.cma.js
3434
js_of_ocaml e.bc.js
3535

3636
Check that building a JS-enabled executable that depends on a library works.

test/blackbox-tests/test-cases/jsoo/no-check-prim.t/run.t

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -10,21 +10,21 @@ Compilation using jsoo
1010
ocamldep bin/.technologic.eobjs/z.impl.d
1111
ocamlopt lib/.x.objs/native/x__.{cmx,o}
1212
ocamlc lib/.x.objs/byte/x__Y.{cmi,cmo,cmt}
13-
js_of_ocaml .js/default/js_of_ocaml-compiler.runtime/jsoo_runtime.cma.{js,jsoo-shape}
14-
js_of_ocaml .js/default/js_of_ocaml/js_of_ocaml.cma.{js,jsoo-shape}
15-
js_of_ocaml .js/default/stdlib/std_exit.cmo.{js,jsoo-shape}
16-
js_of_ocaml .js/default/stdlib/stdlib.cma.{js,jsoo-shape}
13+
js_of_ocaml .js/default/js_of_ocaml-compiler.runtime/jsoo_runtime.cma.js
14+
js_of_ocaml .js/default/js_of_ocaml/js_of_ocaml.cma.js
15+
js_of_ocaml .js/default/stdlib/std_exit.cmo.js
16+
js_of_ocaml .js/default/stdlib/stdlib.cma.js
1717
ocamlopt lib/.x.objs/native/x__Y.{cmx,o}
1818
ocamlc lib/.x.objs/byte/x.{cmi,cmo,cmt}
1919
ocamlopt lib/.x.objs/native/x.{cmx,o}
2020
ocamlc bin/.technologic.eobjs/byte/z.{cmi,cmo,cmt}
2121
ocamlc lib/x.cma
2222
ocamlopt lib/x.{a,cmxa}
2323
ocamlc bin/.technologic.eobjs/byte/technologic.{cmi,cmo,cmt}
24-
js_of_ocaml lib/.x.objs/jsoo/default/x.cma.{js,jsoo-shape}
24+
js_of_ocaml bin/.technologic.eobjs/jsoo/z.cmo.js
25+
js_of_ocaml lib/.x.objs/jsoo/default/x.cma.js
2526
ocamlopt lib/x.cmxs
26-
js_of_ocaml bin/.technologic.eobjs/jsoo/technologic.cmo.{js,jsoo-shape}
27-
js_of_ocaml bin/.technologic.eobjs/jsoo/z.cmo.{js,jsoo-shape}
27+
js_of_ocaml bin/.technologic.eobjs/jsoo/technologic.cmo.js
2828
js_of_ocaml bin/technologic.bc.js
2929
$ node ./_build/default/bin/technologic.bc.js
3030
buy it

0 commit comments

Comments
 (0)