Skip to content

Commit

Permalink
melange: compile_flags
Browse files Browse the repository at this point in the history
Signed-off-by: Javier Chavarri <[email protected]>
  • Loading branch information
jchavarri committed Nov 28, 2022
1 parent 4f3b14a commit 64b6729
Show file tree
Hide file tree
Showing 9 changed files with 86 additions and 31 deletions.
4 changes: 3 additions & 1 deletion src/dune_rules/melange_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -97,7 +97,9 @@ let add_rules_for_entries ~sctx ~dir ~expander ~dir_contents ~scope
>>| Ml_sources.modules_and_obj_dir ~for_:(Melange { target = mel.target })
in
let* () = Check_rules.add_obj_dir sctx ~obj_dir in
let* flags = Super_context.ocaml_flags sctx ~dir mel.flags in
let* flags =
Super_context.ocaml_flags_with_melange sctx ~dir mel.compile_flags
in
let requires_link = Lib.Compile.requires_link compile_info in
let direct_requires = Lib.Compile.direct_requires compile_info in
let* modules, pp =
Expand Down
6 changes: 3 additions & 3 deletions src/dune_rules/melange_stanzas.ml
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ module Emit = struct
; preprocess : Preprocess.With_instrumentation.t Preprocess.Per_module.t
; preprocessor_deps : Dep_conf.t list
; promote : Rule.Promote.t option
; flags : Ocaml_flags.Spec.t
; compile_flags : Ordered_set_lang.Unexpanded.t
; root_module : (Loc.t * Module_name.t) option
; javascript_extension : string
}
Expand Down Expand Up @@ -88,7 +88,7 @@ module Emit = struct
and+ preprocess, preprocessor_deps = Stanza_common.preprocess_fields
and+ promote = field_o "promote" Rule_mode_decoder.Promote.decode
and+ loc_instrumentation, instrumentation = Stanza_common.instrumentation
and+ flags = Ocaml_flags.Spec.decode
and+ compile_flags = Ordered_set_lang.Unexpanded.field "compile_flags"
and+ root_module = field_o "root_module" Module_name.decode_loc
and+ javascript_extension = extension_field "javascript_extension" in
let preprocess =
Expand All @@ -111,7 +111,7 @@ module Emit = struct
; preprocess
; preprocessor_deps
; promote
; flags
; compile_flags
; root_module
; javascript_extension
})
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/melange_stanzas.mli
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ module Emit : sig
; preprocess : Preprocess.With_instrumentation.t Preprocess.Per_module.t
; preprocessor_deps : Dep_conf.t list
; promote : Rule.Promote.t option
; flags : Ocaml_flags.Spec.t
; compile_flags : Ordered_set_lang.Unexpanded.t
; root_module : (Loc.t * Module_name.t) option
; javascript_extension : string
}
Expand Down
24 changes: 21 additions & 3 deletions src/dune_rules/ocaml_flags.ml
Original file line number Diff line number Diff line change
Expand Up @@ -93,7 +93,11 @@ module Spec = struct
let+ common = field_oslu "flags"
and+ byte = field_oslu "ocamlc_flags"
and+ native = field_oslu "ocamlopt_flags"
and+ melange = field_oslu "melc_flags" in
and+ melange =
field_oslu
~check:(Dune_lang.Syntax.since Dune_project.Melange_syntax.t (0, 1))
"melange.compile_flags"
in
let specific = Lib_mode.Map.make ~byte ~native ~melange in
{ common; specific }
end
Expand Down Expand Up @@ -132,7 +136,21 @@ let make ~spec ~default ~eval =
f "ocamlopt flags" spec.specific.ocaml.native
default.specific.ocaml.native
}
; melange = f "melc flags" spec.specific.melange default.specific.melange
; melange =
f "melange compile_flags" spec.specific.melange
default.specific.melange
}
}

let make_with_melange ~melange ~default ~eval =
let f name x standard =
Action_builder.memoize ~cutoff:(List.equal String.equal) name
(eval x ~standard)
in
{ common = default.common
; specific =
{ ocaml = default.specific.ocaml
; melange = f "melange compile_flags" melange default.specific.melange
}
}

Expand Down Expand Up @@ -168,5 +186,5 @@ let dump t =
[ ("flags", common)
; ("ocamlc_flags", byte)
; ("ocamlopt_flags", native)
; ("melc_flags", melange)
; ("melange.compile_flags", melange)
]
9 changes: 9 additions & 0 deletions src/dune_rules/ocaml_flags.mli
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,15 @@ val make :
-> string list Action_builder.t)
-> t

val make_with_melange :
melange:Ordered_set_lang.Unexpanded.t
-> default:t
-> eval:
( Ordered_set_lang.Unexpanded.t
-> standard:string list Action_builder.t
-> string list Action_builder.t)
-> t

val default : dune_version:Dune_lang.Syntax.Version.t -> profile:Profile.t -> t

val empty : t
Expand Down
13 changes: 13 additions & 0 deletions src/dune_rules/super_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -270,6 +270,19 @@ let ocaml_flags t ~dir (spec : Ocaml_flags.Spec.t) =
with_vendored_flags ~ocaml_version flags
| false -> flags

