Skip to content

Commit d15c57b

Browse files
committed
fix(oxcaml): js_of_ocaml compile whole for parameterised instances
Signed-off-by: Arthur Wendling <[email protected]>
1 parent c7c8cb1 commit d15c57b

File tree

5 files changed

+127
-1
lines changed

5 files changed

+127
-1
lines changed

src/dune_lang/js_of_ocaml.ml

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -273,6 +273,10 @@ module In_context = struct
273273
; sourcemap = None
274274
}
275275
;;
276+
277+
let force_whole_program_compilation x =
278+
Mode.Pair.map ~f:(fun x -> { x with compilation_mode = Some Whole_program }) x
279+
;;
276280
end
277281

278282
module Ext = struct

src/dune_lang/js_of_ocaml.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -106,6 +106,7 @@ module In_context : sig
106106

107107
val make : dir:Path.Build.t -> In_buildable.t Mode.Pair.t -> t Mode.Pair.t
108108
val default : t
109+
val force_whole_program_compilation : t Mode.Pair.t -> t Mode.Pair.t
109110
end
110111

111112
module Ext : sig

src/dune_rules/exe_rules.ml

Lines changed: 20 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -128,6 +128,25 @@ let o_files
128128
Mode.Map.Multi.add_all o_files All extra_o_files)
129129
;;
130130

131+
let js_of_ocaml_context ~dir js_of_ocaml compile_info =
132+
let js_of_ocaml = Js_of_ocaml.In_context.make ~dir js_of_ocaml in
133+
let+ has_parameterised_instances =
134+
let+ requires_link = Memo.Lazy.force (Lib.Compile.requires_link compile_info) in
135+
match Resolve.to_result requires_link with
136+
| Error _ -> false
137+
| Ok requires_link ->
138+
List.exists requires_link ~f:(fun lib ->
139+
match Lib.Parameterised.status lib with
140+
| Not_parameterised -> false
141+
| Complete | Partial -> true)
142+
in
143+
(* jsoo supports only whole program compilation of parameterised instances,
144+
not separated compilation. *)
145+
if has_parameterised_instances
146+
then Js_of_ocaml.In_context.force_whole_program_compilation js_of_ocaml
147+
else js_of_ocaml
148+
;;
149+
131150
let executables_rules
132151
~sctx
133152
~dir
@@ -150,7 +169,7 @@ let executables_rules
150169
let* ocaml = Context.ocaml ctx in
151170
let project = Scope.project scope in
152171
let explicit_js_mode = Dune_project.explicit_js_mode project in
153-
let js_of_ocaml = Js_of_ocaml.In_context.make ~dir exes.buildable.js_of_ocaml in
172+
let* js_of_ocaml = js_of_ocaml_context ~dir exes.buildable.js_of_ocaml compile_info in
154173
let* linkages =
155174
let+ jsoo_enabled_modes =
156175
Jsoo_rules.jsoo_enabled_modes ~expander ~dir ~in_context:js_of_ocaml

