Skip to content

Commit

Permalink
Jsoo: make dune aware of sourcemap generation (#10777)
Browse files Browse the repository at this point in the history
* Jsoo: new test case for jsoo
* Jsoo: make dune aware of sourcemap
* fix parsing of sourcemap

Signed-off-by: Hugo Heuzard <hugo.heuzard@gmail.com>
  • Loading branch information
hhugo authored Aug 4, 2024
1 parent 6de363f commit 16328a3
Show file tree
Hide file tree
Showing 15 changed files with 224 additions and 57 deletions.
5 changes: 5 additions & 0 deletions doc/changes/10777.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
- New option to control jsoo sourcemap generation in env and executable stanza
(@hhugo, #10777)

- One can now control jsoo compilation_mode inside an executable stanza
(@hhugo, #10777)
19 changes: 14 additions & 5 deletions doc/jsoo.rst
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ translating OCaml bytecode to JS files. The compiler can be installed with opam:
Compiling to JS
===============

Dune has full support building Js_of_ocaml libraries and executables transparently.
Dune has full support building js_of_ocaml libraries and executables transparently.
There's no need to customize or enable anything to compile OCaml
libraries/executables to JS.

Expand Down Expand Up @@ -46,7 +46,7 @@ And then request the ``.js`` target:
Similar targets are created for libraries, but we recommend sticking to the
executable targets.

If you're using the Js_of_ocaml syntax extension, you must remember to add the
If you're using the js_of_ocaml syntax extension, you must remember to add the
appropriate PPX in the ``preprocess`` field:

.. code:: dune
Expand All @@ -62,7 +62,7 @@ Separate Compilation
Dune supports two modes of compilation:

- Direct compilation of a bytecode program to JavaScript. This mode allows
Js_of_ocaml to perform whole-program deadcode elimination and whole-program
js_of_ocaml to perform whole-program deadcode elimination and whole-program
inlining.

- Separate compilation, where compilation units are compiled to JavaScript
Expand All @@ -71,7 +71,16 @@ Dune supports two modes of compilation:

The separate compilation mode will be selected when the build profile
is ``dev``, which is the default. It can also be explicitly specified
in an ``env`` stanza. See :doc:`/reference/dune/env` for more
information.
in an ``env`` stanza (see :doc:`/reference/dune/env`) or per executable
inside ``(js_of_ocaml (compilation_mode ...))`` (see :doc:`/reference/dune/executable`)

Sourcemap
=========

Js_of_ocaml can generate sourcemap for the generated JavaScript file.
It can either embed it at the end of the ``.js`` file or write it to separate file.
By default, it is inlined when using the ``dev`` build profile and is not generated otherwise.
The behavior can explicitly be specified in an ``env`` stanza (see :doc:`/reference/dune/env`)
or per executable inside ``(js_of_ocaml (sourcemap ...))`` (see :doc:`/reference/dune/executable`)

.. _js_of_ocaml: http://ocsigen.org/js_of_ocaml/
3 changes: 3 additions & 0 deletions doc/reference/dune/env.rst
Original file line number Diff line number Diff line change
Expand Up @@ -45,6 +45,9 @@ Fields supported in ``<settings>`` are:
compilation or not where ``<mode>`` is either ``whole_program`` or
``separate``.

- ``(js_of_ocaml (sourcemap <mode>))`` controls whether to generate sourcemap
or not where ``<mode>`` is either ``no``, ``file`` (to generate sourcemap in a ``.map`` file next the the generated javascript file) or ``inline`` (to inline the sourcemap at the end of the generated JavaScript file).

- ``(js_of_ocaml (runtest_alias <alias-name>))`` specifies the alias under which
:ref:`inline_tests` and tests (:ref:`tests-stanza`) run for the `js` mode.

Expand Down
12 changes: 9 additions & 3 deletions doc/reference/dune/executable.rst
Original file line number Diff line number Diff line change
Expand Up @@ -242,7 +242,7 @@ contains C stubs you may want to use ``(modes exe)``.
js_of_ocaml
~~~~~~~~~~~

In ``library`` and ``executables`` stanzas, you can specify ``js_of_ocaml``
In ``library`` and ``executable`` stanzas, you can specify ``js_of_ocaml``
options using ``(js_of_ocaml (<js_of_ocaml-options>))``.

``<js_of_ocaml-options>`` are all optional:
Expand All @@ -259,10 +259,16 @@ options using ``(js_of_ocaml (<js_of_ocaml-options>))``.
- ``(javascript_files (<files-list>))`` to specify ``js_of_ocaml`` JavaScript
runtime files.

- ``(compilation_mode <mode>)`` where ``<mode>>`` is either ``whole_program`` or ``separate``.
This is only available inside ``executable`` stanzas.

- ``(sourcemap <config>)`` where ``<config>>`` is one of ``no``, ``file`` or ``inline``.
This is only available inside ``executable`` stanzas.

``<flags>`` is specified in the :doc:`/reference/ordered-set-language`.

The default value for ``(flags ...)`` depends on the selected build profile. The
build profile ``dev`` (the default) will enable sourcemap and the pretty
The default values for ``flags``, ``compilation_mode`` and ``sourcemap`` depend on the selected build profile. The
build profile ``dev`` (the default) will enable inline sourcemap, separate compilation and pretty
JavaScript output.

See :ref:`jsoo` for more information.
Expand Down
126 changes: 95 additions & 31 deletions src/dune_rules/jsoo/js_of_ocaml.ml
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,23 @@ end

let field_oslu name = Ordered_set_lang.Unexpanded.field name

module Sourcemap = struct
type t =
| No
| Inline
| File

let decode = enum [ "no", No; "inline", Inline; "file", File ]

let equal x y =
match x, y with
| No, No -> true
| Inline, Inline -> true
| File, File -> true
| No, _ | Inline, _ | File, _ -> false
;;
end

module Flags = struct
type 'flags t =
{ build_runtime : 'flags
Expand All @@ -38,11 +55,7 @@ module Flags = struct

let default ~profile =
if Profile.is_dev profile
then
{ build_runtime = [ "--pretty"; "--source-map-inline" ]
; compile = [ "--pretty"; "--source-map-inline" ]
; link = [ "--source-map-inline" ]
}
then { build_runtime = [ "--pretty" ]; compile = [ "--pretty" ]; link = [] }
else empty
;;

Expand Down Expand Up @@ -87,13 +100,31 @@ module Flags = struct
;;
end

module Compilation_mode = struct
type t =
| Whole_program
| Separate_compilation

let decode = enum [ "whole_program", Whole_program; "separate", Separate_compilation ]

let equal x y =
match x, y with
| Separate_compilation, Separate_compilation -> true
| Whole_program, Whole_program -> true
| Separate_compilation, _ -> false
| Whole_program, _ -> false
;;
end

module In_buildable = struct
type t =
{ flags : Ordered_set_lang.Unexpanded.t Flags.t
; javascript_files : string list
; compilation_mode : Compilation_mode.t option
; sourcemap : Sourcemap.t option
}

let decode =
let decode ~executable =
let* syntax_version = Dune_lang.Syntax.get_exn Stanza.syntax in
if syntax_version < (3, 0)
then
Expand All @@ -106,78 +137,111 @@ module In_buildable = struct
; link = flags (* we set link as well to preserve the old semantic *)
}
; javascript_files
; compilation_mode = None
; sourcemap = None
})
else
fields
(let+ flags = Flags.decode
and+ javascript_files = field "javascript_files" (repeat string) ~default:[] in
{ flags; javascript_files })
and+ javascript_files = field "javascript_files" (repeat string) ~default:[]
and+ compilation_mode =
if executable
then
field_o
"compilation_mode"
(Dune_lang.Syntax.since Stanza.syntax (3, 17) >>> Compilation_mode.decode)
else return None
and+ sourcemap =
if executable
then
field_o
"sourcemap"
(Dune_lang.Syntax.since Stanza.syntax (3, 17) >>> Sourcemap.decode)
else return None
in
{ flags; javascript_files; compilation_mode; sourcemap })
;;

