Browse Source

Merge pull request #4216 from HaxeFoundation/haxe-3.3

Start on Haxe 3.3
Simon Krajewski 10 năm trước cách đây
mục cha
commit
8c2799b093
45 tập tin đã thay đổi với 693 bổ sung208 xóa
  1. 26 22
      analyzer.ml
  2. 115 12
      ast.ml
  3. 1 1
      common.ml
  4. 18 0
      extra/CHANGES.txt
  5. 38 6
      filters.ml
  6. 2 0
      gencpp.ml
  7. 1 5
      gencs.ml
  8. 1 5
      genjava.ml
  9. 2 4
      genjs.ml
  10. 1 3
      genneko.ml
  11. 1 3
      genswf.ml
  12. 33 35
      main.ml
  13. 6 1
      matcher.ml
  14. 3 0
      optimizer.ml
  15. 11 5
      parser.ml
  16. 2 2
      std/haxe/macro/Context.hx
  17. 1 1
      tests/misc/compile.hxml
  18. 6 0
      tests/misc/projects/Issue3975/Main.hx
  19. 2 0
      tests/misc/projects/Issue3975/compile-fail.hxml
  20. 2 0
      tests/misc/projects/Issue3975/compile-fail.hxml.stderr
  21. 3 0
      tests/misc/projects/Issue4114/Main1.hx
  22. 7 0
      tests/misc/projects/Issue4114/Main2.hx
  23. 2 0
      tests/misc/projects/Issue4114/compile1-fail.hxml
  24. 1 0
      tests/misc/projects/Issue4114/compile1-fail.hxml.stderr
  25. 2 0
      tests/misc/projects/Issue4114/compile2-fail.hxml
  26. 1 0
      tests/misc/projects/Issue4114/compile2-fail.hxml.stderr
  27. 3 1
      tests/misc/src/Main.hx
  28. 1 0
      tests/optimization/run.hxml
  29. 82 0
      tests/optimization/src/TestNullChecker.hx
  30. 1 1
      tests/unit/compile-each.hxml
  31. 1 1
      tests/unit/src/unit/TestCSharp.hx
  32. 24 0
      tests/unit/src/unit/issues/Issue2767.hx
  33. 1 1
      tests/unit/src/unit/issues/Issue2958.hx
  34. 2 1
      tests/unit/src/unit/issues/Issue2989.hx
  35. 15 15
      tests/unit/src/unit/issues/Issue3753.hx
  36. 12 0
      tests/unit/src/unit/issues/Issue3804.hx
  37. 34 0
      tests/unit/src/unit/issues/Issue3935.hx
  38. 24 0
      tests/unit/src/unit/issues/Issue4122.hx
  39. 23 0
      tests/unit/src/unit/issues/Issue4158.hx
  40. 26 0
      tests/unit/src/unit/issues/Issue4180.hx
  41. 12 0
      tests/unit/src/unit/issues/Issue4196.hx
  42. 2 1
      tests/unit/src/unitstd/Reflect.unit.hx
  43. 2 2
      type.ml
  44. 31 19
      typeload.ml
  45. 109 61
      typer.ml

+ 26 - 22
analyzer.ml

@@ -236,7 +236,7 @@ module Simplifier = struct
 			with Exit ->
 				begin match follow e.etype with
 					| TAbstract({a_path = [],"Void"},_) -> true
-					| TInst ({ cl_path = [],"Array" }, _) when com.platform = Cpp -> true
+					(* | TInst ({ cl_path = [],"Array" }, _) when com.platform = Cpp -> true *)
 					| _ -> false
 				end
 		in
@@ -765,6 +765,8 @@ module Ssa = struct
 		| TLocal v ->
 			begin try eval_cond ctx (get_var_value v)
 			with Not_found -> [] end
+		| TParenthesis e1 | TMeta(_,e1) | TCast(e1,None) ->
+			eval_cond ctx e1
 		| _ ->
 			[]
 
@@ -776,37 +778,36 @@ module Ssa = struct
 			ctx.var_conds <- IntMap.add v.v_id [cond] ctx.var_conds
 		end
 
-(* 	let apply_cond ctx = function
-		| Equal({v_extra = Some(_,Some {eexpr = TLocal v})} as v0,e1) ->
-			let v' = assign_var ctx v (mk_loc v0 e1.epos) e1.epos in
+	let apply_cond ctx = function
+		| Equal(v,e1) ->
+			let v' = assign_var ctx (get_origin_var v) (mk_loc v e1.epos) e1.epos in
 			append_cond ctx v' (Equal(v',e1)) e1.epos
-		| NotEqual({v_extra = Some(_,Some {eexpr = TLocal v})} as v0,e1) ->
-			let v' = assign_var ctx v (mk_loc v0 e1.epos) e1.epos in
+		| NotEqual(v,e1) ->
+			let v' = assign_var ctx (get_origin_var v) (mk_loc v e1.epos) e1.epos in
 			append_cond ctx v' (NotEqual(v',e1)) e1.epos
-		| _ -> ()
 
 	let apply_not_null_cond ctx v p =
-		apply_cond ctx (NotEqual(v,(mk (TConst TNull) t_dynamic p))) *)
+		apply_cond ctx (NotEqual(v,(mk (TConst TNull) t_dynamic p)))
 
 	let apply com e =
 		let rec handle_if ctx f econd eif eelse =
 			let econd = loop ctx econd in
-			(* let cond = eval_cond ctx econd in *)
+			let cond = eval_cond ctx econd in
 			let join = mk_join_node() in
 			let close = branch ctx eif.epos in
-			(* List.iter (apply_cond ctx) cond; *)
+			List.iter (apply_cond ctx) cond;
 			let eif = loop ctx eif in
 			close join;
 			let eelse = match eelse with
 				| None ->
-					(* let cond = invert_conds cond in *)
-					(* List.iter (apply_cond ctx) cond; *)
+					let cond = invert_conds cond in
+					List.iter (apply_cond ctx) cond;
 					add_branch join ctx.cur_data e.epos;
 					None
 				| Some e ->
 					let close = branch ctx e.epos in
-					(* let cond = invert_conds cond in *)
-					(* List.iter (apply_cond ctx) cond; *)
+					let cond = invert_conds cond in
+					List.iter (apply_cond ctx) cond;
 					let eelse = loop ctx e in
 					close join;
 					Some eelse