test/blackbox-tests/test-cases/oxcaml/dune

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,3 +5,7 @@
55
(cram
66
(deps helpers.sh)
77
(applies_to :whole_subtree))
8+
9+
(cram
10+
(deps %{bin:node} %{bin:js_of_ocaml} %{bin:wasm_of_ocaml})
11+
(applies_to parameterised-jsoo))
Lines changed: 98 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,98 @@
1+
Testing that js_of_ocaml works with the instantiation of parameterised libs.
2+
At the moment, js_of_ocaml does not support the separate compilation of
3+
parameterised instances, so only whole program compilation is available.
4+
5+
$ cat > dune-project <<EOF
6+
> (lang dune 3.21)
7+
> (using oxcaml 0.1)
8+
> EOF
9+
10+
First define a parameter:
11+
12+
$ mkdir param
13+
$ echo 'val param : string' > param/param.mli
14+
$ cat > param/dune <<EOF
15+
> (library_parameter (name param))
16+
> EOF
17+
18+
Then an implementation of this parameter:
19+
20+
$ mkdir impl
21+
$ echo 'let param = Util.util' > impl/impl.ml
22+
$ echo 'let util = "impl"' > impl/util.ml
23+
$ cat > impl/dune <<EOF
24+
> (library (name impl) (implements param))
25+
> EOF
26+
27+
And another implementation:
28+
29+
$ mkdir impl2
30+
$ echo 'let param = "impl2"' > impl2/impl2.ml
31+
$ cat > impl2/dune <<EOF
32+
> (library (name impl2) (implements param))
33+
> EOF
34+
35+
Then a parameterised library:
36+
37+
$ mkdir lib
38+
$ echo 'let lib () = "lib(" ^ Param.param ^ ") " ^ Helper.helper' > lib/lib.ml
39+
$ echo 'let helper = "helper(" ^ Param.param ^ ")"' > lib/helper.ml
40+
$ cat > lib/dune <<EOF
41+
> (library (name lib) (parameters param))
42+
> EOF
43+
44+
And another parameterised library:
45+
46+
$ mkdir lib2
47+
$ echo 'let lib2 () = "lib2(" ^ Lib_param.lib () ^ ", " ^ Lib_impl2.lib () ^ ")"' > lib2/lib2.ml
48+
$ cat > lib2/dune <<EOF
49+
> (library
50+
> (name lib2)
51+
> (parameters param)
52+
> (libraries (lib :as lib_param) (lib impl2 :as lib_impl2)))
53+
> EOF
54+
55+
Then an executable, with a couple more instantiations of parameterised libraries:
56+
57+
$ mkdir bin
58+
$ echo 'let () = A.a (); B.b (); C.c ()' > bin/bin.ml
59+
$ echo 'let a () = print_endline (Lib2_impl.lib2 ())' > bin/a.ml
60+
$ echo 'let b () = print_endline (Lib2_impl2.lib2 ())' > bin/b.ml
61+
$ echo 'let c () = print_endline (Lib_impl.lib ())' > bin/c.ml
62+
$ cat > bin/dune <<EOF
63+
> (executable
64+
> (name bin)
65+
> (modes byte js wasm)
66+
> (libraries
67+
> (lib2 impl :as lib2_impl)
68+
> (lib2 impl2 :as lib2_impl2)
69+
> (lib impl :as lib_impl)))
70+
> EOF
71+
72+
$ dune exec ./bin/bin.exe
73+
lib2(lib(impl) helper(impl), lib(impl2) helper(impl2))
74+
lib2(lib(impl2) helper(impl2), lib(impl2) helper(impl2))
75+
lib(impl) helper(impl)
76+
77+
Testing byte compilation:
78+
79+
$ dune exec ./bin/bin.bc
80+
lib2(lib(impl) helper(impl), lib(impl2) helper(impl2))
81+
lib2(lib(impl2) helper(impl2), lib(impl2) helper(impl2))
82+
lib(impl) helper(impl)
83+
84+
Testing js_of_ocaml:
85+
86+
$ dune build ./bin/bin.bc.js
87+
$ node _build/default/bin/bin.bc.js
88+
lib2(lib(impl) helper(impl), lib(impl2) helper(impl2))
89+
lib2(lib(impl2) helper(impl2), lib(impl2) helper(impl2))
90+
lib(impl) helper(impl)
91+
92+
Testing wasm_of_ocaml:
93+
94+
$ dune build ./bin/bin.bc.wasm.js
95+
$ node _build/default/bin/bin.bc.wasm.js
96+
lib2(lib(impl) helper(impl), lib(impl2) helper(impl2))
97+
lib2(lib(impl2) helper(impl2), lib(impl2) helper(impl2))
98+
lib(impl) helper(impl)

0 commit comments

Comments
 (0)