Skip to content

Commit aa79af2

Browse files
committed
Introduce jsoo shapes
1 parent 619c098 commit aa79af2

File tree

8 files changed

+109
-23
lines changed

8 files changed

+109
-23
lines changed

src/dune_rules/jsoo/js_of_ocaml.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -279,6 +279,7 @@ module Ext = struct
279279
let exe ~mode = Mode.select ~mode ~js:".bc.js" ~wasm:".bc.wasm.js"
280280
let cmo ~mode = Mode.select ~mode ~js:".cmo.js" ~wasm:".wasmo"
281281
let cma ~mode = Mode.select ~mode ~js:".cma.js" ~wasm:".wasma"
282+
let js_shape = ".jsoo-shape"
282283
let runtime ~mode = Mode.select ~mode ~js:".bc.runtime.js" ~wasm:".bc.runtime.wasma"
283284
let wasm_dir = ".bc.wasm.assets"
284285
end

src/dune_rules/jsoo/js_of_ocaml.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -114,6 +114,7 @@ module Ext : sig
114114
val cma : mode:Mode.t -> t
115115
val runtime : mode:Mode.t -> t
116116
val wasm_dir : t
117+
val js_shape : t
117118
end
118119

119120
module Env : sig

src/dune_rules/jsoo/jsoo_rules.ml

Lines changed: 89 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -213,6 +213,27 @@ let wasmoo ~dir sctx =
213213
Super_context.resolve_program sctx ~dir ~loc:None "wasm_of_ocaml"
214214
;;
215215

216+
let jsoo_memo ~dir sctx =
217+
Super_context.resolve_program_memo
218+
sctx
219+
~dir
220+
~loc:None
221+
~where:Original_path
222+
~hint:install_jsoo_hint
223+
"js_of_ocaml"
224+
;;
225+
226+
let jsoo_has_shapes ~dir sctx =
227+
let* jsoo = jsoo_memo ~dir sctx in
228+
let+ jsoo_version = Version.jsoo_version jsoo in
229+
match jsoo_version with
230+
| Some version ->
231+
(match Version.compare version (5, 8) with
232+
| Lt -> false
233+
| Gt | Eq -> true)
234+
| None -> false
235+
;;
236+
216237
type sub_command =
217238
| Compile
218239
| Link
@@ -477,8 +498,26 @@ let link_rule
477498
~config:None
478499
;;
479500

480-
let build_cm' sctx ~dir ~in_context ~mode ~src ~target ~config ~sourcemap =
481-
let spec = Command.Args.Dep src in
501+
let build_cm' sctx ~dir ~in_context ~mode ~src ~target ~config ~shapes ~sourcemap =
502+
let spec =
503+
Command.Args.(
504+
S
505+
[ Dep src
506+
; (match shapes, (mode : Js_of_ocaml.Mode.t) with
507+
| Some shapes, JS ->
508+
S
509+
[ A "--shapes"
510+
; Hidden_targets
511+
[ Path.Build.set_extension target ~ext:Js_of_ocaml.Ext.js_shape ]
512+
; Dyn
513+
(let open Action_builder.O in
514+
let+ shapes = shapes in
515+
S (List.map shapes ~f:(fun s -> S [ A "--load"; Dep s ])))
516+
]
517+
| Some _, Wasm -> S []
518+
| None, _ -> S [])
519+
])
520+
in
482521
let flags = in_context.Js_of_ocaml.In_context.flags in
483522
js_of_ocaml_rule
484523
sctx
@@ -493,17 +532,51 @@ let build_cm' sctx ~dir ~in_context ~mode ~src ~target ~config ~sourcemap =
493532
~sourcemap
494533
;;
495534

496-
let build_cm sctx ~dir ~in_context ~mode ~src ~obj_dir ~config =
535+
let build_cm cctx ~dir ~in_context ~mode ~src ~obj_dir ~config:config_opt =
497536
let name = with_js_ext ~mode (Path.basename src) in
498-
let target = in_obj_dir ~obj_dir ~config [ name ] in
537+
let target = in_obj_dir ~obj_dir ~config:config_opt [ name ] in
538+
let sctx = Compilation_context.super_context cctx in
539+
let ctx = Super_context.context sctx |> Context.build_context in
540+
let+ jsoo_has_shapes =
541+
match mode with
542+
| JS -> jsoo_has_shapes ~dir sctx
543+
| Wasm -> Memo.return false
544+
in
545+
let shapes =
546+
if jsoo_has_shapes
547+
then
548+
Some
549+
(let open Action_builder.O in
550+
let+ libs = Resolve.Memo.read (Compilation_context.requires_link cctx)
551+
and+ config =
552+
match config_opt with
553+
| None ->
554+
let flags = in_context.Js_of_ocaml.In_context.flags in
555+
js_of_ocaml_flags sctx ~dir ~mode flags
556+
|> Action_builder.bind ~f:(fun (x : _ Js_of_ocaml.Flags.t) -> x.compile)
557+
|> Action_builder.map ~f:Config.of_flags
558+
| Some config -> Action_builder.return config
559+
in
560+
Path.build
561+
(in_build_dir
562+
ctx
563+
~config
564+
[ "stdlib"; "stdlib.cma" ^ Js_of_ocaml.Ext.js_shape ])
565+
:: List.concat_map libs ~f:(fun lib ->
566+
List.map
567+
(jsoo_archives ~mode ctx config lib)
568+
~f:(Path.set_extension ~ext:Js_of_ocaml.Ext.js_shape)))
569+
else None
570+
in
499571
build_cm'
500572
sctx
501573
~dir
502574
~in_context
503575
~mode
504576
~src
505577
~target
506-
~config:(Option.map config ~f:Action_builder.return)
578+
~shapes
579+
~config:(Option.map config_opt ~f:Action_builder.return)
507580
~sourcemap:Js_of_ocaml.Sourcemap.Inline
508581
;;
509582

