Skip to content

Commit

Permalink
fix #3268
Browse files Browse the repository at this point in the history
  • Loading branch information
bobzhang committed Jan 14, 2019
1 parent f94ab0e commit 506ac55
Show file tree
Hide file tree
Showing 8 changed files with 3,271 additions and 689 deletions.
1,019 changes: 902 additions & 117 deletions jscomp/bin/all_ounit_tests.ml

Large diffs are not rendered by default.

228 changes: 228 additions & 0 deletions jscomp/build_sorted.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,228 @@
(* Copyright (C) 2019-Present Authors of BuckleScript
*
* This program is free software: you can redistribute it and/or modify
* it under the terms of the GNU Lesser General Public License as published by
* the Free Software Foundation, either version 3 of the License, or
* (at your option) any later version.
*
* In addition to the permissions granted to you by the LGPL, you may combine
* or link a "work that uses the Library" with a publicly distributed version
* of this file to produce a combined library or application, then distribute
* that combined work under the terms of your choosing, with no requirement
* to comply with the obligations normally placed on you by section 4 of the
* LGPL version 3 (or the corresponding section of a later version of the LGPL
* should you choose to use a later version).
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* 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. *)

let reserved_words =
[|
(* keywork *)
"break";
"case"; "catch"; "continue";
"debugger";"default";"delete";"do";
"else";
"finally";"for";"function";
"if"; "then"; "in";"instanceof";
"new";
"return";
"switch";
"this"; "throw"; "try"; "typeof";
"var"; "void"; "while"; "with";

(* reserved in ECMAScript 5 *)
"class"; "enum"; "export"; "extends"; "import"; "super";

"implements";"interface";
"let";
"package";"private";"protected";"public";
"static";
"yield";

(* other *)
"null";
"true";
"false";
"NaN";


"undefined";
"this";

(* also reserved in ECMAScript 3 *)
"abstract"; "boolean"; "byte"; "char"; "const"; "double";
"final"; "float"; "goto"; "int"; "long"; "native"; "short";
"synchronized";
(* "throws"; *)
(* seems to be fine, like nodejs [assert.throws] *)
"transient"; "volatile";

(* also reserved in ECMAScript 6 *)
"await";

"event";
"location";
"window";
"document";
"eval";
"navigator";
(* "self"; *)

"Array";
"Date";
"Math";
"JSON";
"Object";
"RegExp";
"String";
"Boolean";
"Number";
"Buffer"; (* Node *)
"Map"; (* es6*)
"Set";
"Promise";
"Infinity";
"isFinite";

"ActiveXObject";
"XMLHttpRequest";
"XDomainRequest";

"DOMException";
"Error";
"SyntaxError";
"arguments";

"decodeURI";
"decodeURIComponent";
"encodeURI";
"encodeURIComponent";
"escape";
"unescape";

"isNaN";
"parseFloat";
"parseInt";

(** reserved for commonjs and NodeJS globals*)
"require";
"exports";
"module";
"clearImmediate";
"clearInterval";
"clearTimeout";
"console";
"global";
"process";
"require";
"setImmediate";
"setInterval";
"setTimeout";
"__dirname";
"__filename";
"__esModule"
|]


module SSet = Set.Make(String)
let get_predefined_words (fn : string) =
let v = ref SSet.empty in
let in_chan = open_in_bin fn in
(try
while true do
let new_word = input_line in_chan in
if String.length new_word <> 0 then
v := SSet.add new_word !v
done
with End_of_file -> ());
!v

let fill_extra (ss : SSet.t) : SSet.t =
let v = ref ss in
for i = 0 to Array.length reserved_words - 1 do
v := SSet.add reserved_words.(i) !v
done;
!v
let license = {|
(* Copyright (C) 2019-Present Authors of BuckleScript
*
* This program is free software: you can redistribute it and/or modify
* it under the terms of the GNU Lesser General Public License as published by
* the Free Software Foundation, either version 3 of the License, or
* (at your option) any later version.
*
* In addition to the permissions granted to you by the LGPL, you may combine
* or link a "work that uses the Library" with a publicly distributed version
* of this file to produce a combined library or application, then distribute
* that combined work under the terms of your choosing, with no requirement
* to comply with the obligations normally placed on you by section 4 of the
* LGPL version 3 (or the corresponding section of a later version of the LGPL
* should you choose to use a later version).
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* 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. *)

|}
let binary_search = {|

type element = string

let rec binarySearchAux (arr : element array) (lo : int) (hi : int) key : bool =
let mid = (lo + hi)/2 in
let midVal = Array.unsafe_get arr mid in
(* let c = cmp key midVal [@bs] in *)
if key = midVal then true
else if key < midVal then (* a[lo] =< key < a[mid] <= a[hi] *)
if hi = mid then
(Array.unsafe_get arr lo) = key
else binarySearchAux arr lo mid key
else (* a[lo] =< a[mid] < key <= a[hi] *)
if lo = mid then
(Array.unsafe_get arr hi) = key
else binarySearchAux arr mid hi key

let binarySearch (sorted : element array) (key : element) : bool =
let len = Array.length sorted in
if len = 0 then false
else
let lo = Array.unsafe_get sorted 0 in
(* let c = cmp key lo [@bs] in *)
if key < lo then false
else
let hi = Array.unsafe_get sorted (len - 1) in
(* let c2 = cmp key hi [@bs]in *)
if key > hi then false
else binarySearchAux sorted 0 (len - 1) key

let is_reserved s = binarySearch sorted_keywords s
|}
let main () =
let ss = get_predefined_words "keywords.list" in
let ss = fill_extra ss in
let keywords_array =
(SSet.fold
(fun s acc -> acc ^ "\"" ^ s ^ "\";\n "
) ss "let sorted_keywords = [|\n ") ^ "|]\n"
in
let oc = open_out_bin "ext/js_reserved_map.ml" in
output_string oc license ;
output_string oc keywords_array;
output_string oc binary_search;
close_out oc

