Skip to content

Commit

Permalink
Merge branch 'main' into playground/send-warnings-always
Browse files Browse the repository at this point in the history
* main:
  feat: add `-mel-*` flag aliases for CLI flags starting with `-bs-*` (#851)
  • Loading branch information
jchavarri committed Oct 31, 2023
2 parents 9346864 + 99556bd commit a3d407c
Show file tree
Hide file tree
Showing 15 changed files with 63 additions and 52 deletions.
53 changes: 34 additions & 19 deletions bin/melc_cli.ml
Original file line number Diff line number Diff line change
Expand Up @@ -138,21 +138,27 @@ let open_modules =

let bs_syntax_only =
let doc = "Only check syntax" in
Arg.(value & flag & info [ "bs-syntax-only" ] ~doc)
Arg.(value & flag & info [ "bs-syntax-only"; "mel-syntax-only" ] ~doc)

let bs_g =
let doc = "Debug mode" in
Arg.(value & flag & info [ "bs-g" ] ~doc)
Arg.(value & flag & info [ "bs-g"; "mel-g" ] ~doc)

let bs_package_name =
let doc = "Set package name, useful when you want to produce npm packages" in
Arg.(value & opt (some string) None & info [ "bs-package-name" ] ~doc)
Arg.(
value
& opt (some string) None
& info [ "bs-package-name"; "mel-package-name" ] ~doc)

let bs_module_name =
let doc =
"Set the module name (if different than the compilation unit name)"
in
Arg.(value & opt (some string) None & info [ "bs-module-name" ] ~doc)
Arg.(
value
& opt (some string) None
& info [ "bs-module-name"; "mel-module-name" ] ~doc)

let unboxed_types =
let doc = "Unannotated unboxable types will be unboxed" in
Expand Down Expand Up @@ -215,7 +221,7 @@ let bin_annot =
info ~doc:"Enable binary annotations (default: on)" [ "bin-annot" ] );
( Some false,
info ~doc:"Disable binary annotations (default: on)"
[ "bs-no-bin-annot" ] );
[ "bs-no-bin-annot"; "-no-bin-annot" ] );
])

let i =
Expand All @@ -240,15 +246,17 @@ let warn_error =

let bs_stop_after_cmj =
let doc = "Stop after generating the cmj" in
Arg.(value & flag & info [ "bs-stop-after-cmj" ] ~doc)
Arg.(value & flag & info [ "bs-stop-after-cmj"; "mel-stop-after-cmj" ] ~doc)

module Internal = struct
let bs_package_output =
let doc =
"*internal* Set npm-output-path: [opt_module]:path, for example: \
'lib/cjs', 'amdjs:lib/amdjs', 'es6:lib/es6' "
in
Arg.(value & opt_all string [] & info [ "bs-package-output" ] ~doc)
Arg.(
value & opt_all string []
& info [ "bs-package-output"; "mel-package-output" ] ~doc)

let bs_module_type =
let module_system_conv =
Expand All @@ -267,7 +275,7 @@ module Internal = struct
Arg.(
value
& opt (some module_system_conv) None
& info [ "bs-module-type" ] ~doc ~docv)
& info [ "bs-module-type"; "mel-module-type" ] ~doc ~docv)

let as_ppx =
let doc = "*internal* As ppx for editor integration" in
Expand All @@ -283,11 +291,14 @@ module Internal = struct

let bs_gentype =
let doc = "*internal* Pass gentype command" in
Arg.(value & opt (some string) None & info [ "bs-gentype" ] ~doc)
Arg.(
value & opt (some string) None & info [ "bs-gentype"; "mel-gentype" ] ~doc)

let bs_unsafe_empty_array =
let doc = "*internal* Allow [||] to be polymorphic" in
Arg.(value & flag & info [ "bs-unsafe-empty-array" ] ~doc)
Arg.(
value & flag
& info [ "bs-unsafe-empty-array"; "mel-unsafe-empty-array" ] ~doc)