@@ -514,7 +587,10 @@ let setup_separate_compilation_rules sctx components =
514587
let config = Config.of_string s_config in
515588
let pkg = Lib_name.parse_string_exn (Loc.none, s_pkg) in
516589
let ctx = Super_context.context sctx in
517-
let* installed_libs = Lib.DB.installed ctx in
590+
let* installed_libs = Lib.DB.installed ctx
591+
and* jsoo_has_shapes =
592+
jsoo_has_shapes ~dir:(Context.build_context ctx).build_dir sctx
593+
in
518594
Lib.DB.find installed_libs pkg
519595
>>= (function
520596
| None -> Memo.return ()
@@ -546,6 +622,12 @@ let setup_separate_compilation_rules sctx components =
546622
let target =
547623
in_build_dir build_context ~config [ lib_name; with_js_ext ~mode name ]
548624
in
625+
let shapes =
626+
if jsoo_has_shapes
627+
then (* FIXME: we should load shapes *)
628+
Some (Action_builder.return [])
629+
else None
630+
in
549631
build_cm'
550632
sctx
551633
~dir
@@ -555,6 +637,7 @@ let setup_separate_compilation_rules sctx components =
555637
~target
556638
~config:(Some (Action_builder.return config))
557639
~sourcemap:Js_of_ocaml.Sourcemap.Inline
640+
~shapes
558641
|> Super_context.add_rule sctx ~dir)))
559642
;;
560643

src/dune_rules/jsoo/jsoo_rules.mli

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -16,14 +16,14 @@ module Version : sig
1616
end
1717

1818
val build_cm
19-
: Super_context.t
19+
: Compilation_context.t
2020
-> dir:Path.Build.t
2121
-> in_context:Js_of_ocaml.In_context.t
2222
-> mode:Js_of_ocaml.Mode.t
2323
-> src:Path.t
2424
-> obj_dir:Path.Build.t Obj_dir.t
2525
-> config:Config.t option
26-
-> Action.Full.t Action_builder.With_targets.t
26+
-> Action.Full.t Action_builder.With_targets.t Memo.t
2727

2828
val build_exe
2929
: Compilation_context.t

src/dune_rules/lib_rules.ml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -478,7 +478,7 @@ let setup_build_archives (lib : Library.t) ~top_sorted_modules ~cctx ~expander ~
478478
let action_with_targets =
479479
List.map Jsoo_rules.Config.all ~f:(fun config ->
480480
Jsoo_rules.build_cm
481-
sctx
481+
cctx
482482
~dir
483483
~in_context:(Js_of_ocaml.Mode.Pair.select ~mode js_of_ocaml)
484484
~mode
@@ -487,6 +487,7 @@ let setup_build_archives (lib : Library.t) ~top_sorted_modules ~cctx ~expander ~
487487
~obj_dir)
488488
in
489489
Memo.parallel_iter action_with_targets ~f:(fun rule ->
490+
let* rule = rule in
490491
Super_context.add_rule sctx ~dir ~loc:lib.buildable.loc rule)))
491492
in
492493
Memo.when_

src/dune_rules/module_compilation.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -318,9 +318,9 @@ let build_module ?(force_write_cmi = false) ?(precompiled_cmi = false) cctx m =
318318
(* Build *.cmo.js / *.wasmo *)
319319
let sctx = Compilation_context.super_context cctx in
320320
let dir = Compilation_context.dir cctx in
321-
let action_with_targets =
321+
let* action_with_targets =
322322
Jsoo_rules.build_cm
323-
sctx
323+
cctx
324324
~dir
325325
~in_context
326326
~mode

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/std_exit.cmo.js
29-
js_of_ocaml .js/default/stdlib/stdlib.cma.js
30-
js_of_ocaml .b.eobjs/jsoo/b.cmo.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}
3131
js_of_ocaml b.bc.js
32-
js_of_ocaml .e.eobjs/jsoo/e.cmo.js
33-
js_of_ocaml .foo.objs/jsoo/default/foo.cma.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}
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
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
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}
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 bin/.technologic.eobjs/jsoo/z.cmo.js
25-
js_of_ocaml lib/.x.objs/jsoo/default/x.cma.js
24+
js_of_ocaml lib/.x.objs/jsoo/default/x.cma.{js,jsoo-shape}
2625
ocamlopt lib/x.cmxs
27-
js_of_ocaml bin/.technologic.eobjs/jsoo/technologic.cmo.js
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}
2828
js_of_ocaml bin/technologic.bc.js
2929
$ node ./_build/default/bin/technologic.bc.js
3030
buy it

0 commit comments

Comments
 (0)