Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension


Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
7 changes: 6 additions & 1 deletion .github/workflows/workflow.yml
Original file line number Diff line number Diff line change
Expand Up @@ -372,11 +372,16 @@ jobs:
default: "git+https://github.com/ocaml/opam-repository.git"
opam-pin: false

- name: Install Node
uses: actions/setup-node@v6
with:
node-version: latest

- name: Pin deps
run: opam pin add -n . --with-version=3.20.2+ox

- name: Install deps
run: opam install csexp pp re spawn uutf ./dune.opam
run: opam install csexp pp re spawn uutf wasm_of_ocaml-compiler ./dune.opam

- name: Build dune
run: opam exec -- make bootstrap
Expand Down
4 changes: 4 additions & 0 deletions src/dune_lang/js_of_ocaml.ml
Original file line number Diff line number Diff line change
Expand Up @@ -273,6 +273,10 @@ module In_context = struct
; sourcemap = None
}
;;

let force_whole_program_compilation x =
Mode.Pair.map ~f:(fun x -> { x with compilation_mode = Some Whole_program }) x
;;
end

module Ext = struct
Expand Down
1 change: 1 addition & 0 deletions src/dune_lang/js_of_ocaml.mli
Original file line number Diff line number Diff line change
Expand Up @@ -106,6 +106,7 @@ module In_context : sig

val make : dir:Path.Build.t -> In_buildable.t Mode.Pair.t -> t Mode.Pair.t
val default : t
val force_whole_program_compilation : t Mode.Pair.t -> t Mode.Pair.t
end

module Ext : sig
Expand Down
21 changes: 20 additions & 1 deletion src/dune_rules/exe_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -128,6 +128,25 @@ let o_files
Mode.Map.Multi.add_all o_files All extra_o_files)
;;

let js_of_ocaml_context ~dir js_of_ocaml compile_info =
let js_of_ocaml = Js_of_ocaml.In_context.make ~dir js_of_ocaml in
let+ has_parameterised_instances =
let+ requires_link = Memo.Lazy.force (Lib.Compile.requires_link compile_info) in
match Resolve.to_result requires_link with
| Error _ -> false
| Ok requires_link ->
List.exists requires_link ~f:(fun lib ->
match Lib.Parameterised.status lib with
| Not_parameterised -> false
| Complete | Partial -> true)
in
(* jsoo supports only whole program compilation of parameterised instances,
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Is this limitation permanent or will it be relaxed in a later jsoo version?

Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

It would be good to know if support is needed inside the jsoo compiler or if one just need to fix the dune rule ..

Copy link
Collaborator Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I've added some explanations in #12564 (comment) regarding the bytecode error I'm seeing when doing separate compilation in jsoo, so I think it requires an oxcaml-specific patch in jsoo before we can change the dune rules for separate compilation :)

not separated compilation. *)
if has_parameterised_instances
then Js_of_ocaml.In_context.force_whole_program_compilation js_of_ocaml
else js_of_ocaml
;;

let executables_rules
~sctx
~dir
Expand All @@ -150,7 +169,7 @@ let executables_rules
let* ocaml = Context.ocaml ctx in
let project = Scope.project scope in
let explicit_js_mode = Dune_project.explicit_js_mode project in
let js_of_ocaml = Js_of_ocaml.In_context.make ~dir exes.buildable.js_of_ocaml in
let* js_of_ocaml = js_of_ocaml_context ~dir exes.buildable.js_of_ocaml compile_info in
let* linkages =
let+ jsoo_enabled_modes =
Jsoo_rules.jsoo_enabled_modes ~expander ~dir ~in_context:js_of_ocaml
Expand Down
4 changes: 4 additions & 0 deletions test/blackbox-tests/test-cases/oxcaml/dune
Original file line number Diff line number Diff line change
Expand Up @@ -5,3 +5,7 @@
(cram
(deps helpers.sh)
(applies_to :whole_subtree))