let nostdlib =
let doc = "*internal* Don't use stdlib" in
Expand All @@ -297,15 +308,17 @@ module Internal = struct
let doc =
"*internal* (experimental) set the string to be evaluated in OCaml syntax"
in
Arg.(value & opt (some string) None & info [ "bs-eval" ] ~doc)
Arg.(value & opt (some string) None & info [ "bs-eval"; "-eval" ] ~doc)

let bs_cmi_only =
let doc = "*internal* Stop after generating cmi file" in
Arg.(value & flag & info [ "bs-cmi-only" ] ~doc)
Arg.(value & flag & info [ "bs-cmi-only"; "mel-cmi-only" ] ~doc)

let bs_no_version_header =
let doc = "*internal* Don't print version header" in
Arg.(value & flag & info [ "bs-no-version-header" ] ~doc)
Arg.(
value & flag
& info [ "bs-no-version-header"; "mel-no-version-header" ] ~doc)

let bs_cross_module_opt =
Arg.(
Expand All @@ -316,25 +329,27 @@ module Internal = struct
~doc:
"*internal* Enable cross module inlining(experimental), \
default(false)"
[ "bs-cross-module-opt" ] );
[ "bs-cross-module-opt"; "mel-cross-module-opt" ] );
( Some false,
info ~doc:"*internal* Disable cross module inlining(experimental)"
[ "bs-no-cross-module-opt" ] );
[ "bs-no-cross-module-opt"; "mel-no-cross-module-opt" ] );
])

let bs_diagnose =
let doc = "*internal* More verbose output" in
Arg.(value & flag & info [ "bs-diagnose" ] ~doc)
Arg.(value & flag & info [ "bs-diagnose"; "mel-diagnose" ] ~doc)

let bs_no_check_div_by_zero =
let doc =
"*internal* unsafe mode, don't check div by zero and mod by zero"
in
Arg.(value & flag & info [ "bs-no-check-div-by-zero" ] ~doc)
Arg.(
value & flag
& info [ "bs-no-check-div-by-zero"; "mel-no-check-div-by-zero" ] ~doc)

let bs_noassertfalse =
let doc = "*internal* no code for assert false" in
Arg.(value & flag & info [ "bs-noassertfalse" ] ~doc)
Arg.(value & flag & info [ "bs-noassertfalse"; "mel-noassertfalse" ] ~doc)

let noassert =
let doc = "*internal* Do not compile assertion checks" in
Expand All @@ -344,7 +359,7 @@ module Internal = struct
let doc =
"*internal* dont display location with -dtypedtree, -dparsetree"
in
Arg.(value & flag & info [ "bs-loc" ] ~doc)
Arg.(value & flag & info [ "bs-loc"; "mel-loc" ] ~doc)

let impl =
let doc = "*internal* Compile $(docv) as a .ml file" in
Expand Down
16 changes: 8 additions & 8 deletions jscomp/core/js_packages_info.ml
Original file line number Diff line number Diff line change
Expand Up @@ -50,7 +50,7 @@ let same_package_by_name (x : t) (y : t) =

