Browse Source

Merge branch 'development' into dev_js_improvements

Conflicts:
	genjs.ml
Luca Deltodesco 12 năm trước cách đây
mục cha
commit
3d21c222b5

+ 1 - 1
Makefile

@@ -90,7 +90,7 @@ codegen.cmx: optimizer.cmx typeload.cmx typecore.cmx type.cmx genxml.cmx common.
 
 common.cmx: type.cmx ast.cmx
 
-dce.cmx: ast.cmx common.cmx type.cmx
+dce.cmx: ast.cmx common.cmx codegen.cmx type.cmx
 
 genas3.cmx: type.cmx common.cmx codegen.cmx ast.cmx
 

+ 1 - 0
ast.ml

@@ -47,6 +47,7 @@ module Meta = struct
 		| CoreType
 		| CppFileCode
 		| CppNamespaceCode
+		| Dce
 		| Debug
 		| Decl
 		| DefParam

+ 27 - 20
codegen.ml

@@ -623,8 +623,11 @@ let check_private_path ctx t = match t with
 		()
 
 (* Removes generic base classes *)
+
+let is_removable_class c = c.cl_kind = KGeneric && (has_ctor_constraint c || Meta.has Meta.Remove c.cl_meta)
+
 let remove_generic_base ctx t = match t with
-	| TClassDecl c when c.cl_kind = KGeneric && has_ctor_constraint c ->
+	| TClassDecl c when is_removable_class c ->
 		c.cl_extern <- true
 	| _ ->
 		()
@@ -854,6 +857,8 @@ let promote_complex_rhs ctx e =
 			{ e with eexpr = TMeta(m,loop f e1)}
 		| TReturn _ | TThrow _ ->
 			find e
+		| TCast(e1,None) when ctx.config.pf_ignore_unsafe_cast ->
+			loop f e1
 		| _ ->
 			f (find e)
 	and block el =
@@ -1522,28 +1527,29 @@ module Abstract = struct
 	let check_cast ctx tleft eright p =
 		if ctx.com.display then eright else do_check_cast ctx tleft eright p
 
+	let find_multitype_specialization a pl p =
+		let m = mk_mono() in
+		let at = apply_params a.a_types pl a.a_this in
+		let _,cfo =
+			try find_to a pl m
+			with Not_found ->
+				let st = s_type (print_context()) at in
+				if has_mono at then
+					error ("Type parameters of multi type abstracts must be known (for " ^ st ^ ")") p
+				else
+					error ("Abstract " ^ (s_type_path a.a_path) ^ " has no @:to function that accepts " ^ st) p;
+		in
+		match cfo with
+			| None -> assert false
+			| Some cf -> cf, follow m
+
 	let handle_abstract_casts ctx e =
 		let rec loop ctx e = match e.eexpr with
 			| TNew({cl_kind = KAbstractImpl a} as c,pl,el) ->
-				(* a TNew of an abstract implementation is only generated if it is a generic abstract *)
-				let at = apply_params a.a_types pl a.a_this in
-				let m = mk_mono() in
-				let _,cfo =
-					try find_to a pl m
-					with Not_found ->
-						let st = s_type (print_context()) at in
-						if has_mono at then
-							error ("Type parameters of multi type abstracts must be known (for " ^ st ^ ")") e.epos
-						else
-							error ("Abstract " ^ (s_type_path a.a_path) ^ " has no @:to function that accepts " ^ st) e.epos;
-				in
-				begin match cfo with
-				| None -> assert false
-				| Some cf ->
-					let m = follow m in
-					let e = make_static_call ctx c cf a pl ((mk (TConst TNull) (TAbstract(a,pl)) e.epos) :: el) m e.epos in
-					{e with etype = m}
-				end
+				(* a TNew of an abstract implementation is only generated if it is a multi type abstract *)
+				let cf,m = find_multitype_specialization a pl e.epos in
+				let e = make_static_call ctx c cf a pl ((mk (TConst TNull) (TAbstract(a,pl)) e.epos) :: el) m e.epos in
+				{e with etype = m}
 			| TCall(e1, el) ->
 				begin try
 					begin match e1.eexpr with
@@ -1706,6 +1712,7 @@ let post_process ctx filters t =
 	if m.m_processed = 0 then m.m_processed <- !pp_counter;
 	if m.m_processed = !pp_counter then
 	match t with
+	| TClassDecl c when is_removable_class c -> ()
 	| TClassDecl c ->
 		let process_field f =
 			match f.cf_expr with

+ 23 - 4
common.ml

@@ -97,6 +97,8 @@ type platform_config = {
 	pf_pattern_matching : bool;
 	(** can the platform use default values for non-nullable arguments *)
 	pf_can_skip_non_nullable_argument : bool;
+	(** generator ignores TCast(_,None) *)
+	pf_ignore_unsafe_cast : bool;
 }
 
 type context = {
@@ -154,6 +156,7 @@ module Define = struct
 		| As3
 		| CheckXmlProxy
 		| CoreApi
+		| Cppia
 		| Dce
 		| DceDebug
 		| Debug
@@ -217,6 +220,7 @@ module Define = struct
 		| As3 -> ("as3","Defined when outputing flash9 as3 source code")
 		| CheckXmlProxy -> ("check_xml_proxy","Check the used fields of the xml proxy")
 		| CoreApi -> ("core_api","Defined in the core api context")
+		| Cppia -> ("cppia", "Generate experimental cpp instruction assembly")
 		| Dce -> ("dce","The current DCE mode")
 		| DceDebug -> ("dce_debug","Show DCE log")
 		| Debug -> ("debug","Activated when compiling with -debug")
@@ -315,6 +319,7 @@ module MetaInfo = struct
 		| CoreType -> ":coreType",("Identifies an abstract as core type so that it requires no implementation",[UsedOn TAbstract])
 		| CppFileCode -> ":cppFileCode",("",[Platform Cpp])
 		| CppNamespaceCode -> ":cppNamespaceCode",("",[Platform Cpp])
+		| Dce -> ":dce",("Forces dead code elimination even when not -dce full is specified",[UsedOnEither [TClass;TEnum]])
 		| Debug -> ":debug",("Forces debug information to be generated into the Swf even without -debug",[UsedOnEither [TClass;TClassField]; Platform Flash])
 		| Decl -> ":decl",("",[Platform Cpp])
 		| DefParam -> ":defParam",("?",[])
@@ -449,6 +454,7 @@ let default_config =
 		pf_overload = false;
 		pf_pattern_matching = false;
 		pf_can_skip_non_nullable_argument = true;
+		pf_ignore_unsafe_cast = false;
 	}
 
 let get_config com =
@@ -470,6 +476,7 @@ let get_config com =
 			pf_overload = false;
 			pf_pattern_matching = false;
 			pf_can_skip_non_nullable_argument = true;
+			pf_ignore_unsafe_cast = false;
 		}
 	| Js ->
 		{
@@ -485,6 +492,7 @@ let get_config com =
 			pf_overload = false;
 			pf_pattern_matching = false;
 			pf_can_skip_non_nullable_argument = true;
+			pf_ignore_unsafe_cast = true;
 		}
 	| Neko ->
 		{
@@ -500,6 +508,7 @@ let get_config com =
 			pf_overload = false;
 			pf_pattern_matching = false;
 			pf_can_skip_non_nullable_argument = true;
+			pf_ignore_unsafe_cast = true;
 		}
 	| Flash when defined Define.As3 ->
 		{
@@ -515,6 +524,7 @@ let get_config com =
 			pf_overload = false;
 			pf_pattern_matching = false;
 			pf_can_skip_non_nullable_argument = false;
+			pf_ignore_unsafe_cast = false;
 		}
 	| Flash ->
 		{
@@ -530,6 +540,7 @@ let get_config com =
 			pf_overload = false;
 			pf_pattern_matching = false;
 			pf_can_skip_non_nullable_argument = false;
+			pf_ignore_unsafe_cast = false;
 		}
 	| Php ->
 		{
@@ -550,6 +561,7 @@ let get_config com =
 			pf_overload = false;
 			pf_pattern_matching = false;
 			pf_can_skip_non_nullable_argument = true;
+			pf_ignore_unsafe_cast = false;
 		}
 	| Cpp ->
 		{
@@ -565,6 +577,7 @@ let get_config com =
 			pf_overload = false;
 			pf_pattern_matching = false;
 			pf_can_skip_non_nullable_argument = true;
+			pf_ignore_unsafe_cast = false;
 		}
 	| Cs ->
 		{
@@ -580,6 +593,7 @@ let get_config com =
 			pf_overload = true;
 			pf_pattern_matching = false;
 			pf_can_skip_non_nullable_argument = true;
+			pf_ignore_unsafe_cast = false;
 		}
 	| Java ->
 		{
@@ -595,6 +609,7 @@ let get_config com =
 			pf_overload = true;
 			pf_pattern_matching = false;
 			pf_can_skip_non_nullable_argument = true;
+			pf_ignore_unsafe_cast = false;
 		}
 
 let create v args =
@@ -761,10 +776,14 @@ let rec has_feature com f =
 			let r = (try
 				let path = List.rev pack, cl in
 				(match List.find (fun t -> t_path t = path && not (Ast.Meta.has Ast.Meta.RealPath (t_infos t).mt_meta)) com.types with
-				| t when meth = "*" -> (match t with TAbstractDecl a -> Ast.Meta.has Ast.Meta.ValueUsed a.a_meta | _ -> Ast.Meta.has Ast.Meta.Used (t_infos t).mt_meta)
-				| TClassDecl ({cl_extern = true} as c) -> Meta.has Meta.Used (try PMap.find meth c.cl_statics with Not_found -> PMap.find meth c.cl_fields).cf_meta
-				| TClassDecl c -> PMap.exists meth c.cl_statics || PMap.exists meth c.cl_fields
-				| _ -> false)
+				| t when meth = "*" -> (match t with TAbstractDecl a -> Ast.Meta.has Ast.Meta.ValueUsed a.a_meta | _ ->
+					Ast.Meta.has Ast.Meta.Used (t_infos t).mt_meta)
+				| TClassDecl ({cl_extern = true} as c) when com.platform <> Js || cl <> "Array" && cl <> "Math" ->
+					Meta.has Meta.Used (try PMap.find meth c.cl_statics with Not_found -> PMap.find meth c.cl_fields).cf_meta
+				| TClassDecl c ->
+					PMap.exists meth c.cl_statics || PMap.exists meth c.cl_fields
+				| _ ->
+					false)
 			with Not_found ->
 				false
 			) in

+ 57 - 38
dce.ml

@@ -34,6 +34,8 @@ type dce = {
 	mutable marked_fields : tclass_field list;
 	mutable marked_maybe_fields : tclass_field list;
 	mutable t_stack : t list;
+	mutable ts_stack : t list;
+	mutable features : (string,(tclass * tclass_field * bool) list) Hashtbl.t;
 }
 
 (* checking *)
@@ -50,38 +52,36 @@ let is_std_file dce file =
 (* check if a class is kept entirely *)
 let keep_whole_class dce c =
 	Meta.has Meta.Keep c.cl_meta
-	|| not (dce.full || is_std_file dce c.cl_module.m_extra.m_file)
+	|| not (dce.full || is_std_file dce c.cl_module.m_extra.m_file || has_meta Meta.Dce c.cl_meta)
 	|| super_forces_keep c
 	|| (match c with
-		| { cl_extern = true; cl_path = ([],("Math"|"Array"))} when dce.com.platform = Js -> false
+		| { cl_path = ([],("Math"|"Array"))} when dce.com.platform = Js -> false
 		| { cl_extern = true }
 		| { cl_path = ["flash";"_Boot"],"RealBoot" } -> true
 		| { cl_path = [],"String" }
 		| { cl_path = [],"Array" } -> not (dce.com.platform = Js)
 		| _ -> false)
 
-(* check if a metadata contains @:ifFeature with a used feature argument *)
-let has_used_feature com meta =
-	try
-		let _,el,_ = Meta.get Meta.IfFeature meta in
-		List.exists (fun e -> match fst e with
-			| EConst(String s) when Common.has_feature com s -> true
-			| _ -> false
-		) el
-	with Not_found ->
-		false
-
 (* check if a field is kept *)
 let keep_field dce cf =
 	Meta.has Meta.Keep cf.cf_meta
 	|| Meta.has Meta.Used cf.cf_meta
 	|| cf.cf_name = "__init__"
-	|| has_used_feature dce.com cf.cf_meta
 
 (* marking *)
 
+let rec check_feature dce s =
+	try
+		let l = Hashtbl.find dce.features s in
+		List.iter (fun (c,cf,stat) ->
+			mark_field dce c cf stat
+		) l;
+		Hashtbl.remove dce.features s;
+	with Not_found ->
+		()
+
 (* mark a field as kept *)
-let rec mark_field dce c cf stat =
+and mark_field dce c cf stat =
 	let add cf =
 		if not (Meta.has Meta.Used cf.cf_meta) then begin
 			cf.cf_meta <- (Meta.Used,[],cf.cf_pos) :: cf.cf_meta;
@@ -136,26 +136,34 @@ and mark_abstract dce a = if not (Meta.has Meta.Used a.a_meta) then
 	a.a_meta <- (Meta.Used,[],a.a_pos) :: a.a_meta
 
 (* mark a type as kept *)
-and mark_t dce t = match follow t with
-	| TInst({cl_kind = KTypeParameter tl} as c,pl) ->
-		if not (Meta.has Meta.Used c.cl_meta) then begin
-			c.cl_meta <- (Meta.Used,[],c.cl_pos) :: c.cl_meta;
-			List.iter (mark_t dce) tl;
+and mark_t dce t =
+	if not (List.exists (fun t2 -> Type.fast_eq t t2) dce.t_stack) then begin
+		dce.t_stack <- t :: dce.t_stack;
+		begin match follow t with
+		| TInst({cl_kind = KTypeParameter tl} as c,pl) ->
+			if not (Meta.has Meta.Used c.cl_meta) then begin
+				c.cl_meta <- (Meta.Used,[],c.cl_pos) :: c.cl_meta;
+				List.iter (mark_t dce) tl;
+			end;
+			List.iter (mark_t dce) pl
+		| TInst(c,pl) ->
+			mark_class dce c;
+			List.iter (mark_t dce) pl
+		| TFun(args,ret) ->
+			List.iter (fun (_,_,t) -> mark_t dce t) args;
+			mark_t dce ret
+		| TEnum(e,pl) ->
+			mark_enum dce e;
+			List.iter (mark_t dce) pl
+		| TAbstract(a,pl) when Meta.has Meta.MultiType a.a_meta ->
+			mark_t dce (snd (Codegen.Abstract.find_multitype_specialization a pl Ast.null_pos))
+		| TAbstract(a,pl) ->
+			mark_abstract dce a;
+			List.iter (mark_t dce) pl
+		| TLazy _ | TDynamic _ | TAnon _ | TType _ | TMono _ -> ()
 		end;
-		List.iter (mark_t dce) pl
-	| TInst(c,pl) ->
-		mark_class dce c;
-		List.iter (mark_t dce) pl
-	| TFun(args,ret) ->
-		List.iter (fun (_,_,t) -> mark_t dce t) args;
-		mark_t dce ret
-	| TEnum(e,pl) ->
-		mark_enum dce e;
-		List.iter (mark_t dce) pl
-	| TAbstract(a,pl) ->
-		mark_abstract dce a;
-		List.iter (mark_t dce) pl
-	| TLazy _ | TDynamic _ | TAnon _ | TType _ | TMono _ -> ()
+		dce.t_stack <- List.tl dce.t_stack
+	end
 
 let mark_mt dce mt = match mt with
 	| TClassDecl c ->
@@ -198,11 +206,11 @@ let opt f e = match e with None -> () | Some e -> f e
 
 let rec to_string dce t =
 	let push t =
-		dce.t_stack <- t :: dce.t_stack;
-		fun () -> dce.t_stack <- List.tl dce.t_stack
+		dce.ts_stack <- t :: dce.ts_stack;
+		fun () -> dce.ts_stack <- List.tl dce.ts_stack
 	in
 	let t = follow t in
-	if not (List.exists (fun t2 -> Type.fast_eq t t2) dce.t_stack) then match follow t with
+	if not (List.exists (fun t2 -> Type.fast_eq t t2) dce.ts_stack) then match follow t with
 	| TInst(c,pl) as t ->
 		let pop = push t in
 		field dce c "toString" false;
@@ -291,6 +299,7 @@ and expr dce e =
 			mark_t dce v.v_type;
 		) vl;
 	| TCast(e, Some mt) ->