let () = main ()


4 changes: 2 additions & 2 deletions jscomp/compiler.ninja
Original file line number Diff line number Diff line change
Expand Up @@ -196,7 +196,7 @@ build ext/int_vec_util.cmx : optc ext/int_vec_util.ml | ext/int_vec.cmx ext/int_
build ext/int_vec_util.cmi : optc ext/int_vec_util.mli | ext/int_vec.cmi
build ext/int_vec_vec.cmx : optc ext/int_vec_vec.ml | ext/int_vec.cmx ext/int_vec_vec.cmi ext/resize_array.cmx
build ext/int_vec_vec.cmi : optc ext/int_vec_vec.mli | ext/int_vec.cmi ext/vec_gen.cmx
build ext/js_reserved_map.cmx : optc ext/js_reserved_map.ml | ext/js_reserved_map.cmi ext/string_hash_set.cmx
build ext/js_reserved_map.cmx : optc ext/js_reserved_map.ml | ext/js_reserved_map.cmi
build ext/js_reserved_map.cmi : optc ext/js_reserved_map.mli |
build ext/literals.cmx : optc ext/literals.ml | ext/literals.cmi
build ext/literals.cmi : optc ext/literals.mli |
Expand Down Expand Up @@ -686,7 +686,7 @@ build main/jsoo_main.cmi : optc main/jsoo_main.mli |
build main/ounit_tests_main.cmx : optc main/ounit_tests_main.ml | ext/resize_array.cmx main/ounit_tests_main.cmi ounit/oUnit.cmx ounit_tests/ounit_array_tests.cmx ounit_tests/ounit_bal_tree_tests.cmx ounit_tests/ounit_bsb_pkg_tests.cmx ounit_tests/ounit_bsb_regex_tests.cmx ounit_tests/ounit_cmd_tests.cmx ounit_tests/ounit_ffi_error_debug_test.cmx ounit_tests/ounit_hash_set_tests.cmx ounit_tests/ounit_hash_stubs_test.cmx ounit_tests/ounit_hashtbl_tests.cmx ounit_tests/ounit_ident_mask_tests.cmx ounit_tests/ounit_int_vec_tests.cmx ounit_tests/ounit_js_regex_checker_tests.cmx ounit_tests/ounit_json_tests.cmx ounit_tests/ounit_list_test.cmx ounit_tests/ounit_map_tests.cmx ounit_tests/ounit_ordered_hash_set_tests.cmx ounit_tests/ounit_path_tests.cmx ounit_tests/ounit_scc_tests.cmx ounit_tests/ounit_string_tests.cmx ounit_tests/ounit_topsort_tests.cmx ounit_tests/ounit_unicode_tests.cmx ounit_tests/ounit_union_find_tests.cmx ounit_tests/ounit_utf8_test.cmx ounit_tests/ounit_vec_test.cmx
build main/ounit_tests_main.cmi : optc main/ounit_tests_main.mli |