let default = { flags = Flags.standard; javascript_files = [] }
let default =
{ flags = Flags.standard
; javascript_files = []
; compilation_mode = None
; sourcemap = None
}
;;
end

module In_context = struct
type t =
{ flags : Ordered_set_lang.Unexpanded.t Flags.t
; javascript_files : Path.Build.t list
; compilation_mode : Compilation_mode.t option
; sourcemap : Sourcemap.t option
}

let make ~(dir : Path.Build.t) (x : In_buildable.t) =
{ flags = x.flags
; javascript_files =
List.map ~f:(fun name -> Path.Build.relative dir name) x.javascript_files
; compilation_mode = x.compilation_mode
; sourcemap = x.sourcemap
}
;;

let default = { flags = Flags.standard; javascript_files = [] }
end

module Compilation_mode = struct
type t =
| Whole_program
| Separate_compilation

let decode = enum [ "whole_program", Whole_program; "separate", Separate_compilation ]

let equal x y =
match x, y with
| Separate_compilation, Separate_compilation -> true
| Whole_program, Whole_program -> true
| Separate_compilation, _ -> false
| Whole_program, _ -> false
let default =
{ flags = Flags.standard
; javascript_files = []
; compilation_mode = None
; sourcemap = None
}
;;
end

module Env = struct
type 'a t =
{ compilation_mode : Compilation_mode.t option
; sourcemap : Sourcemap.t option
; runtest_alias : Alias.Name.t option
; flags : 'a Flags.t
}

