Procházet zdrojové kódy

Merge branch 'development' into hxb_server_cache_simn_cleanup

# Conflicts:
#	src/compiler/server.ml
#	src/context/common.ml
Simon Krajewski před 1 rokem
rodič
revize
0823f4afd0
42 změnil soubory, kde provedl 307 přidání a 113 odebrání
  1. 2 21
      src/codegen/codegen.ml
  2. 1 1
      src/codegen/gencommon/gencommon.ml
  3. 1 9
      src/codegen/overloads.ml
  4. 7 8
      src/compiler/server.ml
  5. 5 4
      src/context/common.ml
  6. 2 2
      src/context/display/displayPath.ml
  7. 8 1
      src/context/typecore.ml
  8. 2 0
      src/core/error.ml
  9. 10 1
      src/core/stringHelper.ml
  10. 1 1
      src/core/tFunctions.ml
  11. 15 0
      src/core/texpr.ml
  12. 1 1
      src/filters/ES6Ctors.ml
  13. 1 1
      src/filters/exceptions.ml
  14. 37 14
      src/filters/localStatic.ml
  15. 1 0
      src/generators/gencpp.ml
  16. 4 4
      src/generators/gencs.ml
  17. 1 0
      src/generators/genhl.ml
  18. 1 1
      src/generators/genjava.ml
  19. 1 0
      src/generators/genjs.ml
  20. 1 1
      src/generators/genjvm.ml
  21. 3 3
      src/generators/genneko.ml
  22. 1 1
      src/generators/genphp7.ml
  23. 2 1
      src/generators/genpy.ml
  24. 1 0
      src/generators/genswf.ml
  25. 1 0
      src/generators/genswf9.ml
  26. 1 1
      src/generators/hlinterp.ml
  27. 18 12
      src/generators/jvm/jvmFunctions.ml
  28. 1 1
      src/optimization/analyzerTypes.ml
  29. 1 1
      src/typing/callUnification.ml
  30. 1 5
      src/typing/operators.ml
  31. 2 2
      src/typing/typeloadCheck.ml
  32. 1 1
      src/typing/typeloadFields.ml
  33. 1 10
      src/typing/typer.ml
  34. 0 3
      src/typing/typerBase.ml
  35. 1 2
      src/typing/typerEntry.ml
  36. 32 0
      tests/misc/java/projects/Issue11390/Main.hx
  37. 9 0
      tests/misc/java/projects/Issue11390/Setup.hx
  38. 12 0
      tests/misc/java/projects/Issue11390/compile.hxml
  39. 10 0
      tests/misc/java/projects/Issue11390/compile.hxml.stdout
  40. 42 0
      tests/misc/java/projects/Issue11390/project/test/Robot.java
  41. 56 0
      tests/misc/java/projects/Issue11390/project/test/RobotFactory.java
  42. 9 0
      tests/unit/src/unit/issues/Issue11469.hx

+ 2 - 21
src/codegen/codegen.ml

@@ -65,15 +65,6 @@ let add_property_field com c =
 		c.cl_statics <- PMap.add cf.cf_name cf c.cl_statics;
 		c.cl_ordered_statics <- cf :: c.cl_ordered_statics
 
-let escape_res_name name allowed =
-	ExtString.String.replace_chars (fun chr ->
-		if (chr >= 'a' && chr <= 'z') || (chr >= 'A' && chr <= 'Z') || (chr >= '0' && chr <= '9') || chr = '_' || chr = '.' then
-			Char.escaped chr
-		else if List.mem chr allowed then
-			Char.escaped chr
-		else
-			"-x" ^ (string_of_int (Char.code chr))) name
-
 (* -------------------------------------------------------------------------- *)
 (* FIX OVERRIDES *)
 
@@ -384,7 +375,7 @@ module Dump = struct
 			| "pretty" -> dump_types com true
 			| "record" -> dump_record com
 			| "position" -> dump_position com
-			| _ -> dump_types com false 
+			| _ -> dump_types com false
 
 	let dump_dependencies ?(target_override=None) com =
 		let target_name = match target_override with
@@ -428,16 +419,7 @@ let default_cast ?(vtmp="$t") com e texpr t p =
 	let var = mk (TVar (vtmp,Some e)) api.tvoid p in
 	let vexpr = mk (TLocal vtmp) e.etype p in
 	let texpr = Texpr.Builder.make_typeexpr texpr p in
-	let std = (try List.find (fun t -> t_path t = ([],"Std")) com.types with Not_found -> die "" __LOC__) in
-	let fis = (try
-			let c = (match std with TClassDecl c -> c | _ -> die "" __LOC__) in
-			FStatic (c, PMap.find "isOfType" c.cl_statics)
-		with Not_found ->
-			die "" __LOC__
-	) in
-	let std = Texpr.Builder.make_typeexpr std p in
-	let is = mk (TField (std,fis)) (tfun [t_dynamic;t_dynamic] api.tbool) p in
-	let is = mk (TCall (is,[vexpr;texpr])) api.tbool p in
+	let is = Texpr.Builder.resolve_and_make_static_call com.std "isOfType" [vexpr;texpr] p in
 	let enull = Texpr.Builder.make_null vexpr.etype p in
 	let eop = Texpr.Builder.binop OpEq vexpr enull api.tbool p in
 	let echeck = Texpr.Builder.binop OpBoolOr is eop api.tbool p in
