Skip to content

Commit

Permalink
CR
Browse files Browse the repository at this point in the history
  • Loading branch information
vouillon committed Nov 5, 2024
1 parent d31295f commit daa107e
Show file tree
Hide file tree
Showing 4 changed files with 21 additions and 47 deletions.
27 changes: 12 additions & 15 deletions src/dune_rules/jsoo/js_of_ocaml.ml
Original file line number Diff line number Diff line change
Expand Up @@ -188,7 +188,7 @@ module In_buildable = struct
; sourcemap : Sourcemap.t option
}

let decode ~executable ~mode =
let decode ~in_library ~mode =
let* syntax_version = Dune_lang.Syntax.get_exn Stanza.syntax in
if syntax_version < (3, 0)
then
Expand All @@ -206,7 +206,8 @@ module In_buildable = struct
; compilation_mode = None
; sourcemap = None
})
else
else (
let only_in_library decode = if in_library then decode else return None in
fields
(let+ flags = Flags.decode
and+ enabled_if =
Expand All @@ -223,21 +224,17 @@ module In_buildable = struct
(Dune_lang.Syntax.since Stanza.syntax (3, 17) >>> 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
only_in_library
(field_o
"compilation_mode"
(Dune_lang.Syntax.since Stanza.syntax (3, 17) >>> Compilation_mode.decode))
and+ sourcemap =
if executable
then
field_o
"sourcemap"
(Dune_lang.Syntax.since Stanza.syntax (3, 17) >>> Sourcemap.decode)
else return None
only_in_library
(field_o
"sourcemap"
(Dune_lang.Syntax.since Stanza.syntax (3, 17) >>> Sourcemap.decode))
in
{ flags; enabled_if; javascript_files; wasm_files; compilation_mode; sourcemap })
{ flags; enabled_if; javascript_files; wasm_files; compilation_mode; sourcemap }))
;;

let default =
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/jsoo/js_of_ocaml.mli
Original file line number Diff line number Diff line change
Expand Up @@ -88,7 +88,7 @@ module In_buildable : sig
; sourcemap : Sourcemap.t option
}

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

Expand Down
11 changes: 1 addition & 10 deletions src/dune_rules/jsoo/jsoo_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -538,15 +538,6 @@ let setup_separate_compilation_rules sctx components =
let build_context = Context.build_context ctx in
let name = Path.basename fn in
let dir = in_build_dir build_context ~config [ lib_name ] in
let in_context =
{ Js_of_ocaml.In_context.flags = Js_of_ocaml.Flags.standard
; enabled_if = Some Blang.true_
; javascript_files = []
; wasm_files = []
; compilation_mode = None
; sourcemap = None
}
in
let src =
let src_dir = Lib_info.src_dir info in
Path.relative src_dir name
Expand All @@ -557,7 +548,7 @@ let setup_separate_compilation_rules sctx components =
build_cm'
sctx
~dir
~in_context
~in_context:Js_of_ocaml.In_context.default
~mode
~src
~target
Expand Down
28 changes: 7 additions & 21 deletions src/dune_rules/stanzas/buildable.ml
Original file line number Diff line number Diff line change
Expand Up @@ -29,11 +29,12 @@ let decode (for_ : for_) =
(2, 0)
~extra_info:"Use the (foreign_stubs ...) field instead."
in
let only_in_library decode =
let in_library =
match for_ with
| Executable -> return None
| Library _ -> decode
| Library _ -> true
| Executable -> false
in
let only_in_library decode = if in_library then decode else return None in
let add_stubs language ~loc ~names ~flags foreign_stubs =
match names with
| None -> foreign_stubs
Expand Down Expand Up @@ -84,33 +85,18 @@ let decode (for_ : for_) =
~extra_info:"Use the (foreign_archives ...) field instead."
>>> enter (maybe string))))
and+ libraries =
let allow_re_export =
match for_ with
| Library _ -> true
| Executable -> false
in
field "libraries" (Lib_dep.L.decode ~allow_re_export) ~default:[]
field "libraries" (Lib_dep.L.decode ~allow_re_export:in_library) ~default:[]
and+ flags = Ocaml_flags.Spec.decode
and+ js_of_ocaml =
let executable =
match for_ with
| Executable -> true
| Library _ -> false
in
field
"js_of_ocaml"
(Js_of_ocaml.In_buildable.decode ~executable ~mode:JS)
(Js_of_ocaml.In_buildable.decode ~in_library ~mode:JS)
~default:Js_of_ocaml.In_buildable.default
and+ wasm_of_ocaml =
let executable =
match for_ with
| Executable -> true
| Library _ -> false
in
field
"wasm_of_ocaml"
(Dune_lang.Syntax.since Stanza.syntax (3, 17)
>>> Js_of_ocaml.In_buildable.decode ~executable ~mode:Wasm)
>>> Js_of_ocaml.In_buildable.decode ~in_library ~mode:Wasm)
~default:Js_of_ocaml.In_buildable.default
and+ allow_overlapping_dependencies = field_b "allow_overlapping_dependencies"
and+ version = Dune_lang.Syntax.get_exn Stanza.syntax
Expand Down

0 comments on commit daa107e

Please sign in to comment.