Skip to content

Commit feb1e46

Browse files
committed
Add support for jsoo shapes
Signed-off-by: Hugo Heuzard <[email protected]>
1 parent b83bca3 commit feb1e46

File tree

4 files changed

+75
-8
lines changed

4 files changed

+75
-8
lines changed

src/dune_rules/jsoo/jsoo_rules.ml

Lines changed: 72 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -316,6 +316,15 @@ let wasmoo ~dir sctx =
316316
"wasm_of_ocaml"
317317
;;
318318

319+
let jsoo_has_shapes jsoo_version =
320+
match jsoo_version with
321+
| Some version ->
322+
(match Version.compare version (6, 1) with
323+
| Lt -> false
324+
| Gt | Eq -> true)
325+
| None -> false
326+
;;
327+
319328
type sub_command =
320329
| Compile
321330
| Link
@@ -606,8 +615,25 @@ let link_rule
606615
~sourcemap
607616
;;
608617

609-
let build_cm' sctx ~dir ~in_context ~mode ~src ~target ~config ~sourcemap =
610-
let spec = Command.Args.Dep src in
618+
let build_cm' sctx ~dir ~in_context ~mode ~src ~target ~config ~shapes ~sourcemap =
619+
let spec =
620+
Command.Args.(
621+
S
622+
[ Dep src
623+
; Dyn
624+
(let open Action_builder.O in
625+
let* jsoo_version =
626+
let* jsoo = jsoo ~dir sctx in
627+
Action_builder.of_memo @@ Version.jsoo_version jsoo
628+
in
629+
let+ shapes =
630+
match jsoo_has_shapes jsoo_version with
631+
| false -> Action_builder.return []
632+
| true -> shapes
633+
in
634+
S (List.map shapes ~f:(fun s -> S [ A "--load-shape"; Dep s ])))
635+
])
636+
in
611637
let flags = in_context.Js_of_ocaml.In_context.flags in
612638
js_of_ocaml_rule
613639
sctx
@@ -622,17 +648,35 @@ let build_cm' sctx ~dir ~in_context ~mode ~src ~target ~config ~sourcemap =
622648
~sourcemap
623649
;;
624650

625-
let build_cm sctx ~dir ~in_context ~mode ~src ~obj_dir ~config =
651+
let build_cm cctx ~dir ~in_context ~mode ~src ~obj_dir ~config:config_opt =
626652
let name = with_js_ext ~mode (Path.basename src) in
627-
let target = in_obj_dir ~obj_dir ~config [ name ] in
653+
let target = in_obj_dir ~obj_dir ~config:config_opt [ name ] in
654+
let sctx = Compilation_context.super_context cctx in
655+
let ctx = Super_context.context sctx |> Context.build_context in
656+
let shapes =
657+
let open Action_builder.O in
658+
let+ libs = Resolve.Memo.read (Compilation_context.requires_link cctx)
659+
and+ config =
660+
match config_opt with
661+
| None ->
662+
let flags = in_context.Js_of_ocaml.In_context.flags in
663+
js_of_ocaml_flags sctx ~dir ~mode flags
664+
|> Action_builder.bind ~f:(fun (x : _ Js_of_ocaml.Flags.t) -> x.compile)
665+
|> Action_builder.map ~f:Config.of_flags
666+
| Some config -> Action_builder.return config
667+
in
668+
Path.build (in_build_dir ctx ~config [ "stdlib"; with_js_ext ~mode "stdlib.cma" ])
669+
:: List.concat_map libs ~f:(fun lib -> jsoo_archives ~mode ctx config lib)
670+
in
628671
build_cm'
629672
sctx
630673
~dir
631674
~in_context
632675
~mode
633676
~src
634677
~target
635-
~config:(Option.map config ~f:Action_builder.return)
678+
~shapes
679+
~config:(Option.map config_opt ~f:Action_builder.return)
636680
~sourcemap:Js_of_ocaml.Sourcemap.Inline
637681
;;
638682

@@ -649,6 +693,11 @@ let setup_separate_compilation_rules sctx components =
649693
| None -> Memo.return ()
650694
| Some pkg ->
651695
let info = Lib.info pkg in
696+
let requires =
697+
let open Resolve.Memo.O in
698+
let* reqs = Lib.requires pkg in
699+
Lib.closure ~linking:false reqs
700+
in
652701
let lib_name = Lib_name.to_string (Lib.name pkg) in
653702
let* archives =
654703
let archives = (Lib_info.archives info).byte in
@@ -679,6 +728,23 @@ let setup_separate_compilation_rules sctx components =
679728
let target =
680729
in_build_dir build_context ~config [ lib_name; with_js_ext ~mode name ]
681730
in
731+
let shapes =
732+
let open Action_builder.O in
733+
let+ requires = Resolve.Memo.read requires in
734+
let l =
735+
List.concat_map requires ~f:(fun lib ->
736+
jsoo_archives ~mode build_context config lib)
737+
in
738+
match lib_name with
739+
| "stdlib" -> l
740+
| _ ->
741+
Path.build
742+
(in_build_dir
743+
build_context
744+
~config
745+
[ "stdlib"; with_js_ext ~mode "stdlib.cma" ])
746+
:: l
747+
in
682748
build_cm'
683749
sctx
684750
~dir
@@ -688,6 +754,7 @@ let setup_separate_compilation_rules sctx components =
688754
~target
689755
~config:(Some (Action_builder.return config))
690756
~sourcemap:Js_of_ocaml.Sourcemap.Inline
757+
~shapes
691758
|> Super_context.add_rule sctx ~dir)))
692759
;;
693760

src/dune_rules/jsoo/jsoo_rules.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,7 @@ 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

src/dune_rules/lib_rules.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -459,7 +459,7 @@ let setup_build_archives (lib : Library.t) ~top_sorted_modules ~cctx ~expander ~
459459
let action_with_targets =
460460
List.map Jsoo_rules.Config.all ~f:(fun config ->
461461
Jsoo_rules.build_cm
462-
sctx
462+
cctx
463463
~dir
464464
~in_context:
465465
(Js_of_ocaml.In_context.make ~dir lib.buildable.js_of_ocaml

src/dune_rules/module_compilation.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -320,7 +320,7 @@ let build_module ?(force_write_cmi = false) ?(precompiled_cmi = false) cctx m =
320320
let dir = Compilation_context.dir cctx in
321321
let action_with_targets =
322322
Jsoo_rules.build_cm
323-
sctx
323+
cctx
324324
~dir
325325
~in_context
326326
~mode

0 commit comments

Comments
 (0)