(**
TODO: not allowing user to provide such specific package name
For empty package, [-bs-package-output] does not make sense
For empty package, [-mel-package-output] does not make sense
it is only allowed to generate commonjs file in the same directory
*)
let empty : t = { name = None; info = Empty }
Expand Down Expand Up @@ -170,11 +170,11 @@ let add_npm_package_path (t : t) ?module_name s =
let new_info =
match Ext_string.split ~keep_empty:true s ':' with
| [ path ] ->
(* `--bs-package-output just/the/path/segment' means module system
(* `--mel-package-output just/the/path/segment' means module system
/ js extension to come later; separate emission *)
Separate_emission { module_path = path; module_name }
| [ module_system; path ] ->
(* `--bs-package-output module_system:the/path/segment' assumes
(* `--mel-package-output module_system:the/path/segment' assumes
`.js' extension. This is batch compilation (`.cmj' + `.js'
emitted). *)
Batch_compilation
Expand All @@ -189,7 +189,7 @@ let add_npm_package_path (t : t) ?module_name s =
}
:: existing)
| [ module_system; path; suffix ] ->
(* `--bs-package-output module_system:the/path/segment:.ext', batch
(* `--mel-package-output module_system:the/path/segment:.ext', batch
compilation with all info. *)
Batch_compilation
({
Expand All @@ -208,8 +208,8 @@ let add_npm_package_path (t : t) ?module_name s =
| Separate_emission _ ->
raise
(Arg.Bad
"Can't add multiple `-bs-package-output` specs when \
`-bs-stop-after-cmj` is present")
"Can't add multiple `--mel-package-output` specs when \
`--mel-stop-after-cmj` is present")

let is_lower_case c =
(c >= 'a' && c <= 'z')
Expand Down Expand Up @@ -237,8 +237,8 @@ let assemble_output_info (t : t) =
| Batch_compilation infos ->
List.map (fun { output_info; _ } -> output_info) infos
| Separate_emission _ ->
(* Combination of `-bs-package-output -just-dir` and the absence of
`-bs-module-type` *)
(* Combination of `-mel-package-output -just-dir` and the absence of
`-mel-module-type` *)
[ default_output_info ]

(* support es6 modules instead
Expand Down
7 changes: 2 additions & 5 deletions jscomp/core/js_packages_info.mli
Original file line number Diff line number Diff line change
Expand Up @@ -36,9 +36,7 @@ val dump_output_info : Format.formatter -> output_info -> unit
val dump_packages_info : Format.formatter -> t -> unit

val add_npm_package_path : t -> ?module_name:string -> string -> t
(** used by command line option
e.g [-bs-package-output commonjs:xx/path]
*)
(** used by command line option e.g [-mel-package-output commonjs:xx/path] *)

type file_case = Uppercase | Lowercase

Expand All @@ -59,8 +57,7 @@ val get_output_dir : t -> package_dir:string -> Ext_module_system.t -> string
val query_package_infos : t -> Ext_module_system.t -> info_query

(* Note here we compare the package info by order
in theory, we can compare it by set semantics
*)
in theory, we can compare it by set semantics *)

val default_output_info : output_info
val assemble_output_info : t -> output_info list
2 changes: 1 addition & 1 deletion jscomp/core/lam_compile_main.cppo.ml
Original file line number Diff line number Diff line change
Expand Up @@ -339,7 +339,7 @@ let lambda_as_module
| false, None ->
raise (Arg.Bad ("no output specified (use -o <filename>.js)"))
| (_, Some _) ->
(* We use `-bs-module-type` to emit a single JS file after `.cmj`
(* We use `-mel-module-type` to emit a single JS file after `.cmj`
generation. In this case, we don't want the `package_info` from the
`.cmj`, because the suffix and paths will be different. *)
List.iter (fun (output_info : Js_packages_info.output_info) ->
Expand Down
2 changes: 1 addition & 1 deletion jscomp/others/belt_List.ml
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@
]}
*)

[@@@mel.config { flags = [| "-bs-noassertfalse" |] }]
[@@@mel.config { flags = [| "-mel-noassertfalse" |] }]

type 'a t = 'a list

Expand Down
2 changes: 1 addition & 1 deletion jscomp/others/belt_Set.mli
Original file line number Diff line number Diff line change
Expand Up @@ -244,7 +244,7 @@ val reduce : ('value, 'id) t -> 'a -> ('a -> 'value -> 'a) -> 'a
{[
let s0 = fromArray ~id:(module IntCmp) [|5;2;3;5;6|]];;
reduce s0 [] Bs.List.add = [6;5;3;2];;
reduce s0 [] Belt.List.add = [6;5;3;2];;
]}
*)

Expand Down
2 changes: 1 addition & 1 deletion jscomp/others/belt_internalAVLset.ml
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. *)
[@@@mel.config { flags = [| "-bs-noassertfalse" |] }]
[@@@mel.config { flags = [| "-mel-noassertfalse" |] }]

type 'value node = {
mutable value : 'value; [@mel.as "v"]
Expand Down
2 changes: 1 addition & 1 deletion jscomp/others/belt_internalAVLtree.ml
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@
(***********************************************************************)
(* Almost rewritten by authors of ReScript *)

