Skip to content

Commit

Permalink
feat(melange): support enabled_if in melange.emit (#7848)
Browse files Browse the repository at this point in the history
Signed-off-by: Antonio Nuno Monteiro <anmonteiro@gmail.com>
  • Loading branch information
anmonteiro authored Jun 1, 2023
1 parent a60873e commit 30537b5
Show file tree
Hide file tree
Showing 4 changed files with 62 additions and 11 deletions.
23 changes: 13 additions & 10 deletions src/dune_rules/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -144,16 +144,19 @@ end = struct
| true ->
let+ () = Mdx.gen_rules ~sctx ~dir ~scope ~expander mdx in
empty_none)
| Melange_stanzas.Emit.T mel ->
let+ cctx, merlin =
Melange_rules.setup_emit_cmj_rules ~dir_contents ~dir ~scope ~sctx
~expander mel
in
{ merlin = Some merlin
; cctx = Some (mel.loc, cctx)
; js = None
; source_dirs = None
}
| Melange_stanzas.Emit.T mel -> (
Expander.eval_blang expander mel.enabled_if >>= function
| false -> Memo.return empty_none
| true ->
let+ cctx, merlin =
Melange_rules.setup_emit_cmj_rules ~dir_contents ~dir ~scope ~sctx
~expander mel
in
{ merlin = Some merlin
; cctx = Some (mel.loc, cctx)
; js = None
; source_dirs = None
})
| _ -> Memo.return empty_none

let of_stanzas stanzas ~cctxs ~sctx ~src_dir ~ctx_dir ~scope ~dir_contents
Expand Down
9 changes: 8 additions & 1 deletion src/dune_rules/melange/melange_stanzas.ml
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ module Emit = struct
; promote : Rule.Promote.t option
; compile_flags : Ordered_set_lang.Unexpanded.t
; allow_overlapping_dependencies : bool
; enabled_if : Blang.t
}

type Stanza.t += T of t
Expand Down Expand Up @@ -108,7 +109,12 @@ module Emit = struct
and+ allow_overlapping_dependencies =
field_b "allow_overlapping_dependencies"
and+ emit_stdlib = field "emit_stdlib" bool ~default:true
and+ modules = Stanza_common.Modules_settings.decode in
and+ modules = Stanza_common.Modules_settings.decode
and+ enabled_if =
let open Enabled_if in
let allowed_vars = Any in
decode ~allowed_vars ~since:None ()
in
let preprocess =
let init =
let f libname = Preprocess.With_instrumentation.Ordinary libname in
Expand All @@ -133,6 +139,7 @@ module Emit = struct
; promote
; compile_flags
; allow_overlapping_dependencies
; enabled_if
})

let target_dir (emit : t) ~dir = Path.Build.relative dir emit.target
Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/melange/melange_stanzas.mli
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ module Emit : sig
; promote : Rule.Promote.t option
; compile_flags : Ordered_set_lang.Unexpanded.t
; allow_overlapping_dependencies : bool
; enabled_if : Blang.t
}

type Stanza.t += T of t
Expand Down
40 changes: 40 additions & 0 deletions test/blackbox-tests/test-cases/melange/enabled_if.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,40 @@
`enabled_if` in `melange.emit`

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

$ cat > dune <<EOF
> (melange.emit
> (target out)
> (emit_stdlib false)
> (enabled_if %{bin-available:melc}))
> EOF
$ cat > x.ml <<EOF
> let () = Js.log "hello"
> EOF

$ dune rules @melange | grep '\.cmj'
(File (In_build_dir _build/default/.out.mobjs/melange/melange__X.cmj))))
.out.mobjs/melange/melange__X.cmj))))
$ dune build @melange --display short
melc .out.mobjs/melange/melange__X.{cmi,cmj,cmt}
melc out/x.js

$ dune clean

`(enabled_if false)` shouldn't build any JS

$ cat > dune <<EOF
> (melange.emit
> (target out)
> (emit_stdlib false)
> (enabled_if false))
> EOF

$ dune build @melange --display short

No rules attached to the alias

$ dune rules @melange

0 comments on commit 30537b5

Please sign in to comment.