let decode =
fields
@@ let+ compilation_mode = field_o "compilation_mode" Compilation_mode.decode
and+ sourcemap =
field_o
"sourcemap"
(Dune_lang.Syntax.since Stanza.syntax (3, 17) >>> Sourcemap.decode)
and+ runtest_alias = field_o "runtest_alias" Dune_lang.Alias.decode
and+ flags = Flags.decode in
Option.iter ~f:Alias.register_as_standard runtest_alias;
{ compilation_mode; runtest_alias; flags }
{ compilation_mode; sourcemap; runtest_alias; flags }
;;

let equal { compilation_mode; runtest_alias; flags } t =
let equal { compilation_mode; sourcemap; runtest_alias; flags } t =
Option.equal Compilation_mode.equal compilation_mode t.compilation_mode
&& Option.equal Sourcemap.equal sourcemap t.sourcemap
&& Option.equal Alias.Name.equal runtest_alias t.runtest_alias
&& Flags.equal Ordered_set_lang.Unexpanded.equal flags t.flags
;;

let map ~f { compilation_mode; runtest_alias; flags } =
{ compilation_mode; runtest_alias; flags = Flags.map ~f flags }
let map ~f { compilation_mode; sourcemap; runtest_alias; flags } =
{ compilation_mode; sourcemap; runtest_alias; flags = Flags.map ~f flags }
;;

let empty = { compilation_mode = None; runtest_alias = None; flags = Flags.standard }
let empty =
{ compilation_mode = None
; sourcemap = None
; runtest_alias = None
; flags = Flags.standard
}
;;

let default ~profile =
{ compilation_mode = None; runtest_alias = None; flags = Flags.default ~profile }
{ compilation_mode = None
; sourcemap = None
; runtest_alias = None
; flags = Flags.default ~profile
}
;;
end
26 changes: 19 additions & 7 deletions src/dune_rules/jsoo/js_of_ocaml.mli
Original file line number Diff line number Diff line change
Expand Up @@ -38,35 +38,47 @@ module Flags : sig
val dump : string list Action_builder.t t -> Dune_lang.t list Action_builder.t
end

module Sourcemap : sig
type t =
| No
| Inline
| File
end

module Compilation_mode : sig
type t =
| Whole_program
| Separate_compilation
end

module In_buildable : sig
type t =
{ flags : Flags.Spec.t
; javascript_files : string list
; compilation_mode : Compilation_mode.t option
; sourcemap : Sourcemap.t option
}

val decode : t Dune_lang.Decoder.t
val decode : executable:bool -> t Dune_lang.Decoder.t
val default : t
end

module In_context : sig
type t =
{ flags : Flags.Spec.t
; javascript_files : Path.Build.t list
; compilation_mode : Compilation_mode.t option
; sourcemap : Sourcemap.t option
}

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

module Compilation_mode : sig
type t =
| Whole_program
| Separate_compilation
end

module Env : sig
type 'a t =
{ compilation_mode : Compilation_mode.t option
; sourcemap : Sourcemap.t option
; runtest_alias : Alias.Name.t option
; flags : 'a Flags.t
}
Expand Down
Loading

0 comments on commit 16328a3

Please sign in to comment.