Skip to content

Commit 506ac55

Browse files
committed
1 parent f94ab0e commit 506ac55

8 files changed

+3271
-689
lines changed

jscomp/bin/all_ounit_tests.ml

+902-117
Large diffs are not rendered by default.

jscomp/build_sorted.ml

+228
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,228 @@
1+
(* Copyright (C) 2019-Present Authors of BuckleScript
2+
*
3+
* This program is free software: you can redistribute it and/or modify
4+
* it under the terms of the GNU Lesser General Public License as published by
5+
* the Free Software Foundation, either version 3 of the License, or
6+
* (at your option) any later version.
7+
*
8+
* In addition to the permissions granted to you by the LGPL, you may combine
9+
* or link a "work that uses the Library" with a publicly distributed version
10+
* of this file to produce a combined library or application, then distribute
11+
* that combined work under the terms of your choosing, with no requirement
12+
* to comply with the obligations normally placed on you by section 4 of the
13+
* LGPL version 3 (or the corresponding section of a later version of the LGPL
14+
* should you choose to use a later version).
15+
*
16+
* This program is distributed in the hope that it will be useful,
17+
* but WITHOUT ANY WARRANTY; without even the implied warranty of
18+
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
19+
* GNU Lesser General Public License for more details.
20+
*
21+
* You should have received a copy of the GNU Lesser General Public License
22+
* along with this program; if not, write to the Free Software
23+
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. *)
24+
25+
let reserved_words =
26+
[|
27+
(* keywork *)
28+
"break";
29+
"case"; "catch"; "continue";
30+
"debugger";"default";"delete";"do";
31+
"else";
32+
"finally";"for";"function";
33+
"if"; "then"; "in";"instanceof";
34+
"new";
35+
"return";
36+
"switch";
37+
"this"; "throw"; "try"; "typeof";
38+
"var"; "void"; "while"; "with";
39+
40+
(* reserved in ECMAScript 5 *)
41+
"class"; "enum"; "export"; "extends"; "import"; "super";
42+
43+
"implements";"interface";
44+
"let";
45+
"package";"private";"protected";"public";
46+
"static";
47+
"yield";
48+
49+
(* other *)
50+
"null";
51+
"true";
52+
"false";
53+
"NaN";
54+
55+
56+
"undefined";
57+
"this";
58+
59+
(* also reserved in ECMAScript 3 *)
60+
"abstract"; "boolean"; "byte"; "char"; "const"; "double";
61+
"final"; "float"; "goto"; "int"; "long"; "native"; "short";
62+
"synchronized";
63+
(* "throws"; *)
64+
(* seems to be fine, like nodejs [assert.throws] *)
65+
"transient"; "volatile";
66+
67+
(* also reserved in ECMAScript 6 *)
68+
"await";
69+
70+
"event";
71+
"location";
72+
"window";
73+
"document";
74+
"eval";
75+
"navigator";
76+
(* "self"; *)
77+
78+
"Array";
79+
"Date";
80+
"Math";
81+
"JSON";
82+
"Object";
83+
"RegExp";
84+
"String";
85+
"Boolean";
86+
"Number";
87+
"Buffer"; (* Node *)
88+
"Map"; (* es6*)
89+
"Set";
90+
"Promise";
91+
"Infinity";
92+
"isFinite";
93+
94+
"ActiveXObject";
95+
"XMLHttpRequest";
96+
"XDomainRequest";
97+
98+
"DOMException";
99+
"Error";
100+
"SyntaxError";
101+
"arguments";
102+
103+
"decodeURI";
104+
"decodeURIComponent";
105+
"encodeURI";
106+
"encodeURIComponent";
107+
"escape";
108+
"unescape";
109+
110+
"isNaN";
111+
"parseFloat";
112+
"parseInt";
113+
114+
(** reserved for commonjs and NodeJS globals*)
115+
"require";
116+
"exports";
117+
"module";
118+
"clearImmediate";
119+
"clearInterval";
120+
"clearTimeout";
121+
"console";
122+
"global";
123+
"process";
124+
"require";
125+
"setImmediate";
126+
"setInterval";
127+
"setTimeout";
128+
"__dirname";
129+
"__filename";
130+
"__esModule"
131+
|]
132+
133+
134+
module SSet = Set.Make(String)
135+
let get_predefined_words (fn : string) =
136+
let v = ref SSet.empty in
137+
let in_chan = open_in_bin fn in
138+
(try
139+
while true do
140+
let new_word = input_line in_chan in
141+
if String.length new_word <> 0 then
142+
v := SSet.add new_word !v
143+
done
144+
with End_of_file -> ());
145+
!v
146+
147+
let fill_extra (ss : SSet.t) : SSet.t =
148+
let v = ref ss in
149+
for i = 0 to Array.length reserved_words - 1 do
150+
v := SSet.add reserved_words.(i) !v
151+
done;
152+
!v
153+
let license = {|
154+
(* Copyright (C) 2019-Present Authors of BuckleScript
155+
*
156+
* This program is free software: you can redistribute it and/or modify
157+
* it under the terms of the GNU Lesser General Public License as published by
158+
* the Free Software Foundation, either version 3 of the License, or
159+
* (at your option) any later version.
160+
*
161+
* In addition to the permissions granted to you by the LGPL, you may combine
162+
* or link a "work that uses the Library" with a publicly distributed version
163+
* of this file to produce a combined library or application, then distribute
164+
* that combined work under the terms of your choosing, with no requirement
165+
* to comply with the obligations normally placed on you by section 4 of the
166+
* LGPL version 3 (or the corresponding section of a later version of the LGPL
167+
* should you choose to use a later version).
168+
*
169+
* This program is distributed in the hope that it will be useful,
170+
* but WITHOUT ANY WARRANTY; without even the implied warranty of
171+
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
172+
* GNU Lesser General Public License for more details.
173+
*
174+
* You should have received a copy of the GNU Lesser General Public License
175+
* along with this program; if not, write to the Free Software
176+
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. *)
177+
178+
|}
179+
let binary_search = {|
180+
181+
type element = string
182+
183+
let rec binarySearchAux (arr : element array) (lo : int) (hi : int) key : bool =
184+
let mid = (lo + hi)/2 in
185+
let midVal = Array.unsafe_get arr mid in
186+
(* let c = cmp key midVal [@bs] in *)
187+
if key = midVal then true
188+
else if key < midVal then (* a[lo] =< key < a[mid] <= a[hi] *)
189+
if hi = mid then
190+
(Array.unsafe_get arr lo) = key
191+
else binarySearchAux arr lo mid key
192+
else (* a[lo] =< a[mid] < key <= a[hi] *)
193+
if lo = mid then
194+
(Array.unsafe_get arr hi) = key
195+
else binarySearchAux arr mid hi key
196+
197+
let binarySearch (sorted : element array) (key : element) : bool =
198+
let len = Array.length sorted in
199+
if len = 0 then false
200+
else
201+
let lo = Array.unsafe_get sorted 0 in
202+
(* let c = cmp key lo [@bs] in *)
203+
if key < lo then false
204+
else
205+
let hi = Array.unsafe_get sorted (len - 1) in
206+
(* let c2 = cmp key hi [@bs]in *)
207+
if key > hi then false
208+
else binarySearchAux sorted 0 (len - 1) key
209+
210+
let is_reserved s = binarySearch sorted_keywords s
211+
|}
212+
let main () =
213+
let ss = get_predefined_words "keywords.list" in
214+
let ss = fill_extra ss in
215+
let keywords_array =
216+
(SSet.fold
217+
(fun s acc -> acc ^ "\"" ^ s ^ "\";\n "
218+
) ss "let sorted_keywords = [|\n ") ^ "|]\n"
219+
in
220+
let oc = open_out_bin "ext/js_reserved_map.ml" in
221+
output_string oc license ;
222+
output_string oc keywords_array;
223+
output_string oc binary_search;
224+
close_out oc
225+
226+
let () = main ()
227+
228+

