Skip to content

Commit

Permalink
rename [Js_of_ocaml] to [Jsoo]
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Jul 15, 2020
1 parent 0709460 commit ae54784
Show file tree
Hide file tree
Showing 6 changed files with 5 additions and 5 deletions.
4 changes: 2 additions & 2 deletions src/dune/exe.ml
Original file line number Diff line number Diff line change
Expand Up @@ -184,10 +184,10 @@ let link_js ~name ~cm_files ~promote cctx =
let src = exe_path_from_name cctx ~name ~linkage:Linkage.byte in
let flags =
Expander.expand_and_eval_set expander js_of_ocaml.flags
~standard:(Build.return (Js_of_ocaml_rules.standard sctx))
~standard:(Build.return (Jsoo_rules.standard sctx))
in
let top_sorted_cms = Cm_files.top_sorted_cms cm_files ~mode:Mode.Byte in
Js_of_ocaml_rules.build_exe cctx ~js_of_ocaml ~src ~cm:top_sorted_cms
Jsoo_rules.build_exe cctx ~js_of_ocaml ~src ~cm:top_sorted_cms
~flags:(Command.Args.dyn flags) ~promote

let build_and_link_many ~programs ~linkages ~promote ?link_args ?o_files
Expand Down
2 changes: 1 addition & 1 deletion src/dune/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -304,7 +304,7 @@ let gen_rules ~sctx ~dir components : Build_system.extra_sub_directories_to_keep
(Build.write_file (Path.Build.relative dir "configurator") "");
These String.Set.empty
| ".js" :: rest -> (
Js_of_ocaml_rules.setup_separate_compilation_rules sctx rest;
Jsoo_rules.setup_separate_compilation_rules sctx rest;
match rest with
| [] -> All
| _ -> These String.Set.empty )
Expand Down
File renamed without changes.
File renamed without changes.
2 changes: 1 addition & 1 deletion src/dune/lib_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -325,7 +325,7 @@ let setup_build_archives (lib : Dune_file.Library.t) ~dir_contents ~cctx
Path.Build.relative (Obj_dir.obj_dir obj_dir) (Path.Build.basename src)
|> Path.Build.extend_basename ~suffix:".js"
in
Js_of_ocaml_rules.build_cm cctx ~js_of_ocaml ~src ~target);
Jsoo_rules.build_cm cctx ~js_of_ocaml ~src ~target);
if Dynlink_supported.By_the_os.get natdynlink_supported && modes.native then
build_shared ~dir_contents ~sctx lib ~dir ~flags

Expand Down
2 changes: 1 addition & 1 deletion src/dune/module_compilation.ml
Original file line number Diff line number Diff line change
Expand Up @@ -224,7 +224,7 @@ let build_module ~dep_graphs ?(precompiled_cmi = false) cctx m =
let src = Obj_dir.Module.cm_file_unsafe obj_dir m ~kind:Cm_kind.Cmo in
let target = Path.Build.extend_basename src ~suffix:".js" in
SC.add_rules sctx ~dir
(Js_of_ocaml_rules.build_cm cctx ~js_of_ocaml ~src ~target))
(Jsoo_rules.build_cm cctx ~js_of_ocaml ~src ~target))

let ocamlc_i ?(flags = []) ~dep_graphs cctx (m : Module.t) ~output =
let sctx = CC.super_context cctx in
Expand Down

0 comments on commit ae54784

Please sign in to comment.