+		check_feature dce "typed_cast";
 		mark_mt dce mt;
 		expr dce e;
 	| TTypeExpr mt ->
@@ -298,11 +307,13 @@ and expr dce e =
 	| TTry(e, vl) ->
 		expr dce e;
 		List.iter (fun (v,e) ->
+			if v.v_type != t_dynamic then check_feature dce "typed_catch";
 			expr dce e;
 			mark_t dce v.v_type;
 		) vl;
 	| TCall ({eexpr = TLocal ({v_name = "__define_feature__"})},[{eexpr = TConst (TString ft)};e]) ->
 		Common.add_feature dce.com ft;
+		check_feature dce ft;
 		expr dce e
 	(* keep toString method when the class is argument to Std.string or haxe.Log.trace *)
 	| TCall ({eexpr = TField({eexpr = TTypeExpr (TClassDecl ({cl_path = (["haxe"],"Log")} as c))},FStatic (_,{cf_name="trace"}))} as ef, ([e2;_] as args))
@@ -355,6 +366,8 @@ let run com main full =
 		marked_fields = [];
 		marked_maybe_fields = [];
 		t_stack = [];
+		ts_stack = [];
+		features = Hashtbl.create 0;
 	} in
 	begin match main with
 		| Some {eexpr = TCall({eexpr = TField(e,(FStatic(c,cf)))},_)} ->
@@ -362,6 +375,12 @@ let run com main full =
 		| _ ->
 			()
 	end;
+	List.iter (fun m ->
+		List.iter (fun (s,v) ->
+			if Hashtbl.mem dce.features s then Hashtbl.replace dce.features s (v :: Hashtbl.find dce.features s)
+			else Hashtbl.add dce.features s [v]
+		) m.m_extra.m_features;
+	) com.modules;
 	(* first step: get all entry points, which is the main method and all class methods which are marked with @:keep *)
 	List.iter (fun t -> match t with
 		| TClassDecl c ->
@@ -442,7 +461,7 @@ let run com main full =
 					if dce.debug then print_endline ("[DCE] Removed class " ^ (s_type_path c.cl_path));
 					loop acc l)
 			end
- 		| (TEnumDecl e) as mt :: l when Meta.has Meta.Used e.e_meta || Meta.has Meta.Keep e.e_meta || e.e_extern || not (dce.full || is_std_file dce e.e_module.m_extra.m_file) ->
+ 		| (TEnumDecl e) as mt :: l when Meta.has Meta.Used e.e_meta || Meta.has Meta.Keep e.e_meta || e.e_extern || not (dce.full || is_std_file dce e.e_module.m_extra.m_file || has_meta Meta.Dce e.e_meta) ->
 			loop (mt :: acc) l
 		| TEnumDecl e :: l ->
 			if dce.debug then print_endline ("[DCE] Removed enum " ^ (s_type_path e.e_path));

+ 436 - 15
gencpp.ml

@@ -1133,24 +1133,41 @@ let has_default_values args =
 
 exception PathFound of string;;
 
-let hx_stack_push ctx output clazz func_name pos =
-   let file = pos.pfile in
+let gen_hash seed str =
+	let h = ref (Int32.of_int seed) in
+	let cycle = Int32.of_int 223 in
+	for i = 0 to String.length str - 1 do
+		h := Int32.add (Int32.mul !h cycle) (Int32.of_int (int_of_char (String.unsafe_get str i)));
+	done;
+   Printf.sprintf "0x%08lx" !h
+;;
+
+let strip_file ctx file =
 	let flen = String.length file in
 	(* Not quite right - should probably test is file exists *)
-   let stripped_file = try
+   try
 		List.iter (fun path ->
 			let plen = String.length path in
 			if (flen>plen && path=(String.sub file 0 plen ))
 				then raise (PathFound (String.sub file plen (flen-plen)) ) )
-			 (ctx.ctx_common.class_path @ ctx.ctx_common.std_path);
+			 (ctx.class_path @ ctx.std_path);
 		file;
-	with PathFound tail -> tail in
+	with PathFound tail ->
+      tail
+;;
+
+
+let hx_stack_push ctx output clazz func_name pos =
+   let stripped_file = strip_file ctx.ctx_common pos.pfile in
    let qfile = "\"" ^ (Ast.s_escape stripped_file) ^ "\"" in
 	ctx.ctx_file_info := PMap.add qfile qfile !(ctx.ctx_file_info);
-	if (ctx.ctx_dump_stack_line) then
-		output ("HX_STACK_FRAME(\"" ^ clazz ^ "\",\"" ^ func_name ^ "\",\"" ^ 
+	if (ctx.ctx_dump_stack_line) then begin
+      let hash_class_func = gen_hash 0 (clazz^"."^func_name) in
+      let hash_file_line = gen_hash (Lexer.get_error_line pos) stripped_file in
+		output ("HX_STACK_FRAME(\"" ^ clazz ^ "\",\"" ^ func_name ^ "\"," ^ hash_class_func ^ ",\"" ^
                 clazz ^ "." ^ func_name ^ "\"," ^ qfile ^ "," ^
-			    (string_of_int (Lexer.get_error_line pos) ) ^ ")\n")
+			    (string_of_int (Lexer.get_error_line pos) ) ^  "," ^ hash_file_line ^ ")\n")
+   end
 ;;
 
 
@@ -2069,7 +2086,7 @@ let rec all_virtual_functions clazz =
 
 			   (* external mem  Dynamic & *)
 
-let gen_field ctx class_def class_name ptr_name is_static is_interface field =
+let gen_field ctx class_def class_name ptr_name dot_name is_static is_interface field =
 	let output = ctx.ctx_output in
 	ctx.ctx_real_this_ptr <- not is_static;
 	let remap_name = keyword_remap field.cf_name in
@@ -2099,7 +2116,7 @@ let gen_field ctx class_def class_name ptr_name is_static is_interface field =
 		end else begin
 			ctx.ctx_dump_stack_line <- true;
 			(fun() ->
-         hx_stack_push ctx output_i ptr_name field.cf_name function_def.tf_expr.epos;
+         hx_stack_push ctx output_i dot_name field.cf_name function_def.tf_expr.epos;
          if (not is_static) then output_i ("HX_STACK_THIS(this)\n");
 			List.iter (fun (v,_) -> output_i ("HX_STACK_ARG(" ^ (keyword_remap v.v_name) ^ ",\"" ^ v.v_name ^"\")\n") )
             function_def.tf_args )
@@ -2795,6 +2812,7 @@ let access_str a = match a with
 let generate_class_files common_ctx member_types super_deps constructor_deps class_def file_info scriptable =
 	let class_path = class_def.cl_path in
 	let class_name = (snd class_path) ^ "_obj" in
+	let dot_name = join_class_path class_path "." in
 	let is_abstract_impl = match class_def.cl_kind with | KAbstractImpl _ -> true | _ -> false in
 	let smart_class_name =  (snd class_path)  in
 	(*let cpp_file = new_cpp_file common_ctx.file class_path in*)