@@ -519,4 +501,3 @@ module ExtClass = struct
 		let e_assign = mk (TBinop(OpAssign,ef1,e)) e.etype p in
 		add_cl_init c e_assign
 end
-	

+ 1 - 1
src/codegen/gencommon/gencommon.ml

@@ -819,7 +819,7 @@ let run_filters gen =
 
 	reorder_modules gen;
 	t();
-	if !has_errors then abort "Compilation aborted with errors" null_pos
+	if !has_errors then Error.abort "Compilation aborted with errors" null_pos
 
 (* ******************************************* *)
 (* basic generation module that source code compilation implementations can use *)

+ 1 - 9
src/codegen/overloads.ml

@@ -13,7 +13,7 @@ let same_overload_args ?(get_vmtype) t1 t2 f1 f2 =
 			| [],[] ->
 				true
 			| tp1 :: params1,tp2 :: params2 ->
-				let constraints_equal ttp1 ttp2 = 
+				let constraints_equal ttp1 ttp2 =
 					Ast.safe_for_all2 f_eq (get_constraints ttp2) (get_constraints ttp2)
 				in
 				tp1.ttp_name = tp2.ttp_name && constraints_equal tp1 tp2 && loop params1 params2
@@ -79,14 +79,6 @@ let collect_overloads map c i =
 	loop map c;
 	List.rev !acc
 
-let get_overloads (com : Common.context) c i =
-	try
-		com.overload_cache#find (c.cl_path,i)
-	with Not_found ->
-		let l = collect_overloads (fun t -> t) c i in
-		com.overload_cache#add (c.cl_path,i) l;
-		l
-
 (** Overload resolution **)
 module Resolution =
 struct

+ 7 - 8
src/compiler/server.ml

@@ -313,15 +313,14 @@ let check_module sctx ctx m_path m_extra p =
 		in
 		let check_dependencies () =
 			PMap.iter (fun _ (sign,mpath) ->
-				try
-					let m2_extra = (com.cs#get_context sign)#find_module_extra mpath in
-					match check mpath m2_extra with
-					| None -> ()
-					| Some reason -> raise (Dirty (DependencyDirty(mpath,reason)))
+				let m2_extra = try
+					(com.cs#get_context sign)#find_module_extra mpath
 				with Not_found ->
-					()
-					(* HXB_TODO: Investigate why some modules depend on null_module or whatever else has an empty sign string *)
-					(* print_endline ("NOT_FOUND: " ^ (s_type_path mpath) ^ " " ^ (Digest.to_hex sign)); *)
+					die (Printf.sprintf "Could not find dependency %s of %s in the cache" (s_type_path mpath) (s_type_path m_path)) __LOC__;
+				in
+				match check mpath m2_extra with
+				| None -> ()
+				| Some reason -> raise (Dirty (DependencyDirty(mpath,reason)))
 			) m_extra.m_deps;
 		in
 		let check () =

+ 5 - 4
src/context/common.ml

@@ -383,6 +383,7 @@ type context = {
 	mutable user_metas : (string, Meta.user_meta) Hashtbl.t;
 	mutable get_macros : unit -> context option;
 	(* typing state *)
+	mutable std : tclass;
 	mutable global_metadata : (string list * metadata_entry * (bool * bool * bool)) list;
 	shared : shared_context;
 	display_information : display_information;
@@ -868,6 +869,7 @@ let create compilation_step cs version args display_mode =
 			tnull = (fun _ -> die "Could use locate abstract Null<T> (was it redefined?)" __LOC__);
 			tarray = (fun _ -> die "Could not locate class Array<T> (was it redefined?)" __LOC__);
 		};
+		std = null_class;
 		file_lookup_cache = new hashtbl_lookup;
 		file_keys = new file_keys;
 		file_contents = [];
@@ -932,7 +934,8 @@ let clone com is_macro_context =
 		module_lut = new module_lut;
 		hxb_reader_stats = HxbReader.create_hxb_reader_stats ();
 		hxb_writer_stats = HxbWriter.create_hxb_writer_stats ();
-}
+		std = null_class;
+	}
 
 let file_time file = Extc.filetime file
 
@@ -1071,8 +1074,6 @@ let allow_package ctx s =
 	with Not_found ->
 		()
 
-let abort ?(depth = 0) msg p = raise (Error.Fatal_error (Error.make_error ~depth (Custom msg) p))
-
 let platform ctx p = ctx.platform = p
 
 let platform_name_macro com =
@@ -1226,7 +1227,7 @@ let to_utf8 str p =
 	let ccount = ref 0 in
 	UTF8.iter (fun c ->
 		let c = UCharExt.code c in
-		if (c >= 0xD800 && c <= 0xDFFF) || c >= 0x110000 then abort "Invalid unicode char" p;
+		if (c >= 0xD800 && c <= 0xDFFF) || c >= 0x110000 then Error.abort "Invalid unicode char" p;
 		incr ccount;
 		if c > 0x10000 then incr ccount;
 	) u8;

+ 2 - 2
src/context/display/displayPath.ml

@@ -83,7 +83,7 @@ module TypePathHandler = struct
 	let complete_type_path com p =
 		let packs, modules = read_type_path com p in
 		if packs = [] && modules = [] then
