Skip to content

Commit 734967d

Browse files
committed
Disallow (wasm_of_ocaml (sourcemap file))
1 parent 17e954a commit 734967d

File tree

5 files changed

+20
-14
lines changed

5 files changed

+20
-14
lines changed

doc/reference/dune/executable.rst

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -297,7 +297,7 @@ options using ``(wasm_of_ocaml (<wasm_of_ocaml-options>))``.
297297
- ``(wasm_files (<files-list>))`` to specify ``wasm_of_ocaml``
298298
Wasm runtime files.
299299

300-
For the ``(sourcemap <config>)`` option, source maps are generated when ``<config>>`` is either ``file`` or ``inline``. They are put within the ``.bc.wasm.assets`` directory in both cases.
300+
For the ``(sourcemap <config>)`` option, ``<config>`` must be one of ``no`` or ``inline``. Source maps are put within the ``.bc.wasm.assets`` directory.
301301

302302
The default values for ``flags``, ``compilation_mode`` and ``sourcemap`` depend on the selected build profile. The
303303
build profile ``dev`` (the default) will enable sourcemaps, separate compilation and pretty Wasm output.

src/dune_rules/dune_env.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -225,14 +225,14 @@ let js_of_ocaml_field =
225225
field
226226
"js_of_ocaml"
227227
~default:Js_of_ocaml.Env.empty
228-
(Dune_lang.Syntax.since Stanza.syntax (3, 0) >>> Js_of_ocaml.Env.decode)
228+
(Dune_lang.Syntax.since Stanza.syntax (3, 0) >>> Js_of_ocaml.Env.decode ~mode:JS)
229229
;;
230230

231231
let wasm_of_ocaml_field =
232232
field
233233
"wasm_of_ocaml"
234234
~default:Js_of_ocaml.Env.empty
235-
(Dune_lang.Syntax.since Stanza.syntax (3, 17) >>> Js_of_ocaml.Env.decode)
235+
(Dune_lang.Syntax.since Stanza.syntax (3, 17) >>> Js_of_ocaml.Env.decode ~mode:Wasm)
236236
;;
237237

238238
let bin_annot = field_o "bin_annot" (Dune_lang.Syntax.since Stanza.syntax (3, 8) >>> bool)

src/dune_rules/jsoo/js_of_ocaml.ml

Lines changed: 8 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -74,7 +74,11 @@ module Sourcemap = struct
7474
| Inline
7575
| File
7676

77-
let decode = enum [ "no", No; "inline", Inline; "file", File ]
77+
let decode ~mode =
78+
match (mode : Mode.t) with
79+
| JS -> enum [ "no", No; "inline", Inline; "file", File ]
80+
| Wasm -> enum [ "no", No; "inline", Inline ]
81+
;;
7882

7983
let equal x y =
8084
match x, y with
@@ -232,7 +236,7 @@ module In_buildable = struct
232236
only_in_executable
233237
(field_o
234238
"sourcemap"
235-
(Dune_lang.Syntax.since Stanza.syntax (3, 17) >>> Sourcemap.decode))
239+
(Dune_lang.Syntax.since Stanza.syntax (3, 17) >>> Sourcemap.decode ~mode))
236240
in
237241
{ flags; enabled_if; javascript_files; wasm_files; compilation_mode; sourcemap }))
238242
;;
@@ -301,13 +305,13 @@ module Env = struct
301305
; enabled_if : Blang.t option
302306
}
303307

304-
let decode =
308+
let decode ~mode =
305309
fields
306310
@@ let+ compilation_mode = field_o "compilation_mode" Compilation_mode.decode
307311
and+ sourcemap =
308312
field_o
309313
"sourcemap"
310-
(Dune_lang.Syntax.since Stanza.syntax (3, 17) >>> Sourcemap.decode)
314+
(Dune_lang.Syntax.since Stanza.syntax (3, 17) >>> Sourcemap.decode ~mode)
311315
and+ runtest_alias = field_o "runtest_alias" Dune_lang.Alias.decode
312316
and+ flags = Flags.decode
313317
and+ enabled_if =

src/dune_rules/jsoo/js_of_ocaml.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -127,7 +127,7 @@ module Env : sig
127127

128128
val map : f:('a -> 'b) -> 'a t -> 'b t
129129
val equal : Ordered_set_lang.Unexpanded.t t -> Ordered_set_lang.Unexpanded.t t -> bool
130-
val decode : Ordered_set_lang.Unexpanded.t t Dune_lang.Decoder.t
130+
val decode : mode:Mode.t -> Ordered_set_lang.Unexpanded.t t Dune_lang.Decoder.t
131131
val default : profile:Profile.t -> string list t
132132
val empty : Ordered_set_lang.Unexpanded.t t
133133
end

src/dune_rules/jsoo/jsoo_rules.ml

Lines changed: 8 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -259,12 +259,14 @@ let js_of_ocaml_rule
259259
| Compile -> S []
260260
| Link -> A "link"
261261
| Build_runtime -> A "build-runtime")
262-
; (match (sourcemap : Js_of_ocaml.Sourcemap.t), mode with
263-
| No, _ -> A "--no-source-map"
264-
| Inline, _ | File, Wasm ->
265-
(* With wasm_of_ocaml, source maps are always inline *)
266-
A "--source-map-inline"
267-
| File, JS ->
262+
; (match (sourcemap : Js_of_ocaml.Sourcemap.t) with
263+
| No -> A "--no-source-map"
264+
| Inline -> A "--source-map-inline"
265+
| File ->
266+
assert (
267+
match mode with
268+
| JS -> true
269+
| Wasm -> false);
268270
S
269271
[ A "--source-map"
270272
; Hidden_targets [ Path.Build.set_extension target ~ext:".map" ]

0 commit comments

Comments
 (0)