jscomp/compiler.ninja

+2-2
Original file line numberDiff line numberDiff line change
@@ -196,7 +196,7 @@ build ext/int_vec_util.cmx : optc ext/int_vec_util.ml | ext/int_vec.cmx ext/int_
196196
build ext/int_vec_util.cmi : optc ext/int_vec_util.mli | ext/int_vec.cmi
197197
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
198198
build ext/int_vec_vec.cmi : optc ext/int_vec_vec.mli | ext/int_vec.cmi ext/vec_gen.cmx
199-
build ext/js_reserved_map.cmx : optc ext/js_reserved_map.ml | ext/js_reserved_map.cmi ext/string_hash_set.cmx
199+
build ext/js_reserved_map.cmx : optc ext/js_reserved_map.ml | ext/js_reserved_map.cmi
200200
build ext/js_reserved_map.cmi : optc ext/js_reserved_map.mli |
201201
build ext/literals.cmx : optc ext/literals.ml | ext/literals.cmi
202202
build ext/literals.cmi : optc ext/literals.mli |
@@ -686,7 +686,7 @@ build main/jsoo_main.cmi : optc main/jsoo_main.mli |
686686
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
687687
build main/ounit_tests_main.cmi : optc main/ounit_tests_main.mli |
688688

689-
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
689+
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
690690
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
691691
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
692692
build depends/depends.cmxa : archive depends/bs_exception.cmx depends/ast_extract.cmx depends/binary_ast.cmx

0 commit comments

Comments
 (0)