let ocaml_flags_with_melange t ~dir melange =
let* expander = Env_tree.expander t ~dir in
let* flags =
let+ ocaml_flags = Env_tree.get_node t ~dir >>= Env_node.ocaml_flags in
Ocaml_flags.make_with_melange ~melange ~default:ocaml_flags
~eval:(Expander.expand_and_eval_set expander)
in
build_dir_is_vendored dir >>| function
| true ->
let ocaml_version = (Env_tree.context t).version in
with_vendored_flags ~ocaml_version flags
| false -> flags

let js_of_ocaml_runtest_alias t ~dir =
let+ js_of_ocaml = Env_tree.get_node t ~dir >>= Env_node.js_of_ocaml in
match js_of_ocaml.runtest_alias with
Expand Down
3 changes: 3 additions & 0 deletions src/dune_rules/super_context.mli
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,9 @@ val context_env : t -> Env.t
val ocaml_flags :
t -> dir:Path.Build.t -> Ocaml_flags.Spec.t -> Ocaml_flags.t Memo.t

val ocaml_flags_with_melange :
t -> dir:Path.Build.t -> Ordered_set_lang.Unexpanded.t -> Ocaml_flags.t Memo.t

val js_of_ocaml_runtest_alias : t -> dir:Path.Build.t -> Alias.Name.t Memo.t

val js_of_ocaml_compilation_mode :
Expand Down
22 changes: 20 additions & 2 deletions test/blackbox-tests/test-cases/melange/flags.t
Original file line number Diff line number Diff line change
@@ -1,10 +1,12 @@
Test (flags) field on melange.emit stanza
Test flags and compile_flags fields on melange.emit stanza

$ cat > dune-project <<EOF
> (lang dune 3.6)
> (using melange 0.1)
> EOF

Using flags field in melange.emit stanzas is not supported

$ cat > dune <<EOF
> (melange.emit
> (target output)
Expand All @@ -22,7 +24,23 @@ The code in main contains unused var (warning 26) and illegal backlash (warning

Building should not fail as warnings are silenced

$ dune build output/main.js
File "dune", line 5, characters 2-7:
5 | (flags -w -14-26))
^^^^^
Error: Unknown field flags
[1]

Should use compile_flags

$ cat > dune <<EOF
> (melange.emit
> (target output)
> (entries main)
> (module_system commonjs)
> (compile_flags -w -14-26))
> EOF

$ dune build output/main.js
$ node _build/default/output/main.js
hello

34 changes: 13 additions & 21 deletions test/blackbox-tests/test-cases/melange/ocaml-flags.t
Original file line number Diff line number Diff line change
@@ -1,18 +1,18 @@
Test melc_flags, ocamlc_flags and ocamlopt_flags fields on melange.emit stanza
Test melange.compile_flags, ocamlc_flags and ocamlopt_flags fields on melange.emit stanza

$ cat > dune-project <<EOF
> (lang dune 3.6)
> (using melange 0.1)
> EOF

Create dune file that uses melc_flags
Create dune file that uses melange.compile_flags

$ cat > dune <<EOF
> (melange.emit
> (target output)
> (entries main)
> (module_system commonjs)
> (melc_flags -w -14-26))
> (compile_flags -w -14-26))
> EOF

The code in main contains unused var (warning 26) and illegal backlash (warning 14)
Expand All @@ -38,17 +38,13 @@ Update dune file to use ocamlc_flags
> (ocamlc_flags -w -14-26))
> EOF

Building should fail as ocamlc flags are ignored in melange builds
Building should fail as ocamlc flags are not supported in melange emit stanzas

$ dune build output/main.js
File "main.ml", line 1, characters 9-11:
1 | let t = "\e\n" in
^^
Error (warning 14 [illegal-backslash]): illegal backslash escape in string.
File "main.ml", line 1, characters 4-5:
1 | let t = "\e\n" in
^
Error (warning 26 [unused-var]): unused variable t.
File "dune", line 5, characters 2-14:
5 | (ocamlc_flags -w -14-26))
^^^^^^^^^^^^
Error: Unknown field ocamlc_flags
[1]

Update dune file to use ocamlopt_flags
Expand All @@ -61,15 +57,11 @@ Update dune file to use ocamlopt_flags
> (ocamlopt_flags -w -14-26))
> EOF

Building should fail as ocamlopt flags are ignored in melange builds
Building should fail as ocamlopt flags are not supported in melange emit stanzas

$ dune build output/main.js
File "main.ml", line 1, characters 9-11:
1 | let t = "\e\n" in
^^
Error (warning 14 [illegal-backslash]): illegal backslash escape in string.
File "main.ml", line 1, characters 4-5:
1 | let t = "\e\n" in
^
Error (warning 26 [unused-var]): unused variable t.
File "dune", line 5, characters 2-16:
5 | (ocamlopt_flags -w -14-26))
^^^^^^^^^^^^^^
Error: Unknown field ocamlopt_flags
[1]

0 comments on commit 64b6729

Please sign in to comment.