Skip to content

Commit

Permalink
feat(melange): add manifest information for melange.emit
Browse files Browse the repository at this point in the history
Signed-off-by: Antonio Nuno Monteiro <[email protected]>
  • Loading branch information
davesnx authored and anmonteiro committed Dec 15, 2024
1 parent 3fc17ee commit 54d234c
Show file tree
Hide file tree
Showing 5 changed files with 129 additions and 12 deletions.
2 changes: 1 addition & 1 deletion otherlibs/chrome-trace/src/chrome_trace.mli
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@
https://docs.google.com/document/d/1CvAClvFfyA5R-PhYUmn5OOQtYMH4h6I0nSsKchNAySU/preview *)

module Json : sig
(** Simplifies JSON type *)
(** Simplified JSON type *)
type t =
[ `Int of int
| `Float of float
Expand Down
79 changes: 68 additions & 11 deletions src/dune_rules/melange/melange_rules.ml
Original file line number Diff line number Diff line change
@@ -1,5 +1,17 @@
open Import
open Memo.O
module Json = Dune_stats.Json

(* attach [deps] to the specified [alias] AND the (dune default) [all] alias.
when [alias] is not supplied, {!Melange_stanzas.Emit.implicit_alias} is
assumed. *)
let add_deps_to_aliases ?(alias = Melange_stanzas.Emit.implicit_alias) ~dir deps =
let alias = Alias.make alias ~dir in
let dune_default_alias = Alias.make Alias0.all ~dir in
let attach alias = Rules.Produce.Alias.add_deps alias deps in
Memo.parallel_iter ~f:attach [ alias; dune_default_alias ]
;;

let output_of_lib =
let public_lib ~info ~target_dir lib_name =
Expand Down Expand Up @@ -47,6 +59,52 @@ let make_js_name ~js_ext ~output m =
Path.Build.relative dst_dir basename
;;

module Manifest = struct
type mapping =
{ source : Path.t
; targets : Path.Build.t list
}

type t = { mappings : mapping list }

let sexp_of_mapping { source; targets } =
let source_str = Path.to_string source in
let target_strs = List.map targets ~f:Path.Build.to_string in
`Assoc [ source_str, `List (List.map target_strs ~f:(fun s -> `String s)) ]
;;

let json_of_t t = `List (List.map t.mappings ~f:sexp_of_mapping)
let to_string t = Json.to_string (json_of_t t)

let create_mapping ~module_systems ~output m =
let source = Module.file m ~ml_kind:Impl |> Option.value_exn in
let targets =
List.map module_systems ~f:(fun (_, js_ext) -> make_js_name ~js_ext ~output m)
in
{ source; targets }
;;

let setup_manifest_rule ~sctx ~dir ~target_dir ~mode mappings =
let manifest_path = Path.Build.relative target_dir "melange-manifest.sexp" in
Format.eprintf "Creating manifest rule@.";
Format.eprintf " dir: %s@." (Path.Build.to_string dir);
Format.eprintf " target_dir: %s@." (Path.Build.to_string target_dir);
Format.eprintf " mappings count: %d@." (List.length mappings);
Format.eprintf " manifest path: %s@." (Path.Build.to_string manifest_path);
let manifest = { mappings } in
let manifest_str = to_string manifest in
Format.eprintf " manifest content:@.%s@." manifest_str;
let* () =
Action_builder.return manifest_str
|> Action_builder.write_file_dyn manifest_path
|> Super_context.add_rule sctx ~dir:target_dir ~mode
in
let manifest_dep = Action_builder.path (Path.build manifest_path) in
let* () = add_deps_to_aliases ~dir:target_dir manifest_dep in
Memo.return ()
;;
end

let modules_in_obj_dir ~sctx ~scope ~preprocess modules =
let* version =
let+ ocaml = Context.ocaml (Super_context.context sctx) in
Expand Down Expand Up @@ -248,17 +306,6 @@ let build_js
Super_context.add_rule sctx ~dir ~loc ~mode build)
;;

(* attach [deps] to the specified [alias] AND the (dune default) [all] alias.
when [alias] is not supplied, {!Melange_stanzas.Emit.implicit_alias} is
assumed. *)
let add_deps_to_aliases ?(alias = Melange_stanzas.Emit.implicit_alias) ~dir deps =
let alias = Alias.make alias ~dir in
let dune_default_alias = Alias.make Alias0.all ~dir in
let attach alias = Rules.Produce.Alias.add_deps alias deps in
Memo.parallel_iter ~f:attach [ alias; dune_default_alias ]
;;

let setup_emit_cmj_rules
~sctx
~dir
Expand Down Expand Up @@ -480,6 +527,16 @@ let setup_entries_js
let* () =
setup_runtime_assets_rules sctx ~dir ~target_dir ~mode ~output ~for_:`Emit mel
in
let* () =
match mel.emit_manifest with
| true ->
let mappings =
List.map modules_for_js ~f:(fun m ->
Manifest.create_mapping ~module_systems ~output m)
in
Manifest.setup_manifest_rule ~sctx ~dir ~target_dir ~mode mappings
| false -> Memo.return ()
in
let local_modules_and_obj_dir =
Some (Modules.With_vlib.modules local_modules, local_obj_dir)
in
Expand Down
3 changes: 3 additions & 0 deletions src/dune_rules/melange/melange_stanzas.ml
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@ module Emit = struct
; module_systems : (Melange.Module_system.t * Filename.Extension.t) list
; modules : Stanza_common.Modules_settings.t
; emit_stdlib : bool
; emit_manifest : bool
; libraries : Lib_dep.t list
; package : Package.t option
; preprocess : Preprocess.With_instrumentation.t Preprocess.Per_module.t
Expand Down Expand Up @@ -115,6 +116,7 @@ module Emit = struct
and+ compile_flags = Ordered_set_lang.Unexpanded.field "compile_flags"
and+ allow_overlapping_dependencies = field_b "allow_overlapping_dependencies"
and+ emit_stdlib = field "emit_stdlib" bool ~default:true
and+ emit_manifest = field "emit_manifest" bool ~default:false
and+ modules = Stanza_common.Modules_settings.decode
and+ enabled_if =
let open Enabled_if in
Expand All @@ -134,6 +136,7 @@ module Emit = struct
; module_systems
; modules
; emit_stdlib
; emit_manifest
; libraries
; package
; preprocess
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 @@ -9,6 +9,7 @@ module Emit : sig
; module_systems : (Melange.Module_system.t * string) list
; modules : Stanza_common.Modules_settings.t
; emit_stdlib : bool
; emit_manifest : bool
; libraries : Lib_dep.t list
; package : Package.t option
; preprocess : Preprocess.With_instrumentation.t Preprocess.Per_module.t
Expand Down
56 changes: 56 additions & 0 deletions test/blackbox-tests/test-cases/melange/manifest.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,56 @@
Test melange manifest

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

$ cat > dune <<EOF
> (melange.emit
> (target output)
> (emit_manifest true)
> (modules main))
> EOF

$ cat > main.ml <<EOF
> Js.log "hello"
> EOF

$ dune build @melange
Creating manifest rule
dir: _build/default
target_dir: _build/default/output
mappings count: 1
manifest path: _build/default/output/melange-manifest.sexp
manifest content:
[{"_build/default/main.ml":["_build/default/output/main.js"]}]

$ ls _build/default/output
main.js
melange-manifest.sexp
node_modules

$ cat _build/default/output/melange-manifest.sexp
[{"_build/default/main.ml":["_build/default/output/main.js"]}]

$ dune rules @melange | grep -C 3 "manifest"
Creating manifest rule
dir: _build/default
target_dir: _build/default/output
mappings count: 1
manifest path: _build/default/output/melange-manifest.sexp
manifest content:
[{"_build/default/main.ml":["_build/default/output/main.js"]}]

((deps ())
(targets
((files (_build/default/output/melange-manifest.sexp)) (directories ())))
(context default)
(action
(chdir
_build/default
(write-file
output/melange-manifest.sexp
"[{\"_build/default/main.ml\":[\"_build/default/output/main.js\"]}]"))))
((deps

0 comments on commit 54d234c

Please sign in to comment.