@@ -843,15 +844,15 @@ module Ssa = struct
 				let close = branch ctx e.epos in
 				List.iter (fun (v,co) ->
 					declare_var ctx v e.epos;
-(* 					match co with
+					match co with
 						| Some TNull when (match v.v_type with TType({t_path=["haxe"],"PosInfos"},_) -> false | _ -> true) -> ()
-						| _ -> apply_not_null_cond ctx v e.epos *)
+						| _ -> apply_not_null_cond ctx v e.epos
 				) tf.tf_args;
 				let e' = loop ctx tf.tf_expr in
 				close (mk_join_node());
 				{e with eexpr = TFunction {tf with tf_expr = e'}}
 			(* var modifications *)
-			| TBinop(OpAssign,({eexpr = TLocal v} as e1),e2) when v.v_name <> "this" ->
+			| TBinop(OpAssign,({eexpr = TLocal v} as e1),e2) ->
 				let e2 = loop ctx e2 in
 				let _ = assign_var ctx v e2 e1.epos in
 				{e with eexpr = TBinop(OpAssign,e1,e2)}
@@ -912,7 +913,7 @@ module Ssa = struct
 				e
 			| TFor(v,e1,ebody) ->
 				declare_var ctx v e.epos;
-				(* apply_not_null_cond ctx v e1.epos; *)
+				apply_not_null_cond ctx v e1.epos;
 				let v' = IntMap.find v.v_id ctx.cur_data.nd_var_map in
 				let e1 = loop ctx e1 in
 				let ebody = handle_loop_body ctx ebody in
@@ -928,7 +929,7 @@ module Ssa = struct
 				close_join_node ctx join_ex e.epos;
 				let catches = List.map (fun (v,e) ->
 					declare_var ctx v e.epos;
-					(* apply_not_null_cond ctx v e.epos; *)
+					apply_not_null_cond ctx v e.epos;
 					let close = branch ctx e.epos in
 					let e = loop ctx e in
 					close join_bottom;
@@ -1131,7 +1132,7 @@ module ConstPropagation = struct
 				e'
 			else
 				e
- 		| TEnumParameter(e1,ef,i) ->
+		| TEnumParameter(e1,ef,i) ->
 			let ev = value ssa true e1 in
 			begin try
 				value ssa force (semi_awkward_enum_value ssa ev i)
@@ -1484,6 +1485,9 @@ module LocalDce = struct
 			| TVar(v,Some e1) when not (is_used v) ->
 				let e1 = if has_side_effect e1 then loop true e1 else e1 in
 				e1
+			| TVar(v,Some e1) ->
+				let e1 = loop true e1 in
+				{e with eexpr = TVar(v,Some e1)}
 			| TWhile(e1,e2,flag) ->
 				collect e2;
 				let e2 = loop false e2 in
@@ -1550,7 +1554,7 @@ module Config = struct
 			ssa_apply = true;
 			const_propagation = not (Common.raw_defined com "analyzer-no-const-propagation");
 			check_has_effect = (Common.raw_defined com "analyzer-check-has-effect");
-			check = not (Common.raw_defined com "analyzer-no-check");
+			check = (Common.raw_defined com "analyzer-check-null");
 			local_dce = not (Common.raw_defined com "analyzer-no-local-dce") && not (Common.defined com Define.As3);
 			ssa_unapply = not (Common.raw_defined com "analyzer-no-ssa-unapply");
 			simplifier_unapply = not (Common.raw_defined com "analyzer-no-simplify-unapply");
@@ -1609,7 +1613,7 @@ module Run = struct
 					if config.check_has_effect then EffectChecker.run com is_var_expression e;
 					let e,ssa = with_timer "analyzer-ssa-apply" (fun () -> Ssa.apply com e) in
 					let e = if config.const_propagation then with_timer "analyzer-const-propagation" (fun () -> ConstPropagation.apply ssa e) else e in
-					(* let e = if config.check then with_timer "analyzer-checker" (fun () -> Checker.apply ssa e) else e in *)
+					let e = if config.check then with_timer "analyzer-checker" (fun () -> Checker.apply ssa e) else e in
 					let e = if config.local_dce && config.analyzer_use && not has_unbound && not is_var_expression then with_timer "analyzer-local-dce" (fun () -> LocalDce.apply e) else e in
 					let e = if config.ssa_unapply then with_timer "analyzer-ssa-unapply" (fun () -> Ssa.unapply com e) else e in
 					List.iter (fun f -> f()) ssa.Ssa.cleanup;

+ 115 - 12
ast.ml

@@ -143,7 +143,7 @@ module Meta = struct
 		| Remove
 		| Require
 		| RequiresAssign
-		(* | Resolve *)
+		| Resolve
 		| ReplaceReflection
 		| Rtti
 		| Runtime
@@ -730,7 +730,7 @@ let map_expr loop (e,p) =
 	| EIf (e,e1,e2) -> EIf (loop e, loop e1, opt loop e2)
 	| EWhile (econd,e,f) -> EWhile (loop econd, loop e, f)
 	| ESwitch (e,cases,def) -> ESwitch (loop e, List.map (fun (el,eg,e) -> List.map loop el, opt loop eg, opt loop e) cases, opt (opt loop) def)
-	| ETry (e, catches) -> ETry (loop e, List.map (fun (n,t,e) -> n,ctype t,loop e) catches)
+	| ETry (e,catches) -> ETry (loop e, List.map (fun (n,t,e) -> n,ctype t,loop e) catches)
 	| EReturn e -> EReturn (opt loop e)
 	| EBreak -> EBreak
 	| EContinue -> EContinue
@@ -745,16 +745,119 @@ let map_expr loop (e,p) =
 	) in
 	(e,p)
 
-let rec s_expr (e,_) =
-	match e with
-	| EConst c -> s_constant c
-	| EParenthesis e -> "(" ^ (s_expr e) ^ ")"
-	| EArrayDecl el -> "[" ^ (String.concat "," (List.map s_expr el)) ^ "]"
-	| EObjectDecl fl -> "{" ^ (String.concat "," (List.map (fun (n,e) -> n ^ ":" ^ (s_expr e)) fl)) ^ "}"
-	| EBinop (op,e1,e2) -> s_expr e1 ^ s_binop op ^ s_expr e2
-	| ECall (e,el) -> s_expr e ^ "(" ^ (String.concat ", " (List.map s_expr el)) ^ ")"
-	| EField (e,f) -> s_expr e ^ "." ^ f
-	| _ -> "'???'"
+let s_expr e =
+	let rec s_expr_inner tabs (e,_) =
+		match e with
+		| EConst c -> s_constant c
+		| EArray (e1,e2) -> s_expr_inner tabs e1 ^ "[" ^ s_expr_inner tabs e2 ^ "]"
+		| EBinop (op,e1,e2) -> s_expr_inner tabs e1 ^ " " ^ s_binop op ^ " " ^ s_expr_inner tabs e2
+		| EField (e,f) -> s_expr_inner tabs e ^ "." ^ f
+		| EParenthesis e -> "(" ^ (s_expr_inner tabs e) ^ ")"
+		| EObjectDecl fl -> "{ " ^ (String.concat ", " (List.map (fun (n,e) -> n ^ " : " ^ (s_expr_inner tabs e)) fl)) ^ " }"
+		| EArrayDecl el -> "[" ^ s_expr_list tabs el ", " ^ "]"
+		| ECall (e,el) -> s_expr_inner tabs e ^ "(" ^ s_expr_list tabs el ", " ^ ")"
+		| ENew (t,el) -> "new " ^ s_complex_type_path tabs t ^ "(" ^ s_expr_list tabs el ", " ^ ")"
+		| EUnop (op,Postfix,e) -> s_expr_inner tabs e ^ s_unop op
+		| EUnop (op,Prefix,e) -> s_unop op ^ s_expr_inner tabs e
+		| EFunction (Some n,f) -> "function " ^ n ^ s_func tabs f
+		| EFunction (None,f) -> "function" ^ s_func tabs f
+		| EVars vl -> "var " ^ String.concat ", " (List.map (s_var tabs) vl)
+		| EBlock [] -> "{ }"
+		| EBlock el -> s_block tabs el "{" "\n" "}"
+		| EFor (e1,e2) -> "for (" ^ s_expr_inner tabs e1 ^ ") " ^ s_expr_inner tabs e2
+		| EIn (e1,e2) -> s_expr_inner tabs e1 ^ " in " ^ s_expr_inner tabs e2
+		| EIf (e,e1,None) -> "if (" ^ s_expr_inner tabs e ^ ") " ^ s_expr_inner tabs e1
+		| EIf (e,e1,Some e2) -> "if (" ^ s_expr_inner tabs e ^ ") " ^ s_expr_inner tabs e1 ^ " else " ^ s_expr_inner tabs e2
+		| EWhile (econd,e,NormalWhile) -> "while (" ^ s_expr_inner tabs econd ^ ") " ^ s_expr_inner tabs e
+		| EWhile (econd,e,DoWhile) -> "do " ^ s_expr_inner tabs e ^ " while (" ^ s_expr_inner tabs econd ^ ")"
+		| ESwitch (e,cases,def) -> "switch " ^ s_expr_inner tabs e ^ " {\n\t" ^ tabs ^ String.concat ("\n\t" ^ tabs) (List.map (s_case tabs) cases) ^
+			(match def with None -> "" | Some def -> "\n\t" ^ tabs ^ "default:" ^
+			(match def with None -> "" | Some def -> s_expr_omit_block tabs def)) ^ "\n" ^ tabs ^ "}" 
+		| ETry (e,catches) -> "try " ^ s_expr_inner tabs e ^ String.concat "" (List.map (s_catch tabs) catches)
+		| EReturn e -> "return" ^ s_opt_expr tabs e " "
+		| EBreak -> "break"
+		| EContinue -> "continue"
+		| EUntyped e -> "untyped " ^ s_expr_inner tabs e
+		| EThrow e -> "throw " ^ s_expr_inner tabs e
+		| ECast (e,Some t) -> "cast (" ^ s_expr_inner tabs e ^ ", " ^ s_complex_type tabs t ^ ")"
+		| ECast (e,None) -> "cast " ^ s_expr_inner tabs e
+		| ETernary (e1,e2,e3) -> s_expr_inner tabs e1 ^ " ? " ^ s_expr_inner tabs e2 ^ " : " ^ s_expr_inner tabs e3
+		| ECheckType (e,t) -> "(" ^ s_expr_inner tabs e ^ " : " ^ s_complex_type tabs t ^ ")"
+		| EMeta (m,e) -> s_metadata tabs m ^ " " ^ s_expr_inner tabs e
+		| _ -> ""
+	and s_expr_list tabs el sep =
+		(String.concat sep (List.map (s_expr_inner tabs) el))
+	and s_complex_type_path tabs t =	
+		(String.concat "." t.tpackage) ^ if List.length t.tpackage > 0 then "." else "" ^
+		t.tname ^
+		match t.tsub with
+		| Some s -> "." ^ s
+		| None -> "" ^
+		s_type_param_or_consts tabs t.tparams
+	and s_type_param_or_consts tabs pl =
+		if List.length pl > 0
+		then "<" ^ (String.concat "," (List.map (s_type_param_or_const tabs) pl)) ^ ">"
+		else ""
+	and s_type_param_or_const tabs p =
+		match p with
+		| TPType t -> s_complex_type tabs t
+		| TPExpr e -> s_expr_inner tabs e
+	and s_complex_type tabs ct =
+		match ct with
+		| CTPath t -> s_complex_type_path tabs t
+		| CTFunction (cl,c) -> if List.length cl > 0 then String.concat " -> " (List.map (s_complex_type tabs) cl) else "Void" ^ " -> " ^ s_complex_type tabs c
+		| CTAnonymous fl -> "{ " ^ String.concat "; " (List.map (s_class_field tabs) fl) ^ "}";
+		| CTParent t -> "(" ^ s_complex_type tabs t ^ ")"
+		| CTOptional t -> "?" ^ s_complex_type tabs t
+		| CTExtend (tl, fl) -> "{> " ^ String.concat " >, " (List.map (s_complex_type_path tabs) tl) ^ ", " ^ String.concat ", " (List.map (s_class_field tabs) fl) ^ " }"
+	and s_class_field tabs f =
+		match f.cff_doc with
+		| Some s -> "/**\n\t" ^ tabs ^ s ^ "\n**/\n"
+		| None -> "" ^
+		if List.length f.cff_meta > 0 then String.concat ("\n" ^ tabs) (List.map (s_metadata tabs) f.cff_meta) else "" ^
+		if List.length f.cff_access > 0 then String.concat " " (List.map s_access f.cff_access) else "" ^
+		match f.cff_kind with
+		| FVar (t,e) -> "var " ^ f.cff_name ^ s_opt_complex_type tabs t " : " ^ s_opt_expr tabs e " = "
+		| FProp (get,set,t,e) -> "var " ^ f.cff_name ^ "(" ^ get ^ "," ^ set ^ ")" ^ s_opt_complex_type tabs t " : " ^ s_opt_expr tabs e " = "
+		| FFun func -> "function " ^ f.cff_name ^ s_func tabs func
+	and s_metadata tabs (s,e,_) =
+		"@" ^ Meta.to_string s ^ if List.length e > 0 then "(" ^ s_expr_list tabs e ", " ^ ")" else ""
+	and s_opt_complex_type tabs t pre =
+		match t with
+		| Some s -> pre ^ s_complex_type tabs s
+		| None -> ""
+	and s_opt_expr tabs e pre =
+		match e with
+		| Some s -> pre ^ s_expr_inner tabs s
+		| None -> ""
+	and s_func tabs f =
+		s_type_param_list tabs f.f_params ^
+		"(" ^ String.concat ", " (List.map (s_func_arg tabs) f.f_args) ^ ")" ^
+		s_opt_complex_type tabs f.f_type ":" ^
+		s_opt_expr tabs f.f_expr " "
+	and s_type_param tabs t =
+		t.tp_name ^ s_type_param_list tabs t.tp_params ^
+		if List.length t.tp_constraints > 0 then ":(" ^ String.concat ", " (List.map (s_complex_type tabs) t.tp_constraints) ^ ")" else ""
+	and s_type_param_list tabs tl =
+		if List.length tl > 0 then "<" ^ String.concat ", " (List.map (s_type_param tabs) tl) ^ ">" else ""
+	and s_func_arg tabs (n,o,t,e) =
+		if o then "?" else "" ^ n ^ s_opt_complex_type tabs t ":" ^ s_opt_expr tabs e " = "
+	and s_var tabs (n,t,e) =
+		n ^ s_opt_complex_type tabs t ":" ^ s_opt_expr tabs e " = "
+	and s_case tabs (el,e1,e2) =
+		"case " ^ s_expr_list tabs el ", " ^
+		(match e1 with None -> ":" | Some e -> " if (" ^ s_expr_inner tabs e ^ "):") ^
+		(match e2 with None -> "" | Some e -> s_expr_omit_block tabs e)
+	and s_catch tabs (n,t,e) =
+		" catch(" ^ n ^ ":" ^ s_complex_type tabs t ^ ") " ^ s_expr_inner tabs e
+	and s_block tabs el opn nl cls =
+		 opn ^ "\n\t" ^ tabs ^ (s_expr_list (tabs ^ "\t") el (";\n\t" ^ tabs)) ^ ";" ^ nl ^ tabs ^ cls
+	and s_expr_omit_block tabs e =
+		match e with
+		| (EBlock [],_) -> ""
+		| (EBlock el,_) -> s_block (tabs ^ "\t") el "" "" ""
+		| _ -> s_expr_inner (tabs ^ "\t") e ^ ";"
+	in s_expr_inner "" e
 
 let get_value_meta meta =
 	try

+ 1 - 1
common.ml

@@ -465,7 +465,7 @@ module MetaInfo = struct
 		| Remove -> ":remove",("Causes an interface to be removed from all implementing classes before generation",[UsedOn TClass])
 		| Require -> ":require",("Allows access to a field only if the specified compiler flag is set",[HasParam "Compiler flag to check";UsedOn TClassField])
 		| RequiresAssign -> ":requiresAssign",("Used internally to mark certain abstract operator overloads",[Internal])
-		(* | Resolve -> ":resolve",("Abstract fields marked with this metadata can be used to resolve unknown fields",[UsedOn TClassField]) *)
+		| Resolve -> ":resolve",("Abstract fields marked with this metadata can be used to resolve unknown fields",[UsedOn TClassField])
 		| ReplaceReflection -> ":replaceReflection",("Used internally to specify a function that should replace its internal __hx_functionName counterpart",[Platforms [Java;Cs]; UsedOnEither[TClass;TEnum]; Internal])
 		| Rtti -> ":rtti",("Adds runtime type informations",[UsedOn TClass])
 		| Runtime -> ":runtime",("?",[])

+ 18 - 0
extra/CHANGES.txt

@@ -1,3 +1,21 @@
+2015-??-??: 3.3.0
+
+	New features:
+
+	all : support @:resolve on abstracts (#3753)
+	all : support completion on { if the expected type is a structure (#3907)
+
+	Bugfixes:
+
+	all : properly disallowed assigning methods to structures with read-accessors (#3975)
+	all : fixed a bug related to abstract + Int/Float and implicit casts (#4122)
+
+	General improvements and optimizations:
+
+	all : added support for determining minimal types in Map literals (#4196)
+	all : allowed @:native on abstracts to set the name of the implementation class (#4158)
+	all : allowed creating closures on abstract inline methods (#4165)
+
 2015-05-12: 3.2.0
 
 	New features:

+ 38 - 6
filters.ml

@@ -5,13 +5,45 @@ open Typecore
 
 (* PASS 1 begin *)
 
-let rec verify_ast e = match e.eexpr with
-	| TField(_) ->
+let rec verify_ast ctx e =
+	let not_null e e1 = match e1.eexpr with
+		| TConst TNull -> display_error ctx ("Invalid null expression: " ^ (s_expr_pretty "" (s_type (print_context())) e)) e.epos
+		| _ -> ()
+	in
+	let rec loop e = match e.eexpr with
+	| TField(e1,_) ->
+		not_null e e1;
 		()
+	| TArray(e1,e2) ->
+		not_null e e1;
+		loop e1;
+		loop e2
+	| TCall(e1,el) ->
+		not_null e e1;
+		loop e1;
+		List.iter loop el
+	| TUnop(_,_,e1) ->
+		not_null e e1;
+		loop e1
+	(* probably too messy *)
+(* 	| TBinop((OpEq | OpNotEq),e1,e2) ->
+		loop e1;
+		loop e2
+	| TBinop((OpAssign | OpAssignOp _),e1,e2) ->
+		not_null e e1;
+		loop e1;
+		loop e2
+	| TBinop(op,e1,e2) ->
+		not_null e e1;
+		not_null e e2;
+		loop e1;
+		loop e2 *)
 	| TTypeExpr(TClassDecl {cl_kind = KAbstractImpl a}) when not (Meta.has Meta.RuntimeValue a.a_meta) ->
 		error "Cannot use abstract as value" e.epos
 	| _ ->
-		Type.iter verify_ast e
+		Type.iter loop e
+	in
+	loop e
 
 (*
 	Wraps implicit blocks in TIf, TFor, TWhile, TFunction and TTry with real ones
@@ -874,7 +906,7 @@ let apply_native_paths ctx t =
 			let meta,path = get_real_path e.e_meta e.e_path in
 			e.e_meta <- meta :: e.e_meta;
 			e.e_path <- path;
-		| TAbstractDecl a ->
+		| TAbstractDecl a when Meta.has Meta.CoreType a.a_meta ->
 			let meta,path = get_real_path a.a_meta a.a_path in
 			a.a_meta <- meta :: a.a_meta;
 			a.a_path <- path;
@@ -1120,7 +1152,7 @@ let run com tctx main =
 		] in
 		List.iter (run_expression_filters tctx filters) new_types;
 		Analyzer.Run.run_on_types tctx new_types;
-		List.iter (iter_expressions [verify_ast]) new_types;
+		List.iter (iter_expressions [verify_ast tctx]) new_types;
 		let filters = [
 			Optimizer.sanitize com;
 			if com.config.pf_add_final_return then add_final_return else (fun e -> e);
@@ -1154,7 +1186,7 @@ let run com tctx main =
 			rename_local_vars tctx;
 		] in
 		List.iter (run_expression_filters tctx filters) new_types;
-		List.iter (iter_expressions [verify_ast]) new_types;
+		List.iter (iter_expressions [verify_ast tctx]) new_types;
 	end;
 	next_compilation();
 	List.iter (fun f -> f()) (List.rev com.filters); (* macros onGenerate etc. *)

+ 2 - 0
gencpp.ml

@@ -5785,6 +5785,7 @@ let generate_source common_ctx =
       | _ -> cmd_defines := !cmd_defines ^ " -D" ^ name ^ "=\"" ^ (escape_command value) ^ "\"" ) common_ctx.defines;
    write_build_options common_ctx (common_ctx.file ^ "/Options.txt") common_ctx.defines;
    if ( not (Common.defined common_ctx Define.NoCompilation) ) then begin
+      let t = Common.timer "generate cpp - native compilation" in
       let old_dir = Sys.getcwd() in
       Sys.chdir common_ctx.file;
       let cmd = ref "haxelib run hxcpp Build.xml haxe" in
@@ -5794,6 +5795,7 @@ let generate_source common_ctx =
       print_endline !cmd;
       if common_ctx.run_command !cmd <> 0 then failwith "Build failed";
       Sys.chdir old_dir;
+      t()
    end
    ;;
 

+ 1 - 5
gencs.ml

@@ -3291,8 +3291,6 @@ let configure gen =
 
 	TypeParams.RenameTypeParameters.run gen;
 
-	let t = Common.timer "code generation" in
-
 	let parts = Str.split_delim (Str.regexp "[\\/]+") gen.gcon.file in
 	mkdir_recursive "" parts;
 	generate_modules gen "cs" "src" module_gen out_files;
@@ -3308,9 +3306,7 @@ let configure gen =
 		print_endline cmd;
 		if gen.gcon.run_command cmd <> 0 then failwith "Build failed";
 		Sys.chdir old_dir;
-	end;
-
-	t()
+	end
 
 (* end of configure function *)
 

+ 1 - 5
genjava.ml

@@ -2471,8 +2471,6 @@ let configure gen =
 
 	TypeParams.RenameTypeParameters.run gen;
 
-	let t = Common.timer "code generation" in
-
 	let parts = Str.split_delim (Str.regexp "[\\/]+") gen.gcon.file in
 	mkdir_recursive "" parts;
 	generate_modules_t gen "java" "src" change_path module_gen out_files;
@@ -2489,9 +2487,7 @@ let configure gen =
 		print_endline cmd;
 		if gen.gcon.run_command cmd <> 0 then failwith "Build failed";
 		Sys.chdir old_dir;
-	end;
-
-	t()
+	end
 
 (* end of configure function *)
 

+ 2 - 4
genjs.ml

@@ -256,7 +256,7 @@ let write_mappings ctx =
 
 let newline ctx =
 	match Rbuffer.nth ctx.buf (Rbuffer.length ctx.buf - 1) with
-	| '}' | '{' | ':' when not ctx.separator -> print ctx "\n%s" ctx.tabs
+	| '}' | '{' | ':' | ';' when not ctx.separator -> print ctx "\n%s" ctx.tabs
 	| _ -> print ctx ";\n%s" ctx.tabs
 
 let newprop ctx =
@@ -1232,7 +1232,6 @@ let gen_single_expr ctx e expr =
 	str
 
 let generate com =
-	let t = Common.timer "generate js" in
 	(match com.js_gen with
 	| Some g -> g()
 	| None ->
@@ -1400,6 +1399,5 @@ let generate com =
 	if com.debug then write_mappings ctx else (try Sys.remove (com.file ^ ".map") with _ -> ());
 	let ch = open_out_bin com.file in
 	Rbuffer.output_buffer ch ctx.buf;
-	close_out ch);
-	t()
+	close_out ch)
 

+ 1 - 3
genneko.ml

@@ -783,7 +783,6 @@ let build ctx types =
 
 let generate com =
 	let ctx = new_context com (if Common.defined com Define.NekoV1 then 1 else 2) false in
-	let t = Common.timer "neko generation" in
 	let libs = (EBlock (generate_libs_init com.neko_libs) , { psource = "<header>"; pline = 1; }) in
 	let el = build ctx com.types in
 	let emain = (match com.main with None -> [] | Some e -> [gen_expr ctx e]) in
@@ -819,5 +818,4 @@ let generate com =
 		if command ("nekoc -p \"" ^ neko_file ^ "\"") <> 0 then failwith "Failed to print neko code";
 		Sys.remove neko_file;
 		Sys.rename ((try Filename.chop_extension com.file with _ -> com.file) ^ "2.neko") neko_file;
-	end;
-	t()
+	end

+ 1 - 3
genswf.ml

@@ -1076,8 +1076,7 @@ let merge com file priority (h1,tags1) (h2,tags2) =
 	let tags = loop tags1 tags2 in
 	header, tags
 
-let generate com swf_header =
-	let t = Common.timer "generate swf" in
+let generate swf_header com =
 	let swc = if Common.defined com Define.Swc then Some (ref "") else None in
 	let file , codeclip = (try let f , c = ExtString.String.split com.file "@" in f, Some c with _ -> com.file , None) in
 	(* list exports *)
@@ -1165,7 +1164,6 @@ let generate com swf_header =
 		in
 		{header with h_frame_count = header.h_frame_count + 1},loop tags
 	| _ -> swf in
-	t();
 	(* write swf/swc *)
 	let t = Common.timer "write swf" in
 	let level = (try int_of_string (Common.defined_value com Define.SwfCompressLevel) with Not_found -> 9) in

+ 33 - 35
main.ml

@@ -1290,7 +1290,6 @@ try
 		("--interp", Arg.Unit (fun() ->
 			Common.define com Define.Interp;
 			set_platform Neko "";
-			no_output := true;
 			interp := true;
 		),": interpret the program using internal macro system");
 		("--macro", Arg.String (fun e ->
@@ -1484,7 +1483,7 @@ try
 	end else begin
 		ctx.setup();
 		Common.log com ("Classpath : " ^ (String.concat ";" com.class_path));
-		Common.log com ("Defines : " ^ (String.concat ";" (PMap.foldi (fun v _ acc -> v :: acc) com.defines [])));
+		Common.log com ("Defines : " ^ (String.concat ";" (PMap.foldi (fun k v acc -> (match v with "1" -> k | _ -> k ^ "=" ^ v) :: acc) com.defines [])));
 		let t = Common.timer "typing" in
 		Typecore.type_expr_ref := (fun ctx e with_type -> Typer.type_expr ctx e with_type);
 		let tctx = Typer.create com in
@@ -1529,45 +1528,44 @@ try
 			| Cpp | Cs | Java | Php -> Common.mkdir_from_path (com.file ^ "/.")
 			| _ -> Common.mkdir_from_path com.file
 		end;
-		(match com.platform with
-		| _ when !no_output ->
+		if not !no_output then begin
 			if !interp then begin
 				let ctx = Interp.create com (Typer.make_macro_api tctx Ast.null_pos) in
 				Interp.add_types ctx com.types (fun t -> ());
 				(match com.main with
 				| None -> ()
 				| Some e -> ignore(Interp.eval_expr ctx e));
-			end;
-		| Cross ->
-			()
-		| Flash when Common.defined com Define.As3 ->
-			Common.log com ("Generating AS3 in : " ^ com.file);
-			Genas3.generate com;
-		| Flash ->
-			Common.log com ("Generating swf : " ^ com.file);
-			Genswf.generate com !swf_header;
-		| Neko ->
-			Common.log com ("Generating neko : " ^ com.file);
-			Genneko.generate com;
-		| Js ->
-			Common.log com ("Generating js : " ^ com.file);
-			Genjs.generate com
-		| Php ->
-			Common.log com ("Generating PHP in : " ^ com.file);
-			Genphp.generate com;
-		| Cpp ->
-			Common.log com ("Generating Cpp in : " ^ com.file);
-			Gencpp.generate com;
-		| Cs ->
-			Common.log com ("Generating Cs in : " ^ com.file);
-			Gencs.generate com;
-		| Java ->
-			Common.log com ("Generating Java in : " ^ com.file);
-			Genjava.generate com;
-		| Python ->
-			Common.log com ("Generating python in : " ^ com.file);
-			Genpy.generate com;
-		);
+			end else if com.platform = Cross then
+				()
+			else begin
+				let generate,name = match com.platform with
+				| Flash when Common.defined com Define.As3 ->
+					Genas3.generate,"AS3"
+				| Flash ->
+					Genswf.generate !swf_header,"swf"
+				| Neko ->
+					Genneko.generate,"neko"
+				| Js ->
+					Genjs.generate,"js"
+				| Php ->
+					Genphp.generate,"php"
+				| Cpp ->
+					Gencpp.generate,"cpp"
+				| Cs ->
+					Gencs.generate,"cs"
+				| Java ->
+					Genjava.generate,"java"
+				| Python ->
+					Genpy.generate,"python"
+				| Cross ->
+					assert false
+				in
+				Common.log com ("Generating " ^ name ^ ": " ^ com.file);
+				let t = Common.timer ("generate " ^ name) in
+				generate com;
+				t()
+			end
+		end
 	end;
 	Sys.catch_break false;
 	List.iter (fun f -> f()) (List.rev com.final_filters);

+ 6 - 1
matcher.ml

@@ -1004,6 +1004,9 @@ let convert_con ctx con = match con.c_def with
 	| CConst c -> mk_const ctx con.c_pos c
 	| CType mt -> mk (TTypeExpr mt) t_dynamic con.c_pos
 	| CExpr e -> e
+	| CEnum(e,ef) when Meta.has Meta.FakeEnum e.e_meta ->
+		let e_mt = !type_module_type_ref ctx (TEnumDecl e) None con.c_pos in
+		mk (TField(e_mt,FEnum(e,ef))) con.c_type con.c_pos
 	| CEnum(e,ef) -> mk_const ctx con.c_pos (TInt (Int32.of_int ef.ef_index))
 	| CArray i -> mk_const ctx con.c_pos (TInt (Int32.of_int i))
 	| CAny | CFields _ -> assert false
@@ -1027,6 +1030,8 @@ let convert_switch mctx st cases loop =
 			e
 	in
 	let e = match follow st.st_type with
+	| TEnum(en,_) when Meta.has Meta.FakeEnum en.e_meta ->
+		wrap_exhaustive (e_st)
 	| TEnum(_) ->
 		wrap_exhaustive (mk_index_call())
 	| TAbstract(a,pl) when (match Abstract.get_underlying_type a pl with TEnum(_) -> true | _ -> false) ->
@@ -1176,7 +1181,7 @@ let match_expr ctx e cases def with_type p =
 			let e = type_expr ctx e Value in
 			begin match follow e.etype with
 			(* TODO: get rid of the XmlType check *)
-			| TEnum(en,_) when (match en.e_path with (["neko" | "php" | "flash" | "cpp"],"XmlType") -> true | _ -> Meta.has Meta.FakeEnum en.e_meta) ->
+			| TEnum(en,_) when (match en.e_path with (["neko" | "php" | "flash" | "cpp"],"XmlType") -> true | _ -> false) ->
 				raise Exit
 			| TAbstract({a_path=[],("Int" | "Float" | "Bool")},_) | TInst({cl_path = [],"String"},_) when (Common.defined ctx.com Common.Define.NoPatternMatching) ->
 				raise Exit;

+ 3 - 0
optimizer.ml

@@ -1618,6 +1618,9 @@ let optimize_completion_expr e =
 						e)
 				| EFunction (_,f) ->
 					Ast.map_expr (subst_locals { r = PMap.foldi (fun n i acc -> if List.exists (fun (a,_,_,_) -> a = n) f.f_args then acc else PMap.add n i acc) locals.r PMap.empty }) e
+				| EObjectDecl [] ->
+					(* this probably comes from { | completion so we need some context} *)
+					raise Exit
 				| _ ->
 					Ast.map_expr (subst_locals locals) e
 			in

+ 11 - 5
parser.ml

@@ -1201,11 +1201,17 @@ and expr = parser
 			make_meta name params (secure_expr s) p
 		with Display e ->
 			display (make_meta name params e p))
-	| [< '(BrOpen,p1); b = block1; '(BrClose,p2); s >] ->
-		let e = (b,punion p1 p2) in
-		(match b with
-		| EObjectDecl _ -> expr_next e s
-		| _ -> e)
+	| [< '(BrOpen,p1); s >] ->
+		if is_resuming p1 then display (EDisplay ((EObjectDecl [],p1),false),p1);
+		(match s with parser
+		| [< '(Binop OpOr,p2) when do_resume() >] ->
+			set_resume p1;
+			display (EDisplay ((EObjectDecl [],p1),false),p1);
+		| [< b = block1; '(BrClose,p2); s >] ->
+			let e = (b,punion p1 p2) in
+			(match b with
+			| EObjectDecl _ -> expr_next e s
+			| _ -> e))
 	| [< '(Kwd Macro,p); s >] ->
 		parse_macro_expr p s
 	| [< '(Kwd Var,p1); v = parse_var_decl >] -> (EVars [v],p1)

+ 2 - 2
std/haxe/macro/Context.hx

@@ -341,7 +341,7 @@ class Context {
 	/**
 		Types expression `e` and returns its type.
 
-		Typing the expression may result in an compiler error which can be
+		Typing the expression may result in a compiler error which can be
 		caught using `try ... catch`.
 	**/
 	public static function typeof( e : Expr ) : Type {
@@ -351,7 +351,7 @@ class Context {
 	/**
 		Types expression `e` and returns the corresponding `TypedExpr`.
 
-		Typing the expression may result in an compiler error which can be
+		Typing the expression may result in a compiler error which can be
 		caught using `try ... catch`.
 	**/
 	@:require(haxe_ver >= 3.1)

+ 1 - 1
tests/misc/compile.hxml

@@ -1,2 +1,2 @@
 -cp src
---run Main
+--run Main

+ 6 - 0
tests/misc/projects/Issue3975/Main.hx

@@ -0,0 +1,6 @@
+class Main {
+	static function main() {
+		var a = ["a", "b"];
+		var a2 : { var pop(get,never) : Void -> Void; } = a;
+	}
+}

+ 2 - 0
tests/misc/projects/Issue3975/compile-fail.hxml

@@ -0,0 +1,2 @@
+-main Main
+--interp

+ 2 - 0
tests/misc/projects/Issue3975/compile-fail.hxml.stderr

@@ -0,0 +1,2 @@
+Main.hx:4: characters 2-54 : Array<String> should be { pop : Void -> Void }
+Main.hx:4: characters 2-54 : Field pop is method but should be (get,never)

+ 3 - 0
tests/misc/projects/Issue4114/Main1.hx

@@ -0,0 +1,3 @@
+class Main {
+	static function main():String { }
+}

+ 7 - 0
tests/misc/projects/Issue4114/Main2.hx

@@ -0,0 +1,7 @@
+class Main {
+	static function main() {
+		if (Math.random() > 0.5) {
+			return (null : Dynamic);
+		}
+	}
+}

+ 2 - 0
tests/misc/projects/Issue4114/compile1-fail.hxml

@@ -0,0 +1,2 @@
+-main Main1
+--interp

+ 1 - 0
tests/misc/projects/Issue4114/compile1-fail.hxml.stderr

@@ -0,0 +1 @@
+Main1.hx:2: characters 31-34 : Missing return: String

+ 2 - 0
tests/misc/projects/Issue4114/compile2-fail.hxml

@@ -0,0 +1,2 @@
+-main Main2
+--interp

+ 1 - 0
tests/misc/projects/Issue4114/compile2-fail.hxml.stderr

@@ -0,0 +1 @@
+Main2.hx:3: lines 3-5 : Missing return: Unknown<0>

+ 3 - 1
tests/misc/src/Main.hx

@@ -20,13 +20,15 @@ class Main {
 	macro static public function compileProjects():ExprOf<Result> {
 		var count = 0;
 		var failures = 0;
+		var filter = haxe.macro.Context.definedValue("MISC_TEST_FILTER");
+		var filterRegex = filter == null ? ~/.*/ : new EReg(filter, "");
 		function browse(dirPath) {
 			var dir = FileSystem.readDirectory(dirPath);
 			for (file in dir) {
 				var path = Path.join([dirPath, file]);
 				if (FileSystem.isDirectory(path)) {
 					browse(path);
-				} else if (file.endsWith(".hxml") && !file.endsWith("-each.hxml")) {
+				} else if (file.endsWith(".hxml") && !file.endsWith("-each.hxml") && filterRegex.match(path)) {
 					var old = Sys.getCwd();
 					Sys.setCwd(dirPath);
 					Sys.println('Running haxe $path');

+ 1 - 0
tests/optimization/run.hxml

@@ -7,6 +7,7 @@
 
 --next
 -main TestNullChecker
+-D analyzer-check-null
 --interp
 
 --next

+ 82 - 0
tests/optimization/src/TestNullChecker.hx

@@ -69,6 +69,76 @@ class TestNullChecker extends TestBase {
 		@:analyzer(testIsNotNull) ns;
 	}
 
+	function testReturn1() {
+		var ns = getNullString();
+		if (ns == null) {
+			return;
+		}
+		@:analyzer(testIsNotNull) ns;
+	}
+
+	function testReturn2() {
+		var ns = getNullString();
+		if (ns != null) {
+
+		} else {
+			return;
+		}
+		@:analyzer(testIsNotNull) ns;
+	}
+
+	// doesn't work yet due to || transformation
+	//function testReturn3() {
+		//var ns = getNullString();
+		//if (ns == null || getTrue()) {
+			//return;
+		//}
+		//@:analyzer(testIsNotNull) ns;
+	//}
+
+	function testReturn4() {
+		var ns = getNullString();
+		if (ns != null && getTrue()) {
+
+		} else {
+			return;
+		}
+		@:analyzer(testIsNull) ns;
+	}
+
+	function testBreak() {
+		var ns = getNullString();
+		while (true) {
+			if (ns == null) {
+				break;
+			}
+			@:analyzer(testIsNotNull) ns;
+		}
+		@:analyzer(testIsNull) ns;
+	}
+
+	function testContinue() {
+		var ns = getNullString();
+		while (true) {
+			if (getTrue()) {
+				break; // to terminate
+			}
+			if (ns == null) {
+				continue;
+			}
+			@:analyzer(testIsNotNull) ns;
+		}
+		@:analyzer(testIsNull) ns;
+	}
+
+	function testThrow() {
+		var ns = getNotNullString();
+		if (ns == null) {
+			throw false;
+		}
+		@:analyzer(testIsNotNull) ns;
+	}
+
 	function getString() {
 		return "foo";
 	}
@@ -76,4 +146,16 @@ class TestNullChecker extends TestBase {
 	function getNullString():Null<String> {
 		return null;
 	}
+
+	function getNotNullString():Null<String> {
+		return "foo";
+	}
+
+	function getTrue() {
+		return true;
+	}
+
+	function getFalse() {
+		return false;
+	}
 }

+ 1 - 1
tests/unit/compile-each.hxml

@@ -5,4 +5,4 @@
 -resource res1.txt@re/s?!%[]))("'1.txt
 -resource res2.bin@re/s?!%[]))("'1.bin
 -dce full
-#-D analyzer
+-D analyzer

+ 1 - 1
tests/unit/src/unit/TestCSharp.hx

@@ -37,7 +37,7 @@ class TestCSharp extends Test
 
 	function testIssue3474()
 	{
-		var a:IEditableTextBuffer = null;
+		var a:IEditableTextBuffer = cast null;
 		eq(a,null);
 		var didRun = false;
 		try

+ 24 - 0
tests/unit/src/unit/issues/Issue2767.hx

@@ -0,0 +1,24 @@
+package unit.issues;
+
+private abstract A(Array<Int>) {
+	public function new() {
+		this = [];
+	}
+
+	public inline function add(i : Int) : Void {
+		this.push(i);
+	}
+
+	public function get() {
+		return this.pop();
+	}
+}
+
+class Issue2767 extends Test {
+	function test() {
+		var a = new A();
+		var f = a.add;
+		f(12);
+		eq(12, a.get());
+	}
+}

+ 1 - 1
tests/unit/src/unit/issues/Issue2958.hx

@@ -6,7 +6,7 @@ class Issue2958 extends Test {
     function test() {
         eq(
            typeString((null : Asset<["test", 1]>)),
-           "unit.issues._Issue2958.Asset<[\"test\",1]>"
+           "unit.issues._Issue2958.Asset<[\"test\", 1]>"
         );
     }
 

+ 2 - 1
tests/unit/src/unit/issues/Issue2989.hx

@@ -4,7 +4,8 @@ class Issue2989 extends Test
 {
 	public function test()
 	{
-		Std.is(null,Array);
+		var n = null;
+		Std.is(n, Array);
 		new haxe.ds.Vector<Int>(10);
 	}
 }

+ 15 - 15
tests/unit/src/unit/issues/Issue3753.hx

@@ -42,20 +42,20 @@ private abstract D(Map<String, String>) from Map<String, String> {
 
 class Issue3753 extends Test {
 	function test() {
-		//var a:A = ["foo" => "bar", "bar" => "baz"];
-		//eq("bar", a.foo);
-		//eq("baz", a.bar);
-//
-		//var a:B = ["foo" => "bar", "bar" => "baz"];
-		//eq("bar", a.foo);
-		//eq("baz", a.bar);
-//
-		//var a:C = ["foo" => "bar", "bar" => "baz"];
-		//eq("bar", a.foo);
-		//eq("baz", a.bar);
-//
-		//var a:D = ["foo" => "bar", "bar" => "baz"];
-		//eq("bar", a.foo);
-		//eq("baz", a.bar);
+		var a:A = ["foo" => "bar", "bar" => "baz"];
+		eq("bar", a.foo);
+		eq("baz", a.bar);
+
+		var a:B = ["foo" => "bar", "bar" => "baz"];
+		eq("bar", a.foo);
+		eq("baz", a.bar);
+
+		var a:C = ["foo" => "bar", "bar" => "baz"];
+		eq("bar", a.foo);
+		eq("baz", a.bar);
+
+		var a:D = ["foo" => "bar", "bar" => "baz"];
+		eq("bar", a.foo);
+		eq("baz", a.bar);
 	}
 }

+ 12 - 0
tests/unit/src/unit/issues/Issue3804.hx

@@ -0,0 +1,12 @@
+package unit.issues;
+
+@:generic
+private class C<T> {
+	public function new() {}
+}
+
+class Issue3804 extends Test {
+	function test() {
+		var v:C<Int> = new C();
+	}
+}

+ 34 - 0
tests/unit/src/unit/issues/Issue3935.hx

@@ -0,0 +1,34 @@
+package unit.issues;
+
+private class MyClass {
+	public function new() { }
+}
+
+class Issue3935 extends Test {
+	function test() {
+		var c:haxe.ds.IntMap<Dynamic> = [1=>2, 3=>"4"];
+		var c:haxe.ds.StringMap<Dynamic> = ["1"=>2, "3"=>"4"];
+		var m = new MyClass();
+		var m2 = new MyClass();
+		var c:haxe.ds.ObjectMap<MyClass, Dynamic> = [m => 1, m2 => "1"];
+		var c:haxe.ds.EnumValueMap<haxe.macro.Expr.ExprDef, Dynamic> = [EBreak => 1, EContinue => "2"];
+	}
+
+	function testMap() {
+		var c:Map<Int, Dynamic> = [1=>2, 3=>"4"];
+		var c:Map<String, Dynamic> = ["1"=>2, "3"=>"4"];
+		var m = new MyClass();
+		var m2 = new MyClass();
+		var c:Map<MyClass, Dynamic> = [m => 1, m2 => "1"];
+		var c:Map<haxe.macro.Expr.ExprDef, Dynamic> = [EBreak => 1, EContinue => "2"];
+	}
+
+	function testFail() {
+		t(unit.TestType.typeError([1=>2, 3=>"4"]));
+		t(unit.TestType.typeError(["1"=>2, "3"=>"4"]));
+		var m = new MyClass();
+		var m2 = new MyClass();
+		t(unit.TestType.typeError([m => 1, m2 => "1"]));
+		t(unit.TestType.typeError([EBreak => 1, EContinue => "2"]));
+	}
+}

+ 24 - 0
tests/unit/src/unit/issues/Issue4122.hx

@@ -0,0 +1,24 @@
+package unit.issues;
+
+@:enum
+private abstract Test2(Int) to Int {
+	var PROP = 123;
+}
+
+private abstract Test3(Int) {
+	static public var PROP = 123;
+}
+
+class Issue4122 extends Test {
+	function test() {
+		eq(130, Test2.PROP + 7);
+		unit.TestType.typedAs(Test2.PROP + 7, 7);
+		feq(130.5, Test2.PROP + 7.5);
+		unit.TestType.typedAs(Test2.PROP + 7.5, 7.5);
+
+		eq(130, Test3.PROP + 7);
+		unit.TestType.typedAs(Test3.PROP + 7, 7);
+		feq(130.5, Test3.PROP + 7.5);
+		unit.TestType.typedAs(Test3.PROP + 7.5, 7.5);
+	}
+}

+ 23 - 0
tests/unit/src/unit/issues/Issue4158.hx

@@ -0,0 +1,23 @@
+package unit.issues;
+
+@:forward @:native("Short")
+private abstract TestAbstract(TestClass) from TestClass to TestClass {
+    public inline function new() {
+        this = new TestClass();
+    }
+    public function getValue2() {
+        return this.value * 2;
+    }
+}
+
+private class TestClass {
+    public var value:Int = 1;
+    public function new() { }
+}
+
+class Issue4158 extends Test {
+	function test() {
+		var o = new TestAbstract();
+		eq(2, o.getValue2());
+	}
+}

+ 26 - 0
tests/unit/src/unit/issues/Issue4180.hx

@@ -0,0 +1,26 @@
+package unit.issues;
+
+private abstract A(Int) {
+	public function new(v) this = v;
+	@:op(A-B) function _(a:Int):A;
+	public function get() return this;
+}
+
+class Issue4180 extends Test {
+	@:isVar static var a(get,set):A;
+	static function set_a(value:A):A return a = value;
+	static function get_a():A return a;
+
+	static var a2(default,set):A;
+	static function set_a2(value:A):A return a2 = value;
+
+	function test() {
+		a = new A(0);
+		a -= 5;
+		eq(-5, a.get());
+
+		a2 = new A(0);
+		a2 -= 5;
+		eq(-5, a2.get());
+	}
+}

+ 12 - 0
tests/unit/src/unit/issues/Issue4196.hx

@@ -0,0 +1,12 @@
+package unit.issues;
+
+class Issue4196 extends Test {
+	function test() {
+		var f = [
+			'a' => {"id": { "deep" : 5 }},
+			'b' => {"id": {}}
+		];
+		var a:Map<String, {id:{}}>;
+		unit.TestType.typedAs(f, a);
+	}
+}

+ 2 - 1
tests/unit/src/unitstd/Reflect.unit.hx

@@ -15,7 +15,8 @@ Reflect.field(c, "prop") == "prop";
 Reflect.field(c, "func")() == "foo";
 // As3 invokes the getter
 Reflect.field(c, "propAcc") == #if as3 "1" #else "0" #end;
-Reflect.field(null, null) == null;
+var n = null;
+Reflect.field(n, n) == null;
 Reflect.field(1, "foo") == null;
 
 // setField

+ 2 - 2
type.ml

@@ -1322,8 +1322,8 @@ let unify_kind k1 k2 =
 			| MethDynamic -> direct_access v.v_read && direct_access v.v_write
 			| MethMacro -> false
 			| MethNormal | MethInline ->
-				match v.v_write with
-				| AccNo | AccNever -> true
+				match v.v_read,v.v_write with
+				| AccNormal,(AccNo | AccNever) -> true
 				| _ -> false)
 		| Method m1, Method m2 ->
 			match m1,m2 with

+ 31 - 19
typeload.ml

@@ -200,7 +200,7 @@ let make_module ctx mpath file tdecls loadp =
 				(match !decls with
 				| (TClassDecl c,_) :: _ ->
 					List.iter (fun m -> match m with
-						| ((Meta.Build | Meta.CoreApi | Meta.Allow | Meta.Access | Meta.Enum | Meta.Dce),_,_) ->
+						| ((Meta.Build | Meta.CoreApi | Meta.Allow | Meta.Access | Meta.Enum | Meta.Dce | Meta.Native),_,_) ->
 							c.cl_meta <- m :: c.cl_meta;
 						| _ ->
 							()
@@ -1000,8 +1000,16 @@ let check_interfaces ctx c =
 	List.iter (fun (intf,params) -> check_interface ctx c intf params) c.cl_implements
 
 let rec return_flow ctx e =
-	let error() = display_error ctx "A return is missing here" e.epos; raise Exit in
+	let error() =
+		display_error ctx (Printf.sprintf "Missing return: %s" (s_type (print_context()) ctx.ret)) e.epos; raise Exit
+	in
 	let return_flow = return_flow ctx in
+	let rec uncond e = match e.eexpr with
+		| TIf _ | TWhile _ | TSwitch _ | TTry _ -> ()
+		| TReturn _ | TThrow _ -> raise Exit
+		| _ -> Type.iter uncond e
+	in
+	let has_unconditional_flow e = try uncond e; false with Exit -> true in
 	match e.eexpr with
 	| TReturn _ | TThrow _ -> ()
 	| TParenthesis e | TMeta(_,e) ->
@@ -1010,7 +1018,7 @@ let rec return_flow ctx e =
 		let rec loop = function
 			| [] -> error()
 			| [e] -> return_flow e
-			| { eexpr = TReturn _ } :: _ | { eexpr = TThrow _ } :: _ -> ()
+			| e :: _ when has_unconditional_flow e -> ()
 			| _ :: l -> loop l
 		in
 		loop el
@@ -1550,21 +1558,25 @@ let type_function ctx args ret fmode f do_display p =
 		| TMeta((Meta.MergeBlock,_,_), ({eexpr = TBlock el} as e1)) -> e1
 		| _ -> e
 	in
-	let rec loop e =
-		match e.eexpr with
-		| TReturn (Some e) -> (match follow e.etype with TAbstract({a_path = [],"Void"},[]) -> () | _ -> raise Exit)
-		| TFunction _ -> ()
-		| _ -> Type.iter loop e
+	let has_return e =
+		let rec loop e =
+			match e.eexpr with
+			| TReturn (Some _) -> raise Exit
+			| TFunction _ -> ()
+			| _ -> Type.iter loop e
+		in
+		try loop e; false with Exit -> true
 	in
-	let have_ret = (try loop e; false with Exit -> true) in
-	if have_ret then
-		(try return_flow ctx e with Exit -> ())
-	else (try type_eq EqStrict ret ctx.t.tvoid with Unify_error _ ->
-		match e.eexpr with
-		(* accept final throw (issue #1923) *)
-		| TThrow _ -> ()
-		| TBlock el when (match List.rev el with ({eexpr = TThrow _} :: _) -> true | _ -> false) -> ()
-		| _ -> display_error ctx ("Missing return " ^ (s_type (print_context()) ret)) p);
+	begin match follow ret with
+		| TAbstract({a_path=[],"Void"},_) -> ()
+		(* We have to check for the presence of return expressions here because
+		   in the case of Dynamic ctx.ret is still a monomorph. If we indeed
+		   don't have a return expression we can link the monomorph to Void. We
+		   can _not_ use type_iseq to avoid the Void check above because that
+		   would turn Dynamic returns to Void returns. *)
+		| TMono t when not (has_return e) -> ignore(link t ret ctx.t.tvoid)
+		| _ -> (try return_flow ctx e with Exit -> ())
+	end;
 	let rec loop e =
 		match e.eexpr with
 		| TCall ({ eexpr = TConst TSuper },_) -> raise Exit
@@ -2362,7 +2374,7 @@ let init_class ctx c p context_init herits fields =
 									display_error ctx ("First argument of implementation function must be " ^ (s_type (print_context()) tthis)) f.cff_pos
 							end;
 							loop ml
-(* 						| (Meta.Resolve,_,_) :: _ ->
+						| (Meta.Resolve,_,_) :: _ ->
 							let targ = if Meta.has Meta.Impl f.cff_meta then tthis else ta in
 							begin match follow t with
 								| TFun([(_,_,t1);(_,_,t2)],_) ->
@@ -2372,7 +2384,7 @@ let init_class ctx c p context_init herits fields =
 									end
 								| _ ->
 									error ("Field type of resolve must be " ^ (s_type (print_context()) targ) ^ " -> String -> T") f.cff_pos
-							end *)
+							end
 						| _ :: ml ->
 							loop ml
 						| [] ->

+ 109 - 61
typer.ml

@@ -540,36 +540,36 @@ let collect_toplevel_identifiers ctx =
 (* ---------------------------------------------------------------------- *)
 (* PASS 3 : type expression & check structure *)
 
-let rec base_params t =
-	let tl = ref [] in
-	let rec loop t = (match t with
-		| TInst(cl, params) ->
-			(match cl.cl_kind with
-			| KTypeParameter tl -> List.iter loop tl
-			| _ -> ());
-			List.iter (fun (ic, ip) ->
-				let t = apply_params cl.cl_params params (TInst (ic,ip)) in
-				loop t
-			) cl.cl_implements;
-			(match cl.cl_super with None -> () | Some (csup, pl) ->
-				let t = apply_params cl.cl_params params (TInst (csup,pl)) in
-				loop t);
-			tl := t :: !tl;
-		| TEnum(en,(_ :: _ as tl2)) ->
-			tl := (TEnum(en,List.map (fun _ -> t_dynamic) tl2)) :: !tl;
-			tl := t :: !tl;
-		| TType (td,pl) ->
-			loop (apply_params td.t_params pl td.t_type);
-			(* prioritize the most generic definition *)
-			tl := t :: !tl;
-		| TLazy f -> loop (!f())
-		| TMono r -> (match !r with None -> () | Some t -> loop t)
-		| _ -> tl := t :: !tl)
-	in
-	loop t;
-	!tl
-
 let rec unify_min_raise ctx (el:texpr list) : t =
+	let rec base_types t =
+		let tl = ref [] in
+		let rec loop t = (match t with
+			| TInst(cl, params) ->
+				(match cl.cl_kind with
+				| KTypeParameter tl -> List.iter loop tl
+				| _ -> ());
+				List.iter (fun (ic, ip) ->
+					let t = apply_params cl.cl_params params (TInst (ic,ip)) in
+					loop t
+				) cl.cl_implements;
+				(match cl.cl_super with None -> () | Some (csup, pl) ->
+					let t = apply_params cl.cl_params params (TInst (csup,pl)) in
+					loop t);
+				tl := t :: !tl;
+			| TEnum(en,(_ :: _ as tl2)) ->
+				tl := (TEnum(en,List.map (fun _ -> t_dynamic) tl2)) :: !tl;
+				tl := t :: !tl;
+			| TType (td,pl) ->
+				loop (apply_params td.t_params pl td.t_type);
+				(* prioritize the most generic definition *)
+				tl := t :: !tl;
+			| TLazy f -> loop (!f())
+			| TMono r -> (match !r with None -> () | Some t -> loop t)
+			| _ -> tl := t :: !tl)
+		in
+		loop t;
+		!tl
+	in
 	match el with
 	| [] -> mk_mono()
 	| [e] -> e.etype
@@ -631,7 +631,7 @@ let rec unify_min_raise ctx (el:texpr list) : t =
 		with Not_found ->
 			(* Second pass: Get all base types (interfaces, super classes and their interfaces) of most general type.
 			   Then for each additional type filter all types that do not unify. *)
-			let common_types = base_params t in
+			let common_types = base_types t in
 			let dyn_types = List.fold_left (fun acc t ->
 				let rec loop c =
 					Meta.has Meta.UnifyMinDynamic c.cl_meta || (match c.cl_super with None -> false | Some (c,_) -> loop c)
@@ -989,10 +989,6 @@ let rec acc_get ctx g p =
 		(* build a closure with first parameter applied *)
 		(match follow et.etype with
 		| TFun (_ :: args,ret) ->
-			begin match follow e.etype,cf.cf_kind with
-				| TAbstract _,Method MethInline -> error "Cannot create closure on abstract inline method" e.epos
-				| _ -> ()
-			end;
 			let tcallb = TFun (args,ret) in
 			let twrap = TFun ([("_e",false,e.etype)],tcallb) in
 			(* arguments might not have names in case of variable fields of function types, so we generate one (issue #2495) *)
@@ -1005,7 +1001,7 @@ let rec acc_get ctx g p =
 			let ecallb = mk (TFunction {
 				tf_args = List.map (fun (o,v) -> v,if o then Some TNull else None) args;
 				tf_type = ret;
-				tf_expr = mk (TReturn (Some ecall)) t_dynamic p;
+				tf_expr = (match follow ret with | TAbstract ({a_path = [],"Void"},_) -> ecall | _ -> mk (TReturn (Some ecall)) t_dynamic p);
 			}) tcallb p in
 			let ewrap = mk (TFunction {
 				tf_args = [ve,None];
@@ -1633,14 +1629,14 @@ and type_field ?(resume=false) ctx e i p mode =
 			(match ctx.curfun, e.eexpr with
 			| FunMemberAbstract, TConst (TThis) -> type_field ctx {e with etype = apply_params a.a_params pl a.a_this} i p mode;
 			| _ -> raise Not_found)
-(* 		with Not_found -> try
+		with Not_found -> try
 			let c = (match a.a_impl with None -> raise Not_found | Some c -> c) in
 			let cf = PMap.find "resolve" c.cl_statics in
 			if not (Meta.has Meta.Resolve cf.cf_meta) then raise Not_found;
 			let et = type_module_type ctx (TClassDecl c) None p in
 			let t = apply_params a.a_params pl (field_type ctx c [] cf p) in
 			let ef = mk (TField (et,FStatic (c,cf))) t p in
-			AKExpr ((!build_call_ref) ctx (AKUsing(ef,c,cf,e)) [EConst (String i),p] NoValue p) *)
+			AKExpr ((!build_call_ref) ctx (AKUsing(ef,c,cf,e)) [EConst (String i),p] NoValue p)
 		with Not_found ->
 			if !static_abstract_access_through_instance then error ("Invalid call to static function " ^ i ^ " through abstract instance") p
 			else no_field())
@@ -1919,7 +1915,7 @@ let rec type_binop ctx op e1 e2 is_assign_op with_type p =
 			let ev = mk (TLocal v) e.etype p in
 			let get = type_binop ctx op (EField ((EConst (Ident v.v_name),p),cf.cf_name),p) e2 true with_type p in
 			let e' = match get.eexpr with
-				| TBinop _ ->
+				| TBinop _ | TMeta((Meta.RequiresAssign,_,_),_) ->
 					unify ctx get.etype t p;
 					make_call ctx (mk (TField (ev,quick_field_dynamic ev.etype ("set_" ^ cf.cf_name))) (tfun [t] t) p) [get] t p
 				| _ ->
@@ -2085,6 +2081,18 @@ and type_binop2 ctx op (e1 : texpr) (e2 : Ast.expr) is_assign_op wt p =
 		| KUnk, KParam t ->
 			unify ctx e1.etype tfloat e1.epos;
 			tfloat
+		| KAbstract _,KFloat ->
+			unify ctx e1.etype tfloat e1.epos;
+			tfloat
+		| KFloat, KAbstract _ ->
+			unify ctx e2.etype tfloat e2.epos;
+			tfloat
+		| KAbstract _,KInt ->
+			unify ctx e1.etype ctx.t.tint e1.epos;
+			ctx.t.tint
+		| KInt, KAbstract _ ->
+			unify ctx e2.etype ctx.t.tint e2.epos;
+			ctx.t.tint
 		| KAbstract _,_
 		| _,KAbstract _
 		| KParam _, _
@@ -2999,34 +3007,63 @@ and type_expr ctx (e,p) (with_type:with_type) =
 			mk (TLocal v) v.v_type p;
 		]) v.v_type p
 	| EArrayDecl ((EBinop(OpArrow,_,_),_) as e1 :: el) ->
-		let keys = Hashtbl.create 0 in
-		let (tkey,tval),resume =
+		let (tkey,tval,has_type),resume =
 			let get_map_params t = match follow t with
-				| TAbstract({a_path=[],"Map"},[tk;tv]) -> tk,tv
-				| _ -> mk_mono(),mk_mono()
+				| TAbstract({a_path=[],"Map"},[tk;tv]) -> tk,tv,true
+				| TInst({cl_path=["haxe";"ds"],"IntMap"},[tv]) -> ctx.t.tint,tv,true
+				| TInst({cl_path=["haxe";"ds"],"StringMap"},[tv]) -> ctx.t.tstring,tv,true
+				| TInst({cl_path=["haxe";"ds"],("ObjectMap" | "EnumValueMap")},[tk;tv]) -> tk,tv,true
+				| _ -> mk_mono(),mk_mono(),false
 			in
 			match with_type with
 			| WithType t -> get_map_params t,false
 			| WithTypeResume t -> get_map_params t,true
-			| _ -> (mk_mono(),mk_mono()),false
+			| _ -> (mk_mono(),mk_mono(),false),false
 		in
+		let keys = Hashtbl.create 0 in
 		let unify_with_resume ctx e t p =
 			if resume then try Codegen.AbstractCast.cast_or_unify_raise ctx t e p with Error (Unify l,p) -> raise (WithTypeError(l,p))
 			else Codegen.AbstractCast.cast_or_unify ctx t e p
 		in
-		let type_arrow e1 e2 =
-			let e1 = type_expr ctx e1 (WithType tkey) in
+		let check_key e_key =
 			try
-				let p = Hashtbl.find keys e1.eexpr in
-				display_error ctx "Duplicate key" e1.epos;
+				let p = Hashtbl.find keys e_key.eexpr in
+				display_error ctx "Duplicate key" e_key.epos;
 				error "Previously defined here" p
 			with Not_found ->
-				Hashtbl.add keys e1.eexpr e1.epos;
+				Hashtbl.add keys e_key.eexpr e_key.epos;
+		in
+		let el = e1 :: el in
+		let el_kv = List.map (fun e -> match fst e with
+			| EBinop(OpArrow,e1,e2) -> e1,e2
+			| _ -> error "Expected a => b" (pos e)
+		) el in
+		let el_k,el_v,tkey,tval = if has_type then begin
+			let el_k,el_v = List.fold_left (fun (el_k,el_v) (e1,e2) ->
+				let e1 = type_expr ctx e1 (WithType tkey) in
+				check_key e1;
 				let e1 = unify_with_resume ctx e1 tkey e1.epos in
 				let e2 = type_expr ctx e2 (WithType tval) in
 				let e2 = unify_with_resume ctx e2 tval e2.epos in
-				e1,e2
-		in
+				(e1 :: el_k,e2 :: el_v)
+			) ([],[]) el_kv in
+			el_k,el_v,tkey,tval
+		end else begin
+			let el_k,el_v = List.fold_left (fun (el_k,el_v) (e1,e2) ->
+				let e1 = type_expr ctx e1 Value in
+				check_key e1;
+				let e2 = type_expr ctx e2 Value in
+				(e1 :: el_k,e2 :: el_v)
+			) ([],[]) el_kv in
+			let unify_min_resume el = try
+				unify_min_raise ctx el
+			with Error (Unify l,p) when resume ->
+				 raise (WithTypeError(l,p))
+			in
+			let tkey = unify_min_resume el_k in
+			let tval = unify_min_resume el_v in
+			el_k,el_v,tkey,tval
+		end in
 		let m = Typeload.load_module ctx ([],"Map") null_pos in
 		let a,c = match m.m_types with
 			| (TAbstractDecl ({a_impl = Some c} as a)) :: _ -> a,c
@@ -3034,18 +3071,11 @@ and type_expr ctx (e,p) (with_type:with_type) =
 		in
 		let tmap = TAbstract(a,[tkey;tval]) in
 		let cf = PMap.find "set" c.cl_statics in
-		let el = e1 :: el in
 		let v = gen_local ctx tmap in
 		let ev = mk (TLocal v) tmap p in
 		let ec = type_module_type ctx (TClassDecl c) None p in
 		let ef = mk (TField(ec,FStatic(c,cf))) (tfun [tkey;tval] ctx.t.tvoid) p in
-		let el = ev :: List.fold_left (fun acc e -> match fst e with
-			| EBinop(OpArrow,e1,e2) ->
-				let e1,e2 = type_arrow e1 e2 in
-				(make_call ctx ef [ev;e1;e2] ctx.com.basic.tvoid p) :: acc
-			| _ ->
-				error "Expected a => b" (snd e)
-		) [] el in
+		let el = ev :: List.map2 (fun e1 e2 -> (make_call ctx ef [ev;e1;e2] ctx.com.basic.tvoid p)) el_k el_v in
 		let enew = mk (TNew(c,[tkey;tval],[])) tmap p in
 		let el = (mk (TVar (v,Some enew)) t_dynamic p) :: (List.rev el) in
 		mk (TBlock el) tmap p
@@ -3337,7 +3367,20 @@ and type_expr ctx (e,p) (with_type:with_type) =
 				let monos = List.map (fun _ -> mk_mono()) c.cl_params in
 				let ct, f = get_constructor ctx c monos p in
 				ignore (unify_constructor_call c monos f ct);
-				Codegen.build_generic ctx c p monos
+				begin try
+					Codegen.build_generic ctx c p monos
+				with Codegen.Generic_Exception _ as exc ->
+					(* If we have an expected type, just use that (issue #3804) *)
+					begin match with_type with
+						| WithType t | WithTypeResume t ->
+							begin match follow t with
+								| TMono _ -> raise exc
+								| t -> t
+							end
+						| _ ->
+							raise exc
+					end
+				end
 			| mt ->
 				error ((s_type_path (t_infos mt).mt_path) ^ " cannot be constructed") p
 		in
@@ -3511,7 +3554,7 @@ and type_expr ctx (e,p) (with_type:with_type) =
 		let texpr = loop t in
 		mk (TCast (type_expr ctx e Value,Some texpr)) t p
 	| EDisplay (e,iscall) ->
-		handle_display ctx e iscall p
+		handle_display ctx e iscall with_type p
 	| EDisplayNew t ->
 		let t = Typeload.load_instance ctx t p true in
 		(match follow t with
@@ -3608,7 +3651,7 @@ and get_stored_typed_expr com id =
 	build_expr  e
 
 
-and handle_display ctx e_ast iscall p =
+and handle_display ctx e_ast iscall with_type p =
 	let old = ctx.in_display in
 	ctx.in_display <- true;
 	let get_submodule_fields path =
@@ -3757,6 +3800,11 @@ and handle_display ctx e_ast iscall p =
 					end else
 						acc
 				) c.cl_statics fields
+			| TAnon a when PMap.is_empty a.a_fields ->
+				begin match with_type with
+				| WithType t | WithTypeResume t -> get_fields t
+				| _ -> a.a_fields
+				end
 			| TAnon a ->
 				(match !(a.a_status) with
 				| Statics c ->