Skip to content

Commit

Permalink
fix(melange): unify public libraries (in-workspace vs external)
Browse files Browse the repository at this point in the history
Signed-off-by: Antonio Nuno Monteiro <[email protected]>
  • Loading branch information
anmonteiro committed Feb 22, 2023
1 parent e7c0a10 commit 86885fa
Show file tree
Hide file tree
Showing 3 changed files with 34 additions and 27 deletions.
12 changes: 1 addition & 11 deletions src/dune_rules/melange/melange_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -20,23 +20,13 @@ let output_of_lib ~target_dir lib =
let info = Lib.info lib in
match Lib_info.status info with
| Private _ -> `Private_library_or_emit target_dir
| Installed | Installed_private ->
| Installed | Installed_private | Public _ ->
let lib_name = Lib_info.name info in
let src_dir = Lib_info.src_dir info in
`Public_library
( src_dir
, Path.Build.L.relative target_dir
[ "node_modules"; Lib_name.to_string lib_name ] )
| Public _ ->
let lib_name = Lib_info.name info in
let src_dir = Lib_info.src_dir info in
`Public_library
( src_dir
, Path.Build.L.relative target_dir
[ "node_modules"
; Lib_name.to_string lib_name
; Path.Source.to_string (Path.drop_build_context_exn src_dir)
] )

let make_js_name ~js_ext ~output m =
let basename = Melange.js_basename m ^ js_ext in
Expand Down
43 changes: 30 additions & 13 deletions src/dune_rules/module_compilation.ml
Original file line number Diff line number Diff line change
Expand Up @@ -49,21 +49,41 @@ let copy_interface ~sctx ~dir ~obj_dir ~cm_kind m =
(Path.build (Obj_dir.Module.cm_file_exn obj_dir m ~kind:cmi_kind))
~dst:(Obj_dir.Module.cm_public_file_exn obj_dir m ~kind:cmi_kind)))

let melange_args (cm_kind : Lib_mode.Cm_kind.t) lib_name module_ =
let melange_args (cctx : Compilation_context.t) (cm_kind : Lib_mode.Cm_kind.t)
module_ =
match cm_kind with
| Ocaml (Cmi | Cmo | Cmx) | Melange Cmi -> []
| Melange Cmj ->
let bs_package_name =
match lib_name with
| None -> []
let bs_package_name, bs_package_output =
let package_output =
Module.file ~ml_kind:Impl module_ |> Option.value_exn |> Path.parent_exn
in
match Compilation_context.public_lib_name cctx with
| None -> ([], package_output)
| Some lib_name ->
[ Command.Args.A "--bs-package-name"; A (Lib_name.to_string lib_name) ]
in
let package_output =
Module.file ~ml_kind:Impl module_ |> Option.value_exn |> Path.parent_exn
let package_output = package_output |> Path.as_in_build_dir_exn in
let dir =
let lib_root_dir =
Compilation_context.dir cctx |> Path.Build.to_string
in
let src_dir = package_output |> Path.Build.to_string in
let build_context =
let ctx, _ =
Path.Build.extract_build_context_dir_exn package_output
in
ctx
in
String.drop_prefix src_dir ~prefix:lib_root_dir
|> Option.value_exn
|> String.drop_prefix_if_exists ~prefix:"/"
|> Path.Build.relative build_context
in

( [ Command.Args.A "--bs-package-name"; A (Lib_name.to_string lib_name) ]
, Path.build dir )
in
Command.Args.A "--bs-stop-after-cmj" :: A "--bs-package-output"
:: Command.Args.Path package_output :: A "--bs-module-name"
:: Command.Args.Path bs_package_output :: A "--bs-module-name"
:: A (Melange.js_basename module_)
:: bs_package_name

Expand Down Expand Up @@ -238,10 +258,7 @@ let build_cm cctx ~force_write_cmi ~precompiled_cmi ~cm_kind (m : Module.t)
; Command.Args.as_any
(Lib_mode.Cm_kind.Map.get (CC.includes cctx) cm_kind)
; As extra_args
; S
(melange_args cm_kind
(Compilation_context.public_lib_name cctx)
m)
; S (melange_args cctx cm_kind m)
; A "-no-alias-deps"
; opaque_arg
; As (Fdo.phase_flags phase)
Expand Down
6 changes: 3 additions & 3 deletions test/blackbox-tests/test-cases/melange/public.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ Cmj rules should include --bs-package-output
$ dune rules my_project/app/.app.objs/melange/app.cmj |
> grep -e "--bs-package-output" --after-context=1
--bs-package-output
my_project/app
.

Cmj rules should include --bs-package-name
$ dune rules my_project/app/.app.objs/melange/app.cmj |
Expand All @@ -15,13 +15,13 @@ Cmj rules should include --bs-package-name
$ output=my_project/output

Js rules should include --bs-module-type
$ dune rules $output/node_modules/pkg.app/my_project/app/b.js |
$ dune rules $output/node_modules/pkg.app/b.js |
> grep -e "--bs-module-type" --after-context=1
--bs-module-type
commonjs

Js rules should include --bs-package-name
$ dune rules $output/node_modules/pkg.app/my_project/app/b.js |
$ dune rules $output/node_modules/pkg.app/b.js |
> grep -e "--bs-package-name" --after-context=1
--bs-package-name
pkg
Expand Down

0 comments on commit 86885fa

Please sign in to comment.