-			(abort ("No modules found in " ^ String.concat "." p) null_pos)
+			(Error.abort ("No modules found in " ^ String.concat "." p) null_pos)
 		else
 			let packs = List.map (fun n -> make_ci_package (p,n) []) packs in
 			let modules = List.map (fun n -> make_ci_module (p,n)) modules in
@@ -158,7 +158,7 @@ module TypePathHandler = struct
 			in
 			Some fields
 		with _ ->
-			abort ("Could not load module " ^ (s_type_path (p,c))) null_pos
+			Error.abort ("Could not load module " ^ (s_type_path (p,c))) null_pos
 end
 
 let resolve_position_by_path ctx path p =

+ 8 - 1
src/context/typecore.ml

@@ -100,7 +100,6 @@ type typer_globals = {
 	retain_meta : bool;
 	mutable core_api : typer option;
 	mutable macros : ((unit -> unit) * typer) option;
-	mutable std : tclass;
 	mutable std_types : module_def;
 	type_patches : (path, (string * bool, type_patch) Hashtbl.t * type_patch) Hashtbl.t;
 	mutable module_check_policies : (string list * module_check_policy list * bool) list;
@@ -776,6 +775,14 @@ let create_deprecation_context ctx = {
 	curmod = ctx.m.curmod;
 }
 
+let get_overloads (com : Common.context) c i =
+	try
+		com.overload_cache#find (c.cl_path,i)
+	with Not_found ->
+		let l = Overloads.collect_overloads (fun t -> t) c i in
+		com.overload_cache#add (c.cl_path,i) l;
+		l
+
 (* -------------- debug functions to activate when debugging typer passes ------------------------------- *)
 
 (*

+ 2 - 0
src/core/error.ml

@@ -51,6 +51,8 @@ let rec recurse_error ?(depth = 0) cb err =
 exception Fatal_error of error
 exception Error of error
 
+let abort ?(depth = 0) msg p = raise (Fatal_error (make_error ~depth (Custom msg) p))
+
 let string_source t = match follow t with
 	| TInst(c,tl) -> PMap.foldi (fun s _ acc -> s :: acc) (TClass.get_all_fields c tl) []
 	| TAnon a -> PMap.fold (fun cf acc -> cf.cf_name :: acc) a.a_fields []

+ 10 - 1
src/core/stringHelper.ml

@@ -48,4 +48,13 @@ let s_escape ?(hex=true) s =
 		| c when int_of_char c < 32 && hex -> Buffer.add_string b (Printf.sprintf "\\x%.2X" (int_of_char c))
 		| c -> Buffer.add_char b c
 	done;
-	Buffer.contents b
+	Buffer.contents b
+
+let escape_res_name name allowed =
+	ExtString.String.replace_chars (fun chr ->
+		if (chr >= 'a' && chr <= 'z') || (chr >= 'A' && chr <= 'Z') || (chr >= '0' && chr <= '9') || chr = '_' || chr = '.' then
+			Char.escaped chr
+		else if List.mem chr allowed then
+			Char.escaped chr
+		else
+			"-x" ^ (string_of_int (Char.code chr))) name

+ 1 - 1
src/core/tFunctions.ml

@@ -291,7 +291,7 @@ let null_abstract = {
 }
 
 let add_dependency ?(skip_postprocess=false) m mdep =
-	if m != null_module && (m.m_path != mdep.m_path || m.m_extra.m_sign != mdep.m_extra.m_sign) then begin
+	if m != null_module && mdep != null_module && (m.m_path != mdep.m_path || m.m_extra.m_sign != mdep.m_extra.m_sign) then begin
 		m.m_extra.m_deps <- PMap.add mdep.m_id (mdep.m_extra.m_sign, mdep.m_path) m.m_extra.m_deps;
 		(* In case the module is cached, we'll have to run post-processing on it again (issue #10635) *)
 		if not skip_postprocess then m.m_extra.m_processed <- 0

+ 15 - 0
src/core/texpr.ml

@@ -561,6 +561,21 @@ module Builder = struct
 
 	let index basic e index t p =
 		mk (TArray (e,mk (TConst (TInt (Int32.of_int index))) basic.tint p)) t p
+
+	let resolve_and_make_static_call c name args p =
+		ignore(c.cl_build());
+		let cf = try
+			PMap.find name c.cl_statics
+		with Not_found ->
+			die "" __LOC__
+		in
+		let ef = make_static_field c cf (mk_zero_range_pos p) in
+		let tret = match follow ef.etype with
+			| TFun(_,r) -> r
+			| _ -> assert false
+		in
+		mk (TCall (ef, args)) tret p
+
 end
 
 let set_default basic a c p =

+ 1 - 1
src/filters/ES6Ctors.ml

@@ -84,7 +84,7 @@ let rewrite_ctors com =
 		let rec mark_needs_ctor_skipping cl =
 			(* for non haxe-generated extern classes we can't generate any valid code, so just fail *)
 			if (has_class_flag cl CExtern) && not (Meta.has Meta.HxGen cl.cl_meta) then begin
-				abort "Must call `super()` constructor before accessing `this` in classes derived from an extern class with constructor" p_this_access;
+				Error.abort "Must call `super()` constructor before accessing `this` in classes derived from an extern class with constructor" p_this_access;
 			end;
 			try
 				Hashtbl.find needs_ctor_skipping cl.cl_path

+ 1 - 1
src/filters/exceptions.ml

@@ -63,7 +63,7 @@ let haxe_exception_instance_call ctx haxe_exception method_name args p =
 *)
 let std_is ctx e t p =
 	let t = follow t in
-	let std_cls = ctx.typer.g.std in
+	let std_cls = ctx.typer.com.std in
 	let isOfType_field =
 		try PMap.find "isOfType" std_cls.cl_statics
 		with Not_found -> raise_typing_error ("Std has no field isOfType") p

+ 37 - 14
src/filters/localStatic.ml

@@ -3,11 +3,18 @@ open Type
 open Typecore
 open Error
 
-let promote_local_static ctx lut v eo =
-	let name = Printf.sprintf "%s_%s" ctx.curfield.cf_name v.v_name in
+type lscontext = {
+	ctx : typer;
+	lut : (int,tclass_field) Hashtbl.t;
+	mutable added_fields : tclass_field list;
+}
+
+let promote_local_static lsctx run v eo =
+	let name = Printf.sprintf "%s_%s" lsctx.ctx.curfield.cf_name v.v_name in
+	let c = lsctx.ctx.curclass in
 	begin try
-		let cf = PMap.find name ctx.curclass.cl_statics in
-		display_error ctx.com (Printf.sprintf "The expanded name of this local (%s) conflicts with another static field" name) v.v_pos;
+		let cf = PMap.find name c.cl_statics in
+		display_error lsctx.ctx.com (Printf.sprintf "The expanded name of this local (%s) conflicts with another static field" name) v.v_pos;
 		raise_typing_error ~depth:1 "Conflicting field was found here" cf.cf_name_pos;
 	with Not_found ->
 		let cf = mk_field name ~static:true v.v_type v.v_pos v.v_pos in
@@ -16,34 +23,45 @@ let promote_local_static ctx lut v eo =
 		| None ->
 			()
 		| Some e ->
+			let no_local_in_static p =
+				raise_typing_error "Accessing local variables in static initialization is not allowed" p
+			in
 			let rec loop e = match e.eexpr with
-				| TLocal _ | TFunction _ ->
-					raise_typing_error "Accessing local variables in static initialization is not allowed" e.epos
+				| TLocal v when has_var_flag v VStatic ->
+					run e
+				| TFunction _ | TLocal _ ->
+					no_local_in_static e.epos
 				| TConst (TThis | TSuper) ->
 					raise_typing_error "Accessing `this` in static initialization is not allowed" e.epos
 				| TReturn _ | TBreak | TContinue ->
 					raise_typing_error "This kind of control flow in static initialization is not allowed" e.epos
 				| _ ->
-					iter loop e
+					map_expr loop e
 			in
-			loop e;
+			let e = loop e in
 			cf.cf_expr <- Some e
 		end;
-		TClass.add_field ctx.curclass cf;
-		Hashtbl.add lut v.v_id cf
+		lsctx.added_fields <- cf :: lsctx.added_fields;
+		(* Add to lookup early so that the duplication check works. *)
+		c.cl_statics <- PMap.add cf.cf_name cf c.cl_statics;
+		Hashtbl.add lsctx.lut v.v_id cf
 	end
 
 let find_local_static lut v =
 	Hashtbl.find lut v.v_id
 
 let run ctx e =
-	let local_static_lut = Hashtbl.create 0 in
+	let lsctx = {
+		ctx = ctx;
+		lut = Hashtbl.create 0;
+		added_fields = [];
+	} in
 	let c = ctx.curclass in
 	let rec run e = match e.eexpr with
 		| TBlock el ->
 			let el = ExtList.List.filter_map (fun e -> match e.eexpr with
 				| TVar(v,eo) when has_var_flag v VStatic ->
-					promote_local_static ctx local_static_lut v eo;
+					promote_local_static lsctx run v eo;
 					None
 				| _ ->
 					Some (run e)
@@ -51,7 +69,7 @@ let run ctx e =
 			{ e with eexpr = TBlock el }
 		| TLocal v when has_var_flag v VStatic ->
 			begin try
-				let cf = find_local_static local_static_lut v in
+				let cf = find_local_static lsctx.lut v in
 				Texpr.Builder.make_static_field c cf e.epos
 			with Not_found ->
 				raise_typing_error (Printf.sprintf "Could not find local static %s (id %i)" v.v_name v.v_id) e.epos
@@ -59,4 +77,9 @@ let run ctx e =
 		| _ ->
 			Type.map_expr run e
 	in
-	run e
+	let e = run e in
+	(* Add to ordered list in reverse order *)
+	List.iter (fun cf ->
+		c.cl_ordered_statics <- cf :: c.cl_ordered_statics
+	) lsctx.added_fields;
+	e

+ 1 - 0
src/generators/gencpp.ml

@@ -19,6 +19,7 @@
 open Extlib_leftovers
 open Ast
 open Type
+open Error
 open Common
 open Globals
 

+ 4 - 4
src/generators/gencs.ml

@@ -1798,7 +1798,7 @@ let generate con =
 					let code, code_pos =
 						match code.eexpr with
 						| TConst (TString s) -> s, code.epos
-						| _ -> abort "The `code` argument for cs.Syntax.code must be a string constant" code.epos
+						| _ -> Error.abort "The `code` argument for cs.Syntax.code must be a string constant" code.epos
 					in
 					begin
 						let rec reveal_expr expr =
@@ -1820,11 +1820,11 @@ let generate con =
 					let code =
 						match code.eexpr with
 						| TConst (TString s) -> s
-						| _ -> abort "The `code` argument for cs.Syntax.plainCode must be a string constant" code.epos
+						| _ -> Error.abort "The `code` argument for cs.Syntax.plainCode must be a string constant" code.epos
 					in
 					write w (String.concat "\n" (ExtString.String.nsplit code "\r\n"))
 				| _ ->
-					abort (Printf.sprintf "Unknown cs.Syntax method `%s` with %d arguments" meth (List.length args)) pos
+					Error.abort (Printf.sprintf "Unknown cs.Syntax method `%s` with %d arguments" meth (List.length args)) pos
 			and do_call w e el =
 				let params, el = extract_tparams [] el in
 				let params = List.rev params in
@@ -3420,7 +3420,7 @@ let generate con =
 					gen.gcon.file ^ "/src/Resources"
 			in
 			Hashtbl.iter (fun name v ->
-				let name = Codegen.escape_res_name name ['/'] in
+				let name = StringHelper.escape_res_name name ['/'] in
 				let full_path = src ^ "/" ^ name in
 				Path.mkdir_from_path full_path;
 

+ 1 - 0
src/generators/genhl.ml

@@ -23,6 +23,7 @@ open Extlib_leftovers
 open Globals
 open Ast
 open Type
+open Error
 open Common
 open Hlcode
 

+ 1 - 1
src/generators/genjava.ml

@@ -2652,7 +2652,7 @@ let generate con =
 	let res = ref [] in
 	Hashtbl.iter (fun name v ->
 		res := { eexpr = TConst(TString name); etype = gen.gcon.basic.tstring; epos = null_pos } :: !res;
-		let name = Codegen.escape_res_name name ['/'] in
+		let name = StringHelper.escape_res_name name ['/'] in
 		let full_path = gen.gcon.file ^ "/src/" ^ name in
 		Path.mkdir_from_path full_path;
 

+ 1 - 0
src/generators/genjs.ml

@@ -20,6 +20,7 @@ open Extlib_leftovers
 open Globals
 open Ast
 open Type
+open Error
 open Common
 open JsSourcemap
 

+ 1 - 1
src/generators/genjvm.ml

@@ -3083,7 +3083,7 @@ let generate jvm_flag com =
 		end
 	) com.native_libs.java_libs in
 	Hashtbl.iter (fun name v ->
-		let filename = Codegen.escape_res_name name ['/';'-'] in
+		let filename = StringHelper.escape_res_name name ['/';'-'] in
 		gctx.out#add_entry v filename;
 	) com.resources;
 	let generate_real_types () =

+ 3 - 3
src/generators/genneko.ml

@@ -170,7 +170,7 @@ let gen_constant ctx pe c =
 			if (h land 128 = 0) <> (h land 64 = 0) then raise Exit;
 			int p (Int32.to_int i)
 		with _ ->
-			if ctx.version < 2 then abort "This integer is too big to be compiled to a Neko 31-bit integer. Please use a Float instead" pe;
+			if ctx.version < 2 then Error.abort "This integer is too big to be compiled to a Neko 31-bit integer. Please use a Float instead" pe;
 			(EConst (Int32 i),p))
 	| TFloat f -> (EConst (Float (Texpr.replace_separators f "")),p)
 	| TString s -> call p (field p (ident p "String") "new") [gen_big_string ctx p s]
@@ -237,7 +237,7 @@ and gen_expr ctx e =
 		(match follow e.etype with
 		| TFun (args,_) ->
 			let n = List.length args in
-			if n > 5 then abort "Cannot create closure with more than 5 arguments" e.epos;
+			if n > 5 then Error.abort "Cannot create closure with more than 5 arguments" e.epos;
 			let tmp = ident p "@tmp" in
 			EBlock [
 				(EVars ["@tmp", Some (gen_expr ctx e2); "@fun", Some (field p tmp f.cf_name)] , p);
@@ -798,7 +798,7 @@ let generate com =
 				else
 					loop (p + 1)
 			in
-			abort msg (loop 0)
+			Error.abort msg (loop 0)
 	end;
 	let command cmd args = try com.run_command_args cmd args with _ -> -1 in
 	let neko_file = (try Filename.chop_extension com.file with _ -> com.file) ^ ".neko" in

+ 1 - 1
src/generators/genphp7.ml

@@ -35,7 +35,7 @@ let write_resource dir name data =
 	let rdir = dir ^ "/res" in
 	if not (Sys.file_exists dir) then Unix.mkdir dir 0o755;
 	if not (Sys.file_exists rdir) then Unix.mkdir rdir 0o755;
-	let name = Codegen.escape_res_name name [] in
+	let name = StringHelper.escape_res_name name [] in
 	let ch = open_out_bin (rdir ^ "/" ^ name) in
 	output_string ch data;
 	close_out ch

+ 2 - 1
src/generators/genpy.ml

@@ -19,6 +19,7 @@
 open Extlib_leftovers
 open Globals
 open Ast
+open Error
 open Type
 open Common
 open Texpr.Builder
@@ -2269,7 +2270,7 @@ module Generator = struct
 				end else
 					","
 				in
-				let k_enc = Codegen.escape_res_name k [] in
+				let k_enc = StringHelper.escape_res_name k [] in
 				print ctx "%s\"%s\": open('%%s.%%s'%%(_file,'%s'),'rb').read()" prefix (StringHelper.s_escape k) k_enc;
 
 				let f = open_out_bin (ctx.com.file ^ "." ^ k_enc) in

+ 1 - 0
src/generators/genswf.ml

@@ -20,6 +20,7 @@ open Swf
 open As3hl
 open ExtString
 open Type
+open Error
 open Common
 open Ast
 open Globals

+ 1 - 0
src/generators/genswf9.ml

@@ -20,6 +20,7 @@ open Extlib_leftovers
 open Globals
 open Ast
 open Type
+open Error
 open As3
 open As3hl
 open Common

+ 1 - 1
src/generators/hlinterp.ml

@@ -2209,7 +2209,7 @@ let check code macros =
 					Globals.pmin = low;
 					Globals.pmax = low + (dline lsr 20);
 				} in
-				Common.abort msg pos
+				Error.abort msg pos
 			end else
 				failwith (Printf.sprintf "\n%s:%d: %s" file dline msg)
 		in

+ 18 - 12
src/generators/jvm/jvmFunctions.ml

@@ -317,6 +317,8 @@ module JavaFunctionalInterfaces = struct
 	let unify jfi args ret =
 		let params = ref [] in
 		let rec unify jsig1 jsig2 = match jsig1,jsig2 with
+			| TObject _,TObject((["java";"lang"],"Object"),[]) ->
+				true
 			| TObject(path1,params1),TObject(path2,params2) ->
 				path1 = path2 &&
 				unify_params params1 params2
@@ -362,7 +364,7 @@ module JavaFunctionalInterfaces = struct
 		| None,None ->
 			loop jfi.jargs args
 		| Some jsig1,Some jsig2 ->
-			if unify jsig1 jsig2 then loop jfi.jargs args
+			if unify jsig2 jsig1 then loop jfi.jargs args
 			else None
 		| _ ->
 			None
@@ -441,24 +443,28 @@ class typed_function
 				Hashtbl.add implemented_interfaces path true;
 			end
 		in
+		let spawn_invoke_next name msig is_bridge =
+			let flags = [MPublic] in
+			let flags = if is_bridge then MBridge :: MSynthetic :: flags else flags in
+			jc_closure#spawn_method name msig flags
+		in
 		let spawn_forward_function meth_from meth_to is_bridge =
 			let msig = method_sig meth_from.dargs meth_from.dret in
 			if not (jc_closure#has_method meth_from.name msig) then begin
-				let flags = [MPublic] in
-				let flags = if is_bridge then MBridge :: MSynthetic :: flags else flags in
-				let jm_invoke_next = jc_closure#spawn_method meth_from.name msig flags in
+				let jm_invoke_next = spawn_invoke_next meth_from.name msig is_bridge in
 				functions#make_forward_method jc_closure jm_invoke_next meth_from meth_to;
 			end
 		in
 		let check_functional_interfaces meth =
-			try
-				let l = JavaFunctionalInterfaces.find_compatible meth.dargs meth.dret functional_interface_filter in
-				List.iter (fun (jfi,params) ->
-					add_interface jfi.jpath params;
-					spawn_forward_function {meth with name=jfi.jname} meth false;
-				) l
-			with Not_found ->
-				()
+			let l = JavaFunctionalInterfaces.find_compatible meth.dargs meth.dret functional_interface_filter in
+			List.iter (fun (jfi,params) ->
+				add_interface jfi.jpath params;
+				let msig = method_sig jfi.jargs jfi.jret in
+				if not (jc_closure#has_method jfi.jname msig) then begin
+					let jm_invoke_next = spawn_invoke_next jfi.jname msig false in
+					functions#make_forward_method_jsig jc_closure jm_invoke_next meth.name jfi.jargs jfi.jret meth.dargs meth.dret
+				end
+			) l
 		in
 		let rec loop meth =
 			check_functional_interfaces meth;

+ 1 - 1
src/optimization/analyzerTypes.ml

@@ -218,7 +218,7 @@ module BasicBlock = struct
 		bb
 
 	let in_scope bb bb' = match bb'.bb_scopes with
-		| [] -> abort (Printf.sprintf "Scope-less block (kind: %s)" (s_block_kind bb'.bb_kind)) bb'.bb_pos
+		| [] -> Error.abort (Printf.sprintf "Scope-less block (kind: %s)" (s_block_kind bb'.bb_kind)) bb'.bb_pos
 		| scope :: _ -> List.mem scope bb.bb_scopes
 
 	let terminator_map f term = match term with

+ 1 - 1
src/typing/callUnification.ml

@@ -228,7 +228,7 @@ let unify_field_call ctx fa el_typed el p inline =
 			else
 				List.map (fun (t,cf) ->
 					cf
-				) (Overloads.get_overloads ctx.com c cf.cf_name)
+				) (get_overloads ctx.com c cf.cf_name)
 			in
 			cfl,Some c,false,TClass.get_map_function c tl,(fun t -> t)
 		| FHAbstract(a,tl,c) ->

+ 1 - 5
src/typing/operators.ml

@@ -201,11 +201,7 @@ let make_binop ctx op e1 e2 is_assign_op p =
 				call_to_string ctx e
 			| KInt | KFloat | KString -> e
 			| KUnk | KDyn | KNumParam _ | KStrParam _ | KOther ->
-				let std = type_type ctx ([],"Std") e.epos in
-				let acc = acc_get ctx (type_field_default_cfg ctx std "string" e.epos (MCall []) WithType.value) in
-				ignore(follow acc.etype);
-				let acc = (match acc.eexpr with TField (e,FClosure (Some (c,tl),f)) -> { acc with eexpr = TField (e,FInstance (c,tl,f)) } | _ -> acc) in
-				make_call ctx acc [e] ctx.t.tstring e.epos
+				Texpr.Builder.resolve_and_make_static_call ctx.com.std "string" [e] e.epos
 			| KAbstract (a,tl) ->
 				try
 					AbstractCast.cast_or_unify_raise ctx tstring e p

+ 2 - 2
src/typing/typeloadCheck.ml

@@ -243,7 +243,7 @@ let check_overriding ctx c f =
 		let p = f.cf_name_pos in
 		let i = f.cf_name in
 		if has_class_field_flag f CfOverload then begin
-			let overloads = Overloads.get_overloads ctx.com csup i in
+			let overloads = get_overloads ctx.com csup i in
 			List.iter (fun (t,f2) ->
 				(* check if any super class fields are vars *)
 				match f2.cf_kind with
@@ -378,7 +378,7 @@ module Inheritance = struct
 				let map2, t2, f2 = class_field_no_interf c f.cf_name in
 				let t2, f2 =
 					if f2.cf_overloads <> [] || has_class_field_flag f2 CfOverload then
-						let overloads = Overloads.get_overloads ctx.com c f.cf_name in
+						let overloads = get_overloads ctx.com c f.cf_name in
 						is_overload := true;
 						List.find (fun (t1,f1) -> Overloads.same_overload_args t t1 f f1) overloads
 					else

+ 1 - 1
src/typing/typeloadFields.ml

@@ -1475,7 +1475,7 @@ let create_property (ctx,cctx,fctx) c f (get,set,t,eo) p =
 			let cf = PMap.find m c.cl_statics in
 			(cf.cf_type,cf) :: (List.map (fun cf -> cf.cf_type,cf) cf.cf_overloads)
 		end else
-			Overloads.get_overloads ctx.com c m
+			get_overloads ctx.com c m
 	in
 	let cf = {
 		(mk_field name ~public:(is_public (ctx,cctx) f.cff_access None) ret f.cff_pos (pos f.cff_name)) with

+ 1 - 10
src/typing/typer.ml

@@ -2014,16 +2014,7 @@ and type_expr ?(mode=MGet) ctx (e,p) (with_type:WithType.t) =
 			if ctx.in_display && DisplayPosition.display_position#enclosed_in p_t then
 				DisplayEmitter.display_module_type ctx mt p_t;
 			let e_t = type_module_type ctx mt p_t in
-			let e_Std_isOfType =
-				ignore(ctx.g.std.cl_build());
-				let cf = try
-					PMap.find "isOfType" ctx.g.std.cl_statics
-				with Not_found ->
-					die "" __LOC__
-				in
-				Texpr.Builder.make_static_field ctx.g.std cf (mk_zero_range_pos p)
-			in
-			mk (TCall (e_Std_isOfType, [e; e_t])) ctx.com.basic.tbool p
+			Texpr.Builder.resolve_and_make_static_call ctx.com.std "isOfType" [e;e_t] p
 		| _ ->
 			display_error ctx.com "Unsupported type for `is` operator" p_t;
 			Texpr.Builder.make_bool ctx.com.basic false p

+ 0 - 3
src/typing/typerBase.ml

@@ -231,9 +231,6 @@ let type_module_type ctx t p =
 	in
 	loop t None
 
-let type_type ctx tpath p =
-	type_module_type ctx (Typeload.load_type_def ctx p (mk_type_path tpath)) p
-
 let mk_module_type_access ctx t p =
 	AKExpr (type_module_type ctx t p)
 

+ 1 - 2
src/typing/typerEntry.ml

@@ -20,7 +20,6 @@ let create com macros =
 			doinline = com.display.dms_inline && not (Common.defined com Define.NoInline);
 			retain_meta = Common.defined com Define.RetainUntypedMeta;
 			std_types = null_module;
-			std = null_class;
 			global_using = [];
 			complete = false;
 			type_hints = [];
@@ -138,7 +137,7 @@ let create com macros =
 	) m.m_types;
 	let m = TypeloadModule.load_module ctx ([],"Std") null_pos in
 	List.iter (fun mt -> match mt with
-		| TClassDecl ({cl_path = ([],"Std")} as c) -> ctx.g.std <- c;
+		| TClassDecl ({cl_path = ([],"Std")} as c) -> ctx.com.std <- c;
 		| _ -> ()
 	) m.m_types;
 	let m = TypeloadModule.load_module ctx ([],"Array") null_pos in

+ 32 - 0
tests/misc/java/projects/Issue11390/Main.hx

@@ -0,0 +1,32 @@
+package;
+
+import test.Robot;
+import test.RobotFactory;
+
+class Main {
+	public static function main() {
+		var robot1 = RobotFactory.buildMathRobot();
+		var robot2 = RobotFactory.buildGreetRobot(robot1);
+		var robot3 = RobotFactory.buildManufactureRobot();
+
+		robot1.performTask(add);
+		robot1.performTask(function(a:Int, b:Int):Int {
+			return a - b;
+		});
+
+		robot2.performTask(function (target:Robot) {
+            trace('Hello, ${target.toString()}!');
+        }, () -> {
+			trace('Cleanup...');
+		});
+
+		robot3.performTask(function (robotType:String) {
+			trace('Manufacturing ${robotType}...');
+			return robot2;
+		});
+	}
+
+	static function add(a:Int, b:Int):Int {
+		return a + b;
+	}
+}

+ 9 - 0
tests/misc/java/projects/Issue11390/Setup.hx

@@ -0,0 +1,9 @@
+import sys.FileSystem;
+
+function main() {
+	Sys.setCwd("./project");
+	FileSystem.createDirectory("./out");
+	Sys.command("javac", ["-d", "out", "test/Robot.java", "test/RobotFactory.java", "-g"]);
+	Sys.setCwd("./out");
+	Sys.command("jar", ["cf", "test.jar", "test/Robot.class", "test/Robot$CleanupTask.class", "test/Robot$MathOperation.class", "test/Robot$GreetRobot.class", "test/Robot$ManufactureRobot.class", "test/RobotFactory.class", "test/RobotFactory$1.class", "test/RobotFactory$2.class", "test/RobotFactory$3.class"]);
+}

+ 12 - 0
tests/misc/java/projects/Issue11390/compile.hxml

@@ -0,0 +1,12 @@
+--main Setup
+--interp
+
+--next
+
+--main Main
+--java-lib project/out/test.jar
+--jvm run.jar
+
+--next
+
+--cmd java -jar run.jar

+ 10 - 0
tests/misc/java/projects/Issue11390/compile.hxml.stdout

@@ -0,0 +1,10 @@
+Robot.performTask() called!
+Result: 7
+Robot.performTask() called!
+Result: -1
+Robot.performTask() called!
+Main.hx:18: Hello, Robot!
+Main.hx:20: Cleanup...
+Robot.performTask() called!
+Main.hx:24: Manufacturing Greet...
+Output: Robot

+ 42 - 0
tests/misc/java/projects/Issue11390/project/test/Robot.java

@@ -0,0 +1,42 @@
+package test;
+
+public abstract class Robot<T> {
+    public Robot() {}
+
+    public void performTask(T listener) {
+        System.out.println("Robot.performTask() called!");
+    }
+
+    public void performTask(T listener, CleanupTask cleanupTask) {
+        System.out.println("Robot.performTask() called!");
+        cleanupTask.cleanup();
+    }
+
+    /**
+     * MathOperation
+     */
+    @FunctionalInterface
+    public interface MathOperation {
+        public int operate(int a, int b);
+    }
+
+    @FunctionalInterface
+    public interface GreetRobot {
+        public void greet(Robot robot);
+    }
+
+    @FunctionalInterface
+    public interface ManufactureRobot<T extends Robot> {
+        public T manufacture(String robotType);
+    }
+
+    @FunctionalInterface
+    public interface CleanupTask {
+        public void cleanup();
+    }
+
+    @Override
+    public String toString() {
+        return "Robot";
+    }
+}

+ 56 - 0
tests/misc/java/projects/Issue11390/project/test/RobotFactory.java

@@ -0,0 +1,56 @@
+package test;
+
+import test.Robot.GreetRobot;
+import test.Robot.ManufactureRobot;
+import test.Robot.MathOperation;
+
+public class RobotFactory {
+    public static Robot<MathOperation> buildMathRobot() {
+        return new Robot<MathOperation>() {
+            public void performTask(MathOperation listener) {
+                System.out.println("Robot.performTask() called!");
+                int result = listener.operate(3, 4);
+                System.out.println("Result: " + result);
+            }
+
+            public void performTask(MathOperation listener, CleanupTask cleanupTask) {
+                System.out.println("Robot.performTask() called!");
+                int result = listener.operate(3, 4);
+                System.out.println("Result: " + result);
+                cleanupTask.cleanup();
+            }
+        };
+    }
+
+    public static Robot<GreetRobot> buildGreetRobot(Robot target) {
+        return new Robot<GreetRobot>() {
+            public void performTask(GreetRobot listener) {
+                System.out.println("Robot.performTask() called!");
+                listener.greet(target);
+            }
+
+            public void performTask(GreetRobot listener, CleanupTask cleanupTask) {
+                System.out.println("Robot.performTask() called!");
+                listener.greet(target);
+                cleanupTask.cleanup();
+            }
+        };
+    }
+
+    public static Robot<ManufactureRobot<Robot<GreetRobot>>> buildManufactureRobot() {
+        return new Robot<ManufactureRobot<Robot<GreetRobot>>>() {
+            public void performTask(ManufactureRobot<Robot<GreetRobot>> listener) {
+                System.out.println("Robot.performTask() called!");
+                Robot<GreetRobot> output = listener.manufacture("Greet");
+                System.out.println("Output: " + output.toString());
+            }
+
+            public void performTask(ManufactureRobot<Robot<GreetRobot>> listener, CleanupTask cleanupTask) {
+                System.out.println("Robot.performTask() called!");
+                Robot<GreetRobot> output = listener.manufacture("Greet");
+                System.out.println("Output: " + output.toString());
+                cleanupTask.cleanup();
+            }
+        };
+    }
+}

+ 9 - 0
tests/unit/src/unit/issues/Issue11469.hx

@@ -0,0 +1,9 @@
+package unit.issues;
+
+class Issue11469 extends Test {
+	function test() {
+		static var c = 10;
+		static var d = c + 1;
+		eq(11, d);
+	}
+}