build ext/ext.cmxa : archive ext/ext_array.cmx ext/ext_bytes.cmx ext/ext_char.cmx ext/ext_cmp.cmx ext/ext_string.cmx ext/ext_list.cmx ext/ext_color.cmx ext/vec_gen.cmx ext/resize_array.cmx ext/string_vec.cmx ext/ext_file_pp.cmx ext/literals.cmx ext/ext_pervasives.cmx ext/ext_sys.cmx ext/ext_path.cmx ext/ext_filename.cmx ext/ext_format.cmx ext/ext_util.cmx ext/hashtbl_gen.cmx ext/string_hashtbl.cmx ext/hash_set_gen.cmx ext/string_hash_set.cmx ext/js_reserved_map.cmx ext/ext_ident.cmx ext/ext_int.cmx ext/ext_io.cmx ext/ext_utf8.cmx ext/ext_js_regex.cmx ext/map_gen.cmx ext/string_map.cmx ext/ext_json_types.cmx ext/ext_json.cmx ext/ext_json_noloc.cmx ext/ext_position.cmx ext/ext_json_parse.cmx ext/ext_json_write.cmx ext/ext_marshal.cmx ext/ext_modulename.cmx ext/ext_namespace.cmx ext/ext_option.cmx ext/ext_pp.cmx ext/int_map.cmx ext/set_gen.cmx ext/ident_set.cmx ext/ext_pp_scope.cmx ext/ext_ref.cmx ext/int_vec.cmx ext/int_vec_vec.cmx ext/ext_scc.cmx ext/ext_stack.cmx ext/set_int.cmx ext/ext_topsort.cmx ext/hash_set.cmx ext/hash_set_ident_mask.cmx ext/hash_set_poly.cmx ext/hashtbl_make.cmx ext/ident_hash_set.cmx ext/ident_hashtbl.cmx ext/ident_map.cmx ext/int_hash_set.cmx ext/int_hashtbl.cmx ext/int_vec_util.cmx ext/ordered_hash_map_gen.cmx ext/ordered_hash_map_local_ident.cmx ext/ordered_hash_set_gen.cmx ext/ordered_hash_set_ident.cmx ext/ordered_hash_set_make.cmx ext/ordered_hash_set_string.cmx ext/string_set.cmx ext/union_find.cmx
build ext/ext.cmxa : archive ext/ext_array.cmx ext/ext_bytes.cmx ext/ext_char.cmx ext/ext_cmp.cmx ext/ext_string.cmx ext/ext_list.cmx ext/ext_color.cmx ext/vec_gen.cmx ext/resize_array.cmx ext/string_vec.cmx ext/ext_file_pp.cmx ext/literals.cmx ext/ext_pervasives.cmx ext/ext_sys.cmx ext/ext_path.cmx ext/ext_filename.cmx ext/ext_format.cmx ext/ext_util.cmx ext/hashtbl_gen.cmx ext/string_hashtbl.cmx ext/js_reserved_map.cmx ext/ext_ident.cmx ext/ext_int.cmx ext/ext_io.cmx ext/ext_utf8.cmx ext/ext_js_regex.cmx ext/map_gen.cmx ext/string_map.cmx ext/ext_json_types.cmx ext/ext_json.cmx ext/ext_json_noloc.cmx ext/ext_position.cmx ext/ext_json_parse.cmx ext/ext_json_write.cmx ext/ext_marshal.cmx ext/ext_modulename.cmx ext/ext_namespace.cmx ext/ext_option.cmx ext/ext_pp.cmx ext/int_map.cmx ext/set_gen.cmx ext/ident_set.cmx ext/ext_pp_scope.cmx ext/ext_ref.cmx ext/int_vec.cmx ext/int_vec_vec.cmx ext/ext_scc.cmx ext/ext_stack.cmx ext/set_int.cmx ext/ext_topsort.cmx ext/hash_set_gen.cmx ext/hash_set.cmx ext/hash_set_ident_mask.cmx ext/hash_set_poly.cmx ext/hashtbl_make.cmx ext/ident_hash_set.cmx ext/ident_hashtbl.cmx ext/ident_map.cmx ext/int_hash_set.cmx ext/int_hashtbl.cmx ext/int_vec_util.cmx ext/ordered_hash_map_gen.cmx ext/ordered_hash_map_local_ident.cmx ext/ordered_hash_set_gen.cmx ext/ordered_hash_set_ident.cmx ext/ordered_hash_set_make.cmx ext/ordered_hash_set_string.cmx ext/string_hash_set.cmx ext/string_set.cmx ext/union_find.cmx
build common/common.cmxa : archive common/bs_loc.cmx common/bs_version.cmx common/js_config.cmx common/bs_warnings.cmx common/ext_log.cmx common/lam_methname.cmx common/ml_binary.cmx
build syntax/syntax.cmxa : archive syntax/bs_syntaxerr.cmx syntax/bs_ast_iterator.cmx syntax/ast_utf8_string.cmx syntax/ast_compatible.cmx syntax/ast_utf8_string_interp.cmx syntax/ast_literal.cmx syntax/ast_comb.cmx syntax/ast_core_type.cmx syntax/bs_ast_invariant.cmx syntax/ast_payload.cmx syntax/ast_attributes.cmx syntax/bs_ast_mapper.cmx syntax/external_arg_spec.cmx syntax/external_ffi_types.cmx syntax/ast_polyvar.cmx syntax/external_process.cmx syntax/ast_pat.cmx syntax/ast_external_mk.cmx syntax/ast_exp.cmx syntax/ast_util.cmx syntax/ast_core_type_class_type.cmx syntax/ast_signature.cmx syntax/ast_structure.cmx syntax/ast_derive.cmx syntax/ast_derive_util.cmx syntax/ast_derive_abstract.cmx syntax/ast_derive_constructor.cmx syntax/ast_derive_dyn.cmx syntax/ast_derive_js_mapper.cmx syntax/ast_derive_projector.cmx syntax/ast_tuple_pattern_flatten.cmx syntax/ast_exp_apply.cmx syntax/ast_exp_extension.cmx syntax/ast_lift.cmx syntax/ast_primitive.cmx syntax/ast_tdcls.cmx syntax/ppx_entry.cmx
build depends/depends.cmxa : archive depends/bs_exception.cmx depends/ast_extract.cmx depends/binary_ast.cmx
Expand Down

0 comments on commit 506ac55

Please sign in to comment.