(cram
(deps %{bin:node} %{bin:js_of_ocaml} %{bin:wasm_of_ocaml})
(applies_to parameterised-jsoo))
100 changes: 100 additions & 0 deletions test/blackbox-tests/test-cases/oxcaml/parameterised-jsoo.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,100 @@
Testing that js_of_ocaml works with the instantiation of parameterised libs.
At the moment, js_of_ocaml does not support the separate compilation of
parameterised instances, so only whole program compilation is available.

$ cat > dune-project <<EOF
> (lang dune 3.21)
> (using oxcaml 0.1)
> EOF

First define a parameter:

$ mkdir param
$ echo 'val param : string' > param/param.mli
$ cat > param/dune <<EOF
> (library_parameter (name param))
> EOF

Then an implementation of this parameter:

$ mkdir impl
$ echo 'let param = Util.util' > impl/impl.ml
$ echo 'let util = "impl"' > impl/util.ml
$ cat > impl/dune <<EOF
> (library (name impl) (implements param))
> EOF

And another implementation:

$ mkdir impl2
$ echo 'let param = "impl2"' > impl2/impl2.ml
$ cat > impl2/dune <<EOF
> (library (name impl2) (implements param))
> EOF

Then a parameterised library:

$ mkdir lib
$ echo 'let lib () = "lib(" ^ Param.param ^ ") " ^ Helper.helper' > lib/lib.ml
$ echo 'let helper = "helper(" ^ Param.param ^ ")"' > lib/helper.ml
$ cat > lib/dune <<EOF
> (library (name lib) (parameters param))
> EOF

And another parameterised library:

$ mkdir lib2
$ echo 'let lib2 () = "lib2(" ^ Lib_param.lib () ^ ", " ^ Lib_impl2.lib () ^ ")"' > lib2/lib2.ml
$ cat > lib2/dune <<EOF
> (library
> (name lib2)
> (parameters param)
> (libraries
> (instantiate lib :as lib_param)
> (instantiate lib impl2 :as lib_impl2)))
> EOF

Then an executable, with a couple more instantiations of parameterised libraries:

$ mkdir bin
$ echo 'let () = A.a (); B.b (); C.c ()' > bin/bin.ml
$ echo 'let a () = print_endline (Lib2_impl.lib2 ())' > bin/a.ml
$ echo 'let b () = print_endline (Lib2_impl2.lib2 ())' > bin/b.ml
$ echo 'let c () = print_endline (Lib_impl.lib ())' > bin/c.ml
$ cat > bin/dune <<EOF
> (executable
> (name bin)
> (modes byte js wasm)
> (libraries
> (instantiate lib2 impl :as lib2_impl)
> (instantiate lib2 impl2 :as lib2_impl2)
> (instantiate lib impl :as lib_impl)))
> EOF

$ dune exec ./bin/bin.exe
lib2(lib(impl) helper(impl), lib(impl2) helper(impl2))
lib2(lib(impl2) helper(impl2), lib(impl2) helper(impl2))
lib(impl) helper(impl)

Testing byte compilation:

$ dune exec ./bin/bin.bc
lib2(lib(impl) helper(impl), lib(impl2) helper(impl2))
lib2(lib(impl2) helper(impl2), lib(impl2) helper(impl2))
lib(impl) helper(impl)

Testing js_of_ocaml:

$ dune build ./bin/bin.bc.js
$ node _build/default/bin/bin.bc.js
lib2(lib(impl) helper(impl), lib(impl2) helper(impl2))
lib2(lib(impl2) helper(impl2), lib(impl2) helper(impl2))
lib(impl) helper(impl)

Testing wasm_of_ocaml:

$ dune build ./bin/bin.bc.wasm.js
$ node _build/default/bin/bin.bc.wasm.js
lib2(lib(impl) helper(impl), lib(impl2) helper(impl2))
lib2(lib(impl2) helper(impl2), lib(impl2) helper(impl2))
lib(impl) helper(impl)
Loading