[@@@mel.config { flags = [| "-bs-noassertfalse" |] }]
[@@@mel.config { flags = [| "-mel-noassertfalse" |] }]

type ('k, 'v) node = {
mutable key : 'k; [@mel.as "k"]
Expand Down
12 changes: 6 additions & 6 deletions jscomp/others/dune
Original file line number Diff line number Diff line change
Expand Up @@ -20,8 +20,8 @@
dom_storage
dom_storage2)
(melange.compile_flags
-bs-no-check-div-by-zero
-bs-cross-module-opt
-mel-no-check-div-by-zero
-mel-cross-module-opt
-unsafe
-nopervasives
-nostdlib
Expand All @@ -36,8 +36,8 @@
(pps melange.ppx -unsafe))
(modules dom dom_storage dom_storage2)
(melange.compile_flags
-bs-no-check-div-by-zero
-bs-cross-module-opt
-mel-no-check-div-by-zero
-mel-cross-module-opt
-unsafe
-nopervasives
-nostdlib))
Expand Down Expand Up @@ -69,8 +69,8 @@
node_process)
(stdlib)
(melange.compile_flags
-bs-no-check-div-by-zero
-bs-cross-module-opt
-mel-no-check-div-by-zero
-mel-cross-module-opt
-unsafe
-open
Js__Melange_mini_stdlib))
Expand Down
2 changes: 1 addition & 1 deletion jscomp/others/internal_map.cppo.ml
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
[@@@mel.config {flags = [| "-bs-noassertfalse" |]}]
[@@@mel.config {flags = [| "-mel-noassertfalse" |]}]
#ifdef TYPE_STRING
type key = string
#elif defined TYPE_INT
Expand Down
2 changes: 1 addition & 1 deletion jscomp/runtime/caml_hash.ml
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. *)
[@@@mel.config { flags = [| "-bs-noassertfalse" |] }]
[@@@mel.config { flags = [| "-mel-noassertfalse" |] }]

open Melange_mini_stdlib

Expand Down
4 changes: 2 additions & 2 deletions jscomp/runtime/dune
Original file line number Diff line number Diff line change
Expand Up @@ -7,8 +7,8 @@
(melange.compile_flags
-nopervasives
-nostdlib
-bs-no-check-div-by-zero
-bs-cross-module-opt
-mel-no-check-div-by-zero
-mel-cross-module-opt
-unsafe))

(rule
Expand Down
3 changes: 1 addition & 2 deletions jscomp/stdlib/camlinternalLazy.ml
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. *)

[@@@mel.config { flags = [|"-bs-no-cross-module-opt" |]}]
[@@@mel.config { flags = [|"--mel-no-cross-module-opt" |]}]
(* Internals of forcing lazy values. *)

type 'a t = 'a lazy_t
Expand Down Expand Up @@ -95,4 +95,3 @@ let force_val (type a) (lzv : a lazy_t) : a =
let lzv : _ concrete = castToConcrete lzv in
if lzv.tag then lzv.value else
force_val_lazy_block (of_concrete lzv)

4 changes: 2 additions & 2 deletions jscomp/stdlib/dune
Original file line number Diff line number Diff line change
Expand Up @@ -37,8 +37,8 @@
(modules_before_stdlib CamlinternalFormatBasics CamlinternalAtomic)
(internal_modules Camlinternal*))
(melange.compile_flags
-bs-no-check-div-by-zero
-bs-cross-module-opt
-mel-no-check-div-by-zero
-mel-cross-module-opt
-nolabels
-w
-9))
Expand Down
2 changes: 1 addition & 1 deletion jscomp/stdlib/sys.cppo.ml
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
[@@@mel.config { flags = [|"-bs-no-cross-module-opt"; |]}]
[@@@mel.config { flags = [|"--mel-no-cross-module-opt"; |]}]
#2 "stdlib/sys.mlp"
(**************************************************************************)
(* *)
Expand Down

0 comments on commit a3d407c

Please sign in to comment.