@@ -2871,7 +2889,7 @@ let generate_class_files common_ctx member_types super_deps constructor_deps cla
 			| Some definition ->
 					(match  definition.cf_expr with
 					| Some { eexpr = TFunction function_def } ->
-      				hx_stack_push ctx output_cpp smart_class_name "new" function_def.tf_expr.epos;
+      				hx_stack_push ctx output_cpp dot_name "new" function_def.tf_expr.epos;
 		            List.iter (fun (a,(t,o)) -> output_cpp ("\nHX_STACK_ARG(" ^ (keyword_remap o) ^ ",\"" ^ a ^"\")\n") ) constructor_arg_var_list;
 
 						if (has_default_values function_def.tf_args) then begin
@@ -2920,7 +2938,7 @@ let generate_class_files common_ctx member_types super_deps constructor_deps cla
 	(match class_def.cl_init with
 	| Some expression ->
 		output_cpp ("void " ^ class_name^ "::__init__() {\n");
-      hx_stack_push ctx output_cpp smart_class_name "__init__" expression.epos;
+      hx_stack_push ctx output_cpp dot_name "__init__" expression.epos;
 		gen_expression (new_context common_ctx cpp_file debug file_info) false (to_block expression);
 		output_cpp "}\n\n";
 	| _ -> ());
@@ -2931,10 +2949,10 @@ let generate_class_files common_ctx member_types super_deps constructor_deps cla
    let implemented_instance_fields = List.filter should_implement_field class_def.cl_ordered_fields in
 
 	List.iter
-		(gen_field ctx class_def class_name smart_class_name false class_def.cl_interface)
+		(gen_field ctx class_def class_name smart_class_name dot_name false class_def.cl_interface)
 		class_def.cl_ordered_fields;
 	List.iter
-		(gen_field ctx class_def class_name smart_class_name true class_def.cl_interface) statics_except_meta;
+		(gen_field ctx class_def class_name smart_class_name dot_name true class_def.cl_interface) statics_except_meta;
 	output_cpp "\n";
 
 
@@ -3659,12 +3677,409 @@ let gen_extern_enum common_ctx enum_def file_info =
 	file#close
 ;;
 
+let remove_parens expression = 
+   match expression.eexpr with
+   | TParenthesis e -> e
+   | TMeta(_,e) -> e
+   | _ -> expression
+;;
+
+let is_this expression =
+   match (remove_parens expression).eexpr with
+   | TConst TThis -> true
+   | _ -> false
+;;
+
+let is_assign_op op =
+   match op with
+   | OpAssign 
+   | OpAssignOp _ -> true
+   | _ -> false
+;;
+
+
+class script_writer common_ctx filename =
+	object(this)
+	val indent_str = "\t"
+	val mutable indent = ""
+	val mutable indents = []
+	val mutable just_finished_block = false
+	val mutable classCount = 0
+	val mutable enumCount = 0
+   val buffer = Buffer.create 0
+   val identTable = Hashtbl.create 0
+   val fileTable = Hashtbl.create 0
+   val identBuffer = Buffer.create 0
+	method stringId name = 
+      try ( Hashtbl.find identTable name )
+	   with Not_found -> begin
+         let size = Hashtbl.length identTable in
+         Hashtbl.add identTable name size;
+         Buffer.add_string identBuffer ((string_of_int (String.length name)) ^ " " ^ name ^ "\n");
+         size;
+      end
+	method incClasses = classCount <- classCount +1
+	method incEnums = enumCount <- enumCount + 1
+	method stringText name = (string_of_int (this#stringId name)) ^ " "
+   val typeTable = Hashtbl.create 0
+   val typeBuffer = Buffer.create 0
+   method typeId name = 
+      try ( Hashtbl.find typeTable name )
+	   with Not_found -> begin
+         let size = Hashtbl.length typeTable in
+         Hashtbl.add typeTable name size;
+         Buffer.add_string typeBuffer ((string_of_int (String.length name)) ^ " " ^ name ^ "\n");
+         size;
+      end
+	method typeText typeT = (string_of_int (this#typeId (type_string_suff "" typeT))) ^ " "
+	method writeType typeT = this#write (this#typeText typeT)
+	method boolText value = if value then "1" else "0"
+	method writeBool value = this#write (if value then "1 " else "0 ")
+	method staticText value = if value then "s" else "m"
+   method write str = Buffer.add_string buffer str ; just_finished_block <- false
+	method wint ival = this#write ((string_of_int ival)^" ")
+	method ident name = this#wint (this#stringId name)
+   method instText clazz = match clazz.cl_path with
+       | ([],"Array") -> string_of_int (this#typeId "Array< ::Dynamic >") ^ " "
+       | _ -> this#typeText (TInst(clazz,[]))
+   method instName clazz = this#write (this#instText clazz)
+   method enumText e = this#typeText (TEnum(e,[]))
+   method enumName e = this#write (this#enumText e)
+	method close = 
+      let out_file = open_out filename in
+      output_string out_file "CPPIA\n";
+      let idents =  Buffer.contents identBuffer in
+      output_string out_file ((string_of_int (Hashtbl.length identTable)) ^ "\n");
+      output_string out_file idents;
+      let types =  Buffer.contents typeBuffer in
+      output_string out_file ((string_of_int (Hashtbl.length typeTable)) ^ "\n");
+      output_string out_file types;
+      output_string out_file ( (string_of_int classCount) ^ " " ^ (string_of_int enumCount) ^ "\n" );
+      let contents = Buffer.contents buffer in
+      output_string out_file contents;
+      close_out out_file
+   method fileId file =
+      try ( Hashtbl.find fileTable file )
+	   with Not_found -> begin
+         let stripped_file = strip_file common_ctx file in
+         let result = this#stringId stripped_file in
+         Hashtbl.add fileTable file result;
+         result;
+      end
+   method constText c = match c with
+	| TInt i -> Printf.sprintf "i%ld " i
+	| TFloat f -> "f" ^ f ^ " "
+	| TString s -> "s" ^ (this#stringText s)
+	| TBool b -> if b then "TRUE " else "FALSE "
+	| TNull -> "NULL "
+	| TThis -> "THIS "
+	| TSuper -> "SUPER "
+
+   method fileText file = string_of_int (this#fileId file)
+	method indent_one = this#write indent_str
+	method push_indent = indents <- indent_str::indents; indent <- String.concat "" indents
+	method pop_indent = match indents with
+							| h::tail -> indents <- tail; indent <- String.concat "" indents
+							| [] -> indent <- "/*?*/";
+	method write_i x = this#write (indent ^ x)
+	method get_indent = indent
+	method begin_expr = this#push_indent
+	method end_expr = if not just_finished_block then this#write "\n"; this#pop_indent; just_finished_block <- true
+   method func isStatic funcName ret args isInterface fieldExpression =
+       this#write ("FUNCION " ^ (this#staticText isStatic) ^ " " ^ (this#stringText funcName) ^ " ");
+       this#write ((this#typeText ret) ^ (string_of_int (List.length args)) ^ " ");
+       List.iter (fun (name,opt,typ) -> this#write ( (this#stringText name) ^ (this#boolText opt) ^ " " ^ (this#typeText typ) ^ " " )) args;
+       this#write "\n";
+       if (not isInterface) then begin
+          match fieldExpression with
+          | Some ({ eexpr = TFunction function_def } as e) -> this#gen_expression e
+          | _ -> print_endline ("Missing function body for " ^ funcName );
+       end
+   method var readAcc writeAcc isStatic name varType =
+       this#write ("VAR " ^ (this#staticText isStatic) ^ " " ^ readAcc ^ " " ^ writeAcc ^ " " ^ (this#stringText name)^ (this#typeText varType) ^ "\n" )
+   method writeVar v =
+       this#ident v.v_name;
+       this#wint v.v_id;
+       this#writeBool v.v_capture;
+       this#writeType v.v_type;
+   method writeList prefix len = this#write (prefix ^" "  ^ (string_of_int (len)) ^ "\n");
+   method gen_expression expr =
+     let expression = remove_parens expr in
+     this#begin_expr;
+     this#write ((string_of_int (Lexer.get_error_line expression.epos) ) ^ "\t" ^ (this#fileText expression.epos.pfile) ^ indent);
+     (match expression.eexpr with
+     | TFunction function_def -> this#write ("FUN " ^ (this#typeText function_def.tf_type) ^ (string_of_int (List.length function_def.tf_args)) ^ "\n" );
+         List.iter (fun(arg,init) ->
+            this#write (indent ^ indent_str );
+            this#writeVar arg;
+            match init with
+            | Some const -> this#write ("1 " ^ (this#constText const) ^ "\n")
+            | _ -> this#write "0\n";
+         ) function_def.tf_args;
+         this#gen_expression function_def.tf_expr;
+     | TBlock expr_list -> this#writeList "BLOCK" (List.length expr_list);
+         List.iter this#gen_expression expr_list;
+     | TConst const -> this#write (this#constText const)
+     | TBreak -> this#write "BREAK ";
+     | TContinue -> this#write "CONT ";
+
+     | TBinop (op,e1,e2) when is_assign_op op->
+        let op_name = (Ast.s_binop op) ^ " " in
+        let expression = remove_parens e1 in
+        (match expression.eexpr with
+        | TField (obj, acc) ->
+           (match acc with
+           | FDynamic name -> this#write ("FNAME" ^ op_name ^ (this#stringText name) ^ "\n");
+                this#gen_expression obj;
+           | FStatic (class_def,field) -> this#write ("FSTATIC" ^ op_name^ (this#instText class_def) ^ " " ^ (this#stringText field.cf_name) ^ "\n");
+           | FInstance (_,field) when is_this obj -> this#write ("FTHIS" ^ op_name ^ (this#typeText obj.etype) ^ " " ^ (this#stringText field.cf_name) ^ "\n");
+           | FInstance (_,field) -> this#write ("FINST" ^ op_name ^ (this#typeText obj.etype) ^ " " ^ (this#stringText field.cf_name) ^ "\n");
+                this#gen_expression obj;
+           | FClosure (_,field)
+           | FAnon (field) -> this#write ("FNAME" ^ op_name ^ (this#stringText field.cf_name) ^ "\n");
+                this#gen_expression obj;
+           | FEnum (enum,field) -> this#write ("FENUM" ^ op_name  ^ (this#enumText enum) ^ " " ^ (this#stringText field.ef_name) ^ "\n");
+           )
+        | TArray (e1, e2) -> this#write ("ARRAYI" ^ op_name ^ (this#typeText expression.etype) ^ "\n");
+           this#gen_expression e1;
+           this#gen_expression e2;
+        | TLocal var -> this#write ("VAR" ^ op_name ^ (string_of_int var.v_id) ^ "\n");
+        | _ -> assert false
+        );
+        this#gen_expression e2;
+     | TBinop (OpEq ,e1, { eexpr = TConst TNull } ) -> this#write "ISNULL\n";
+        this#gen_expression e1;
+     | TBinop (OpNotEq ,e1, { eexpr = TConst TNull }) -> this#write "NOTNULL\n";
+        this#gen_expression e1;
+     | TBinop (OpEq , { eexpr = TConst TNull }, e1) -> this#write "ISNULL\n";
+        this#gen_expression e1;
+     | TBinop (OpNotEq, { eexpr = TConst TNull }, e1) -> this#write "NOTNULL\n";
+        this#gen_expression e1;
+     | TBinop (op,e1,e2) -> this#write ((Ast.s_binop op) ^ "\n");
+        this#gen_expression e1;
+        this#gen_expression e2;
+     | TThrow e -> this#write "THROW\n";
+        this#gen_expression e;
+     | TArrayDecl expr_list -> this#writeList "ADEF" (List.length expr_list);
+        List.iter this#gen_expression expr_list;
+     | TIf (e,e1,e2) ->
+        (match e2 with
+        | None ->
+           this#write "IF\n";
+           this#gen_expression e;
+           this#gen_expression e1;
+        | Some elze ->
+           this#write "IFELSE\n";
+           this#gen_expression e;
+           this#gen_expression e1;
+           this#gen_expression elze; )
+     | TCall (func, arg_list) ->
+        (match (remove_parens func).eexpr with
+        | TField (obj,FStatic (class_def,field) ) ->
+               this#write ("CALLSTATIC " ^ (this#instText class_def) ^ " " ^ (this#stringText field.cf_name) ^
+                  (string_of_int (List.length arg_list)) ^ "\n");
+        | TField (obj,FInstance (_,field) ) when is_this obj ->
+               this#write ("CALLTHIS " ^ (this#typeText obj.etype) ^ " " ^ (this#stringText field.cf_name) ^
+                  (string_of_int (List.length arg_list)) ^ "\n");
+        | TField (obj,FInstance (_,field) ) ->
+               this#write ("CALLMEMBER " ^ (this#typeText obj.etype) ^ " " ^ (this#stringText field.cf_name) ^
+                  (string_of_int (List.length arg_list)) ^ "\n");
+               this#gen_expression obj;
+        | _ -> this#writeList "CALL " (List.length arg_list);
+               this#gen_expression func;
+        );
+        List.iter this#gen_expression arg_list;
+     | TField (obj, acc) ->
+        (match acc with
+        | FDynamic name -> this#write ("FNAME " ^ (this#stringText name) ^ "\n");
+             this#gen_expression obj;
+        | FStatic (class_def,field) -> this#write ("FSTATIC " ^ (this#instText class_def) ^ " " ^ (this#stringText field.cf_name) );
+        | FInstance (_,field) when is_this obj -> this#write ("FTHIS " ^ (this#typeText obj.etype) ^ " " ^ (this#stringText field.cf_name) );
+        | FInstance (_,field) -> this#write ("FINST " ^ (this#typeText obj.etype) ^ " " ^ (this#stringText field.cf_name) ^ "\n");
+             this#gen_expression obj;
+        | FClosure (_,field)
+        | FAnon (field) -> this#write ("FNAME " ^ (this#stringText field.cf_name) ^ "\n");
+             this#gen_expression obj;
+        | FEnum (enum,field) -> this#write ("FENUM " ^ (this#enumText enum) ^ " " ^ (this#stringText field.ef_name) );
+        )
+     | TArray (e1, e2) -> this#write ("ARRAYI " ^ (this#typeText expression.etype) ^ "\n");
+        this#gen_expression e1;
+        this#gen_expression e2;
+     | TUnop (op, flag, e) ->
+        this#write ((match op,flag with
+        | Increment, Prefix -> "++"
+        | Increment, _ -> "+++"
+        | Decrement, Prefix -> "--"
+        | Decrement, _ -> "---"
+        | Not, _ -> "!"
+        | Neg, _ -> "NEG"
+        | NegBits, _ -> "~" ) ^ "\n");
+        this#gen_expression e;
+     (* TODO - lval op-assign local/member/array *)
+     | TLocal var -> this#write ("VAR " ^ (string_of_int var.v_id) );
+
+     | TVars var_list ->
+         List.iter (fun (tvar, optional_init) ->
+            match optional_init with
+            | None -> this#write "VARDECL ";
+                      this#writeVar tvar;
+            | Some init ->this#write "VARDECLI ";
+                      this#writeVar tvar;
+                      this#write "\n";
+                      this#gen_expression init;
+         ) var_list
+     | TNew (clazz,params,arg_list) -> this#writeList ("NEW " ^ (this#typeText (TInst(clazz,params)))) (List.length arg_list);
+         List.iter this#gen_expression arg_list;
+     | TReturn optval -> (match optval with
+         | None -> this#write "RETURN\n"
+         | Some value -> this#write "RETVAL\n";
+                       this#gen_expression value;
+         )
+     | TObjectDecl (
+        ("fileName" , { eexpr = (TConst (TString file)) }) ::
+           ("lineNumber" , { eexpr = (TConst (TInt line)) }) ::
+              ("className" , { eexpr = (TConst (TString class_name)) }) ::
+                 ("methodName", { eexpr = (TConst (TString meth)) }) :: [] ) ->
+            this#write ("POSINFO " ^ (this#stringText file) ^ (Printf.sprintf "%ld" line) ^ " " ^
+                         (this#stringText class_name) ^ " " ^  (this#stringText meth))
+ 
+     | TObjectDecl values ->this#write ("OBJDEF " ^ (string_of_int (List.length values)));
+         List.iter (fun (name,_) -> this#write (this#stringText name)  ) values;
+         this#write "\n";
+         List.iter (fun (_,e) -> this#gen_expression e ) values;
+     | TTypeExpr _ -> ()
+     | TWhile (e1,e2,flag) -> this#write ("WHILE " ^ (if flag=NormalWhile then "1" else "0" ) ^ "\n");
+         this#gen_expression e1;
+         this#gen_expression e2;
+     | TFor (tvar,init,loop) -> this#write ("FOR ");
+         this#writeVar tvar;
+         this#write "\n";
+         this#gen_expression init;
+         this#gen_expression loop;
+     | TEnumParameter (expr,_,i) ->
+         let enum = match follow expr.etype with TEnum(enum,_) -> expr.etype | _ -> assert false in
+         this#write ("ENUMI " ^ (this#typeText enum) ^ (string_of_int i) ^ "\n");
+         this#gen_expression expr;
+     | TSwitch (condition,cases,optional_default)  ->
+         this#write ("SWITCH " ^ (string_of_int (List.length cases)) ^ " " ^
+                            (match optional_default with None -> "0" | Some _ -> "1") ^ "\n");
+          List.iter (fun (cases_list,expression) ->
+             this#writeList ("\t\t\t"^indent) (List.length cases_list);
+             List.iter (fun value -> this#gen_expression value ) cases_list;
+             this#gen_expression expression;
+         ) cases;
+         (match optional_default with None -> () | Some expr -> this#gen_expression expr);
+     | TTry (e,catches)  ->
+         this#writeList "TRY " (List.length catches);
+         this#gen_expression e;
+         List.iter ( fun (tvar,catch_expr) ->
+             this#write ("\t\t\t"^indent);
+             this#writeVar tvar;
+             this#write "\n";
+             this#gen_expression catch_expr;
+         ) catches;
+     | TCast (cast,None) ->
+         this#write "VCAST\n";
+         this#gen_expression cast;
+     | TCast (cast,Some t) ->
+         let class_name = (join_class_path_remap (t_path t) "::" ) in
+         this#write ("CAST " ^ (string_of_int (this#typeId class_name)) ^ "\n");
+         this#gen_expression cast;
+
+     | TParenthesis _ | TMeta(_,_) | TPatMatch _ -> assert false
+     );
+     this#end_expr;
+end;;
+
+let generate_script_class common_ctx script class_def =
+   script#incClasses;
+   script#write (if class_def.cl_interface then "INTFERFACE " else "CLASS ");
+   script#instName class_def;
+   (match class_def.cl_super with
+      | None -> script#ident ""
+      | Some (c,_) -> script#instName c);
+   script#wint (List.length class_def.cl_implements);
+   List.iter (fun(c,_) -> script#instName c) class_def.cl_implements;
+   script#write "\n";
+   script#write ((string_of_int ( (List.length class_def.cl_ordered_fields) +
+                                  (List.length class_def.cl_ordered_statics))) ^ "\n");
+   let generate_field isStatic field =
+      match field.cf_kind, field.cf_type with
+	   | Var { v_read = AccInline; v_write = AccNever },_ ->
+         script#write "INLINE\n";
+	   | Var v,t ->
+         let mode_code mode = match mode with
+         | AccNormal -> "N"
+         | AccNo -> "!"
+         | AccNever -> "!"
+         | AccResolve -> "R"
+         | AccCall -> "C"
+         | AccInline	-> "N"
+         | AccRequire (_,_) -> "?"
+         in
+         script#var (mode_code v.v_read) (mode_code v.v_write) isStatic field.cf_name t
+	   | Method MethDynamic, TFun(a,r) ->
+         script#var "N" "N" isStatic field.cf_name (TFun(a,r))
+	   | Method _, TFun(args,ret) when field.cf_name="new" ->
+         script#func true "new" (TInst(class_def,[])) args false field.cf_expr
+	   | Method _, TFun (args,ret) ->
+         script#func isStatic field.cf_name ret args class_def.cl_interface field.cf_expr
+	   | Method _, _ -> print_endline ("Unknown method type " ^ (join_class_path class_def.cl_path "." ) ^field.cf_name);
+   in
+   List.iter (generate_field false) class_def.cl_ordered_fields;
+   List.iter (generate_field true) class_def.cl_ordered_statics;
+   script#write "\n";
+;;
+
+let generate_script_enum common_ctx script enum_def meta =
+   script#incEnums;
+   script#write "ENUM";
+   script#enumName enum_def;
+   script#write "\n"
+;;
+
+
+let generate_cppia common_ctx =
+	let script = new script_writer common_ctx common_ctx.file in
+   let debug = true in
+   ignore (script#stringId "");
+   ignore (script#typeId "");
+
+  	List.iter (fun object_def ->
+		(match object_def with
+		| TClassDecl class_def when class_def.cl_extern ->
+         () (*if (gen_externs) then gen_extern_class common_ctx class_def;*)
+		| TClassDecl class_def ->
+			let is_internal = is_internal_class class_def.cl_path in
+			let is_generic_def = match class_def.cl_kind with KGeneric -> true | _ -> false in
+			if (is_internal || (is_macro class_def.cl_meta) || is_generic_def) then
+				( if debug then print_endline (" internal class " ^ (join_class_path class_def.cl_path ".") ))
+			else begin
+				generate_script_class common_ctx script class_def
+			end
+		| TEnumDecl enum_def when enum_def.e_extern -> ()
+		| TEnumDecl enum_def ->
+			let is_internal = is_internal_class enum_def.e_path in
+			if (is_internal) then
+				(if debug then print_endline (" internal enum " ^ (join_class_path enum_def.e_path ".") ))
+			else begin
+				let meta = Codegen.build_metadata common_ctx object_def in
+				if (enum_def.e_extern) then
+					(if debug then print_endline ("external enum " ^  (join_class_path enum_def.e_path ".") ));
+				generate_script_enum common_ctx script enum_def meta
+			end
+		| TTypeDecl _ | TAbstractDecl _ -> (* already done *) ()
+		);
+	) common_ctx.types;
+
+   script#close
+;;
 
 
 (*
  The common_ctx contains the haxe AST in the "types" field and the resources
 *)
-let generate common_ctx =
+let generate_source common_ctx =
 	make_base_directory common_ctx.file;
 
 	let debug = false in
@@ -3762,5 +4177,11 @@ let generate common_ctx =
 	end
 	;;
 
+let generate common_ctx =
+   if (Common.defined common_ctx Define.Cppia) then
+      generate_cppia common_ctx
+   else
+      generate_source common_ctx
+;;
 
 

+ 9 - 4
genphp.ml

@@ -1158,7 +1158,7 @@ and gen_expr ctx e =
 			let se1 = s_expr_name e1 in
 			let se2 = s_expr_name e2 in
 			if
-				e1.eexpr = TConst (TNull)
+				   e1.eexpr = TConst (TNull)
 				|| e2.eexpr = TConst (TNull)
 			then begin
 				(match e1.eexpr with
@@ -1179,8 +1179,8 @@ and gen_expr ctx e =
 				| _ ->
 					gen_field_op ctx e2);
 			end else if
-					((se1 = "Int" || se1 = "Null<Int>") && (se2 = "Int" || se2 = "Null<Int>"))
-					|| ((se1 = "Float" || se1 = "Null<Float>") && (se2 = "Float" || se2 = "Null<Float>"))
+				   ((se1 = "Int" || se1 = "Null<Int>") && (se2 = "Int" || se2 = "Null<Int>"))
+				|| ((se1 = "Float" || se1 = "Null<Float>") && (se2 = "Float" || se2 = "Null<Float>"))
 			then begin
 				gen_field_op ctx e1;
 				spr ctx s_phop;
@@ -1217,9 +1217,14 @@ and gen_expr ctx e =
 				spr ctx s_phop;
 				gen_field_op ctx e2;
 			end else begin
+				let tmp = define_local ctx "_t" in
+				print ctx "(is_object($%s = " tmp;
 				gen_field_op ctx e1;
-				spr ctx s_op;
+				print ctx ") && !($%s instanceof Enum) ? $%s%s" tmp tmp s_phop;
 				gen_field_op ctx e2;
+				print ctx " : $%s%s" tmp s_op;
+				gen_field_op ctx e2;
+				spr ctx ")";
 			end
 		| _ ->
 			leftside e1;

+ 5 - 0
genswf9.ml

@@ -1374,6 +1374,11 @@ and gen_call ctx retval e el r =
 		gen_expr ctx true e;
 		gen_expr ctx true t;
 		write ctx (HOp A3OIs)
+	| TField (_,FStatic ({ cl_path = [],"Std" },{ cf_name = "is" })),[e;{ eexpr = TTypeExpr (TClassDecl _) } as t] ->
+		(* fast inlining of Std.is with known values *)
+		gen_expr ctx true e;
+		gen_expr ctx true t;
+		write ctx (HOp A3OIs)
 	| TLocal { v_name = "__as__" }, [e;t] ->
 		gen_expr ctx true e;
 		gen_expr ctx true t;

+ 25 - 0
interp.ml

@@ -193,11 +193,13 @@ let decode_expr_ref = ref (fun e -> assert false)
 let encode_clref_ref = ref (fun c -> assert false)
 let enc_hash_ref = ref (fun h -> assert false)
 let enc_array_ref = ref (fun l -> assert false)
+let dec_array_ref = ref (fun v -> assert false)
 let enc_string_ref = ref (fun s -> assert false)
 let make_ast_ref = ref (fun _ -> assert false)
 let make_complex_type_ref = ref (fun _ -> assert false)
 let get_ctx() = (!get_ctx_ref)()
 let enc_array (l:value list) : value = (!enc_array_ref) l
+let dec_array (l:value) : value list = (!dec_array_ref) l
 let encode_complex_type (t:Ast.complex_type) : value = (!encode_complex_type_ref) t
 let encode_type (t:Type.t) : value = (!encode_type_ref) t
 let decode_type (v:value) : Type.t = (!decode_type_ref) v
@@ -2463,6 +2465,28 @@ let macro_lib =
 				VNull
 			| _ -> error()
 		);
+		"apply_params", Fun3 (fun tpl tl t ->
+			let tpl = List.map (fun v ->
+				match v with
+				| VObject o ->
+					let name = match get_field o (hash "name") with VString s -> s | _ -> assert false in
+					let t = decode_type (get_field o (hash "t")) in
+					name,t
+				| _ -> assert false
+			) (dec_array tpl) in
+			let tl = List.map decode_type (dec_array tl) in
+			let rec map t = match t with
+				| TInst({cl_kind = KTypeParameter _},_) ->
+					begin try
+						(* use non-physical equality check here to make apply_params work *)
+						snd (List.find (fun (_,t2) -> type_iseq t t2) tpl)
+					with Not_found ->
+						Type.map map t
+					end
+				| _ -> Type.map map t
+			in
+			encode_type (apply_params tpl tl (map (decode_type t)))
+		);
 	]
 
 (* ---------------------------------------------------------------------- *)
@@ -4541,6 +4565,7 @@ make_ast_ref := make_ast;
 make_complex_type_ref := make_type;
 encode_complex_type_ref := encode_ctype;
 enc_array_ref := enc_array;
+dec_array_ref := dec_array;
 encode_type_ref := encode_type;
 decode_type_ref := decode_type;
 encode_expr_ref := encode_expr;

+ 1 - 1
libs

@@ -1 +1 @@
-Subproject commit 97ddb4d99884042469e34d1be94b3605d51fbf43
+Subproject commit ff2e0f209eb9fcec663437e66b5f76b8e730130b

+ 2 - 1
main.ml

@@ -160,7 +160,8 @@ let make_path f =
 		| _ -> cl
 	) in
 	let error() =
-		let msg =
+		let msg = "Could not process argument " ^ f in
+		let msg = msg ^ "\n" ^
 			if String.length f == 0 then
 				"Class name must not be empty"
 			else match (List.hd (List.rev cl)).[0] with

+ 61 - 7
matcher.ml

@@ -106,6 +106,7 @@ type matcher = {
 	mutable outcomes : (pat list,out) PMap.t;
 	mutable toplevel_or : bool;
 	mutable used_paths : (int,bool) Hashtbl.t;
+	mutable has_extractor : bool;
 }
 
 exception Not_exhaustive of pat * st
@@ -452,17 +453,21 @@ let to_pattern ctx e t =
 			end
 		| (EObjectDecl fl) ->
 			let is_matchable cf = match cf.cf_kind with Method _ | Var {v_read = AccCall} -> false | _ -> true in
-			let is_valid_field_name fields n p =
+			let is_valid_field_name fields co n p =
 				try
 					let cf = PMap.find n fields in
 					if not (is_matchable cf) then error ("Cannot match against method or property with getter " ^ n) p;
+					begin match co with
+					| Some c when not (Typer.can_access ctx c cf false) -> error ("Cannot match against private field " ^ n) p
+					| _ -> ()
+					end
 				with Not_found ->
-					error (unify_error_msg (print_context()) (has_extra_field t n)) p
+					error ((s_type t) ^ " has no field " ^ n ^ " that can be matched against") p;
 			in
 			pctx.pc_is_complex <- true;
 			begin match follow t with
 			| TAnon {a_fields = fields} ->
-				List.iter (fun (n,(_,p)) -> is_valid_field_name fields n p) fl;
+				List.iter (fun (n,(_,p)) -> is_valid_field_name fields None n p) fl;
 				let sl,pl,i = PMap.foldi (fun n cf (sl,pl,i) ->
 					if not (is_matchable cf) then
 						sl,pl,i
@@ -478,7 +483,7 @@ let to_pattern ctx e t =
 				) fields ([],[],0) in
 				mk_con_pat (CFields(i,sl)) pl t p
 			| TInst(c,tl) ->
-				List.iter (fun (n,(_,p)) -> is_valid_field_name c.cl_fields n p) fl;
+				List.iter (fun (n,(_,p)) -> is_valid_field_name c.cl_fields (Some c) n p) fl;
 				let sl,pl,i = PMap.foldi (fun n cf (sl,pl,i) ->
 					if not (is_matchable cf) then
 						sl,pl,i
@@ -946,7 +951,7 @@ let convert_switch ctx st cases loop =
 	| TAbstract(a,_) when Meta.has Meta.FakeEnum a.a_meta ->
 		mk (TMeta((Meta.Exhaustive,[],p), e_st)) e_st.etype e_st.epos
 	| TAbstract({a_path = [],"Bool"},_) ->
-		mk (TMeta((Meta.Exhaustive,[],p), e_st)) e_st.etype e_st.epos		
+		mk (TMeta((Meta.Exhaustive,[],p), e_st)) e_st.etype e_st.epos
 	| _ ->
 		e_st
 	in
@@ -975,6 +980,51 @@ let convert_switch ctx st cases loop =
 
 (* Decision tree compilation *)
 
+let transform_extractors mctx stl cases =
+	let rec loop cl = match cl with
+		| (epat,eg,e) :: cl ->
+			let ex = ref [] in
+			let exc = ref 0 in
+			let rec find_ex e = match fst e with
+				| EBinop(OpArrow, e1, e2) ->
+					let p = pos e in
+					let ec = EConst (Ident ("__ex" ^ string_of_int (!exc))),snd e in
+					let ecall = match fst e1 with
+						| EConst(Ident s) -> ECall((EField(ec,s),p),[]),p
+						| _ -> ECall(e1,[ec]),p
+					in
+					ex := (ecall,e2) :: !ex;
+					incr exc;
+					ec
+				| _ ->
+					Ast.map_expr find_ex e
+			in
+			let p = pos epat in
+			let epat = find_ex epat in
+			if !exc = 0 then (epat,eg,e) :: loop cl else begin
+				mctx.has_extractor <- true;
+				let esubjects = EArrayDecl (List.map fst !ex),p in
+				let case1 = [EArrayDecl (List.map snd !ex),p],eg,e in
+				let cases = match cl with
+					| [] -> [case1]
+					| [(EConst (Ident "_"),_),_,e] -> case1 :: [[(EConst (Ident "_"),p)],None,e]
+					| _ ->
+						let cl2 = List.map (fun (epat,eg,e) -> [epat],eg,e) (loop cl) in
+						let st = match stl with st :: stl -> st | _ -> error "Unsupported" p in
+						let subj = convert_st mctx.ctx st in
+						let e_subj = Interp.make_ast subj in
+						case1 :: [[(EConst (Ident "_"),p)],None,Some (ESwitch(e_subj,cl2,None),p)]
+				in
+				let eswitch = (ESwitch(esubjects,cases,None)),p in
+				(epat,None,Some eswitch) :: loop cl
+			end
+		| [] ->
+			[]
+	in
+	loop cases
+
+let extractor_depth = ref 0
+
 let match_expr ctx e cases def with_type p =
 	let need_val,with_type,tmono = match with_type with
 		| NoValue -> false,NoValue,None
@@ -1042,6 +1092,7 @@ let match_expr ctx e cases def with_type p =
 		dt_cache = Hashtbl.create 0;
 		dt_lut = DynArray.create ();
 		dt_count = 0;
+		has_extractor = false;
 	} in
 	(* flatten cases *)
 	let cases = List.map (fun (el,eg,e) ->
@@ -1049,6 +1100,8 @@ let match_expr ctx e cases def with_type p =
 		collapse_case el,eg,e
 	) cases in
 	let is_complex = ref false in
+	let cases = transform_extractors mctx stl cases in
+	if mctx.has_extractor then incr extractor_depth;
 	let add_pattern_locals (pat,locals,complex) =
 		PMap.iter (fun n (v,p) -> ctx.locals <- PMap.add n v ctx.locals) locals;
 		if complex then is_complex := true;
@@ -1116,7 +1169,7 @@ let match_expr ctx e cases def with_type p =
 	let check_unused () =
 		let unused p =
 			display_error ctx "This pattern is unused" p;
-			let old_error = ctx.on_error in
+ 			let old_error = ctx.on_error in
 			ctx.on_error <- (fun ctx s p -> ctx.on_error <- old_error; raise Exit);
 	 		let check_expr e p =
 				try begin match fst e with
@@ -1175,7 +1228,8 @@ let match_expr ctx e cases def with_type p =
 		error ("Unmatched patterns: " ^ (s_st_r true false st (s_pat pat))) st.st_pos
 	in
 	(* check for unused patterns *)
-	check_unused();
+	if !extractor_depth = 0 then check_unused();
+	if mctx.has_extractor then decr extractor_depth;
 	(* determine type of switch statement *)
 	let t = if not need_val then
 		mk_mono()

+ 12 - 2
optimizer.ml

@@ -33,9 +33,9 @@ let has_side_effect e =
 	let rec loop e =
 		match e.eexpr with
 		| TConst _ | TLocal _ | TField _ | TTypeExpr _ | TFunction _ -> ()
-		| TPatMatch _ | TNew _ | TCall _ | TEnumParameter _ | TBinop ((OpAssignOp _ | OpAssign),_,_) | TUnop ((Increment|Decrement),_,_) -> raise Exit
+		| TPatMatch _ | TNew _ | TCall _ | TBinop ((OpAssignOp _ | OpAssign),_,_) | TUnop ((Increment|Decrement),_,_) -> raise Exit
 		| TReturn _ | TBreak | TContinue | TThrow _ | TCast (_,Some _) -> raise Exit
-		| TArray _ | TCast (_,None) | TBinop _ | TUnop _ | TParenthesis _ | TMeta _ | TWhile _ | TFor _ | TIf _ | TTry _ | TSwitch _ | TArrayDecl _ | TVars _ | TBlock _ | TObjectDecl _ -> Type.iter loop e
+		| TArray _ | TEnumParameter _ | TCast (_,None) | TBinop _ | TUnop _ | TParenthesis _ | TMeta _ | TWhile _ | TFor _ | TIf _ | TTry _ | TSwitch _ | TArrayDecl _ | TVars _ | TBlock _ | TObjectDecl _ -> Type.iter loop e
 	in
 	try
 		loop e; false
@@ -832,6 +832,16 @@ let rec reduce_loop ctx e =
 			| OpEq -> { e with eexpr = TConst (TBool true) }
 			| OpNotEq -> { e with eexpr = TConst (TBool false) }
 			| _ -> e)
+		| TFunction _, TConst TNull ->
+			(match op with
+			| OpEq -> { e with eexpr = TConst (TBool false) }
+			| OpNotEq -> { e with eexpr = TConst (TBool true) }
+			| _ -> e)
+		| TConst TNull, TFunction _ ->
+			(match op with
+			| OpEq -> { e with eexpr = TConst (TBool false) }
+			| OpNotEq -> { e with eexpr = TConst (TBool true) }
+			| _ -> e)
 		| TConst (TInt a), TConst (TInt b) ->
 			let opt f = try { e with eexpr = TConst (TInt (f a b)) } with Exit -> e in
 			let check_overflow f =

+ 5 - 5
parser.ml

@@ -601,7 +601,7 @@ and parse_type_decl s =
 and parse_class doc meta cflags need_name s =
 	let opt_name = if need_name then type_name else (fun s -> match popt type_name s with None -> "" | Some n -> n) in
 	match s with parser
-	| [< n , p1 = parse_class_flags; name = opt_name; tl = parse_constraint_params; hl = psep Comma parse_class_herit; '(BrOpen,_); fl, p2 = parse_class_fields false p1 >] ->
+	| [< n , p1 = parse_class_flags; name = opt_name; tl = parse_constraint_params; hl = psep Comma parse_class_herit; '(BrOpen,_); fl, p2 = parse_class_fields (not need_name) p1 >] ->
 		(EClass {
 			d_name = name;
 			d_doc = doc;
@@ -908,7 +908,7 @@ and parse_class_field s =
 	match s with parser
 	| [< meta = parse_meta; al = parse_cf_rights true []; s >] ->
 		let name, pos, k = (match s with parser
-		| [< '(Kwd Var,p1); name, _ = ident; s >] ->
+		| [< '(Kwd Var,p1); name, _ = dollar_ident; s >] ->
 			(match s with parser
 			| [< '(POpen,_); i1 = property_ident; '(Comma,_); i2 = property_ident; '(PClose,_) >] ->
 				let t = (match s with parser
@@ -966,7 +966,7 @@ and parse_cf_rights allow_static l = parser
 	| [< >] -> l
 
 and parse_fun_name = parser
-	| [< '(Const (Ident name),_) >] -> name
+	| [< name,_ = dollar_ident >] -> name
 	| [< '(Kwd New,_) >] -> "new"
 
 and parse_fun_param = parser
@@ -1009,7 +1009,7 @@ and parse_class_herit = parser
 	| [< '(Kwd Implements,_); t = parse_type_path >] -> HImplements t
 
 and block1 = parser
-	| [< '(Const (Ident name),p); s >] -> block2 name (Ident name) p s
+	| [< name,p = dollar_ident; s >] -> block2 name (Ident name) p s
 	| [< '(Const (String name),p); s >] -> block2 (quote_ident name) (String name) p s
 	| [< b = block [] >] -> EBlock b
 
@@ -1272,7 +1272,7 @@ and parse_switch_cases eswitch cases = parser
 		List.rev cases , None
 
 and parse_catch etry = parser
-	| [< '(Kwd Catch,p); '(POpen,_); name, _ = ident; s >] ->
+	| [< '(Kwd Catch,p); '(POpen,_); name, _ = dollar_ident; s >] ->
 		match s with parser
 		| [< '(DblDot,_); t = parse_complex_type; '(PClose,_); s >] ->
 			(try

+ 44 - 27
std/Lambda.hx

@@ -24,11 +24,11 @@
 	The `Lambda` class is a collection of methods to support functional
 	programming. It is ideally used with 'using Lambda' and then acts as an
 	extension to Iterable types.
-	
+
 	On static platforms, working with the Iterable structure might be slower
 	than performing the operations directly on known types, such as Array and
 	List.
-	
+
 	If the first argument to any of the methods is null, the result is
 	unspecified.
 **/
@@ -36,7 +36,7 @@ class Lambda {
 
 	/**
 		Creates an Array from Iterable `it`.
-		
+
 		If `it` is an Array, this function returns a copy of it.
 	**/
 	public static function array<A>( it : Iterable<A> ) : Array<A> {
@@ -48,7 +48,7 @@ class Lambda {
 
 	/**
 		Creates a List form Iterable `it`.
-		
+
 		If `it` is a List, this function returns a copy of it.
 	**/
 	public static function list<A>( it : Iterable<A> ) : List<A> {
@@ -60,9 +60,9 @@ class Lambda {
 
 	/**
 		Creates a new List by applying function `f` to all elements of `it`.
-		
+
 		The order of elements is preserved.
-		
+
 		If `f` is null, the result is unspecified.
 	**/
 	public static function map<A,B>( it : Iterable<A>, f : A -> B ) : List<B> {
@@ -74,9 +74,9 @@ class Lambda {
 
 	/**
 		Similar to map, but also passes the index of each element to `f`.
-		
+
 		The order of elements is preserved.
-		
+
 		If `f` is null, the result is unspecified.
 	**/
 	public static function mapi<A,B>( it : Iterable<A>, f : Int -> A -> B ) : List<B> {
@@ -89,10 +89,10 @@ class Lambda {
 
 	/**
 		Tells if `it` contains `elt`.
-		
+
 		This function returns true as soon as an element is found which is equal
 		to `elt` according to the `==` operator.
-		
+
 		If no such element is found, the result is false.
 	**/
 	public static function has<A>( it : Iterable<A>, elt : A ) : Bool {
@@ -104,12 +104,12 @@ class Lambda {
 
 	/**
 		Tells if `it` contains an element for which `f` is true.
-		
+
 		This function returns true as soon as an element is found for which a
 		call to `f` returns true.
-		
+
 		If no such element is found, the result is false.
-		
+
 		If `f` is null, the result is unspecified.
 	**/
 	public static function exists<A>( it : Iterable<A>, f : A -> Bool ) {
@@ -121,14 +121,14 @@ class Lambda {
 
 	/**
 		Tells if `f` is true for all elements of `it`.
-		
+
 		This function returns false as soon as an element is found for which a
 		call to `f` returns false.
-		
+
 		If no such element is found, the result is true.
-		
+
 		In particular, this function always returns true if `it` is empty.
-		
+
 		If `f` is null, the result is unspecified.
 	**/
 	public static function foreach<A>( it : Iterable<A>, f : A -> Bool ) {
@@ -140,7 +140,7 @@ class Lambda {
 
 	/**
 		Calls `f` on all elements of `it`, in order.
-		
+
 		If `f` is null, the result is unspecified.
 	**/
 	public static function iter<A>( it : Iterable<A>, f : A -> Void ) {
@@ -151,9 +151,9 @@ class Lambda {
 	/**
 		Returns a List containing those elements of `it` for which `f` returned
 		true.
-		
+
 		If `it` is empty, the result is the empty List even if `f` is null.
-		
+
 		Otherwise if `f` is null, the result is unspecified.
 	**/
 	public static function filter<A>( it : Iterable<A>, f : A -> Bool ) {
@@ -167,13 +167,13 @@ class Lambda {
 	/**
 		Functional fold on Iterable `it`, using function `f` with start argument
 		`first`.
-		
+
 		If `it` has no elements, the result is `first`.
-		
+
 		Otherwise the first element of `it` is passed to `f` alongside `first`.
 		The result of that call is then passed to `f` with the next element of
 		`it`, and so on until `it` has no more elements.
-		
+
 		If `it` or `f` are null, the result is unspecified.
 	**/
 	public static function fold<A,B>( it : Iterable<A>, f : A -> B -> B, first : B ) : B {
@@ -185,7 +185,7 @@ class Lambda {
 	/**
 		Returns the number of elements in `it` for which `pred` is true, or the
 		total number of elements in `it` if `pred` is null.
-		
+
 		This function traverses all elements.
 	**/
 	public static function count<A>( it : Iterable<A>, ?pred : A -> Bool ) {
@@ -209,9 +209,9 @@ class Lambda {
 
 	/**
 		Returns the index of the first element `v` within Iterable `it`.
-		
+
 		This function uses operator `==` to check for equality.
-		
+
 		If `v` does not exist in `it`, the result is -1.
 	**/
 	public static function indexOf<T>( it : Iterable<T>, v : T ) : Int {
@@ -224,10 +224,27 @@ class Lambda {
 		return -1;
 	}
 
+	/**
+		Returns the first element of `it` for which `f` is true.
+
+		This function returns true as soon as an element is found for which a
+		call to `f` returns true.
+
+		If no such element is found, the result is null.
+
+		If `f` is null, the result is unspecified.
+	**/
+	public static function find<T>( it : Iterable<T>, f : T -> Bool ) : Null<T> {
+		for( v in it ) {
+			if(f(v)) return v;
+		}
+		return null;
+	}
+
 	/**
 		Returns a new List containing all elements of Iterable `a` followed by
 		all elements of Iterable `b`.
-		
+
 		If `a` or `b` are null, the result is unspecified.
 	**/
 	public static function concat<T>( a : Iterable<T>, b : Iterable<T> ) : List<T> {

+ 73 - 36
std/haxe/Int64.hx

@@ -21,7 +21,7 @@
  */
 package haxe;
 
-class Int64 {
+class Int64 { 
 
 	var high : Int;
 	var low : Int;
@@ -31,11 +31,38 @@ class Int64 {
 		this.low = i32(low);
 	}
 
+	#if php
+	/*
+		private function to correctly handle 32-bit integer overflow on php 
+		see: http://stackoverflow.com/questions/300840/force-php-integer-overflow
+	*/
+	private static function i32php(value:Int):Int { 
+			value = (value & untyped __php__("0xFFFFFFFF"));
+ 		    if ( (value & untyped __php__("0x80000000"))!=0 )
+		        value = -(((~value) & untyped __php__("0xFFFFFFFF")) + 1);
+		    return value;
+	}
+	#end
+
+	/*
+		private function to correctly handle 32-bit ushr on php
+		see: https://github.com/HaxeFoundation/haxe/commit/1a878aa90708040a41b0dd59f518d83b09ede209
+	*/
+	private static inline function ushr32(v:Int,n:Int):Int { 
+		#if php
+		 	return (v >> n) & (untyped __php__("0x7fffffff") >> (n-1));
+		#else
+			return v>>>n;
+		#end
+	}
+
 	@:extern static inline function i32(i) {
-		#if (php || js || flash8)
-		return i | 0;
+		#if (js || flash8)
+			return i | 0;
+		#elseif php
+			return i32php(i); // handle overflow of 32-bit integers correctly 
 		#else
-		return i;
+			return i;
 		#end
 	}
 
@@ -63,15 +90,15 @@ class Int64 {
 		var ten = ofInt(10);
 		while( !isZero(i) ) {
 			var r = divMod(i, ten);
-			str = r.modulus.low + str;
-			i = r.quotient;
+			str = r.modulus.low + str; 
+			i = r.quotient; 
 		}
 		if( neg ) str = "-" + str;
 		return str;
 	}
 
 	public static inline function make( high : Int, low : Int ) : Int64 {
-		return new Int64(high, low);
+		return new Int64(high, low); 
 	}
 
 	public static inline function ofInt( x : Int ) : Int64 {
@@ -84,7 +111,7 @@ class Int64 {
 				return -toInt(neg(x));
 			throw "Overflow";
 		}
-		return x.low;
+		return x.low; 
 	}
 
 	public static function getLow( x : Int64 ) : Int {
@@ -104,8 +131,8 @@ class Int64 {
 	}
 
 	public static function sub( a : Int64, b : Int64 ) : Int64 {
-		var high = a.high - b.high;
-		var low = a.low - b.low;
+		var high = i32(a.high - b.high); // i32() call required to match add
+		var low = i32(a.low - b.low); // i32() call required to match add
 		if( uicompare(a.low,b.low) < 0 )
 			high--;
 		return new Int64(high, low);
@@ -113,14 +140,14 @@ class Int64 {
 
 	public static function mul( a : Int64, b : Int64 ) : Int64 {
 		var mask = 0xFFFF;
-		var al = a.low & mask, ah = a.low >>> 16;
-		var bl = b.low & mask, bh = b.low >>> 16;
+		var al = a.low & mask, ah = ushr32(a.low , 16); 
+		var bl = b.low & mask, bh = ushr32(b.low , 16); 
 		var p00 = al * bl;
 		var p10 = ah * bl;
 		var p01 = al * bh;
 		var p11 = ah * bh;
 		var low = p00;
-		var high = i32(p11 + (p01 >>> 16) + (p10 >>> 16));
+		var high = i32(p11 + ushr32(p01 , 16) + ushr32(p10 , 16));
 		p01 = i32(p01 << 16); low = i32(low + p01); if( uicompare(low, p01) < 0 ) high = i32(high + 1);
 		p10 = i32(p10 << 16); low = i32(low + p10); if( uicompare(low, p10) < 0 ) high = i32(high + 1);
 		high = i32(high + i32mul(a.low,b.high));
@@ -132,39 +159,49 @@ class Int64 {
 		var quotient = new Int64(0, 0);
 		var mask = new Int64(0, 1);
 		divisor = new Int64(divisor.high, divisor.low);
-		while( divisor.high >= 0 ) {
+		while( divisor.high >= 0 ) { 
 			var cmp = ucompare(divisor, modulus);
-			divisor.high = (divisor.high << 1) | (divisor.low >>> 31);
-			divisor.low <<= 1;
-			mask.high = (mask.high << 1) | (mask.low >>> 31);
-			mask.low <<= 1;
+			divisor.high = i32( i32(divisor.high << 1) | ushr32(divisor.low , 31) ); 
+			divisor.low = i32(divisor.low << 1); 
+			mask.high = i32( i32(mask.high << 1) | ushr32(mask.low , 31) ); 
+			mask.low = i32(mask.low << 1);
 			if( cmp >= 0 ) break;
 		}
-		while( (mask.low | mask.high) != 0 ) {
+		while( i32(mask.low | mask.high) != 0 ) { 
 			if( ucompare(modulus, divisor) >= 0 ) {
-				quotient.high |= mask.high;
-				quotient.low |= mask.low;
+				quotient.high= i32(quotient.high | mask.high); 
+				quotient.low= i32(quotient.low | mask.low); 
 				modulus = sub(modulus,divisor);
 			}
-			mask.low = (mask.low >>> 1) | (mask.high << 31);
-			mask.high >>>= 1;
+			mask.low = i32( ushr32(mask.low , 1) | i32(mask.high << 31) ); 
+			mask.high = ushr32(mask.high , 1); 
 
-			divisor.low = (divisor.low >>> 1) | (divisor.high << 31);
-			divisor.high >>>= 1;
+			divisor.low = i32( ushr32(divisor.low , 1) | i32(divisor.high << 31) ); 
+			divisor.high = ushr32(divisor.high , 1); 
 		}
 		return { quotient : quotient, modulus : modulus };
 	}
 
-	public static inline function div( a : Int64, b : Int64 ) : Int64 {
-		var sign = (a.high | b.high) < 0;
+	public static function div( a : Int64, b : Int64 ) : Int64 { 
+		if(b.high==0) // handle special cases of 0 and 1
+			switch(b.low) {
+			case 0:	throw "divide by zero";
+			case 1: return new Int64(a.high,a.low);
+			} 
+		var sign = ((a.high<0) || (b.high<0)) && (!( (a.high<0) && (b.high<0))); // make sure we get the correct sign
 		if( a.high < 0 ) a = neg(a);
 		if( b.high < 0 ) b = neg(b);
 		var q = divMod(a, b).quotient;
 		return sign ? neg(q) : q;
 	}
 
-	public static inline function mod( a : Int64, b : Int64 ) : Int64 {
-		var sign = (a.high | b.high) < 0;
+	public static function mod( a : Int64, b : Int64 ) : Int64 {
+		if(b.high==0) // handle special cases of 0 and 1
+			switch(b.low) {
+			case 0:	throw "modulus by zero";
+			case 1: return ofInt(0);
+			}
+		var sign = a.high<0; // the sign of a modulus is the sign of the value being mod'ed
 		if( a.high < 0 ) a = neg(a);
 		if( b.high < 0 ) b = neg(b);
 		var m = divMod(a, b).modulus;
@@ -172,15 +209,15 @@ class Int64 {
 	}
 
 	public static inline function shl( a : Int64, b : Int ) : Int64 {
-		return if( b & 63 == 0 ) a else if( b & 63 < 32 ) new Int64( (a.high << b) | (a.low >>> (32-(b&63))), a.low << b ) else new Int64( a.low << (b - 32), 0 );
+		return if( b & 63 == 0 ) a else if( b & 63 < 32 ) new Int64( (a.high << b) | ushr32(a.low, i32(32-(b&63))), a.low << b ) else new Int64( a.low << i32(b - 32), 0 );
 	}
 
 	public static inline function shr( a : Int64, b : Int ) : Int64 {
-		return if( b & 63 == 0 ) a else if( b & 63 < 32 ) new Int64( a.high >> b, (a.low >>> b) | (a.high << (32 - (b&63))) ) else new Int64( a.high >> 31, a.high >> (b - 32) );
+		return if( b & 63 == 0 ) a else if( b & 63 < 32 ) new Int64( a.high >> b, ushr32(a.low,b) | (a.high << i32(32 - (b&63))) ) else new Int64( a.high >> 31, a.high >> i32(b - 32) );
 	}
 
 	public static inline function ushr( a : Int64, b : Int ) : Int64 {
-		return if( b & 63 == 0 ) a else if( b & 63 < 32 ) new Int64( a.high >>> b, (a.low >>> b) | (a.high << (32 - (b&63))) ) else new Int64( 0, a.high >>> b - 32 );
+		return if( b & 63 == 0 ) a else if( b & 63 < 32 ) new Int64( ushr32(a.high, b), ushr32(a.low, b) | (a.high << i32(32 - (b&63))) ) else new Int64( 0, ushr32(a.high, i32(b - 32)) );
 	}
 
 	public static inline function and( a : Int64, b : Int64 ) : Int64 {
@@ -196,8 +233,8 @@ class Int64 {
 	}
 
 	public static inline function neg( a : Int64 ) : Int64 {
-		var high = ~a.high;
-		var low = -a.low;
+		var high = i32(~a.high); 
+		var low = i32(-a.low); 
 		if( low == 0 )
 			high++;
 		return new Int64(high,low);
@@ -212,11 +249,11 @@ class Int64 {
 	}
 
 	static function uicompare( a : Int, b : Int ) {
-		return a < 0 ? (b < 0 ? ~b - ~a : 1) : (b < 0 ? -1 : a - b);
+		return a < 0 ? (b < 0 ? i32(~b - ~a) : 1) : (b < 0 ? -1 : i32(a - b));
 	}
 
 	public static inline function compare( a : Int64, b : Int64 ) : Int {
-		var v = a.high - b.high;
+		var v = i32(a.high - b.high); 
 		return if( v != 0 ) v else uicompare(a.low,b.low);
 	}
 

+ 1 - 1
std/haxe/Resource.hx

@@ -33,7 +33,7 @@ package haxe;
 class Resource {
 
 	#if (java || cs)
-	static var content : Array<String>;
+	@:keep static var content : Array<String>;
 	#else
 	static var content : Array<{ name : String, data : String, str : String }>;
 	#end

+ 69 - 0
std/haxe/macro/Build.hx

@@ -49,4 +49,73 @@ class Build {
 		}
 		return fields;
 	}
+
+	macro static public function exposeUnderlyingFields(fieldExprs:Array<Expr>):Array<Field> {
+		var fields = Context.getBuildFields();
+		var a = switch(Context.getLocalClass().get().kind) {
+			case KAbstractImpl(a): a;
+			case _: throw "";
+		}
+		var tThis = a.get().type;
+		var map:Type->Type = function(t) return t;
+		var c = switch(tThis.follow()) {
+			case TInst(c, tl):
+				var c = c.get();
+				if (tl.length > 0) map = function(t) {
+					var t2 = t.applyTypeParameters(c.params, tl);
+					return t2;
+				}
+				c;
+			case _: Context.error("Underlying type of exposing abstract must be a class", Context.currentPos());
+		}
+		function getIdentName(e) return switch(e.expr) {
+			case EConst(CIdent(s)): s;
+			case _: Context.error("Identifier expected", e.pos);
+		}
+		function toField(cf:ClassField) {
+			var name = cf.name;
+			return {
+				name: name,
+				doc: cf.doc,
+				access: [AStatic, APublic, AInline],
+				pos: cf.pos,
+				meta: [{name: ":impl", params: [], pos: cf.pos}],
+				kind: switch(cf.type.follow()) {
+					case TFun(args, ret):
+						var args = args.map(function(arg) return {
+							name: arg.name,
+							opt: arg.opt,
+							type: arg.t.toComplexType(),
+							value: null
+						});
+						var expr = macro return this.$name($a{args.map(function(arg) return macro $i{arg.name})});
+						args.unshift({name: "this", type: null, opt:false, value: null});
+						FFun({
+							args: args,
+							ret: ret.toComplexType(),
+							expr: expr,
+							params: cf.params.map(function(param) return {
+								name: param.name,
+								constraints: [],
+								params: []
+							})
+						});
+					case _: throw "";
+				}
+			}
+		}
+		for (fieldExpr in fieldExprs) {
+			var fieldName = getIdentName(fieldExpr);
+			var cField = c.findField(fieldName, false);
+			if (cField == null) Context.error('Underlying type has no field $fieldName', fieldExpr.pos);
+			switch(cField.kind) {
+				case FMethod(_):
+				case _: Context.error("Only function fields can be exposed", fieldExpr.pos);
+			}
+			cField.type = map(cField.type);
+			var field = toField(cField);
+			fields.push(field);
+		}
+		return fields;
+	}
 }

+ 93 - 0
std/haxe/macro/Expr.hx

@@ -41,37 +41,130 @@ enum Constant {
 }
 
 enum Binop {
+	/**
+		`+`
+	**/
 	OpAdd;
+	/**
+		`*`
+	**/
 	OpMult;
+	/**
+		`/`
+	**/
 	OpDiv;
+	/**
+		`-`
+	**/
 	OpSub;
+	/**
+		`=`
+	**/
 	OpAssign;
+	/**
+		`==`
+	**/
 	OpEq;
+	/**
+		`!=`
+	**/
 	OpNotEq;
+	/**
+		`>`
+	**/
 	OpGt;
+	/**
+		`>=`
+	**/
 	OpGte;
+	/**
+		`<`
+	**/
 	OpLt;
+	/**
+		`<=`
+	**/
 	OpLte;
+	/**
+		`&`
+	**/
 	OpAnd;
+	/**
+		`|`
+	**/
 	OpOr;
+	/**
+		`^`
+	**/
 	OpXor;
+	/**
+		`&&`
+	**/
 	OpBoolAnd;
+	/**
+		`||`
+	**/
 	OpBoolOr;
+	/**
+		`<<`
+	**/
 	OpShl;
+	/**
+		`>>`
+	**/
 	OpShr;
+	/**
+		`>>>`
+	**/
 	OpUShr;
+	/**
+		`%`
+	**/
 	OpMod;
+	/**
+		`+=`
+		`-=`
+		`/=`
+		`*=`
+		`<<=`
+		`>>=`
+		`>>>=`
+		`|=`
+		`&=`
+		`^=`
+	**/
 	OpAssignOp( op : Binop );
+	/**
+		`...`
+	**/
 	OpInterval;
+	/**
+		`=>`
+	**/
 	OpArrow;
 }
 
 
 enum Unop {
+	/**
+		`++`
+	**/
 	OpIncrement;
+	/**
+		`--`
+	**/
 	OpDecrement;
+	/**
+		`!`
+	**/
 	OpNot;
+	/**
+		`-`
+	**/
 	OpNeg;
+	/**
+		`~`
+	**/
 	OpNegBits;
 }
 

+ 15 - 0
std/haxe/macro/MacroStringTools.hx

@@ -67,5 +67,20 @@ class MacroStringTools {
 		return Lambda.fold(sl, function(s, e) return e == null ? (macro $i{s}) : (macro $e.$s), null);
 	}
 	
+	/**
+		Converts a path given by package `pack` and name `name` to a `String`
+		separated by dots.
+		
+		If `pack` has no elements, the result is `name`.
+		
+		If `pack` is null, the result is unspecified.
+		
+		Otherwise the elements of `pack` are joined with a separating dot, with
+		an appended dot separating the result from `name`.
+	**/
+	static public function toDotPath(pack:Array<String>, name:String):String {
+		return if (pack.length == 0) name else pack.join(".") + "." +name;
+	}
+	
 	#end
 }

+ 8 - 3
std/haxe/macro/Type.hx

@@ -43,6 +43,11 @@ typedef AnonType = {
 	//var status : AnonStatus;
 }
 
+typedef TypeParameter = {
+	var name: String;
+	var t: Type;
+}
+
 typedef BaseType = {
 	var pack : Array<String>;
 	var name : String;
@@ -50,7 +55,7 @@ typedef BaseType = {
 	var pos : Expr.Position;
 	var isPrivate : Bool;
 	var isExtern : Bool;
-	var params : Array<{ name : String, t : Type }>;
+	var params : Array<TypeParameter>;
 	var meta : MetaAccess;
 	var doc : Null<String>;
 	function exclude() : Void;
@@ -60,7 +65,7 @@ typedef ClassField = {
 	var name : String;
 	var type : Type;
 	var isPublic : Bool;
-	var params : Array<{ name : String, t : Type }>;
+	var params : Array<TypeParameter>;
 	var meta : MetaAccess;
 	var kind : FieldKind;
 	function expr() : Null<TypedExpr>;
@@ -99,7 +104,7 @@ typedef EnumField = {
 	var meta : MetaAccess;
 	var index : Int;
 	var doc : Null<String>;
-	var params : Array<{ name : String, t : Type }>;
+	var params : Array<TypeParameter>;
 }
 
 typedef EnumType = {> BaseType,

+ 57 - 0
std/haxe/macro/TypeTools.hx

@@ -57,6 +57,12 @@ class TypeTools {
 	static public inline function follow( t : Type, ?once : Bool ) : Type
 		return Context.follow(t, once);
 		
+	/**
+		Returns true if `t1` and `t2` unify, false otherwise.
+	**/
+	static public inline function unify( t1 : Type, t2:Type ) : Bool
+		return Context.unify(t1, t2);
+		
 	/**
 		Returns a syntax-level type corresponding to Type `t`.
 		
@@ -97,10 +103,61 @@ class TypeTools {
 		case _: throw "Enum instance expected";
 	}
 
+	/**
+		Applies the type parameters `typeParameters` to type `t` with the given
+		types `concreteTypes`.
+		
+		This function replaces occurences of type parameters in `t` if they are
+		part of `typeParameters`. The array index of such a type parameter is
+		then used to lookup the concrete type in `concreteTypes`.
+		
+		If `typeParameters.length` is not equal to `concreteTypes.length`, an
+		exception of type `String` is thrown.
+		
+		If `typeParameters.length` is 0, `t` is returned unchanged.
+		
+		If either argument is `null`, the result is unspecified.
+	**/
+	static public function applyTypeParameters(t:Type, typeParameters:Array<TypeParameter>, concreteTypes:Array<Type>):Type {
+		if (typeParameters.length != concreteTypes.length)
+			throw 'Incompatible arguments: ${typeParameters.length} type parameters and ${concreteTypes.length} concrete types';
+		else if (typeParameters.length == 0)
+			return t;
+		return Context.load("apply_params", 3)(typeParameters.map(function(tp) return {name:untyped tp.name.__s, t:tp.t}), concreteTypes, t);
+	}
+	
 	/**
 		Converts type `t` to a human-readable String representation.
 	**/
 	static public function toString( t : Type ) : String return new String(Context.load("s_type", 1)(t));
 	#end
 	
+	/**
+		Resolves the field named `name` on class `c`.
+		
+		If `isStatic` is true, the classes' static fields are checked. Otherwise
+		the classes' member fields are checked.
+		
+		If the field is found, it is returned. Otherwise if `c` has a super
+		class, `findField` recursively checks that super class. Otherwise null
+		is returned.
+		
+		If any argument is null, the result is unspecified.
+	**/
+	static public function findField(c:ClassType, name:String, isStatic:Bool = false):Null<ClassField> {
+		var field = (isStatic ? c.statics : c.fields).get().find(function(field) return field.name == name);
+		return if(field != null) field;
+			else if (c.superClass != null) findField(c.superClass.t.get(), name, isStatic);
+			else null;
+	}
+	
+	/**
+		Gets the value of a reference `r`.
+		
+		If `r` is null, the result is unspecified. Otherwise `r.get()` is
+		called.
+	**/
+	static inline function deref<T>(r:Ref<T>):T {
+		return r.get();
+	}
 }

+ 3 - 3
std/haxe/remoting/ExternalConnection.hx

@@ -67,8 +67,8 @@ class ExternalConnection implements Connection implements Dynamic<Connection> {
 		#if flash
 			data = flash.external.ExternalInterface.call("haxe.remoting.ExternalConnection.doCall",__data.name,__path.join("."),params);
 		#elseif js
-			var fobj : Dynamic = untyped window.document[__data.flash];
-			if( fobj == null ) fobj = untyped window.document.getElementById(__data.flash);
+			var fobj : Dynamic = (untyped js.Browser.document)[cast __data.flash]; // FIXME(bruno): Why is this necessary?
+			if( fobj == null ) fobj = js.Browser.document.getElementById(__data.flash);
 			if( fobj == null ) throw "Could not find flash object '"+__data.flash+"'";
 			try	data = fobj.externalRemotingCall(__data.name,__path.join("."),params) catch( e : Dynamic ) {};
 		#end
@@ -78,7 +78,7 @@ class ExternalConnection implements Connection implements Dynamic<Connection> {
 			try {
 				// check that swf in on the same domain
 				domain = fobj.src.split("/")[2];
-				pageDomain = js.Browser.window.location.host;
+				pageDomain = js.Browser.location.host;
 			} catch( e : Dynamic ) {
 				domain = null;
 				pageDomain = null;

+ 2 - 2
std/haxe/remoting/FlashJsConnection.hx

@@ -141,8 +141,8 @@ class FlashJsConnection #if flash implements AsyncConnection implements Dynamic<
 
 	static function flashCall( flashObj : String, name : String, path : String, params : String ) : String {
 		try {
-			var fobj : Dynamic = untyped window.document[flashObj];
-			if( fobj == null ) fobj = untyped window.document.getElementById[flashObj];
+			var fobj : Dynamic = (untyped js.Browser.document)[__data.flash]; // FIXME(bruno): Why is this necessary?
+			if( fobj == null ) fobj = js.Browser.document.getElementById(flashObj);
 			if( fobj == null ) throw "Could not find flash object '"+flashObj+"'";
 			var data = null;
 			try data = fobj.flashJsRemotingCall(name,path,params) catch( e : Dynamic ) {};

+ 4 - 1
std/haxe/web/Dispatch.hx

@@ -59,7 +59,7 @@ enum DispatchError {
 	DETooManyValues;
 }
 
-private class Redirect {
+class Redirect {
 	public function new() {
 	}
 }
@@ -258,6 +258,9 @@ class Dispatch {
 						}
 						return MRSpod(i.toString(), lock);
 					}
+					else if ( name == "haxe.web.Dispatch" ) {
+						return MRDispatch;
+					}
 					csup = csup.t.get().superClass;
 				}
 				Context.error("Unsupported dispatch type '"+i.toString()+"'",p);

+ 4 - 4
std/haxe/web/Request.hx

@@ -32,7 +32,7 @@ class Request {
 		#elseif php
 		return php.Web.getParams();
 		#elseif js
-		var get : String = untyped window.location.search.substr(1);
+		var get : String = js.Browser.location.search.substr(1);
 		var params = new haxe.ds.StringMap();
 		for( p in ~/[&;]/g.split(get) ) {
 			var pl = p.split("=");
@@ -53,7 +53,7 @@ class Request {
 		#elseif php
 		return php.Web.getHostName();
 		#elseif js
-		return untyped window.location.host; // includes port
+		return js.Browser.location.host; // includes port
 		#end
 	}
 
@@ -66,8 +66,8 @@ class Request {
 		#elseif php
 		return php.Web.getURI();
 		#elseif js
-		return untyped window.location.pathname;
+		return js.Browser.location.pathname;
 		#end
 	}
 
-}
+}

+ 5 - 5
std/java/io/NativeInput.hx

@@ -37,17 +37,17 @@ import java.io.EOFException;
 
 	override public function readByte():Int
 	{
+		var ret = 0;
 		try
 		{
-			return stream.read();
-		}
-		catch (e:EOFException) {
-			throw new Eof();
+			ret = stream.read();
 		}
-
 		catch (e:IOException) {
 			throw haxe.io.Error.Custom(e);
 		}
+		if ( ret == -1 )
+			throw new Eof();
+		return ret;
 	}
 
 	override public function readBytes(s:Bytes, pos:Int, len:Int):Int

+ 10 - 4
std/js/Browser.hx

@@ -25,12 +25,18 @@ import js.html.Storage;
 import js.html.XMLHttpRequest;
 
 class Browser {
+	public static var window(get, never):js.html.DOMWindow;
+	inline static function get_window() return untyped __js__("window");
 
-	public static var window(default,null) : js.html.DOMWindow = untyped __js__("typeof window != \"undefined\" ? window : null");
-	public static var document(default,null) : js.html.Document = untyped __js__("typeof window != \"undefined\" ? window.document : null");
-	public static var location(default,null) : js.html.Location = untyped __js__("typeof window != \"undefined\" ? window.location : null");
-	public static var navigator(default,null) : js.html.Navigator = untyped __js__("typeof window != \"undefined\" ? window.navigator : null");
+	public static var document(get, never):js.html.Document;
+	inline static function get_document() return untyped __js__("window.document");
 
+	public static var location(get, never):js.html.Location;
+	inline static function get_location() return untyped __js__("window.location");
+
+	public static var navigator(get, never):js.html.Navigator;
+	inline static function get_navigator() return untyped __js__("window.navigator");
+	
 	/**
 	 * Safely gets the browser's local storage, or returns null if localStorage is unsupported or
 	 * disabled.

+ 2 - 2
std/js/JQuery.hx

@@ -56,7 +56,7 @@ typedef JqEvent = {
 	// propagation
 	function isDefaultPrevented() : Bool;
 	function isImmediatePropagationStopped() : Bool;
-	function isPropationStopped() : Bool;
+	function isPropagationStopped() : Bool;
 	function preventDefault() : Void;
 	function stopImmediatePropagation() : Void;
 	function stopPropagation() : Void;
@@ -398,7 +398,7 @@ extern class JQuery implements ArrayAccess<Element> {
 		if( untyped __js__("typeof($) == 'undefined'") )
 			haxe.macro.Compiler.includeFile("js/jquery-latest.min.js");
 		#end
-		var q : Dynamic = window.jQuery;
+		var q : Dynamic = (untyped js.Browser.window).jQuery;
 		js.JQuery = q;
 		__feature__('js.JQuery.iterator',
 			q.fn.iterator = function() return { pos : 0, j : __this__, hasNext : function() return __this__.pos < __this__.j.length, next : function() return $(__this__.j[__this__.pos++]) }

+ 8 - 6
std/js/Scroll.hx

@@ -21,11 +21,13 @@
  */
 package js;
 
+import js.Browser.*;
+
 class Scroll {
 
-	public static function getTop() : Int untyped {
+	public static function getTop() : Int {
 		var sy = window.pageYOffset;
-		if( __js__("typeof")(sy) == 'number' )
+		if( untyped __js__("typeof")(sy) == 'number' )
 			return sy;
 		if( document.body ) {
 			sy = document.body.scrollTop;
@@ -34,9 +36,9 @@ class Scroll {
 		return document.documentElement.scrollTop;
 	}
 
-	public static function getLeft() : Int untyped {
+	public static function getLeft() : Int {
 		var sx = window.pageXOffset;
-		if( __js__("typeof")(sx) == 'number' )
+		if( untyped __js__("typeof")(sx) == 'number' )
 			return sx;
 		if( document.body ) {
 			sx = document.body.scrollLeft;
@@ -45,8 +47,8 @@ class Scroll {
 		return document.documentElement.scrollLeft;
 	}
 
-	public static function set(left:Int,top:Int) untyped {
+	inline public static function set(left:Int,top:Int) {
 		window.scroll(left,top);
 	}
 
-}
+}

+ 7 - 0
tests/unit/MyAbstract.hx

@@ -314,4 +314,11 @@ abstract FakeEnumAbstract(Int) {
 	var NotFound = 404;
 	var MethodNotAllowed = 405;
 }
+
+@:expose(push, pop)
+abstract ExposingAbstract<S>(Array<S>) {
+	public inline function new() {
+		this = [];
+	}
+}
 #end

+ 7 - 7
tests/unit/TestGADT.hx

@@ -21,27 +21,27 @@ class TestGADT extends Test {
 	function testBasic() {
 		var ti = 1.22;
 		var tb = false;
-		
+
 		var e1 = EConst(CFloat("12"));
 		var e2 = EConst(CFloat("8"));
 		var e3 = EConst(CFloat("12"));
-		
+
 		var eadd = EBinop(OpAdd,e1,e2);
 		var s = eval(eadd);
 		TestType.typedAs(s, ti);
 		eq(s,20);
-		
+
 		var eeq = EBinop(OpEq,e1,e2);
 		var s = eval(eeq);
 		TestType.typedAs(s, tb);
 		eq(s,false);
-		
+
 		var eeq = EBinop(OpEq,e1,e3);
 		var s = eval(eeq);
 		TestType.typedAs(s, tb);
 		eq(s,true);
 	}
-	
+
 	static function evalConst<T>(c:Constant<T>):T {
 		return switch (c) {
 			case CString(s): s;
@@ -49,14 +49,14 @@ class TestGADT extends Test {
 			case CFloat(f): Std.parseFloat(f);
 		}
 	}
-	
+
 	static function evalBinop<T,C>(op:Binop<C,T>, e1:Expr<C>, e2:Expr<C>):T {
 		return switch(op) {
 			case OpAdd: eval(e1) + eval(e2);
 			case OpEq: eval(e1) == eval(e2);
 		}
 	}
-	
+
 	static function eval<T>(e:Expr<T>):T {
 		return switch(e) {
 			case EConst(c): evalConst(c);

+ 156 - 17
tests/unit/TestMatch.hx

@@ -1,6 +1,9 @@
 package unit;
+import haxe.ds.Option;
 import haxe.macro.Expr;
 
+using unit.TestMatch;
+
 enum Tree<T> {
 	Leaf(t:T);
 	Node(l:Tree<T>, r:Tree<T>);
@@ -21,14 +24,26 @@ enum NE {
 	A(?x:Int);
 }
 
-class TestMatch extends Test {
-	static macro function getErrorMessage(e:Expr) {
+enum MiniType {
+	MTString(t:MiniRef<String>, tl:Array<MiniType>);
+	MTInt(t:MiniRef<Int>, tl:Array<MiniType>);
+}
+
+typedef MiniRef<T> = {
+	public function get():T;
+}
+
+class TestMatchMacro {
+	static public macro function getErrorMessage(e:Expr) {
 		var result = try {
 			haxe.macro.Context.typeof(e);
 			"no error";
 		} catch (e:Dynamic) Std.string(e.message);
 		return macro $v{result};
 	}
+}
+
+class TestMatch extends Test {
 
 	static function switchNormal(e:Expr):String {
 		return switch(e.expr) {
@@ -314,58 +329,58 @@ class TestMatch extends Test {
 	}
 
 	function testNonExhaustiveness() {
-		eq("Unmatched patterns: false", getErrorMessage(switch(true) {
+		eq("Unmatched patterns: false", TestMatchMacro.getErrorMessage(switch(true) {
 			case true:
 		}));
-		eq("Unmatched patterns: OpNegBits | OpNeg", getErrorMessage(switch(OpIncrement) {
+		eq("Unmatched patterns: OpNegBits | OpNeg", TestMatchMacro.getErrorMessage(switch(OpIncrement) {
 			case OpIncrement:
 			case OpDecrement:
 			case OpNot:
 		}));
-		eq("Unmatched patterns: Node(Leaf(_),_)", getErrorMessage(switch(Leaf("foo")) {
+		eq("Unmatched patterns: Node(Leaf(_),_)", TestMatchMacro.getErrorMessage(switch(Leaf("foo")) {
 			case Node(Leaf("foo"), _):
 			case Leaf(_):
 		}));
-		eq("Unmatched patterns: Leaf", getErrorMessage(switch(Leaf("foo")) {
+		eq("Unmatched patterns: Leaf", TestMatchMacro.getErrorMessage(switch(Leaf("foo")) {
 			case Node(_, _):
 			case Leaf(_) if (false):
 		}));
-		eq("Unmatched patterns: Leaf(_)", getErrorMessage(switch(Leaf("foo")) {
+		eq("Unmatched patterns: Leaf(_)", TestMatchMacro.getErrorMessage(switch(Leaf("foo")) {
 			case Node(_, _):
 			case Leaf("foo"):
 		}));
-		eq("Unmatched patterns: [_,false,_]", getErrorMessage(switch [1, true, "foo"] {
+		eq("Unmatched patterns: [_,false,_]", TestMatchMacro.getErrorMessage(switch [1, true, "foo"] {
 			case [_, true, _]:
 		}));
 		//var x:Null<Bool> = true;
-		//eq("Unmatched patterns: null", getErrorMessage(switch x {
+		//eq("Unmatched patterns: null", TestMatchMacro.getErrorMessage(switch x {
 			//case true:
 			//case false:
 		//}));
 		//var t:Null<Tree<String>> = null;
-		//eq("Unmatched patterns: null", getErrorMessage(switch t {
+		//eq("Unmatched patterns: null", TestMatchMacro.getErrorMessage(switch t {
 			//case Leaf(_):
 			//case Node(_):
 		//}));
 	}
 
 	function testInvalidBinding() {
-		eq("Variable y must appear exactly once in each sub-pattern", getErrorMessage(switch(Leaf("foo")) {
+		eq("Variable y must appear exactly once in each sub-pattern", TestMatchMacro.getErrorMessage(switch(Leaf("foo")) {
 			case Leaf(x) | Leaf(y):
 		}));
-		eq("Variable y must appear exactly once in each sub-pattern", getErrorMessage(switch(Leaf("foo")) {
+		eq("Variable y must appear exactly once in each sub-pattern", TestMatchMacro.getErrorMessage(switch(Leaf("foo")) {
 			case Leaf(x) | Leaf(x) | Leaf(y):
 		}));
-		eq("Variable x must appear exactly once in each sub-pattern", getErrorMessage(switch(Leaf("foo")) {
+		eq("Variable x must appear exactly once in each sub-pattern", TestMatchMacro.getErrorMessage(switch(Leaf("foo")) {
 			case Leaf(x) | Leaf(x) | Leaf(_):
 		}));
-		eq("Variable l must appear exactly once in each sub-pattern", getErrorMessage(switch(Leaf("foo")) {
+		eq("Variable l must appear exactly once in each sub-pattern", TestMatchMacro.getErrorMessage(switch(Leaf("foo")) {
 			case Node(l = Leaf(x),_) | Node(Leaf(x), _):
 		}));
-		eq("Variable l must appear exactly once in each sub-pattern", getErrorMessage(switch(Leaf("foo")) {
+		eq("Variable l must appear exactly once in each sub-pattern", TestMatchMacro.getErrorMessage(switch(Leaf("foo")) {
 			case Node(l = Leaf(l), _):
 		}));
-		eq("String should be unit.Tree<String>", getErrorMessage(switch(Leaf("foo")) {
+		eq("String should be unit.Tree<String>", TestMatchMacro.getErrorMessage(switch(Leaf("foo")) {
 			case Node(l = Leaf(_), _) | Leaf(l):
 		}));
 	}
@@ -437,12 +452,136 @@ class TestMatch extends Test {
 		}
 		eq(r, 1);
 		
-		eq("Unmatched patterns: 405", getErrorMessage(switch(a) {
+		eq("Unmatched patterns: 405", TestMatchMacro.getErrorMessage(switch(a) {
 			case NotFound:
 		}));
 		#end
 	}
 
+	function testExtractors() {
+		function f(i) {
+			return switch(i) {
+				case 1,2,3: 1;
+				case even => true: 2;
+				case 4: throw "unreachable";
+				case _: 3;
+			}
+		}
+		
+		eq(1, f(1));
+		eq(1, f(2));
+		eq(1, f(3));
+		eq(2, f(4));
+		eq(3, f(5));
+		eq(3, f(7));
+		eq(3, f(9));
+		eq(2, f(6));
+		eq(2, f(8));
+		
+		function ref<T>(t:T):MiniRef<T> return {
+			get: function() return t
+		}
+		
+		function f(t:MiniType) {
+			return switch (t) {
+				case MTString(deref => "Foo", []): "Foo";
+				case MTString(deref => "Bar" | "Baz", _): "BarBaz";
+				case MTInt(deref => i, []): 'Int:$i';
+				case MTString(_): "OtherString";
+				case _: "Other";
+			}
+		}
+		
+		eq("Foo", f(MTString(ref("Foo"), [])));
+		eq("BarBaz", f(MTString(ref("Bar"), [])));
+		eq("BarBaz", f(MTString(ref("Baz"), [])));
+		eq("OtherString", f(MTString(ref("a"), [])));
+		eq("OtherString", f(MTString(ref(""), [])));
+		eq("Int:12", f(MTInt(ref(12), [])));
+		eq("Other", f(MTInt(ref(12), [MTInt(ref(10),[])])));
+		
+		function g(i : Array<Int>) {
+			return switch(i) {
+				case [x]: 1;
+				case isPair => Some(p) : p.a+p.b;
+				case arr: 3;
+			}
+		}
+
+		eq(3, g([]));
+		eq(1, g([1]));
+		eq(5, g([2, 3]));
+		eq(3, g([2, 3, 4]));
+		
+		var anon = {
+			odd: function(i) return i & 1 != 0
+		};
+		
+		var i = 9;
+		var r = switch(i) {
+			case 1: 1;
+			case anon.odd => true: 2;
+			case 9: 3;
+			case _: 4;
+		}
+		eq(2, r);
+		
+		function mul(i1,i2) return i1 * i2;
+		
+		function check(i) {
+			return switch(i) {
+				case 1: 1;
+				case mul.bind(4) => 8: 2;
+				case mul.bind(5) => 15: 3;
+				case _: 4;
+			}
+		}
+		
+		eq(1, check(1));
+		eq(2, check(2));
+		eq(3, check(3));
+		eq(4, check(4));
+		
+		function is<T>(pred : T -> Bool) return function (x : T) {
+			return pred(x)?Some(x):None;
+		}
+
+		function isNot<T>(pred : T -> Bool) return function (x : T) {
+			return (!pred(x))?Some(x):None;
+		}
+
+		function testArgs<T>(i:Int, s:String, t:T) {
+			return Std.string(t);
+		}
+		function h(i : Array<Int>) {
+			return switch(i) {
+				case [x]: 1;
+				case isPair => Some({ a : a, b : b }) if (a < 0): 42;
+				case isPair => Some({ a : is(even) => Some(a), b : b }) : a+b;
+				case isPair => Some({ a : isNot(even) => Some(a), b : b }) : a*b;
+				case testArgs.bind(1, "foo") => "[99,98,97]": 99;
+				case arr: 3;
+			}
+		}
+		
+		eq(3, h([]));
+		eq(1, h([1]));
+		eq(1, h([2]));
+		eq(5, h([2, 3]));
+		eq(3, h([1, 3]));
+		eq(3, h([2, 3, 4]));
+		eq(42, h([-1, 3]));
+		eq(99, h([99,98,97]));
+	}
+	
+	static function isPair<T>(t:Array<T>) return t.length == 2 ? Some({a:t[0], b:t[1]}) : None;
+	
+	static function even(i:Int) {
+		return i & 1 == 0;
+	}
+	
+	static function deref<T>(ref:MiniRef<T>) return ref.get();
+	
 	#if false
 	 //all lines marked as // unused should give an error
 	function testRedundance() {

+ 22 - 0
tests/unit/TestPhp.hx

@@ -54,6 +54,28 @@ class TestPhp extends Test
 		var result = pattern.replace("$a","A").replace("$b","B");
 		eq("AB", result);
 	}
+
+	function testIssue2146()
+	{
+		f(Class2146.test());
+	}
+}
+
+class Class2146 {
+    var array:Array<Class2146>;
+    function new() {
+        array = new Array<Class2146>();
+    }
+
+    public static function test() {
+        var a = new Class2146();
+        var b = new Class2146();
+        var c = new Class2146();
+        a.array.push(b);
+        b.array.push(a);
+        c.array.push(a);
+        return Lambda.has(c.array,b);
+    }
 }
 
 enum Annotation {

+ 8 - 0
tests/unit/TestType.hx

@@ -860,4 +860,12 @@ class TestType extends Test {
 		var a:Array<unit.MyAbstract.MyInt> = [1, 2, 3];
 		var b:Array<unit.MyAbstract.MyInt2> = a;
 	}
+	
+	function testExposingAbstract() {
+		#if !macro
+		var ea = new unit.MyAbstract.ExposingAbstract();
+		ea.push(12);
+		eq(12, ea.pop());
+		#end
+	}
 }

+ 3 - 1
type.ml

@@ -285,6 +285,7 @@ and module_def_extra = {
 	mutable m_kind : module_kind;
 	mutable m_binded_res : (string, string) PMap.t;
 	mutable m_macro_calls : string list;
+	mutable m_features : (string *(tclass * tclass_field * bool)) list;
 }
 
 and module_kind =
@@ -382,6 +383,7 @@ let module_extra file sign time kind =
 		m_kind = kind;
 		m_binded_res = PMap.empty;
 		m_macro_calls = [];
+		m_features = [];
 	}
 
 
@@ -1159,7 +1161,7 @@ let rec unify a b =
 	| TEnum(en,_), TAbstract ({ a_path = ["haxe"],"FlatEnum" },[]) when Meta.has Meta.FlatEnum en.e_meta ->
 		()
 	| TFun _, TAbstract ({ a_path = ["haxe"],"Function" },[]) ->
-		()		
+		()
 	| TDynamic t , _ ->
 		if t == a then
 			()

+ 63 - 37
typeload.ml

@@ -169,12 +169,21 @@ let make_module ctx mpath file tdecls loadp =
 					| _ ->
 						f
 				) fields in
-				let acc = make_decl acc (EClass { d_name = d.d_name ^ "_Impl_"; d_flags = [HPrivate]; d_data = fields; d_doc = None; d_params = []; d_meta = [] },p) in
+				let meta = ref [] in
+				if has_meta Meta.Dce a.a_meta then meta := (Meta.Dce,[],p) :: !meta;
+				let acc = make_decl acc (EClass { d_name = d.d_name ^ "_Impl_"; d_flags = [HPrivate]; d_data = fields; d_doc = None; d_params = []; d_meta = !meta },p) in
 				(match !decls with
 				| (TClassDecl c,_) :: _ ->
-					(try c.cl_meta <- (Meta.get Meta.Build a.a_meta) :: c.cl_meta with Not_found -> ());
-					(try c.cl_meta <- (Meta.get Meta.CoreApi a.a_meta) :: c.cl_meta with Not_found -> ());
-					if Meta.has Meta.FakeEnum a.a_meta then c.cl_meta <- (Meta.Build,[ECall((EField((EField((EField((EConst(Ident "haxe"),p),"macro"),p),"Build"),p),"buildFakeEnum"),p),[]),p],p) :: c.cl_meta;
+					List.iter (fun m -> match m with
+						| ((Meta.Build | Meta.CoreApi | Meta.Allow | Meta.Access),_,_) ->
+							c.cl_meta <- m :: c.cl_meta;
+						| (Meta.FakeEnum,_,_) ->
+							c.cl_meta <- (Meta.Build,[ECall((EField((EField((EField((EConst(Ident "haxe"),p),"macro"),p),"Build"),p),"buildFakeEnum"),p),[]),p],p) :: c.cl_meta;
+						| (Meta.Expose,el,_) ->
+							c.cl_meta <- (Meta.Build,[ECall((EField((EField((EField((EConst(Ident "haxe"),p),"macro"),p),"Build"),p),"exposeUnderlyingFields"),p),el),p],p) :: c.cl_meta;
+						| _ ->
+							()
+					) a.a_meta;
 					a.a_impl <- Some c;
 					c.cl_kind <- KAbstractImpl a
 				| _ -> assert false);
@@ -1534,6 +1543,7 @@ let init_class ctx c p context_init herits fields =
 	let loop_cf f =
 		let name = f.cff_name in
 		let p = f.cff_pos in
+		if name.[0] = '$' && not ctx.com.display then error "Field names starting with a dollar are not allowed" p;
 		let stat = List.mem AStatic f.cff_access in
 		let extern = Meta.has Meta.Extern f.cff_meta || c.cl_extern in
 		let is_abstract,allow_inline =
@@ -1678,35 +1688,37 @@ let init_class ctx c p context_init herits fields =
 					let m = mk_mono() in
 					let ta = TAbstract(a, List.map (fun _ -> mk_mono()) a.a_types) in
 					let tthis = if Meta.has Meta.Impl f.cff_meta || Meta.has Meta.To f.cff_meta then monomorphs a.a_types a.a_this else a.a_this in
-					if Meta.has Meta.From f.cff_meta then begin
-						if is_macro then error "Macro cast functions are not supported" cf.cf_pos;
-						(* the return type of a from-function must be the abstract, not the underlying type *)
-						(try unify_raise ctx t (tfun [m] ta) f.cff_pos with Error (Unify l,p) -> error (error_msg (Unify l)) p);
-						a.a_from <- (follow m, Some cf) :: a.a_from
-					end else if Meta.has Meta.To f.cff_meta then begin
-						if is_macro then error "Macro cast functions are not supported" cf.cf_pos;
-						let args = if Meta.has Meta.MultiType a.a_meta then begin
-							(* the return type of multitype @:to functions must unify with a_this *)
-							delay ctx PFinal (fun () -> unify ctx m tthis f.cff_pos);
-							(* the arguments must be compatible with the original constructor, which we have to find at this point *)
-							try (match follow (monomorphs a.a_types (PMap.find "_new" c.cl_statics).cf_type) with
-								| TFun(args,_) -> List.map (fun (_,_,t) -> t) args
-								| _ -> assert false)
-							with Not_found ->
-								error "Constructor of multi-type abstract must be defined before the individual @:to-functions are" cf.cf_pos
-						end else [] in
-						(* the first argument of a to-function must be the underlying type, not the abstract *)
-						(try unify_raise ctx t (tfun (tthis :: args) m) f.cff_pos with Error (Unify l,p) -> error (error_msg (Unify l)) p);
-						if not (Meta.has Meta.Impl cf.cf_meta) then cf.cf_meta <- (Meta.Impl,[],cf.cf_pos) :: cf.cf_meta;
-						a.a_to <- (follow m, Some cf) :: a.a_to
-					end else if Meta.has Meta.ArrayAccess f.cff_meta then begin
-						if is_macro then error "Macro array-access functions are not supported" cf.cf_pos;
-						a.a_array <- cf :: a.a_array;
-					end else if f.cff_name = "_new" && Meta.has Meta.MultiType a.a_meta then
-						do_bind := false
-					else (try match Meta.get Meta.Op cf.cf_meta with
-						| _,[EBinop(op,_,_),_],_ ->
-							if is_macro then error "Macro operator functions are not supported" cf.cf_pos;
+					let rec loop ml = match ml with
+						| (Meta.From,_,_) :: _ ->
+							if is_macro then error "Macro cast functions are not supported" p;
+							(* the return type of a from-function must be the abstract, not the underlying type *)
+							(try type_eq EqStrict ret ta with Unify_error l -> error (error_msg (Unify l)) p);
+							let t = match t with
+								| TFun([_,_,t],_) -> t
+								| _ -> error "@:from cast functions must accept exactly one argument" p
+							in
+							a.a_from <- (t,Some cf) :: a.a_from;
+						| (Meta.To,_,_) :: _ ->
+							if is_macro then error "Macro cast functions are not supported" p;
+							let args = if Meta.has Meta.MultiType a.a_meta then begin
+								(* the return type of multitype @:to functions must unify with a_this *)
+								delay ctx PFinal (fun () -> unify ctx m tthis f.cff_pos);
+								(* the arguments must be compatible with the original constructor, which we have to find at this point *)
+								try (match follow (monomorphs a.a_types (PMap.find "_new" c.cl_statics).cf_type) with
+									| TFun(args,_) -> List.map (fun (_,_,t) -> t) args
+									| _ -> assert false)
+								with Not_found ->
+									error "Constructor of multi-type abstract must be defined before the individual @:to-functions are" cf.cf_pos
+							end else [] in
+							(* the first argument of a to-function must be the underlying type, not the abstract *)
+							(try unify_raise ctx t (tfun (tthis :: args) m) f.cff_pos with Error (Unify l,p) -> error (error_msg (Unify l)) p);
+							if not (Meta.has Meta.Impl cf.cf_meta) then cf.cf_meta <- (Meta.Impl,[],cf.cf_pos) :: cf.cf_meta;
+							a.a_to <- (follow m, Some cf) :: a.a_to
+						| (Meta.ArrayAccess,_,_) :: _ ->
+							if is_macro then error "Macro array-access functions are not supported" p;
+							a.a_array <- cf :: a.a_array;
+						| (Meta.Op,[EBinop(op,_,_),_],_) :: _ ->
+							if is_macro then error "Macro operator functions are not supported" p;
 							let targ = if Meta.has Meta.Impl f.cff_meta then tthis else ta in
 							let left_eq = type_iseq t (tfun [targ;m] (mk_mono())) in
 							let right_eq = type_iseq t (tfun [mk_mono();targ] (mk_mono())) in
@@ -1714,14 +1726,19 @@ let init_class ctx c p context_init herits fields =
 							if right_eq && Meta.has Meta.Commutative f.cff_meta then error ("@:commutative is only allowed if the right argument is not " ^ (s_type (print_context()) targ)) f.cff_pos;
 							a.a_ops <- (op,cf) :: a.a_ops;
 							if fd.f_expr = None then do_bind := false;
-						| _,[EUnop(op,flag,_),_],_ ->
-							if is_macro then error "Macro operator functions are not supported" cf.cf_pos;
+						| (Meta.Op,[EUnop(op,flag,_),_],_) :: _ ->
+							if is_macro then error "Macro operator functions are not supported" p;
 							let targ = if Meta.has Meta.Impl f.cff_meta then tthis else ta in
 							(try type_eq EqStrict t (tfun [targ] (mk_mono())) with Unify_error l -> raise (Error ((Unify l),f.cff_pos)));
 							a.a_unops <- (op,flag,cf) :: a.a_unops;
 							if fd.f_expr = None then do_bind := false;
-						| _ -> ()
-						with Not_found -> ())
+						| _ :: ml ->
+							loop ml
+						| [] ->
+							()
+					in
+					loop f.cff_meta;
+					if f.cff_name = "_new" && Meta.has Meta.MultiType a.a_meta then do_bind := false;
 				| _ ->
 					());
 			init_meta_overloads ctx cf;
@@ -1863,6 +1880,15 @@ let init_class ctx c p context_init herits fields =
 			let fd , constr, f = loop_cf f in
 			let is_static = List.mem AStatic fd.cff_access in
 			if (is_static || constr) && c.cl_interface && f.cf_name <> "__init__" then error "You can't declare static fields in interfaces" p;
+			begin try
+				let _,args,_ = Meta.get Meta.IfFeature f.cf_meta in
+				List.iter (fun e -> match fst e with
+					| EConst(String s) ->
+						ctx.m.curmod.m_extra.m_features <- (s,(c,f,is_static)) :: ctx.m.curmod.m_extra.m_features;
+					| _ ->
+						error "String expected" (pos e)
+				) args
+			with Not_found -> () end;
 			let req = check_require fd.cff_meta in
 			let req = (match req with None -> if is_static || constr then cl_req else None | _ -> req) in
 			(match req with

+ 45 - 23
typer.ml

@@ -205,8 +205,9 @@ let rec can_access ctx c cf stat =
 		true
 	else
 	(* has metadata path *)
-	let make_path c f =
-		fst c.cl_path @ [snd c.cl_path; f.cf_name]
+	let make_path c f = match c.cl_kind with
+		| KAbstractImpl a -> fst a.a_path @ [snd a.a_path; f.cf_name]
+		| _ -> fst c.cl_path @ [snd c.cl_path; f.cf_name]
 	in
 	let rec expr_path acc e =
 		match fst e with
@@ -230,13 +231,22 @@ let rec can_access ctx c cf stat =
 		in
 		loop c.cl_meta || loop f.cf_meta
 	in
-	let cur_path = make_path ctx.curclass ctx.curfield in
+	let cur_paths = ref [] in
+	let rec loop c =
+		cur_paths := make_path c ctx.curfield :: !cur_paths;
+		begin match c.cl_super with
+			| Some (csup,_) -> loop csup
+			| None -> ()
+		end;
+		List.iter (fun (c,_) -> loop c) c.cl_implements;
+	in
+	loop ctx.curclass;
 	let is_constr = cf.cf_name = "new" in
 	let rec loop c =
 		(try
 			(* if our common ancestor declare/override the field, then we can access it *)
 			let f = if is_constr then (match c.cl_constructor with None -> raise Not_found | Some c -> c) else PMap.find cf.cf_name (if stat then c.cl_statics else c.cl_fields) in
-			is_parent c ctx.curclass || has Meta.Allow c f cur_path
+			is_parent c ctx.curclass || (List.exists (has Meta.Allow c f) !cur_paths)
 		with Not_found ->
 			false
 		)
@@ -1749,11 +1759,15 @@ let rec type_binop ctx op e1 e2 is_assign_op p =
 			| (o,cf) :: ops when is_assign_op && o = OpAssignOp(op) || o == op ->
 				(match follow (monomorphs cf.cf_params cf.cf_type) with
 				| TFun([(_,_,t1);(_,_,t2)],r) ->
-					let t1,t2 = if left || Meta.has Meta.Commutative cf.cf_meta then t1,t2 else t2,t1 in
-					if type_iseq t t2 && (if Meta.has Meta.Impl cf.cf_meta then type_iseq (apply_params a.a_types pl a.a_this) t1 else type_iseq (TAbstract(a,pl)) t1) then begin
-						if not (can_access ctx c cf true) then display_error ctx ("Cannot access operator function " ^ (s_type_path a.a_path) ^ "." ^ cf.cf_name) p;
-						cf,r,o = OpAssignOp(op),Meta.has Meta.Commutative cf.cf_meta
-					end else loop ops
+					let impl = Meta.has Meta.Impl cf.cf_meta in
+					(* implementation fields can only be used in left mode (issue #2130) *)
+					if impl && not left then loop ops else begin
+						let t1,t2 = if left || Meta.has Meta.Commutative cf.cf_meta then t1,t2 else t2,t1 in
+						if type_iseq t t2 && (if impl then type_iseq (apply_params a.a_types pl a.a_this) t1 else type_iseq (TAbstract(a,pl)) t1) then begin
+							if not (can_access ctx c cf true) then display_error ctx ("Cannot access operator function " ^ (s_type_path a.a_path) ^ "." ^ cf.cf_name) p;
+							cf,r,o = OpAssignOp(op),Meta.has Meta.Commutative cf.cf_meta
+						end else loop ops
+					end;
 				| _ -> loop ops)
 			| _ :: ops ->
 				loop ops
@@ -2342,6 +2356,7 @@ and type_expr ctx (e,p) (with_type:with_type) =
 			let rec loop (l,acc) (f,e) =
 				let f,add = object_field f in
 				if PMap.mem f acc then error ("Duplicate field in object declaration : " ^ f) p;
+				if f.[0] = '$' then error "Field names starting with a dollar are not allowed" p;
 				let e = type_expr ctx e Value in
 				(match follow e.etype with TAbstract({a_path=[],"Void"},_) -> error "Fields of type Void are not allowed in structures" e.epos | _ -> ());
 				let cf = mk_field f e.etype e.epos in
@@ -2357,6 +2372,7 @@ and type_expr ctx (e,p) (with_type:with_type) =
 			let fl = List.map (fun (n, e) ->
 				let n,add = object_field n in
 				if PMap.mem n !fields then error ("Duplicate field in object declaration : " ^ n) p;
+				if n.[0] = '$' then error "Field names starting with a dollar are not allowed" p;
 				let e = try
 					let t = (PMap.find n a.a_fields).cf_type in
 					let e = Codegen.Abstract.check_cast ctx t (type_expr ctx e (match with_type with WithTypeResume _ -> WithTypeResume t | _ -> WithType t)) p in
@@ -2527,11 +2543,10 @@ and type_expr ctx (e,p) (with_type:with_type) =
 						unify_raise ctx e1.etype t e1.epos;
 						e1
 					with Error (Unify _,_) ->
-						let acc = acc_get ctx (type_field ctx e1 "iterator" e1.epos MCall) e1.epos in
-						let acc = (match acc.eexpr with TField (e,FClosure (c,f)) -> { acc with eexpr = TField (e,match c with None -> FAnon f | Some c -> FInstance (c,f)) } | _ -> acc) in
+						let acc = build_call ctx (type_field ctx e1 "iterator" e1.epos MCall) [] Value e1.epos in
 						try
-							unify_raise ctx acc.etype (tfun [] t) acc.epos;
-							make_call ctx acc [] t e1.epos
+							unify_raise ctx acc.etype t acc.epos;
+							acc
 						with Error (Unify(l),p) ->
 							display_error ctx "Field iterator has an invalid type" acc.epos;
 							display_error ctx (error_msg (Unify l)) p;
@@ -2650,13 +2665,13 @@ and type_expr ctx (e,p) (with_type:with_type) =
 					List.iter (fun pt ->
 						if pt != t_dynamic then error "Catch class parameter must be Dynamic" p;
 					) params;
-					add_feature ctx.com "typed_catch";
 					(match path with
 					| x :: _ , _ -> x
 					| [] , name -> name)
 				| TDynamic _ -> ""
 				| _ -> error "Catch type must be a class" p
 			) in
+			if v.[0] = '$' then display_error ctx "Catch variable names starting with a dollar are not allowed" p;
 			let locals = save_locals ctx in
 			let v = add_local ctx v t in
 			let e = type_expr ctx e with_type in
@@ -2669,7 +2684,7 @@ and type_expr ctx (e,p) (with_type:with_type) =
 	| EThrow e ->
 		let e = type_expr ctx e Value in
 		mk (TThrow e) (mk_mono()) p
-	| ECall (((EConst (Ident s),_) as e),el) ->
+	| ECall (((EConst (Ident s),pc) as e),el) ->
 		(try
 			let en,t = (match with_type with
 				| WithType t | WithTypeResume t ->
@@ -2685,7 +2700,13 @@ and type_expr ctx (e,p) (with_type:with_type) =
 				ctx.on_error <- old;
 			in
 			ctx.on_error <- (fun ctx msg ep ->
-				raise Not_found;
+				(* raise Not_found only if the error is actually about the outside identifier (issue #2148) *)
+				if ep = pc then
+					raise Not_found
+				else begin
+					restore();
+					ctx.on_error ctx msg ep;
+				end
 			);
 			begin try
 				let e = type_call ctx e el with_type p in
@@ -2797,7 +2818,7 @@ and type_expr ctx (e,p) (with_type:with_type) =
 		let v = (match v with
 			| None -> None
 			| Some v ->
-				if v.[0] = '$' then display_error ctx "Variables names starting with a dollar are not allowed" p;
+				if v.[0] = '$' then display_error ctx "Variable names starting with a dollar are not allowed" p;
 				Some (add_local ctx v ft)
 		) in
 		let e , fargs = Typeload.type_function ctx args rt (match ctx.curfun with FunStatic -> FunStatic | _ -> FunMemberLocal) f false p in
@@ -2846,7 +2867,6 @@ and type_expr ctx (e,p) (with_type:with_type) =
 		let e = type_expr ctx e Value in
 		mk (TCast (e,None)) (mk_mono()) p
 	| ECast (e, Some t) ->
-		add_feature ctx.com "typed_cast";
 		let t = Typeload.load_complex_type ctx (pos e) t in
 		let texpr = (match follow t with
 		| TInst (_,params) | TEnum (_,params) ->
@@ -3073,7 +3093,7 @@ and type_call ctx e el (with_type:with_type) p =
 			mk (TCall (mk (TLocal (alloc_var "`trace" t_dynamic)) t_dynamic p,[e;infos])) ctx.t.tvoid p
 		else
 			let me = Meta.ToString,[],pos e in
-			type_expr ctx (ECall ((EField ((EField ((EConst (Ident "haxe"),p),"Log"),p),"trace"),p),[(EMeta (me,e),pos e);EUntyped infos,p]),p) NoValue
+			type_expr ctx (ECall ((EField ((EField ((EConst (Ident "haxe"),p),"Log"),p),"trace"),p),[(EMeta (me,e),pos e);infos]),p) NoValue
 	| (EConst(Ident "callback"),p1),args ->
 		let ecb = try Some (type_ident_raise ctx "callback" p1 MCall) with Not_found -> None in
 		(match ecb with
@@ -3129,6 +3149,9 @@ and build_call ctx acc el (with_type:with_type) p =
 		er,fun () -> ctx.this_stack <- List.tl ctx.this_stack
 	in
 	match acc with
+	| AKInline (ethis,f,fmode,t) when Meta.has Meta.Generic f.cf_meta ->
+		let el,t,e = type_generic_function ctx (ethis,f) el with_type p in
+		make_call ctx e el t p
 	| AKInline (ethis,f,fmode,t) ->
 		let params, tfunc = (match follow t with
 			| TFun (args,r) -> unify_call_params ctx (fopts ethis.etype f) el args r p true
@@ -3156,12 +3179,12 @@ and build_call ctx acc el (with_type:with_type) p =
 				| TAbstract(a,tl) when Meta.has Meta.Impl ef.cf_meta -> apply_params a.a_types tl t,apply_params a.a_types tl a.a_this
 				| te -> t,te
 			in
-			let params,args,r = match t with
+			let params,args,r,eparam = match t with
 				| TFun ((_,_,t1) :: args,r) ->
 					unify ctx tthis t1 eparam.epos;
 					let ef = prepare_using_field ef in
 					begin match unify_call_params ctx (Some (TInst(cl,[]),ef)) el args r p (ef.cf_kind = Method MethInline) with
-					| el,TFun(args,r) -> el,args,r
+					| el,TFun(args,r) -> el,args,r,Codegen.Abstract.check_cast ctx t1 eparam eparam.epos
 					| _ -> assert false
 					end
 				| _ -> assert false
@@ -3639,8 +3662,7 @@ let make_macro_api ctx p =
 			let m, tdef, pos = (try Interp.decode_type_def v with Interp.Invalid_expr -> Interp.exc (Interp.VString "Invalid type definition")) in
 			let mdep = Typeload.type_module ctx m ctx.m.curmod.m_extra.m_file [tdef,pos] pos in
 			mdep.m_extra.m_kind <- MFake;
-			mdep.m_extra.m_time <- -1.;
-			add_dependency ctx.m.curmod mdep;
+			add_dependency mdep ctx.m.curmod;
 		);
 		Interp.module_dependency = (fun mpath file ismacro ->
 			let m = typing_timer ctx (fun() -> Typeload.load_module ctx (parse_path mpath) p) in