Explorar el Código

Merge pull request #3971 from nadako/cs_java_fast_dynamicobject

[cs/java] use native arrays for DynamicObject (see #3945)
Cauê Waneck hace 10 años
padre
commit
fdcca0046d
Se han modificado 5 ficheros con 378 adiciones y 121 borrados
  1. 119 107
      gencommon.ml
  2. 39 4
      gencs.ml
  3. 35 5
      genjava.ml
  4. 117 2
      std/cs/internal/FieldLookup.hx
  5. 68 3
      std/java/internal/FieldLookup.hx

+ 119 - 107
gencommon.ml

@@ -632,8 +632,9 @@ and gen_classes =
 
 	t_iterator : tdef;
 
-	a_vector : tabstract;
-	tvector : Type.t -> Type.t;
+	mutable nativearray_len : texpr -> pos -> texpr;
+	mutable nativearray_type : Type.t -> Type.t;
+	mutable nativearray : Type.t -> Type.t;
 }
 
 (* add here all reflection transformation additions *)
@@ -691,8 +692,9 @@ let new_ctx con =
 
 			t_iterator = get_tdef (get_type con.types ([], "Iterator"));
 
-			a_vector = get_abstract (get_type con.types (["haxe";"ds"],"Vector"));
-			tvector = (fun t -> TAbstract(gen.gclasses.a_vector,[t]));
+			nativearray = (fun _ -> assert false);
+			nativearray_type = (fun _ -> assert false);
+			nativearray_len = (fun _ -> assert false);
 		};
 		gtools = {
 			r_create_empty = (fun eclass t ->
@@ -1213,12 +1215,11 @@ let mk_temp gen name t =
 	let name = gen.gmk_internal_name "temp" (name ^ (string_of_int !tmp_count)) in
 	alloc_var name t
 
-let mk_vector_decl =
-	let v_vector = alloc_var "__array__" t_dynamic in
-	fun gen t el pos ->
+let v_nativearray = alloc_var "__array__" t_dynamic
+let mk_nativearray_decl gen t el pos =
 	{
-		eexpr = TCall(mk_local v_vector pos, el);
-		etype = gen.gclasses.tvector t;
+		eexpr = TCall(mk_local v_nativearray pos, el);
+		etype = gen.gclasses.nativearray t;
 		epos = pos;
 	}
 
@@ -6828,12 +6829,18 @@ struct
 			its only needed features is that it should return the index of the key if found, and the
 			complement of the index of where it should be inserted if not found (Ints).
 
-			hash->hash_array->returning expression
+			hash->hash_array->length->returning expression
 		*)
-		mutable rcf_hash_function : texpr->texpr->texpr;
+		mutable rcf_hash_function : texpr->texpr->texpr->texpr;
 
 		mutable rcf_lookup_function : texpr->texpr;
 
+		(* hash_array->length->pos->value *)
+		mutable rcf_insert_function : texpr->texpr->texpr->texpr->texpr;
+
+		(* hash_array->length->pos->value *)
+		mutable rcf_remove_function : texpr->texpr->texpr->texpr;
+
 		(*
 			class_cl is the real class for Class<> instances.
 			In the current implementation, due to some targets' limitations, (in particular, Java),
@@ -6862,7 +6869,7 @@ struct
 		mutable rcf_handle_statics : bool;
 	}
 
-	let new_ctx gen ft object_iface optimize dynamic_getset_field dynamic_call_field hash_function lookup_function handle_statics =
+	let new_ctx gen ft object_iface optimize dynamic_getset_field dynamic_call_field hash_function lookup_function insert_function remove_function handle_statics =
 		{
 			rcf_gen = gen;
 			rcf_ft = ft;
@@ -6884,6 +6891,9 @@ struct
 			rcf_hash_function = hash_function;
 			rcf_lookup_function = lookup_function;
 
+			rcf_insert_function = insert_function;
+			rcf_remove_function = remove_function;
+
 			rcf_class_cl = None;
 			rcf_class_eager_creation = false;
 
@@ -7047,21 +7057,18 @@ struct
 		let basic = gen.gcon.basic in
 		let pos = cl.cl_pos in
 
-		let vtmp = mk_temp gen "i" basic.tint in
-		let vlen = mk_temp gen "len" basic.tint in
+		let vtmp = alloc_var "i" basic.tint in
 
-		let mk_for arr =
+		let mk_for arr len =
 			let t = if ctx.rcf_optimize then basic.tint else basic.tstring in
 			let convert_str e = if ctx.rcf_optimize then ctx.rcf_lookup_function e else e in
-			let lenlocal = mk_local vlen pos in
 			let tmpinc = { eexpr = TUnop(Ast.Increment, Ast.Postfix, mk_local vtmp pos); etype = basic.tint; epos = pos } in
 			{
 				eexpr = TBlock [
 					{ eexpr = TBinop(OpAssign, mk_local vtmp pos, mk_int ctx 0 pos); etype = basic.tint; epos = pos };
-					{ eexpr = TBinop(OpAssign, lenlocal, mk_field_access gen arr "length" pos); etype = basic.tint; epos = pos };
 					{
 						eexpr = TWhile (
-							{ eexpr = TBinop(Ast.OpLt, mk_local vtmp pos, lenlocal); etype = basic.tbool; epos = pos },
+							{ eexpr = TBinop(Ast.OpLt, mk_local vtmp pos, len); etype = basic.tbool; epos = pos },
 							mk_block (when_found (convert_str { eexpr = TArray (arr, tmpinc); etype = t; epos = pos })),
 							Ast.NormalWhile
 						);
@@ -7077,18 +7084,16 @@ struct
 		let this_t = TInst(cl, List.map snd cl.cl_params) in
 		let this = { eexpr = TConst(TThis); etype = this_t; epos = pos } in
 		let mk_this field t = { (mk_field_access gen this field pos) with etype = t } in
-		[
-			{ eexpr = TVar (vtmp,None); etype = basic.tvoid; epos = pos };
-			{ eexpr = TVar (vlen,None); etype = basic.tvoid; epos = pos };
-		]
-		@
+
+		{ eexpr = TVar (vtmp,None); etype = basic.tvoid; epos = pos }
+		::
 		if ctx.rcf_optimize then
 		[
-			mk_for (mk_this (gen.gmk_internal_name "hx" "hashes") (basic.tarray basic.tint));
-			mk_for (mk_this (gen.gmk_internal_name "hx" "hashes_f") (basic.tarray basic.tint));
+			mk_for (mk_this (gen.gmk_internal_name "hx" "hashes") (gen.gclasses.nativearray basic.tint)) (mk_this (gen.gmk_internal_name "hx" "length") basic.tint);
+			mk_for (mk_this (gen.gmk_internal_name "hx" "hashes_f") (gen.gclasses.nativearray basic.tint)) (mk_this (gen.gmk_internal_name "hx" "length_f") basic.tint);
 		] else [
-			mk_for (mk_this (gen.gmk_internal_name "hx" "hashes") (basic.tarray basic.tstring));
-			mk_for (mk_this (gen.gmk_internal_name "hx" "hashes_f") (basic.tarray basic.tstring));
+			mk_for (mk_this (gen.gmk_internal_name "hx" "hashes") (gen.gclasses.nativearray basic.tstring)) (mk_this (gen.gmk_internal_name "hx" "length") basic.tint);
+			mk_for (mk_this (gen.gmk_internal_name "hx" "hashes_f") (gen.gclasses.nativearray basic.tstring)) (mk_this (gen.gmk_internal_name "hx" "length_f") basic.tint);
 		]
 
 	(* *********************
@@ -7108,13 +7113,18 @@ struct
 		let basic = gen.gcon.basic in
 		let mk_this field t = { (mk_field_access gen this field pos) with etype = t } in
 		let a_t = if ctx.rcf_optimize then basic.tint else basic.tstring in
-		let hx_hashes = mk_this (gen.gmk_internal_name "hx" "hashes") (basic.tarray a_t) in
-		let hx_hashes_f = mk_this (gen.gmk_internal_name "hx" "hashes_f") (basic.tarray a_t) in
-		let hx_dynamics = mk_this (gen.gmk_internal_name "hx" "dynamics") (basic.tarray t_empty) in
-		let hx_dynamics_f = mk_this (gen.gmk_internal_name "hx" "dynamics_f") (basic.tarray basic.tfloat) in
+		let hx_hashes = mk_this (gen.gmk_internal_name "hx" "hashes") (gen.gclasses.nativearray a_t) in
+		let hx_hashes_f = mk_this (gen.gmk_internal_name "hx" "hashes_f") (gen.gclasses.nativearray a_t) in
+		let hx_dynamics = mk_this (gen.gmk_internal_name "hx" "dynamics") (gen.gclasses.nativearray t_empty) in
+		let hx_dynamics_f = mk_this (gen.gmk_internal_name "hx" "dynamics_f") (gen.gclasses.nativearray basic.tfloat) in
+		let hx_length = mk_this (gen.gmk_internal_name "hx" "length") (basic.tint) in
+		let hx_length_f = mk_this (gen.gmk_internal_name "hx" "length_f") (basic.tint) in
 		let res = alloc_var "res" basic.tint in
-		let fst_hash, snd_hash, fst_dynamics, snd_dynamics =
-			if is_float then hx_hashes_f, hx_hashes, hx_dynamics_f, hx_dynamics else hx_hashes, hx_hashes_f, hx_dynamics, hx_dynamics_f
+		let fst_hash, snd_hash, fst_dynamics, snd_dynamics, fst_length, snd_length =
+			if is_float then
+				hx_hashes_f, hx_hashes, hx_dynamics_f, hx_dynamics, hx_length_f, hx_length
+			else
+				hx_hashes, hx_hashes_f, hx_dynamics, hx_dynamics_f, hx_length, hx_length_f
 		in
 		let res_local = mk_local res pos in
 		let gte = {
@@ -7122,12 +7132,10 @@ struct
 			etype = basic.tbool;
 			epos = pos;
 		} in
-		let get_array_t t = match follow t with | TInst({ cl_path = ([],"Array") },[arrtype]) -> arrtype | _ -> assert false in
 		let mk_tarray arr idx =
-			let t = get_array_t arr.etype in
 			{
 				eexpr = TArray(arr, idx);
-				etype = t;
+				etype = gen.gclasses.nativearray_type arr.etype;
 				epos = pos;
 			}
 		in
@@ -7150,11 +7158,11 @@ struct
 				*)
 				let block =
 				[
-					{ eexpr = TVar(res, Some(ctx.rcf_hash_function hash_local fst_hash)); etype = basic.tvoid; epos = pos };
+					{ eexpr = TVar(res, Some(ctx.rcf_hash_function hash_local fst_hash fst_length)); etype = basic.tvoid; epos = pos };
 					{ eexpr = TIf(gte, mk_return (mk_tarray fst_dynamics res_local), Some({
 						eexpr = TBlock(
 						[
-							{ eexpr = TBinop(Ast.OpAssign, res_local, ctx.rcf_hash_function hash_local snd_hash); etype = basic.tint; epos = pos };
+							{ eexpr = TBinop(Ast.OpAssign, res_local, ctx.rcf_hash_function hash_local snd_hash snd_length); etype = basic.tint; epos = pos };
 							{ eexpr = TIf(gte, mk_return (mk_tarray snd_dynamics res_local), None); etype = ret_t; epos = pos }
 						]);
 						etype = ret_t;
@@ -7183,23 +7191,6 @@ struct
 					__hx_dynamics/_f.insert(~res, value_local);
 					return value_local;
 				*)
-				let mk_splice arr at_pos = {
-					eexpr = TCall(
-						mk_field_access gen arr "spliceVoid" pos,
-						[at_pos; { eexpr = TConst(TInt Int32.one); etype = basic.tint; epos = pos }]
-					);
-					etype = basic.tvoid;
-					epos = pos
-				} in
-
-				let mk_insert arr at_pos value = {
-					eexpr = TCall(
-						mk_field_access gen arr "insert" pos,
-						[at_pos; value]);
-					etype = basic.tvoid;
-					epos = pos
-				} in
-
 				let neg_res = { eexpr = TUnop(Ast.NegBits, Ast.Prefix, res_local); etype = basic.tint; epos = pos } in
 
 				let res2 = alloc_var "res2" basic.tint in
@@ -7212,16 +7203,17 @@ struct
 
 				let block =
 				[
-					{ eexpr = TVar(res, Some(ctx.rcf_hash_function hash_local fst_hash)); etype = basic.tvoid; epos = pos };
+					{ eexpr = TVar(res, Some(ctx.rcf_hash_function hash_local fst_hash fst_length)); etype = basic.tvoid; epos = pos };
 					{
 						eexpr = TIf(gte,
 							mk_return { eexpr = TBinop(Ast.OpAssign, mk_tarray fst_dynamics res_local, value_local); etype = value_local.etype; epos = pos },
 							Some({ eexpr = TBlock([
-								{ eexpr = TVar( res2, Some(ctx.rcf_hash_function hash_local snd_hash)); etype = basic.tvoid; epos = pos };
+								{ eexpr = TVar( res2, Some(ctx.rcf_hash_function hash_local snd_hash snd_length)); etype = basic.tvoid; epos = pos };
 								{
 									eexpr = TIf(gte2, { eexpr = TBlock([
-										mk_splice snd_hash res2_local;
-										mk_splice snd_dynamics res2_local
+										ctx.rcf_remove_function snd_hash snd_length res2_local;
+										ctx.rcf_remove_function snd_dynamics snd_length res2_local;
+										mk (TUnop(Decrement,Postfix,snd_length)) basic.tint pos
 									]); etype = t_dynamic; epos = pos }, None);
 									etype = t_dynamic;
 									epos = pos;
@@ -7230,8 +7222,9 @@ struct
 						etype = t_dynamic;
 						epos = pos;
 					};
-					mk_insert fst_hash neg_res hash_local;
-					mk_insert fst_dynamics neg_res value_local;
+					ctx.rcf_insert_function fst_hash fst_length neg_res hash_local;
+					ctx.rcf_insert_function fst_dynamics fst_length neg_res value_local;
+					mk (TUnop(Increment,Postfix,fst_length)) basic.tint pos;
 					mk_return value_local
 				] in
 				block
@@ -7249,10 +7242,12 @@ struct
 		let body = if is_dynamic then begin
 			let mk_this field t = { (mk_field_access gen this field pos) with etype = t } in
 			let a_t = if ctx.rcf_optimize then basic.tint else basic.tstring in
-			let hx_hashes = mk_this (gen.gmk_internal_name "hx" "hashes") (basic.tarray a_t) in
-			let hx_hashes_f = mk_this (gen.gmk_internal_name "hx" "hashes_f") (basic.tarray a_t) in
-			let hx_dynamics = mk_this (gen.gmk_internal_name "hx" "dynamics") (basic.tarray t_empty) in
-			let hx_dynamics_f = mk_this (gen.gmk_internal_name "hx" "dynamics_f") (basic.tarray basic.tfloat) in
+			let hx_hashes = mk_this (gen.gmk_internal_name "hx" "hashes") (gen.gclasses.nativearray a_t) in
+			let hx_hashes_f = mk_this (gen.gmk_internal_name "hx" "hashes_f") (gen.gclasses.nativearray a_t) in
+			let hx_dynamics = mk_this (gen.gmk_internal_name "hx" "dynamics") (gen.gclasses.nativearray t_empty) in
+			let hx_dynamics_f = mk_this (gen.gmk_internal_name "hx" "dynamics_f") (gen.gclasses.nativearray basic.tfloat) in
+			let hx_length = mk_this (gen.gmk_internal_name "hx" "length") (basic.tint) in
+			let hx_length_f = mk_this (gen.gmk_internal_name "hx" "length_f") (basic.tint) in
 			let res = alloc_var "res" basic.tint in
 			let res_local = mk_local res pos in
 			let gte = {
@@ -7260,14 +7255,6 @@ struct
 				etype = basic.tbool;
 				epos = pos;
 			} in
-			let mk_splice arr at_pos = {
-				eexpr = TCall(
-					mk_field_access gen arr "spliceVoid" pos,
-					[at_pos; { eexpr = TConst(TInt Int32.one); etype = basic.tint; epos = pos }]
-				);
-				etype = basic.tvoid;
-				epos = pos
-			} in
 			(*
 				var res = lookup(this.__hx_hashes, hash);
 				if (res >= 0)
@@ -7290,17 +7277,19 @@ struct
 				return false;
 			*)
 			[
-				{ eexpr = TVar(res,Some(ctx.rcf_hash_function local_switch_var hx_hashes)); etype = basic.tvoid; epos = pos };
+				{ eexpr = TVar(res,Some(ctx.rcf_hash_function local_switch_var hx_hashes hx_length)); etype = basic.tvoid; epos = pos };
 				{
 					eexpr = TIf(gte, { eexpr = TBlock([
-						mk_splice hx_hashes res_local;
-						mk_splice hx_dynamics res_local;
+						ctx.rcf_remove_function hx_hashes hx_length res_local;
+						ctx.rcf_remove_function hx_dynamics hx_length res_local;
+						mk (TUnop(Decrement,Postfix,hx_length)) basic.tint pos;
 						mk_return { eexpr = TConst(TBool true); etype = basic.tbool; epos = pos }
 					]); etype = t_dynamic; epos = pos }, Some({ eexpr = TBlock([
-						{ eexpr = TBinop(Ast.OpAssign, res_local, ctx.rcf_hash_function local_switch_var hx_hashes_f); etype = basic.tint; epos = pos };
+						{ eexpr = TBinop(Ast.OpAssign, res_local, ctx.rcf_hash_function local_switch_var hx_hashes_f hx_length_f); etype = basic.tint; epos = pos };
 						{ eexpr = TIf(gte, { eexpr = TBlock([
-							mk_splice hx_hashes_f res_local;
-							mk_splice hx_dynamics_f res_local;
+							ctx.rcf_remove_function hx_hashes_f hx_length_f res_local;
+							ctx.rcf_remove_function hx_dynamics_f hx_length_f res_local;
+							mk (TUnop(Decrement,Postfix,hx_length_f)) basic.tint pos;
 							mk_return { eexpr = TConst(TBool true); etype = basic.tbool; epos = pos }
 						]); etype = t_dynamic; epos = pos }, None); etype = t_dynamic; epos = pos }
 					]); etype = t_dynamic; epos = pos }));
@@ -7373,16 +7362,26 @@ struct
 		let basic = gen.gcon.basic in
 		let hasht = if ctx.rcf_optimize then basic.tint else basic.tstring in
 
+		let hashes_field = gen.gmk_internal_name "hx" "hashes", gen.gclasses.nativearray hasht in
+		let hashes_f_field = gen.gmk_internal_name "hx" "hashes_f", gen.gclasses.nativearray hasht in
+		let dynamics_field = gen.gmk_internal_name "hx" "dynamics", gen.gclasses.nativearray t_empty in
+		let dynamics_f_field = gen.gmk_internal_name "hx" "dynamics_f", gen.gclasses.nativearray basic.tfloat in
 		let fields =
 		[
-			gen.gmk_internal_name "hx" "hashes", basic.tarray hasht;
-			gen.gmk_internal_name "hx" "dynamics", basic.tarray t_empty;
-			gen.gmk_internal_name "hx" "hashes_f", basic.tarray hasht;
-			gen.gmk_internal_name "hx" "dynamics_f", basic.tarray basic.tfloat;
+			hashes_field;
+			dynamics_field;
+			hashes_f_field;
+			dynamics_f_field;
+		] in
+
+		let hashes_var = alloc_var (fst hashes_field) (snd hashes_field) in
+		let hashes_f_var = alloc_var (fst hashes_f_field) (snd hashes_f_field) in
+		let tf_args = [
+			hashes_var, None;
+			alloc_var (fst dynamics_field) (snd dynamics_field), None;
+			hashes_f_var, None;
+			alloc_var (fst dynamics_f_field) (snd dynamics_f_field), None;
 		] in
-		let tf_args = List.map (fun (name, t) ->
-			alloc_var name t, None
-		) fields in
 
 		let this = { eexpr = TConst TThis; etype = TInst(cl, List.map snd cl.cl_params); epos = pos } in
 		let mk_this field t = { (mk_field_access gen this field pos) with etype = t } in
@@ -7395,9 +7394,16 @@ struct
 				tf_type = basic.tvoid;
 				tf_expr =
 				{
-					eexpr = TBlock(List.map (fun (v,_) ->
+					eexpr = TBlock(
+						List.map (fun (v,_) ->
 							{ eexpr = TBinop(Ast.OpAssign, mk_this v.v_name v.v_type, mk_local v pos); etype = v.v_type; epos = pos }
-						) tf_args);
+						) tf_args
+						@
+						[
+							mk (TBinop(OpAssign, mk_this (gen.gmk_internal_name "hx" "length") basic.tint, gen.gclasses.nativearray_len (mk_local hashes_var pos) pos)) basic.tint pos;
+							mk (TBinop(OpAssign, mk_this (gen.gmk_internal_name "hx" "length_f") basic.tint, gen.gclasses.nativearray_len (mk_local hashes_f_var pos) pos)) basic.tint pos;
+						]
+					);
 					etype = basic.tvoid;
 					epos = pos
 				}
@@ -7415,7 +7421,7 @@ struct
 				tf_args = [];
 				tf_expr = {
 					eexpr = TBlock(List.map (fun (f,t) ->
-						{ eexpr = TBinop(Ast.OpAssign, mk_this f t,{ eexpr = TArrayDecl([]); etype = t; epos = pos; }); etype = t; epos = pos }
+						{ eexpr = TBinop(Ast.OpAssign, mk_this f t,{ eexpr = TCall(mk_local v_nativearray pos, []); etype = t; epos = pos; }); etype = t; epos = pos }
 					) fields);
 					etype = basic.tvoid;
 					epos = pos;
@@ -7477,14 +7483,13 @@ struct
 
 			let odecl, odecl_f = List.sort sort_fn odecl, List.sort sort_fn odecl_f in
 
-			let mk_arrdecl el t = { eexpr = TArrayDecl(el); etype = t; epos = pos } in
 			let ret = {
 				e with eexpr = TNew(cl,[],
 					[
-						mk_arrdecl (List.map fst odecl) (basic.tarray hasht);
-						mk_arrdecl (List.map snd odecl) (basic.tarray t_empty);
-						mk_arrdecl (List.map fst odecl_f) (basic.tarray hasht);
-						mk_arrdecl (List.map snd odecl_f) (basic.tarray basic.tfloat)
+						mk_nativearray_decl gen hasht (List.map fst odecl) pos;
+						mk_nativearray_decl gen t_empty (List.map snd odecl) pos;
+						mk_nativearray_decl gen hasht (List.map fst odecl_f) pos;
+						mk_nativearray_decl gen basic.tfloat (List.map snd odecl_f) pos;
 					]);
 			} in
 			match !exprs_before with
@@ -7513,20 +7518,27 @@ struct
 
 				let new_fields =
 				[
-					mk_class_field (gen.gmk_internal_name "hx" "hashes") (basic.tarray hasht) false pos (Var { v_read = AccNormal; v_write = AccNormal }) [];
-					mk_class_field (gen.gmk_internal_name "hx" "dynamics") (basic.tarray t_empty) false pos (Var { v_read = AccNormal; v_write = AccNormal }) [];
-					mk_class_field (gen.gmk_internal_name "hx" "hashes_f") (basic.tarray hasht) false pos (Var { v_read = AccNormal; v_write = AccNormal }) [];
-					mk_class_field (gen.gmk_internal_name "hx" "dynamics_f") (basic.tarray basic.tfloat) false pos (Var { v_read = AccNormal; v_write = AccNormal }) [];
+					mk_class_field (gen.gmk_internal_name "hx" "hashes") (gen.gclasses.nativearray hasht) false pos (Var { v_read = AccNormal; v_write = AccNormal }) [];
+					mk_class_field (gen.gmk_internal_name "hx" "dynamics") (gen.gclasses.nativearray t_empty) false pos (Var { v_read = AccNormal; v_write = AccNormal }) [];
+					mk_class_field (gen.gmk_internal_name "hx" "hashes_f") (gen.gclasses.nativearray hasht) false pos (Var { v_read = AccNormal; v_write = AccNormal }) [];
+					mk_class_field (gen.gmk_internal_name "hx" "dynamics_f") (gen.gclasses.nativearray basic.tfloat) false pos (Var { v_read = AccNormal; v_write = AccNormal }) [];
 				] in
 
 				(if cl.cl_path <> (["haxe"; "lang"], "DynamicObject") then
-					List.iter (fun cf -> cf.cf_expr <- Some { eexpr = TArrayDecl([]); etype = cf.cf_type; epos = cf.cf_pos }) new_fields
+					List.iter (fun cf -> cf.cf_expr <- Some { eexpr = TCall(mk_local v_nativearray pos, []); etype = cf.cf_type; epos = cf.cf_pos }) new_fields
 				);
 
 				let delete = get_delete_field ctx cl true in
+
+				let new_fields = new_fields @ [
+					mk_class_field (gen.gmk_internal_name "hx" "length") (basic.tint) false pos (Var { v_read = AccNormal; v_write = AccNormal }) [];
+					mk_class_field (gen.gmk_internal_name "hx" "length_f") (basic.tint) false pos (Var { v_read = AccNormal; v_write = AccNormal }) [];
+					delete;
+				] in
+
 				List.iter (fun cf ->
 					cl.cl_fields <- PMap.add cf.cf_name cf cl.cl_fields
-				) (delete :: new_fields);
+				) new_fields;
 
 		(*
 				let rec last_ctor cl =
@@ -7543,10 +7555,10 @@ struct
 					This will consist of different parts:
 						Check if there are constructors. If not, create one and add initialization to it (calling super, ok)
 						If there are, add as first statement (or second if there is a super() call in the first)
-						If class has @:$DynamicObject meta, also create another new() class with its parameters as constructor arguments
+						If class has @:dynamicObject meta, also create another new() class with its parameters as constructor arguments
 				*)
 
-				cl.cl_ordered_fields <- cl.cl_ordered_fields @ (delete :: new_fields);
+				cl.cl_ordered_fields <- cl.cl_ordered_fields @ new_fields;
 				if is_override then cl.cl_overrides <- delete :: cl.cl_overrides
 			end
 		end else if not is_override then begin
@@ -9134,7 +9146,7 @@ struct
 						cf.cf_meta <- [];
 
 						let tf_args = List.map (fun (name,opt,t) ->  (alloc_var name t, if opt then Some TNull else None) ) params in
-						let arr_decl = mk_vector_decl gen t_dynamic (List.map (fun (v,_) -> mk_local v pos) tf_args) pos in
+						let arr_decl = mk_nativearray_decl gen t_dynamic (List.map (fun (v,_) -> mk_local v pos) tf_args) pos in
 						let expr = {
 							eexpr = TFunction({
 								tf_args = tf_args;
@@ -9153,7 +9165,7 @@ struct
 						in
 						let cf = mk_class_field name actual_t true pos (Var { v_read = AccNormal; v_write = AccNever }) [] in
 						let args = if has_params then
-							[mk_int gen old_i pos; null (gen.gclasses.tvector t_dynamic) pos]
+							[mk_int gen old_i pos; null (gen.gclasses.nativearray t_dynamic) pos]
 						else
 							[mk_int gen old_i pos]
 						in
@@ -9168,9 +9180,9 @@ struct
 				cl.cl_statics <- PMap.add cf.cf_name cf cl.cl_statics;
 				cf
 			) en.e_names in
-			let constructs_cf = mk_class_field "__hx_constructs" (gen.gclasses.tvector basic.tstring) true pos (Var { v_read = AccNormal; v_write = AccNever }) [] in
+			let constructs_cf = mk_class_field "__hx_constructs" (gen.gclasses.nativearray basic.tstring) true pos (Var { v_read = AccNormal; v_write = AccNever }) [] in
 			constructs_cf.cf_meta <- [Meta.ReadOnly,[],pos];
-			constructs_cf.cf_expr <- Some (mk_vector_decl gen basic.tstring (List.map (fun s -> { eexpr = TConst(TString s); etype = basic.tstring; epos = pos }) en.e_names) pos);
+			constructs_cf.cf_expr <- Some (mk_nativearray_decl gen basic.tstring (List.map (fun s -> { eexpr = TConst(TString s); etype = basic.tstring; epos = pos }) en.e_names) pos);
 
 			cl.cl_ordered_statics <- constructs_cf :: cfs @ cl.cl_ordered_statics ;
 			cl.cl_statics <- PMap.add "__hx_constructs" constructs_cf cl.cl_statics;
@@ -9295,7 +9307,7 @@ struct
 						with Not_found ->
 							f
 						in
-						let cond_array = { (mk_field_access gen f "params" f.epos) with etype = gen.gclasses.tvector t_dynamic } in
+						let cond_array = { (mk_field_access gen f "params" f.epos) with etype = gen.gclasses.nativearray t_dynamic } in
 						{ e with eexpr = TArray(cond_array, mk_int gen i cond_array.epos); }
 					| _ -> Type.map_expr run e
 			in

+ 39 - 4
gencs.ml

@@ -713,6 +713,11 @@ let rec get_fun_modifiers meta access modifiers =
 (* this was the way I found to pass the generator context to be accessible across all functions here *)
 (* so 'configure' is almost 'top-level' and will have all functions needed to make this work *)
 let configure gen =
+	let native_arr_cl = get_cl ( get_type gen (["cs"], "NativeArray") ) in
+	gen.gclasses.nativearray <- (fun t -> TInst(native_arr_cl,[t]));
+	gen.gclasses.nativearray_type <- (function TInst(_,[t]) -> t | _ -> assert false);
+	gen.gclasses.nativearray_len <- (fun e p -> mk_field_access gen e "Length" p);
+
 	let basic = gen.gcon.basic in
 
 	let erase_generics = Common.defined gen.gcon Define.EraseGenerics in
@@ -2711,6 +2716,20 @@ let configure gen =
 	let rcf_static_find = mk_static_field_access_infer (get_cl (get_type gen (["haxe";"lang"], "FieldLookup"))) "findHash" Ast.null_pos [] in
 	let rcf_static_lookup = mk_static_field_access_infer (get_cl (get_type gen (["haxe";"lang"], "FieldLookup"))) "lookupHash" Ast.null_pos [] in
 
+	let rcf_static_insert, rcf_static_remove =
+		if erase_generics then begin
+			let get_specialized_postfix t = match t with
+				| TAbstract({a_path = [],("Float" | "Int" as name)}, _) -> name
+				| TAnon _ | TDynamic _ -> "Dynamic"
+				| _ -> print_endline (debug_type t); assert false
+			in
+			(fun t -> mk_static_field_access_infer (get_cl (get_type gen (["haxe";"lang"], "FieldLookup"))) ("insert" ^ get_specialized_postfix t) Ast.null_pos []),
+			(fun t -> mk_static_field_access_infer (get_cl (get_type gen (["haxe";"lang"], "FieldLookup"))) ("remove" ^ get_specialized_postfix t) Ast.null_pos [])
+		end else
+			(fun t -> mk_static_field_access_infer (get_cl (get_type gen (["haxe";"lang"], "FieldLookup"))) "insert" Ast.null_pos [t]),
+			(fun t -> mk_static_field_access_infer (get_cl (get_type gen (["haxe";"lang"], "FieldLookup"))) "remove" Ast.null_pos [t])
+	in
+
 	let can_be_float = like_float in
 
 	let rcf_on_getset_field main_expr field_expr field may_hash may_set is_unsafe =
@@ -2771,9 +2790,26 @@ let configure gen =
 		TypeParams.RealTypeParams.RealTypeParamsModf.configure gen (TypeParams.RealTypeParams.RealTypeParamsModf.set_only_hxgeneric gen)
 	end;
 
-	let rcf_ctx = ReflectionCFs.new_ctx gen closure_t object_iface true rcf_on_getset_field rcf_on_call_field (fun hash hash_array ->
-		{ hash with eexpr = TCall(rcf_static_find, [hash; hash_array]); etype=basic.tint }
-	) (fun hash -> { hash with eexpr = TCall(rcf_static_lookup, [hash]); etype = gen.gcon.basic.tstring } ) false in
+	let rcf_ctx =
+		ReflectionCFs.new_ctx
+			gen
+			closure_t
+			object_iface
+			true
+			rcf_on_getset_field
+			rcf_on_call_field
+			(fun hash hash_array length -> { hash with eexpr = TCall(rcf_static_find, [hash; hash_array; length]); etype=basic.tint })
+			(fun hash -> { hash with eexpr = TCall(rcf_static_lookup, [hash]); etype = gen.gcon.basic.tstring })
+			(fun hash_array length pos value ->
+				let ecall = mk (TCall(rcf_static_insert value.etype, [hash_array; length; pos; value])) (if erase_generics then hash_array.etype else basic.tvoid) hash_array.epos in
+				if erase_generics then { ecall with eexpr = TBinop(OpAssign, hash_array, ecall) } else ecall
+			)
+			(fun hash_array length pos ->
+				let t = gen.gclasses.nativearray_type hash_array.etype in
+				{ hash_array with eexpr = TCall(rcf_static_remove t, [hash_array; length; pos]); etype = gen.gcon.basic.tvoid }
+			)
+			false
+	in
 
 	ReflectionCFs.UniversalBaseClass.default_config gen (get_cl (get_type gen (["haxe";"lang"],"HxObject")) ) object_iface dynamic_object;
 
@@ -3041,7 +3077,6 @@ let configure gen =
 
 	UnreachableCodeEliminationSynf.configure gen (UnreachableCodeEliminationSynf.traverse gen false true true false);
 
-	let native_arr_cl = get_cl ( get_type gen (["cs"], "NativeArray") ) in
 	ArrayDeclSynf.configure gen (ArrayDeclSynf.default_implementation gen native_arr_cl);
 
 	let goto_special = alloc_var "__goto__" t_dynamic in

+ 35 - 5
genjava.ml

@@ -800,6 +800,11 @@ let rec get_fun_modifiers meta access modifiers =
 (* this was the way I found to pass the generator context to be accessible across all functions here *)
 (* so 'configure' is almost 'top-level' and will have all functions needed to make this work *)
 let configure gen =
+	let native_arr_cl = get_cl ( get_type gen (["java"], "NativeArray") ) in
+	gen.gclasses.nativearray <- (fun t -> TInst(native_arr_cl,[t]));
+	gen.gclasses.nativearray_type <- (function TInst(_,[t]) -> t | _ -> assert false);
+	gen.gclasses.nativearray_len <- (fun e p -> mk_field_access gen e "length" p);
+
 	let basic = gen.gcon.basic in
 
 	let fn_cl = get_cl (get_type gen (["haxe";"lang"],"Function")) in
@@ -2049,6 +2054,14 @@ let configure gen =
 
 	let rcf_static_find = mk_static_field_access_infer (get_cl (get_type gen (["haxe";"lang"], "FieldLookup"))) "findHash" Ast.null_pos [] in
 	(*let rcf_static_lookup = mk_static_field_access_infer (get_cl (get_type gen (["haxe";"lang"], "FieldLookup"))) "lookupHash" Ast.null_pos [] in*)
+	let get_specialized_postfix t = match t with
+		| TAbstract({a_path = [],"Float"}, _) -> "Float"
+		| TInst({cl_path = [],"String"},_) -> "String"
+		| TAnon _ | TDynamic _ -> "Dynamic"
+		| _ -> print_endline (debug_type t); assert false
+	in
+	let rcf_static_insert t = mk_static_field_access_infer (get_cl (get_type gen (["haxe";"lang"], "FieldLookup"))) ("insert" ^ get_specialized_postfix t) Ast.null_pos [] in
+	let rcf_static_remove t = mk_static_field_access_infer (get_cl (get_type gen (["haxe";"lang"], "FieldLookup"))) ("remove" ^ get_specialized_postfix t) Ast.null_pos [] in
 
 	let can_be_float t = like_float (real_type t) in
 
@@ -2104,9 +2117,28 @@ let configure gen =
 		mk_cast ecall.etype { ecall with eexpr = TCall(infer, call_args); etype = t_dynamic }
 	in
 
-	let rcf_ctx = ReflectionCFs.new_ctx gen closure_t object_iface false rcf_on_getset_field rcf_on_call_field (fun hash hash_array ->
-		{ hash with eexpr = TCall(rcf_static_find, [hash; hash_array]); etype=basic.tint }
-	) (fun hash -> hash ) false in
+	let rcf_ctx =
+		ReflectionCFs.new_ctx
+			gen
+			closure_t
+			object_iface
+			false
+			rcf_on_getset_field
+			rcf_on_call_field
+			(fun hash hash_array length -> { hash with eexpr = TCall(rcf_static_find, [hash; hash_array; length]); etype=basic.tint })
+			(fun hash -> hash)
+			(fun hash_array length pos value ->
+				{ hash_array with
+					eexpr = TBinop(OpAssign,
+								hash_array,
+								mk (TCall(rcf_static_insert value.etype, [hash_array; length; pos; value])) hash_array.etype hash_array.epos)
+			})
+			(fun hash_array length pos ->
+				let t = gen.gclasses.nativearray_type hash_array.etype in
+				{ hash_array with eexpr = TCall(rcf_static_remove t, [hash_array; length; pos]); etype = gen.gcon.basic.tvoid }
+			)
+			false
+		in
 
 	ReflectionCFs.UniversalBaseClass.default_config gen (get_cl (get_type gen (["haxe";"lang"],"HxObject")) ) object_iface dynamic_object;
 
@@ -2324,8 +2356,6 @@ let configure gen =
 			| _ -> assert false
 	) true );
 
-	let native_arr_cl = get_cl ( get_type gen (["java"], "NativeArray") ) in
-
 	ExpressionUnwrap.configure gen (ExpressionUnwrap.traverse gen (fun e -> Some { eexpr = TVar(mk_temp gen "expr" e.etype, Some e); etype = gen.gcon.basic.tvoid; epos = e.epos }));
 
 	UnnecessaryCastsRemoval.configure gen;

+ 117 - 2
std/cs/internal/FieldLookup.hx

@@ -98,10 +98,10 @@ package cs.internal;
 		return key;
 	}
 
-	public static function findHash(hash:Int, hashs:Array<Int>):Int
+	public static function findHash(hash:Int, hashs:cs.NativeArray<Int>, length:Int):Int
 	{
 		var min = 0;
-		var max = hashs.length;
+		var max = length;
 
 		while (min < max)
 		{
@@ -120,4 +120,119 @@ package cs.internal;
 		return ~min;
 	}
 
+	#if !erase_generics
+	static function remove<T>(a:cs.NativeArray<T>, length:Int, pos:Int)
+	{
+		cs.system.Array.Copy(a, pos + 1, a, pos, length - pos - 1);
+		a[length - 1] = null;
+	}
+
+	static function insert<T>(a:cs.Ref<cs.NativeArray<T>>, length:Int, pos:Int, x:T)
+	{
+		var capacity = a.Length;
+		if (pos == length)
+		{
+			if (capacity == length)
+			{
+				var newarr = new NativeArray((length << 1) + 1);
+				a.CopyTo(newarr, 0);
+				a = newarr;
+			}
+		}
+		else if (pos == 0)
+		{
+			if (capacity == length)
+			{
+				var newarr = new NativeArray((length << 1) + 1);
+				cs.system.Array.Copy(a, 0, newarr, 1, length);
+				a = newarr;
+			}
+			else
+			{
+				cs.system.Array.Copy(a, 0, a, 1, length);
+			}
+		}
+		else
+		{
+			if (capacity == length)
+			{
+				var newarr = new NativeArray((length << 1) + 1);
+				cs.system.Array.Copy(a, 0, newarr, 0, pos);
+				cs.system.Array.Copy(a, pos, newarr, pos + 1, length - pos);
+				a = newarr;
+			}
+			else
+			{
+				cs.system.Array.Copy(a, pos, a, pos + 1, length - pos);
+				cs.system.Array.Copy(a, 0, a, 0, pos);
+			}
+		}
+		a[pos] = x;
+	}
+	#else
+	static function removeInt(a:cs.NativeArray<Int>, length:Int, pos:Int)
+	{
+		cs.system.Array.Copy(a, pos + 1, a, pos, length - pos - 1);
+		a[length - 1] = 0;
+	}
+	static function removeFloat(a:cs.NativeArray<Float>, length:Int, pos:Int)
+	{
+		cs.system.Array.Copy(a, pos + 1, a, pos, length - pos - 1);
+		a[length - 1] = 0;
+	}
+	static function removeDynamic(a:cs.NativeArray<Dynamic>, length:Int, pos:Int)
+	{
+		cs.system.Array.Copy(a, pos + 1, a, pos, length - pos - 1);
+		a[length - 1] = null;
+	}
+
+	@:extern
+	static inline function __insert<T>(a:cs.NativeArray<T>, length:Int, pos:Int, x:T):cs.NativeArray<T>
+	{
+		var capacity = a.Length;
+		if (pos == length)
+		{
+			if (capacity == length)
+			{
+				var newarr = new NativeArray((length << 1) + 1);
+				a.CopyTo(newarr, 0);
+				a = newarr;
+			}
+		}
+		else if (pos == 0)
+		{
+			if (capacity == length)
+			{
+				var newarr = new NativeArray((length << 1) + 1);
+				cs.system.Array.Copy(a, 0, newarr, 1, length);
+				a = newarr;
+			}
+			else
+			{
+				cs.system.Array.Copy(a, 0, a, 1, length);
+			}
+		}
+		else
+		{
+			if (capacity == length)
+			{
+				var newarr = new NativeArray((length << 1) + 1);
+				cs.system.Array.Copy(a, 0, newarr, 0, pos);
+				cs.system.Array.Copy(a, pos, newarr, pos + 1, length - pos);
+				a = newarr;
+			}
+			else
+			{
+				cs.system.Array.Copy(a, pos, a, pos + 1, length - pos);
+				cs.system.Array.Copy(a, 0, a, 0, pos);
+			}
+		}
+		a[pos] = x;
+		return a;
+	}
+
+	static function insertInt(a:cs.NativeArray<Int>, length:Int, pos:Int, x:Int):cs.NativeArray<Int> return __insert(a, length, pos, x);
+	static function insertFloat(a:cs.NativeArray<Float>, length:Int, pos:Int, x:Float):cs.NativeArray<Float> return __insert(a, length, pos, x);
+	static function insertDynamic(a:cs.NativeArray<Dynamic>, length:Int, pos:Int, x:Dynamic):cs.NativeArray<Dynamic> return __insert(a, length, pos, x);
+	#end
 }

+ 68 - 3
std/java/internal/FieldLookup.hx

@@ -21,6 +21,8 @@
  */
 package java.internal;
 
+import java.lang.System;
+
 @:native('haxe.lang.FieldLookup')
 @:keep
 @:static private class FieldLookup
@@ -34,10 +36,10 @@ package java.internal;
 		return 0;
 	}
 
-	public static function findHash(hash:String, hashs:Array<String>):Int
+	public static function findHash(hash:String, hashs:java.NativeArray<String>, length:Int):Int
 	{
 		var min = 0;
-		var max = hashs.length;
+		var max = length;
 
 		while (min < max)
 		{
@@ -56,4 +58,67 @@ package java.internal;
 		return ~min;
 	}
 
-}
+	static function removeString(a:java.NativeArray<String>, length:Int, pos:Int) {
+		System.arraycopy(a, pos + 1, a, pos, length - pos - 1);
+		a[length - 1] = null;
+	}
+
+	static function removeFloat(a:java.NativeArray<Float>, length:Int, pos:Int) {
+		System.arraycopy(a, pos + 1, a, pos, length - pos - 1);
+		a[length - 1] = 0;
+	}
+
+	static function removeDynamic(a:java.NativeArray<Dynamic>, length:Int, pos:Int) {
+		System.arraycopy(a, pos + 1, a, pos, length - pos - 1);
+		a[length - 1] = null;
+	}
+
+	@:extern
+	static inline function __insert<T>(a:java.NativeArray<T>, length:Int, pos:Int, x:T):java.NativeArray<T>
+	{
+		var capacity = a.length;
+		if (pos == length)
+		{
+			if (capacity == length)
+			{
+				var newarr = new NativeArray((length << 1) + 1);
+				System.arraycopy(a, 0, newarr, 0, a.length);
+				a = newarr;
+			}
+		}
+		else if (pos == 0)
+		{
+			if (capacity == length)
+			{
+				var newarr = new NativeArray((length << 1) + 1);
+				System.arraycopy(a, 0, newarr, 1, length);
+				a = newarr;
+			}
+			else
+			{
+				System.arraycopy(a, 0, a, 1, length);
+			}
+		}
+		else
+		{
+			if (capacity == length)
+			{
+				var newarr = new NativeArray((length << 1) + 1);
+				System.arraycopy(a, 0, newarr, 0, pos);
+				System.arraycopy(a, pos, newarr, pos + 1, length - pos);
+				a = newarr;
+			}
+			else
+			{
+				System.arraycopy(a, pos, a, pos + 1, length - pos);
+				System.arraycopy(a, 0, a, 0, pos);
+			}
+		}
+		a[pos] = x;
+		return a;
+	}
+
+	static function insertString(a:java.NativeArray<String>, length:Int, pos:Int, x:String):java.NativeArray<String> return __insert(a, length, pos, x);
+	static function insertFloat(a:java.NativeArray<Float>, length:Int, pos:Int, x:Float):java.NativeArray<Float> return __insert(a, length, pos, x);
+	static function insertDynamic(a:java.NativeArray<Dynamic>, length:Int, pos:Int, x:Dynamic):java.NativeArray<Dynamic> return __insert(a, length, pos, x);
+}