Quellcode durchsuchen

added tvar structure : allow immediate variable renaming and no name conflicts

Nicolas Cannasse vor 14 Jahren
Ursprung
Commit
47abfef927
17 geänderte Dateien mit 971 neuen und 1035 gelöschten Zeilen
  1. 183 169
      codegen.ml
  2. 1 0
      doc/CHANGES.txt
  3. 69 92
      genas3.ml
  4. 81 81
      gencpp.ml
  5. 55 61
      genjs.ml
  6. 28 107
      genneko.ml
  7. 131 131
      genphp.ml
  8. 5 5
      genswf.ml
  9. 70 64
      genswf8.ml
  10. 82 84
      genswf9.ml
  11. 9 9
      interp.ml
  12. 2 1
      main.ml
  13. 144 121
      optimizer.ml
  14. 49 30
      type.ml
  15. 9 27
      typecore.ml
  16. 9 12
      typeload.ml
  17. 44 41
      typer.ml

+ 183 - 169
codegen.ml

@@ -103,7 +103,7 @@ let extend_remoting ctx c t p async prot =
 	if ctx.com.verbose then print_endline ("Building proxy for " ^ s_type_path path);
 	let decls = (try
 		Typeload.parse_module ctx path p
-	with 
+	with
 		| Not_found -> ctx.com.package_rules <- rules; error ("Could not load proxy module " ^ s_type_path path ^ (if fst path = [] then " (try using absolute path)" else "")) p
 		| e -> ctx.com.package_rules <- rules; raise e) in
 	ctx.com.package_rules <- rules;
@@ -218,7 +218,16 @@ let rec build_generic ctx c p tl =
 			| _ ->
 				try List.assq t subst with Not_found -> Type.map build_type t
 		in
-		let rec build_expr e = map_expr_type build_expr build_type e in
+		let vars = Hashtbl.create 0 in
+		let build_var v =
+			try
+				Hashtbl.find vars v.v_id
+			with Not_found ->
+				let v2 = alloc_var v.v_name (build_type v.v_type) in
+				Hashtbl.add vars v.v_id v2;
+				v2
+		in
+		let rec build_expr e = map_expr_type build_expr build_type build_var e in
 		let build_field f =
 			let t = build_type f.cf_type in
 			{ f with cf_type = t; cf_expr = (match f.cf_expr with None -> None | Some e -> Some (build_expr e)) }
@@ -440,30 +449,30 @@ type usage =
 	| Block of ((usage -> unit) -> unit)
 	| Loop of ((usage -> unit) -> unit)
 	| Function of ((usage -> unit) -> unit)
-	| Declare of string * t
-	| Use of string
+	| Declare of tvar
+	| Use of tvar
 
 let rec local_usage f e =
 	match e.eexpr with
 	| TLocal v ->
 		f (Use v)
 	| TVars l ->
-		List.iter (fun (v,t,e) ->
+		List.iter (fun (v,e) ->
 			(match e with None -> () | Some e -> local_usage f e);
-			f (Declare (v,t));
+			f (Declare v);
 		) l
 	| TFunction tf ->
 		let cc f =
-			List.iter (fun (n,_,t) -> f (Declare (n,t))) tf.tf_args;
+			List.iter (fun (v,_) -> f (Declare v)) tf.tf_args;
 			local_usage f tf.tf_expr;
 		in
 		f (Function cc)
 	| TBlock l ->
 		f (Block (fun f -> List.iter (local_usage f) l))
-	| TFor (v,t,it,e) ->
+	| TFor (v,it,e) ->
 		local_usage f it;
 		f (Loop (fun f ->
-			f (Declare (v,t));
+			f (Declare v);
 			local_usage f e;
 		))
 	| TWhile _ ->
@@ -472,9 +481,9 @@ let rec local_usage f e =
 		))
 	| TTry (e,catchs) ->
 		local_usage f e;
-		List.iter (fun (v,t,e) ->
+		List.iter (fun (v,e) ->
 			f (Block (fun f ->
-				f (Declare (v,t));
+				f (Declare v);
 				local_usage f e;
 			))
 		) catchs;
@@ -484,7 +493,7 @@ let rec local_usage f e =
 			let cc f =
 				(match vars with
 				| None -> ()
-				| Some l ->	List.iter (fun (vo,t) -> match vo with None -> () | Some v -> f (Declare (v,t))) l);
+				| Some l ->	List.iter (function None -> () | Some v -> f (Declare v)) l);
 				local_usage f e;
 			in
 			f (Block cc)
@@ -494,11 +503,14 @@ let rec local_usage f e =
 		iter (local_usage f) e
 
 (* -------------------------------------------------------------------------- *)
-(* PER-BLOCK VARIABLES *)
+(* BLOCK VARIABLES CAPTURE *)
 
 (*
-	This algorithm ensure that variables used in loop sub-functions are captured
-	by value. It transforms the following expression :
+	For some platforms, it will simply mark the variables which are used in closures
+	using the v_capture flag so it can be processed in a more optimized
+
+	For Flash/JS platforms, it will ensure that variables used in loop sub-functions
+	have an unique scope. It transforms the following expression :
 
 	for( x in array )
 		funs.push(function() return x++);
@@ -509,50 +521,43 @@ let rec local_usage f e =
 		var x = [_x];
 		funs.push(function(x) { function() return x[0]++; }(x));
 	}
-
-	This way, each value is captured independantly.
 *)
 
-let block_vars com e =
-
-	let uid = ref 0 in
-	let gen_unique() =
-		incr uid;
-		"$t" ^ string_of_int !uid;
-	in
+let captured_vars com e =
 
 	let t = com.basic in
 
-	let rec mk_init v vt vtmp pos =
-		let at = t.tarray vt in
-		mk (TVars [v,at,Some (mk (TArrayDecl [mk (TLocal vtmp) vt pos]) at pos)]) t.tvoid pos
+	let rec mk_init av v pos =
+		mk (TVars [av,Some (mk (TArrayDecl [mk (TLocal v) v.v_type pos]) av.v_type pos)]) t.tvoid pos
+
+	and mk_var v used =
+		alloc_var v.v_name (PMap.find v.v_id used)
 
 	and wrap used e =
 		match e.eexpr with
 		| TVars vl ->
-			let vl = List.map (fun (v,vt,ve) ->
-				if PMap.mem v used then begin
-					let vt = t.tarray vt in
-					v, vt, Some (mk (TArrayDecl (match ve with None -> [] | Some e -> [wrap used e])) vt e.epos)
-				end else
-					v, vt, (match ve with None -> None | Some e -> Some (wrap used e))
+			let vl = List.map (fun (v,ve) ->
+				if PMap.mem v.v_id used then
+					v, Some (mk (TArrayDecl (match ve with None -> [] | Some e -> [wrap used e])) v.v_type e.epos)
+				else
+					v, (match ve with None -> None | Some e -> Some (wrap used e))
 			) vl in
 			{ e with eexpr = TVars vl }
-		| TLocal v when PMap.mem v used ->
-			mk (TArray ({ e with etype = t.tarray e.etype },mk (TConst (TInt 0l)) t.tint e.epos)) e.etype e.epos
-		| TFor (v,vt,it,expr) when PMap.mem v used ->
-			let vtmp = gen_unique() in
+		| TLocal v when PMap.mem v.v_id used ->
+			mk (TArray ({ e with etype = v.v_type },mk (TConst (TInt 0l)) t.tint e.epos)) e.etype e.epos
+		| TFor (v,it,expr) when PMap.mem v.v_id used ->
+			let vtmp = mk_var v used in
 			let it = wrap used it in
 			let expr = wrap used expr in
-			mk (TFor (vtmp,vt,it,concat (mk_init v vt vtmp e.epos) expr)) e.etype e.epos
+			mk (TFor (vtmp,it,concat (mk_init v vtmp e.epos) expr)) e.etype e.epos
 		| TTry (expr,catchs) ->
-			let catchs = List.map (fun (v,t,e) ->
+			let catchs = List.map (fun (v,e) ->
 				let e = wrap used e in
-				if PMap.mem v used then
-					let vtmp = gen_unique()	in
-					vtmp, t, concat (mk_init v t vtmp e.epos) e
-				else
-					v, t, e
+				try
+					let vtmp = mk_var v used in
+					vtmp, concat (mk_init v vtmp e.epos) e
+				with Not_found ->
+					v, e
 			) catchs in
 			mk (TTry (wrap used expr,catchs)) e.etype e.epos
 		| TMatch (expr,enum,cases,def) ->
@@ -562,13 +567,13 @@ let block_vars com e =
 				let vars = match vars with
 					| None -> None
 					| Some l ->
-						Some (List.map (fun (vo,vt) ->
-							match vo with
-							| Some v when PMap.mem v used ->
-								let vtmp = gen_unique() in
-								e := concat (mk_init v vt vtmp pos) !e;
-								Some vtmp, vt
-							| _ -> vo, vt
+						Some (List.map (fun v ->
+							match v with
+							| Some v when PMap.mem v.v_id used ->
+								let vtmp = mk_var v used in
+								e := concat (mk_init v vtmp pos) !e;
+								Some vtmp
+							| _ -> v
 						) l)
 				in
 				il, vars, !e
@@ -581,45 +586,54 @@ let block_vars com e =
 				function and which are not declared inside it !
 			*)
 			let fused = ref PMap.empty in
-			let tmp_used = ref (PMap.foldi PMap.add used PMap.empty) in
+			let tmp_used = ref used in
 			let rec browse = function
 				| Block f | Loop f | Function f -> f browse
 				| Use v ->
-					(try
-						fused := PMap.add v (PMap.find v !tmp_used) !fused;
-					with Not_found ->
-						())
-				| Declare (v,_) ->
-					tmp_used := PMap.remove v !tmp_used
+					if PMap.mem v.v_id !tmp_used then fused := PMap.add v.v_id v !fused;
+				| Declare v ->
+					tmp_used := PMap.remove v.v_id !tmp_used
 			in
 			local_usage browse e;
-			let vars = PMap.foldi (fun v vt acc -> (v,t.tarray vt) :: acc) !fused [] in
+			let vars = PMap.fold (fun v acc -> v :: acc) !fused [] in
+
 			(* in case the variable has been marked as used in a parallel scope... *)
 			let fexpr = ref (wrap used f.tf_expr) in
-			let fargs = List.map (fun (v,o,vt) ->
-				if PMap.mem v used then
-					let vtmp = gen_unique() in
-					fexpr := concat (mk_init v vt vtmp e.epos) !fexpr;
-					vtmp, o, vt
+			let fargs = List.map (fun (v,o) ->
+				if PMap.mem v.v_id used then
+					let vtmp = mk_var v used in
+					fexpr := concat (mk_init v vtmp e.epos) !fexpr;
+					vtmp, o
 				else
-					v, o, vt
+					v, o
 			) f.tf_args in
 			let e = { e with eexpr = TFunction { f with tf_args = fargs; tf_expr = !fexpr } } in
 			(match com.platform with
 			| Cpp -> e
 			| _ ->
-				let args = List.map (fun (v,t) -> v, None, t) vars in
-				mk (TCall (
-					mk_parent (mk (TFunction {
-						tf_args = args;
-						tf_type = e.etype;
-						tf_expr = mk_block (mk (TReturn (Some e)) e.etype e.epos);
-					}) (TFun (fun_args args,e.etype)) e.epos),
-					List.map (fun (v,t) -> mk (TLocal v) t e.epos) vars)
+				mk (TCall (
+					mk_parent (mk (TFunction {
+						tf_args = List.map (fun v -> v, None) vars;
+						tf_type = e.etype;
+						tf_expr = mk_block (mk (TReturn (Some e)) e.etype e.epos);
+					}) (TFun (List.map (fun v -> v.v_name,false,v.v_type) vars,e.etype)) e.epos),
+					List.map (fun v -> mk (TLocal v) v.v_type e.epos) vars)
 				) e.etype e.epos)
 		| _ ->
 			map_expr (wrap used) e
 
+	and do_wrap used e =
+		if PMap.is_empty used then
+			e
+		else
+			let used = PMap.map (fun v -> 
+				let vt = v.v_type in 
+				v.v_type <- t.tarray vt;
+				v.v_capture <- true;
+				vt
+			) used in
+			wrap used e
+
 	and out_loop e =
 		match e.eexpr with
 		| TFor _ | TWhile _ ->
@@ -642,17 +656,17 @@ let block_vars com e =
 					incr depth;
 					f (collect_vars false);
 					decr depth;
-				| Declare (v,t) ->
-					if in_loop then vars := PMap.add v (!depth,t) !vars;
+				| Declare v ->
+					if in_loop then vars := PMap.add v.v_id !depth !vars;
 				| Use v ->
 					try
-						let d, t = PMap.find v (!vars) in
-						if d <> !depth then used := PMap.add v t !used;
+						let d = PMap.find v.v_id !vars in
+						if d <> !depth then used := PMap.add v.v_id v !used;
 					with Not_found ->
 						()
 			in
 			local_usage (collect_vars false) e;
-			if PMap.is_empty !used then e else wrap !used e
+			do_wrap !used e
 		| _ ->
 			map_expr out_loop e
 	and all_vars e =
@@ -672,21 +686,67 @@ let block_vars com e =
 			incr depth;
 			f collect_vars;
 			decr depth;
-		| Declare (v,t) ->
-			vars := PMap.add v (!depth,t) !vars;
+		| Declare v ->
+			vars := PMap.add v.v_id !depth !vars;
 		| Use v ->
 			try
-				let d, t = PMap.find v (!vars) in
-				if d <> !depth then used := PMap.add v t !used;
+				let d = PMap.find v.v_id !vars in
+				if d <> !depth then used := PMap.add v.v_id v !used;
 			with Not_found -> ()
 		in
-	local_usage collect_vars e;
-	if PMap.is_empty !used then e else wrap !used e
+		local_usage collect_vars e;
+		!used
 	in
 	match com.platform with
-	| Neko | Php | Cross -> e
-	| Cpp -> all_vars e
-	| _ -> out_loop e
+	| Php | Cross -> 
+		e
+	| Neko ->
+		(*
+			this could be optimized to take into account only vars
+			that are actually modified in closures or *after* closure
+			declaration.
+		*)
+		let used = all_vars e in
+		PMap.iter (fun _ v -> v.v_capture <- true) used;
+		e
+	| Cpp ->
+		do_wrap (all_vars e) e
+	| Flash | Flash9 ->
+		let used = all_vars e in
+		PMap.iter (fun _ v -> v.v_capture <- true) used;
+		out_loop e
+	| Js ->
+		out_loop e
+
+(* -------------------------------------------------------------------------- *)
+(* RENAME LOCAL VARS *)
+
+let rename_local_vars com e =
+	let rec loop vars = function
+		| Block f | Loop f | Function f ->
+			f (loop (ref !vars));
+		| Declare v ->
+			(try
+				let vid = PMap.find v.v_name (!vars) in
+				(*
+					block_vars will create some wrapper-functions that are declaring
+					the same variable twice. In that case do not perform a rename since
+					we are sure it's actually the same variable
+				*)
+				if vid = v.v_id then raise Not_found;
+				let count = ref 1 in
+				while PMap.mem (v.v_name ^ string_of_int !count) (!vars) do
+					incr count;
+				done;
+				v.v_name <- v.v_name ^ string_of_int !count;
+			with Not_found ->
+				());
+			vars := PMap.add v.v_name v.v_id !vars;
+		| Use _ ->
+			()
+	in
+	local_usage (loop (ref PMap.empty)) e;
+	e
 
 (* -------------------------------------------------------------------------- *)
 (* CHECK LOCAL VARS INIT *)
@@ -707,14 +767,14 @@ let check_local_vars_init e =
 	let declared = ref [] in
 	let rec loop vars e =
 		match e.eexpr with
-		| TLocal name ->
-			let init = (try PMap.find name !vars with Not_found -> true) in
-			if not init then error ("Local variable " ^ name ^ " used without being initialized") e.epos;
+		| TLocal v ->
+			let init = (try PMap.find v.v_name !vars with Not_found -> true) in
+			if not init then error ("Local variable " ^ v.v_name ^ " used without being initialized") e.epos;
 		| TVars vl ->
-			List.iter (fun (v,_,eo) ->
+			List.iter (fun (v,eo) ->
 				let init = (match eo with None -> false | Some e -> loop vars e; true) in
-				declared := v :: !declared;
-				vars := PMap.add v init !vars
+				declared := v.v_name :: !declared;
+				vars := PMap.add v.v_name init !vars
 			) vl
 		| TBlock el ->
 			let old = !declared in
@@ -723,9 +783,9 @@ let check_local_vars_init e =
 			List.iter (loop vars) el;
 			restore vars old_vars (List.rev !declared);
 			declared := old;
-		| TBinop (OpAssign,{ eexpr = TLocal name },e) ->
+		| TBinop (OpAssign,{ eexpr = TLocal v },e) ->
 			loop vars e;
-			vars := PMap.add name true !vars
+			vars := PMap.add v.v_name true !vars
 		| TIf (e1,e2,eo) ->
 			loop vars e1;
 			let vbase = !vars in
@@ -747,19 +807,19 @@ let check_local_vars_init e =
 			| DoWhile ->
 				loop vars e;
 				loop vars cond)
-		| TFor (v,_,it,e) ->
+		| TFor (v,it,e) ->
 			loop vars it;
 			let old = !vars in
-			vars := PMap.add v true !vars;
+			vars := PMap.add v.v_name true !vars;
 			loop vars e;
 			vars := old;
 		| TFunction f ->
 			let old = !vars in
-			vars := List.fold_left (fun acc (v,_,_) -> PMap.add v true acc) !vars f.tf_args;
+			vars := List.fold_left (fun acc (v,_) -> PMap.add v.v_name true acc) !vars f.tf_args;
 			loop vars f.tf_expr;
 			vars := old;
 		| TTry (e,catches) ->
-			let cvars = List.map (fun (v,_,e) ->
+			let cvars = List.map (fun (v,e) ->
 				let old = !vars in
 				loop vars e;
 				let v = !vars in
@@ -791,7 +851,7 @@ let check_local_vars_init e =
 				vars := old;
 				let tvars = (match vl with
 					| None -> []
-					| Some vl -> List.map (fun (v,_) -> match v with None -> "" | Some v -> vars := PMap.add v true !vars; v) vl
+					| Some vl -> List.map (function None -> "" | Some v -> vars := PMap.add v.v_name true !vars; v.v_name) vl
 				) in
 				loop vars e;
 				restore vars old tvars;
@@ -856,6 +916,9 @@ type stack_context = {
 let stack_context_init com stack_var exc_var pos_var tmp_var use_add p =
 	let t = com.basic in
 	let st = t.tarray t.tstring in
+	let stack_var = alloc_var stack_var st in
+	let exc_var = alloc_var exc_var st in
+	let pos_var = alloc_var pos_var t.tint in
 	let stack_e = mk (TLocal stack_var) st p in
 	let exc_e = mk (TLocal exc_var) st p in
 	let stack_pop = fcall stack_e "pop" [] t.tstring p in
@@ -868,20 +931,21 @@ let stack_context_init com stack_var exc_var pos_var tmp_var use_add p =
 		] t.tvoid p
 	in
 	let stack_return e =
+		let tmp = alloc_var tmp_var e.etype in
 		mk (TBlock [
-			mk (TVars [tmp_var, e.etype, Some e]) t.tvoid e.epos;
+			mk (TVars [tmp, Some e]) t.tvoid e.epos;
 			stack_pop;
-			mk (TReturn (Some (mk (TLocal tmp_var) e.etype e.epos))) e.etype e.epos
+			mk (TReturn (Some (mk (TLocal tmp) e.etype e.epos))) e.etype e.epos
 		]) e.etype e.epos
 	in
 	{
-		stack_var = stack_var;
-		stack_exc_var = exc_var;
-		stack_pos_var = pos_var;
+		stack_var = stack_var.v_name;
+		stack_exc_var = exc_var.v_name;
+		stack_pos_var = pos_var.v_name;
 		stack_pos = p;
 		stack_expr = stack_e;
 		stack_pop = stack_pop;
-		stack_save_pos = mk (TVars [pos_var, t.tint, Some (field stack_e "length" t.tint p)]) t.tvoid p;
+		stack_save_pos = mk (TVars [pos_var, Some (field stack_e "length" t.tint p)]) t.tvoid p;
 		stack_push = stack_push;
 		stack_return = stack_return;
 		stack_restore = [
@@ -911,13 +975,13 @@ let rec stack_block_loop ctx e =
 		ctx.stack_return (stack_block_loop ctx e)
 	| TTry (v,cases) ->
 		let v = stack_block_loop ctx v in
-		let cases = List.map (fun (n,t,e) ->
+		let cases = List.map (fun (v,e) ->
 			let e = stack_block_loop ctx e in
 			let e = (match (mk_block e).eexpr with
 				| TBlock l -> mk (TBlock (ctx.stack_restore @ l)) e.etype e.epos
 				| _ -> assert false
 			) in
-			n , t , e
+			v , e
 		) cases in
 		mk (TTry (v,cases)) e.etype e.epos
 	| _ ->
@@ -971,13 +1035,14 @@ let fix_override com c f fd =
 			let targs, tret = (match follow f2.cf_type with TFun (args,ret) -> args, ret | _ -> assert false) in
 			let changed_args = ref [] in
 			let prefix = "_tmp_" in
-			let nargs = List.map2 (fun ((n,c,t) as cur) (_,_,t2) ->
+			let nargs = List.map2 (fun ((v,c) as cur) (_,_,t2) ->
 				try
-					type_eq EqStrict t t2;
+					type_eq EqStrict v.v_type t2;
 					cur
 				with Unify_error _ ->
-					changed_args := (n,t,t2) :: !changed_args;
-					(prefix ^ n,c,t2)
+					let v2 = alloc_var (prefix ^ v.v_name) t2 in
+					changed_args := (v,v2) :: !changed_args;
+					v2,c
 			) fd.tf_args targs in
 			let fd2 = {
 				tf_args = nargs;
@@ -988,8 +1053,8 @@ let fix_override com c f fd =
 						let e = fd.tf_expr in
 						let el = (match e.eexpr with TBlock el -> el | _ -> [e]) in
 						let p = (match el with [] -> e.epos | e :: _ -> e.epos) in
-						let v = mk (TVars (List.map (fun (n,t,t2) ->
-							(n,t,Some (mk (TCast (mk (TLocal (prefix ^ n)) t2 p,None)) t p))
+						let v = mk (TVars (List.map (fun (v,v2) ->
+							(v,Some (mk (TCast (mk (TLocal v2) v2.v_type p,None)) v.v_type p))
 						) args)) com.basic.tvoid p in
 						{ e with eexpr = TBlock (v :: el) }
 				);
@@ -1017,59 +1082,6 @@ let fix_overrides com t =
 (* -------------------------------------------------------------------------- *)
 (* MISC FEATURES *)
 
-(*
-	Tells if we can find a local var in an expression or inside a sub closure
-*)
-let local_find flag vname e =
-	let rec loop2 e =
-		match e.eexpr with
-		| TFunction f ->
-			if not flag && not (List.exists (fun (a,_,_) -> a = vname) f.tf_args) then loop2 f.tf_expr
-		| TBlock _ ->
-			(try
-				Type.iter loop2 e;
-			with
-				Not_found -> ())
-		| TVars vl ->
-			List.iter (fun (v,t,e) ->
-				(match e with
-				| None -> ()
-				| Some e -> loop2 e);
-				if v = vname then raise Not_found;
-			) vl
-		| TConst TSuper ->
-			if vname = "super" then raise Exit
-		| TLocal v ->
-			if v = vname then raise Exit
-		| _ ->
-			iter loop2 e
-	in
-	let rec loop e =
-		match e.eexpr with
-		| TFunction f ->
-			if not (List.exists (fun (a,_,_) -> a = vname) f.tf_args) then loop2 f.tf_expr
-		| TBlock _ ->
-			(try
-				iter loop e;
-			with
-				Not_found -> ())
-		| TVars vl ->
-			List.iter (fun (v,t,e) ->
-				(match e with
-				| None -> ()
-				| Some e -> loop e);
-				if v = vname then raise Not_found;
-			) vl
-		| _ ->
-			iter loop e
-	in
-	try
-		(if flag then loop2 else loop) e;
-		false
-	with
-		Exit ->
-			true
-
 let rec is_volatile t =
 	match t with
 	| TMono r ->
@@ -1085,7 +1097,8 @@ let rec is_volatile t =
 	| _ ->
 		false
 
-let set_default ctx a c t p =
+let set_default ctx a c p =
+	let t = a.v_type in
 	let ve = mk (TLocal a) t p in
 	let cond =  TBinop (OpEq,ve,mk (TConst TNull) t p) in
 	mk (TIf (mk_parent (mk cond ctx.basic.tbool p), mk (TBinop (OpAssign,ve,mk (TConst c) t p)) t p,None)) ctx.basic.tvoid p
@@ -1182,7 +1195,8 @@ let default_cast ?(vtmp="$t") com e texpr t p =
 		| TEnumDecl e -> TAnon { a_fields = PMap.empty; a_status = ref (EnumStatics e) }
 		| TTypeDecl _ -> assert false
 	in
-	let var = mk (TVars [(vtmp,e.etype,Some e)]) api.tvoid p in
+	let vtmp = alloc_var vtmp e.etype in
+	let var = mk (TVars [vtmp,Some e]) api.tvoid p in
 	let vexpr = mk (TLocal vtmp) e.etype p in
 	let texpr = mk (TTypeExpr texpr) (mk_texpr texpr) p in
 	let std = (try List.find (fun t -> t_path t = ([],"Std")) com.types with Not_found -> assert false) in

+ 1 - 0
doc/CHANGES.txt

@@ -22,6 +22,7 @@
 	neko : changed the result of array-assign expression (was null)
 	flash9 : no longer auto create enums from SWF classes
 		(need explicit "enum" type patch)
+	all : optimized variable tracking/renaming
 
 2011-01-30: 2.07
 	all : fixed completion support with --remap

+ 69 - 92
genas3.ml

@@ -31,12 +31,11 @@ type context = {
 	mutable get_sets : (string * bool,string) Hashtbl.t;
 	mutable curclass : tclass;
 	mutable tabs : string;
-	mutable in_value : string option;
+	mutable in_value : tvar option;
 	mutable in_static : bool;
 	mutable handle_break : bool;
 	mutable imports : (string,string list list) Hashtbl.t;
-	mutable locals : (string,string) PMap.t;
-	mutable inv_locals : (string,string) PMap.t;
+	mutable gen_uid : int;
 	mutable local_types : t list;
 	mutable constructor_block : bool;
 }
@@ -118,8 +117,7 @@ let init infos path =
 		handle_break = false;
 		imports = imports;
 		curclass = null_class;
-		locals = PMap.empty;
-		inv_locals = PMap.empty;
+		gen_uid = 0;
 		local_types = [];
 		get_sets = Hashtbl.create 0;
 		constructor_block = false;
@@ -137,21 +135,12 @@ let close ctx =
 	close_out ctx.ch
 
 let save_locals ctx =
-	let old = ctx.locals in
-	(fun() -> ctx.locals <- old)
+	let old = ctx.gen_uid in
+	(fun() -> ctx.gen_uid <- old)
 
-let define_local ctx l =
-	let rec loop n =
-		let name = (if n = 1 then s_ident l else l ^ string_of_int n) in
-		if PMap.mem name ctx.inv_locals then
-			loop (n+1)
-		else begin
-			ctx.locals <- PMap.add l name ctx.locals;
-			ctx.inv_locals <- PMap.add name l ctx.inv_locals;
-			name
-		end
-	in
-	loop 1
+let gen_local ctx l =
+	ctx.gen_uid <- ctx.gen_uid + 1;
+	if ctx.gen_uid = 1 then l else l ^ string_of_int ctx.gen_uid
 
 let spr ctx s = Buffer.add_string ctx.buf s
 let print ctx = Printf.kprintf (fun s -> Buffer.add_string ctx.buf s)
@@ -200,7 +189,7 @@ let rec type_str ctx t p =
 		if e.e_extern then (match e.e_path with
 			| [], "Void" -> "void"
 			| [], "Bool" -> "Boolean"
-			| _ -> 
+			| _ ->
 				let rec loop = function
 					| [] -> "Object"
 					| (":fakeEnum",[Ast.EConst (Ast.Type n),_],_) :: _ ->
@@ -215,7 +204,7 @@ let rec type_str ctx t p =
 			s_path ctx true e.e_path p
 	| TInst ({ cl_path = ["flash"],"Vector" },[pt]) ->
 		"Vector.<" ^ type_str ctx pt p ^ ">"
-	| TInst (c,_) ->		
+	| TInst (c,_) ->
 		(match c.cl_kind with
 		| KNormal | KGeneric | KGenericInstance _ -> s_path ctx false c.cl_path p
 		| KTypeParameter | KExtension _ | KConstant _  -> "*")
@@ -289,8 +278,7 @@ let gen_constant ctx p = function
 
 let gen_function_header ctx name f params p =
 	let old = ctx.in_value in
-	let old_l = ctx.locals in
-	let old_li = ctx.inv_locals in
+	let locals = save_locals ctx in
 	let old_t = ctx.local_types in
 	ctx.in_value <- None;
 	ctx.local_types <- List.map snd params @ ctx.local_types;
@@ -303,10 +291,9 @@ let gen_function_header ctx name f params p =
 		in
 		" " ^ loop meta
 	);
-	concat ctx "," (fun (arg,c,t) ->
-		let arg = define_local ctx arg in
-		let tstr = type_str ctx t p in
-		print ctx "%s : %s" arg tstr;
+	concat ctx "," (fun (v,c) ->
+		let tstr = type_str ctx v.v_type p in
+		print ctx "%s : %s" (s_ident v.v_name) tstr;
 		match c with
 		| None ->
 			if ctx.constructor_block then print ctx " = %s" (default_value tstr);
@@ -317,8 +304,7 @@ let gen_function_header ctx name f params p =
 	print ctx ") : %s " (type_str ctx f.tf_type p);
 	(fun () ->
 		ctx.in_value <- old;
-		ctx.locals <- old_l;
-		ctx.inv_locals <- old_li;
+		locals();
 		ctx.local_types <- old_t;
 	)
 
@@ -331,71 +317,71 @@ let rec gen_call ctx e el r =
 		spr ctx "(";
 		concat ctx "," (gen_value ctx) el;
 		spr ctx ")";
-	| TLocal "__is__" , [e1;e2] ->
+	| TLocal { v_name = "__is__" } , [e1;e2] ->
 		gen_value ctx e1;
 		spr ctx " is ";
 		gen_value ctx e2;
-	| TLocal "__as__" , [e1;e2] ->
+	| TLocal { v_name = "__as__" }, [e1;e2] ->
 		gen_value ctx e1;
 		spr ctx " as ";
 		gen_value ctx e2;
-	| TLocal "__int__" , [e] ->
+	| TLocal { v_name = "__int__" }, [e] ->
 		spr ctx "int(";
 		gen_value ctx e;
 		spr ctx ")";
-	| TLocal "__float__" , [e] ->
+	| TLocal { v_name = "__float__" }, [e] ->
 		spr ctx "Number(";
 		gen_value ctx e;
 		spr ctx ")";
-	| TLocal "__typeof__", [e] ->
+	| TLocal { v_name = "__typeof__" }, [e] ->
 		spr ctx "typeof ";
 		gen_value ctx e;
-	| TLocal "__keys__", [e] ->
+	| TLocal { v_name = "__keys__" }, [e] ->
 		let ret = (match ctx.in_value with None -> assert false | Some r -> r) in
-		print ctx "%s = new Array()" ret;
+		print ctx "%s = new Array()" ret.v_name;
 		newline ctx;
 		let b = save_locals ctx in
-		let tmp = define_local ctx "$k" in
+		let tmp = gen_local ctx "$k" in
 		print ctx "for(var %s : String in " tmp;
 		gen_value ctx e;
-		print ctx ") %s.push(%s)" ret tmp;
+		print ctx ") %s.push(%s)" ret.v_name tmp;
 		b();
-	| TLocal "__hkeys__", [e] ->
+	| TLocal { v_name = "__hkeys__" }, [e] ->
 		let ret = (match ctx.in_value with None -> assert false | Some r -> r) in
-		print ctx "%s = new Array()" ret;
+		print ctx "%s = new Array()" ret.v_name;
 		newline ctx;
 		let b = save_locals ctx in
-		let tmp = define_local ctx "$k" in
+		let tmp = gen_local ctx "$k" in
 		print ctx "for(var %s : String in " tmp;
 		gen_value ctx e;
-		print ctx ") %s.push(%s.substr(1))" ret tmp;
+		print ctx ") %s.push(%s.substr(1))" ret.v_name tmp;
 		b();
-	| TLocal "__foreach__", [e] ->
+	| TLocal { v_name = "__foreach__" }, [e] ->
 		let ret = (match ctx.in_value with None -> assert false | Some r -> r) in
-		print ctx "%s = new Array()" ret;
+		print ctx "%s = new Array()" ret.v_name;
 		newline ctx;
 		let b = save_locals ctx in
-		let tmp = define_local ctx "$k" in
+		let tmp = gen_local ctx "$k" in
 		print ctx "for each(var %s : * in " tmp;
 		gen_value ctx e;
-		print ctx ") %s.push(%s)" ret tmp;
+		print ctx ") %s.push(%s)" ret.v_name tmp;
 		b();
-	| TLocal "__new__", e :: args ->
+	| TLocal { v_name = "__new__" }, e :: args ->
 		spr ctx "new ";
 		gen_value ctx e;
 		spr ctx "(";
 		concat ctx "," (gen_value ctx) args;
 		spr ctx ")";
-	| TLocal "__delete__", [e;f] ->
+	| TLocal { v_name = "__delete__" }, [e;f] ->
 		spr ctx "delete(";
 		gen_value ctx e;
 		spr ctx "[";
 		gen_value ctx f;
 		spr ctx "]";
 		spr ctx ")";
-	| TLocal "__unprotect__", [e] ->
+	| TLocal { v_name = "__unprotect__" }, [e] ->
 		gen_value ctx e
-	| TLocal "__vector__", [e] ->
+	| TLocal { v_name = "__vector__" }, [e] ->
 		spr ctx (type_str ctx r e.epos);
 		spr ctx "(";
 		gen_value ctx e;
@@ -472,11 +458,11 @@ and gen_expr ctx e =
 	match e.eexpr with
 	| TConst c ->
 		gen_constant ctx e.epos c
-	| TLocal s ->
-		spr ctx (try PMap.find s ctx.locals with Not_found -> error ("Unknown local " ^ s) e.epos)
+	| TLocal v ->
+		spr ctx (s_ident v.v_name)
 	| TEnumField (en,s) ->
 		print ctx "%s.%s" (s_path ctx true en.e_path e.epos) (s_ident s)
-	| TArray ({ eexpr = TLocal "__global__" },{ eexpr = TConst (TString s) }) ->
+	| TArray ({ eexpr = TLocal { v_name = "__global__" } },{ eexpr = TConst (TString s) }) ->
 		let path = Ast.parse_path s in
 		spr ctx (s_path ctx false path e.epos)
 	| TArray (e1,e2) ->
@@ -493,8 +479,6 @@ and gen_expr ctx e =
 		gen_value_op ctx e1;
 		print ctx " %s " (Ast.s_binop op);
 		gen_value_op ctx e2;
-	| TField ({ eexpr = TTypeExpr t },s) when t_path t = ctx.curclass.cl_path && not (PMap.mem s ctx.locals) ->
-		print ctx "%s" (s_ident s)
 	| TField (e,s) | TClosure (e,s) ->
    		gen_value ctx e;
 		gen_field_access ctx e.etype s
@@ -548,7 +532,7 @@ and gen_expr ctx e =
 		let h = gen_function_header ctx None f [] e.epos in
 		let old = ctx.in_static in
 		ctx.in_static <- true;
-		gen_expr ctx (mk_block f.tf_expr);
+		gen_expr ctx f.tf_expr;
 		ctx.in_static <- old;
 		h();
 	| TCall (v,el) ->
@@ -564,10 +548,9 @@ and gen_expr ctx e =
 		()
 	| TVars vl ->
 		spr ctx "var ";
-		concat ctx ", " (fun (n,t,v) ->
-			let n = define_local ctx n in
-			print ctx "%s : %s" n (type_str ctx t e.epos);
-			match v with
+		concat ctx ", " (fun (v,eo) ->
+			print ctx "%s : %s" (s_ident v.v_name) (type_str ctx v.v_type e.epos);
+			match eo with
 			| None -> ()
 			| Some e ->
 				spr ctx " = ";
@@ -614,15 +597,14 @@ and gen_expr ctx e =
 		spr ctx "{ ";
 		concat ctx ", " (fun (f,e) -> print ctx "%s : " (s_ident f); gen_value ctx e) fields;
 		spr ctx "}"
-	| TFor (v,t,it,e) ->
+	| TFor (v,it,e) ->
 		let handle_break = handle_break ctx e in
 		let b = save_locals ctx in
-		let tmp = define_local ctx "$it" in
+		let tmp = gen_local ctx "$it" in
 		print ctx "{ var %s : * = " tmp;
 		gen_value ctx it;
 		newline ctx;
-		let v = define_local ctx v in
-		print ctx "while( %s.hasNext() ) { var %s : %s = %s.next()" tmp v (type_str ctx t e.epos) tmp;
+		print ctx "while( %s.hasNext() ) { var %s : %s = %s.next()" tmp (s_ident v.v_name) (type_str ctx v.v_type e.epos) tmp;
 		newline ctx;
 		gen_expr ctx e;
 		newline ctx;
@@ -631,21 +613,18 @@ and gen_expr ctx e =
 		handle_break();
 	| TTry (e,catchs) ->
 		spr ctx "try ";
-		gen_expr ctx (mk_block e);
-		List.iter (fun (v,t,e) ->
+		gen_expr ctx e;
+		List.iter (fun (v,e) ->
 			newline ctx;
-			let b = save_locals ctx in
-			let v = define_local ctx v in
-			print ctx "catch( %s : %s )" v (type_str ctx t e.epos);
-			gen_expr ctx (mk_block e);
-			b();
+			print ctx "catch( %s : %s )" (s_ident v.v_name) (type_str ctx v.v_type e.epos);
+			gen_expr ctx e;
 		) catchs;
 	| TMatch (e,_,cases,def) ->
 		print ctx "{";
 		let bend = open_block ctx in
 		newline ctx;
 		let b = save_locals ctx in
-		let tmp = define_local ctx "$e" in
+		let tmp = gen_local ctx "$e" in
 		print ctx "var %s : enum = " tmp;
 		gen_value ctx e;
 		newline ctx;
@@ -661,17 +640,16 @@ and gen_expr ctx e =
 			| None | Some [] -> ()
 			| Some l ->
 				let n = ref (-1) in
-				let l = List.fold_left (fun acc (v,t) -> incr n; match v with None -> acc | Some v -> (v,t,!n) :: acc) [] l in
+				let l = List.fold_left (fun acc v -> incr n; match v with None -> acc | Some v -> (v,!n) :: acc) [] l in
 				match l with
 				| [] -> ()
 				| l ->
 					spr ctx "var ";
-					concat ctx ", " (fun (v,t,n) ->
-						let v = define_local ctx v in
-						print ctx "%s : %s = %s.params[%d]" v (type_str ctx t e.epos) tmp n;
+					concat ctx ", " (fun (v,n) ->
+						print ctx "%s : %s = %s.params[%d]" (s_ident v.v_name) (type_str ctx v.v_type e.epos) tmp n;
 					) l;
 					newline ctx);
-			gen_expr ctx (mk_block e);
+			gen_expr ctx e;
 			print ctx "break";
 			newline ctx;
 			b()
@@ -680,7 +658,7 @@ and gen_expr ctx e =
 		| None -> ()
 		| Some e ->
 			spr ctx "default:";
-			gen_expr ctx (mk_block e);
+			gen_expr ctx e;
 			print ctx "break";
 			newline ctx;
 		);
@@ -700,7 +678,7 @@ and gen_expr ctx e =
 				gen_value ctx e;
 				spr ctx ":";
 			) el;
-			gen_expr ctx (mk_block e2);
+			gen_expr ctx e2;
 			print ctx "break";
 			newline ctx;
 		) cases;
@@ -708,7 +686,7 @@ and gen_expr ctx e =
 		| None -> ()
 		| Some e ->
 			spr ctx "default:";
-			gen_expr ctx (mk_block e);
+			gen_expr ctx e;
 			print ctx "break";
 			newline ctx;
 		);
@@ -723,7 +701,7 @@ and gen_expr ctx e =
 and gen_value ctx e =
 	let assign e =
 		mk (TBinop (Ast.OpAssign,
-			mk (TLocal (match ctx.in_value with None -> assert false | Some v -> "$r")) t_dynamic e.epos,
+			mk (TLocal (match ctx.in_value with None -> assert false | Some r -> r)) t_dynamic e.epos,
 			e
 		)) e.etype e.epos
 	in
@@ -731,8 +709,8 @@ and gen_value ctx e =
 		let old = ctx.in_value in
 		let t = type_str ctx e.etype e.epos in
 		let locs = save_locals ctx in
-		let tmp = define_local ctx "$r" in
-		ctx.in_value <- Some tmp;
+		let r = alloc_var (gen_local ctx "$r") e.etype in
+		ctx.in_value <- Some r;
 		if ctx.in_static then
 			print ctx "function() : %s " t
 		else
@@ -741,7 +719,7 @@ and gen_value ctx e =
 			spr ctx "{";
 			let b = open_block ctx in
 			newline ctx;
-			print ctx "var %s : %s" tmp t;
+			print ctx "var %s : %s" r.v_name t;
 			newline ctx;
 			b
 		end else
@@ -750,7 +728,7 @@ and gen_value ctx e =
 		(fun() ->
 			if block then begin
 				newline ctx;
-				print ctx "return %s" tmp;
+				print ctx "return %s" r.v_name;
 				b();
 				newline ctx;
 				spr ctx "}";
@@ -764,7 +742,7 @@ and gen_value ctx e =
 		)
 	in
 	match e.eexpr with
-	| TCall ({ eexpr = TLocal "__keys__" },_) | TCall ({ eexpr = TLocal "__hkeys__" },_) ->
+	| TCall ({ eexpr = TLocal { v_name = "__keys__" } },_) | TCall ({ eexpr = TLocal { v_name = "__hkeys__" } },_) ->
 		let v = value true in
 		gen_expr ctx e;
 		v()
@@ -841,15 +819,14 @@ and gen_value ctx e =
 	| TTry (b,catchs) ->
 		let v = value true in
 		gen_expr ctx (mk (TTry (assign b,
-			List.map (fun (v,t,e) -> v, t , assign e) catchs
+			List.map (fun (v,e) -> v, assign e) catchs
 		)) e.etype e.epos);
 		v()
 
 let generate_field ctx static f =
 	newline ctx;
 	ctx.in_static <- static;
-	ctx.locals <- PMap.empty;
-	ctx.inv_locals <- PMap.empty;
+	ctx.gen_uid <- 0;
 	List.iter (fun(m,pl,_) ->
 		match m,pl with
 		| ":meta", [Ast.ECall ((Ast.EConst (Ast.Ident n | Ast.Type n),_),args),_] ->
@@ -890,7 +867,7 @@ let generate_field ctx static f =
 		in
 		if not static then loop ctx.curclass;
 		let h = gen_function_header ctx (Some (s_ident f.cf_name, f.cf_meta)) fd f.cf_params p in
-		gen_expr ctx (mk_block fd.tf_expr);
+		gen_expr ctx fd.tf_expr;
 		h();
 		newline ctx
 	| _ ->
@@ -905,7 +882,7 @@ let generate_field ctx static f =
 					if o then print ctx " = %s" (default_value tstr);
 				) args;
 				print ctx ") : %s " (type_str ctx r p);
-			| _ when is_getset -> 
+			| _ when is_getset ->
 				let t = type_str ctx f.cf_type p in
 				let id = s_ident f.cf_name in
 				(match f.cf_kind with
@@ -1070,7 +1047,7 @@ let generate_enum ctx e =
 		print ctx "public static var __meta__ : * = ";
 		gen_expr ctx e;
 		newline ctx);
-	print ctx "public static var __constructs__ : Array = [%s];" (String.concat "," (List.map (fun s -> "\"" ^ Ast.s_escape s ^ "\"") e.e_names));	
+	print ctx "public static var __constructs__ : Array = [%s];" (String.concat "," (List.map (fun s -> "\"" ^ Ast.s_escape s ^ "\"") e.e_names));
 	cl();
 	newline ctx;
 	print ctx "}";

+ 81 - 81
gencpp.ml

@@ -113,7 +113,7 @@ let rec make_class_directories base dir_list =
            ( ((String.length path)=2) && ((String.sub path 1 1)=":") ) ) ) then
 		         if not (Sys.file_exists path) then
 			          Unix.mkdir path 0o755;
-		make_class_directories (if (path="") then "/" else path) remaining 
+		make_class_directories (if (path="") then "/" else path) remaining
 	);;
 
 
@@ -161,7 +161,7 @@ type context =
 	mutable ctx_class_member_types : (string,string) Hashtbl.t;
 }
 
-let new_context common_ctx writer debug = 
+let new_context common_ctx writer debug =
 	{
 	ctx_common = common_ctx;
 	ctx_writer = writer;
@@ -349,7 +349,7 @@ let rec class_string klass suffix params =
 				| TInst ({ cl_path = [],"Float" },_)
 				| TEnum ({ e_path = [],"Bool" },_) -> "Dynamic"
 				| _ -> "/*NULL*/" ^ (type_string t) )
-			| _ -> assert false); 
+			| _ -> assert false);
 	(* Normal class *)
 	| _ -> "::" ^ (join_class_path klass.cl_path "::") ^ suffix
 	)
@@ -394,12 +394,12 @@ and type_string_suff suffix haxe_type =
 	| TDynamic haxe_type -> "Dynamic" ^ suffix
 	| TLazy func -> type_string_suff suffix ((!func)())
 	)
-and type_string haxe_type = 
+and type_string haxe_type =
 	type_string_suff "" haxe_type;;
 
 let is_array haxe_type =
 	match follow haxe_type with
-	| TInst (klass,params) -> 
+	| TInst (klass,params) ->
 		(match klass.cl_path with
 		| [] , "Array" -> not (is_type_param (List.hd params))
 		| _ -> false )
@@ -409,7 +409,7 @@ let is_array haxe_type =
 		| _ -> false )
 	| _ -> false
 	;;
- 
+
 
 
 (* Get the type and output it to the stream *)
@@ -438,7 +438,7 @@ let is_interface obj = is_interface_type obj.etype;;
 let is_function_member expression =
 	match (follow expression.etype) with | TFun (_,_) -> true | _ -> false;;
 
-let is_internal_member member = 
+let is_internal_member member =
    match member with
 	| "__Field" | "__IField" | "__Run" | "__Is" | "__GetClass" | "__GetType" | "__ToString"
 	| "__s" | "__GetPtr" | "__SetField" | "__length" | "__IsArray" | "__SetThis" | "__Internal"
@@ -447,7 +447,7 @@ let is_internal_member member =
    | _ -> false;;
 
 
-let is_dynamic_accessor name acc field class_def = 
+let is_dynamic_accessor name acc field class_def =
  ( ( acc ^ "_" ^ field.cf_name) = name ) &&
   ( not (List.exists (fun f -> f.cf_name=name) class_def.cl_ordered_fields) )
 ;;
@@ -469,7 +469,7 @@ let gen_arg name default_val arg_type prefix =
 	(fst pair) ^ " " ^ (snd pair);;
 
 let rec gen_arg_list arg_list prefix =
-  String.concat "," (List.map (fun (name,o,arg_type) -> (gen_arg name o arg_type prefix) ) arg_list)
+  String.concat "," (List.map (fun (v,o) -> (gen_arg v.v_name o v.v_type prefix) ) arg_list)
 
 
 let rec gen_tfun_arg_list arg_list =
@@ -526,7 +526,7 @@ let special_to_hex s =
 	Buffer.contents b;;
 
 
-let has_utf8_chars s = 
+let has_utf8_chars s =
 	let result = ref false in
 	for i = 0 to String.length s - 1 do
 		result := !result || ( Char.code (String.unsafe_get s i) > 127 )
@@ -537,7 +537,7 @@ let escape_null s =
 	let b = Buffer.create 0 in
    String.iter (fun ch -> if (ch=='\x00') then Buffer.add_string b "\\000" else Buffer.add_char b ch ) s;
    Buffer.contents b;;
- 
+
 let str s =
 	let escaped = Ast.s_escape s in
       let null_escaped = escape_null escaped in
@@ -555,7 +555,7 @@ let str s =
 
 (* When we are in a "real" object, we refer to ourselves as "this", but
 	if we are in a local class that is used to generate return values,
-	we use the fake "__this" pointer. 
+	we use the fake "__this" pointer.
 	If we are in an "Anon" object, then the "this" refers to the anon object (eg List iterator) *)
 let clear_real_this_ptr ctx dynamic_this =
 	let old_flag = ctx.ctx_real_this_ptr in
@@ -613,7 +613,7 @@ let rec iter_retval f retval e =
 	| TWhile (e1,e2,_) ->
 		f true e1;
 		f false e2;
-	| TFor (_,_,e1,e2) ->
+	| TFor (_,e1,e2) ->
 		f true e1;
 		f false e2;
 	| TThrow e
@@ -640,7 +640,7 @@ let rec iter_retval f retval e =
 		f true e;
 		List.iter (f true) el
 	| TVars vl ->
-		List.iter (fun (_,_,e) -> match e with None -> () | Some e -> f true e) vl
+		List.iter (fun (_,e) -> match e with None -> () | Some e -> f true e) vl
 	| TFunction fu ->
 		f false fu.tf_expr
 	| TIf (e,e1,e2) ->
@@ -657,7 +657,7 @@ let rec iter_retval f retval e =
 		(match def with None -> () | Some e -> f false e)
 	| TTry (e,catches) ->
 		f retval e;
-		List.iter (fun (_,_,e) -> f false e) catches
+		List.iter (fun (_,e) -> f false e) catches
 	| TReturn eo ->
 		(match eo with None -> () | Some e -> f true e)
 	| TCast (e,_) ->
@@ -677,7 +677,7 @@ let only_int_cases cases =
 	match cases with
 	| [] -> false
 	| _ ->
-	not (List.exists (fun (cases,expression) -> 
+	not (List.exists (fun (cases,expression) ->
 			List.exists (fun case -> match case.eexpr with TConst (TInt _) -> false | _ -> true ) cases
 				) cases );;
 
@@ -689,7 +689,7 @@ let contains_break expression =
 	let rec check_all expression =
 		Type.iter (fun expr -> match expr.eexpr with
 			| TBreak -> raise BreakFound
-			| TFor (_,_,_,_)
+			| TFor _
 			| TFunction _
 			| TWhile (_,_,_) -> ()
 			| _ -> check_all expr;
@@ -710,7 +710,7 @@ let tmatch_params_to_args params =
 	| Some l ->
 		let n = ref (-1) in
 		List.fold_left
-			(fun acc (v,t) -> incr n; match v with None -> acc | Some v -> (v,t,!n) :: acc) [] l)
+			(fun acc v -> incr n; match v with None -> acc | Some v -> (v.v_name,v.v_type,!n) :: acc) [] l)
 
 exception AlreadySafe;;
 exception PossibleRecursion;;
@@ -743,30 +743,30 @@ let find_undeclared_variables_ctx ctx undeclared declarations this_suffix allow_
 	let rec find_undeclared_variables undeclared declarations this_suffix allow_this expression =
 		match expression.eexpr with
 		| TVars var_list ->
-			List.iter (fun (var_name, var_type, optional_init) ->
-				Hashtbl.add declarations (keyword_remap var_name) ();
+			List.iter (fun (tvar, optional_init) ->
+				Hashtbl.add declarations (keyword_remap tvar.v_name) ();
 				if (ctx.ctx_debug) then
-					output ("/* found var " ^ var_name ^ "*/ ");
+					output ("/* found var " ^ tvar.v_name ^ "*/ ");
 				match optional_init with
 				| Some expression -> find_undeclared_variables undeclared declarations this_suffix allow_this expression
 				| _ -> ()
 				) var_list
-		| TFunction func -> List.iter ( fun (arg_name, opt_val, arg_type) ->
+		| TFunction func -> List.iter ( fun (tvar, opt_val) ->
 				if (ctx.ctx_debug) then
-					output ("/* found arg " ^ arg_name ^ " = " ^ (type_string arg_type) ^ " */ ");
-				Hashtbl.add declarations (keyword_remap arg_name) () ) func.tf_args;
+					output ("/* found arg " ^ tvar.v_name ^ " = " ^ (type_string tvar.v_type) ^ " */ ");
+				Hashtbl.add declarations (keyword_remap tvar.v_name) () ) func.tf_args;
 				find_undeclared_variables undeclared declarations this_suffix false func.tf_expr
 		| TTry (try_block,catches) ->
 			find_undeclared_variables undeclared declarations this_suffix allow_this try_block;
-			List.iter (fun (name,t,catch_expt) ->
+			List.iter (fun (tvar,catch_expt) ->
 				let old_decs = Hashtbl.copy declarations in
-				Hashtbl.add declarations (keyword_remap name) ();
+				Hashtbl.add declarations (keyword_remap tvar.v_name) ();
 				find_undeclared_variables undeclared declarations this_suffix allow_this catch_expt;
 				Hashtbl.clear declarations;
 				Hashtbl.iter ( Hashtbl.add declarations ) old_decs
 				) catches;
-		| TLocal local_name ->
-         let name = keyword_remap local_name in
+		| TLocal tvar ->
+         let name = keyword_remap tvar.v_name in
 			if  not (Hashtbl.mem declarations name) then
 				Hashtbl.replace undeclared name (type_string expression.etype)
 		| TMatch (condition, enum, cases, default) ->
@@ -775,8 +775,8 @@ let find_undeclared_variables_ctx ctx undeclared declarations this_suffix allow_
 				let old_decs = Hashtbl.copy declarations in
 				(match params with
 				| None -> ()
-				| Some l -> List.iter (fun (opt_name,t) ->
-					match opt_name with | Some name -> Hashtbl.add declarations (keyword_remap name) () | _ -> ()  )
+				| Some l -> List.iter (fun (opt_var) ->
+					match opt_var with | Some v -> Hashtbl.add declarations (keyword_remap v.v_name) () | _ -> ()  )
 					l  );
 				find_undeclared_variables undeclared declarations this_suffix allow_this expression;
 				Hashtbl.clear declarations;
@@ -786,9 +786,9 @@ let find_undeclared_variables_ctx ctx undeclared declarations this_suffix allow_
 			| Some expr ->
 				find_undeclared_variables undeclared declarations this_suffix allow_this expr;
 			);
-		| TFor (var_name, var_type, init, loop) ->
+		| TFor (tvar, init, loop) ->
 			let old_decs = Hashtbl.copy declarations in
-			Hashtbl.add declarations (keyword_remap var_name) ();
+			Hashtbl.add declarations (keyword_remap tvar.v_name) ();
 			find_undeclared_variables undeclared declarations this_suffix allow_this init;
 			find_undeclared_variables undeclared declarations this_suffix allow_this loop;
 			Hashtbl.clear declarations;
@@ -846,7 +846,7 @@ let rec is_dynamic_in_cpp ctx expr =
                | _ -> ctx.ctx_dbgout "/* not TFun */";  true
            );
 		| TParenthesis(expr) -> is_dynamic_in_cpp ctx expr
-		| TLocal name when name = "__global__" -> false
+		| TLocal { v_name = "__global__" } -> false
 		| TConst TNull -> true
 		| _ -> ctx.ctx_dbgout "/* other */";  false (* others ? *) )
 		in
@@ -924,10 +924,10 @@ let rec define_local_function_ctx ctx func_name func_def =
 		let declarations = Hashtbl.create 0 in
 		let undeclared = Hashtbl.create 0 in
 		(* Add args as defined variables *)
-		List.iter ( fun (arg_name, opt_val, arg_type) ->
+		List.iter ( fun (arg_var, opt_val) ->
 			if (ctx.ctx_debug) then
-				output ("/* found arg " ^ arg_name ^ " = " ^ (type_string arg_type) ^" */ ");
-			Hashtbl.add declarations (keyword_remap arg_name) () ) func_def.tf_args;
+				output ("/* found arg " ^ arg_var.v_name ^ " = " ^ (type_string arg_var.v_type) ^" */ ");
+			Hashtbl.add declarations (keyword_remap arg_var.v_name) () ) func_def.tf_args;
 		find_undeclared_variables_ctx ctx undeclared declarations "" true func_def.tf_expr;
 
 		let has_this = Hashtbl.mem undeclared "this" in
@@ -940,7 +940,7 @@ let rec define_local_function_ctx ctx func_name func_def =
 
 		(* actual function, called "run" *)
 		let args_and_types = List.map
-				(fun (name,_,arg_type) -> (type_string arg_type) ^ " " ^ name ) func_def.tf_args in
+				(fun (v,_) -> (type_string v.v_type) ^ " " ^ v.v_name ) func_def.tf_args in
 		let block = is_block func_def.tf_expr in
 		let func_type = type_string func_def.tf_type in
 		output_i (func_type ^ " run(" ^ (String.concat "," args_and_types) ^ ")");
@@ -1199,8 +1199,8 @@ and gen_expression ctx retval expression =
 	| TCall (func, arg_list) ->
       let rec is_variable e = match e.eexpr with
          | TField _ -> false
-	      | TEnumField _ -> false
-		   | TLocal name when name = "__global__" -> false
+	     | TEnumField _ -> false
+		 | TLocal { v_name = "__global__" } -> false
          | TParenthesis p -> is_variable p
          | _ -> true
       in
@@ -1277,7 +1277,7 @@ and gen_expression ctx retval expression =
 		)
 
 
-	| TLocal local_name -> output (keyword_remap local_name);
+	| TLocal v -> output (keyword_remap v.v_name);
 	| TEnumField (enum, name) ->
 			output ("::" ^ (join_class_path enum.e_path "::") ^ "_obj::" ^ name)
 	| TArray (array_expr,_) when (is_null array_expr) -> output "Dynamic()"
@@ -1323,13 +1323,13 @@ and gen_expression ctx retval expression =
 			else
 				output (class_name ^ "_obj::" ^ remap_name);
 		(* Special internal access *)
-		| TLocal name when name = "__global__" ->
+		| TLocal { v_name = "__global__" } ->
 			output ("::" ^ member )
 		| TConst TSuper -> output (if ctx.ctx_real_this_ptr then "this" else "__this");
 						output ("->super::" ^ remap_name)
 		| TConst TThis when ctx.ctx_real_this_ptr -> output ( "this->" ^ remap_name )
 		| TConst TNull -> output "null()"
-		| _ -> 
+		| _ ->
 			gen_expression ctx true field_object;
          ctx.ctx_dbgout "/* TField */";
          if (is_internal_member member) then begin
@@ -1422,15 +1422,15 @@ and gen_expression ctx retval expression =
 
 	| TVars var_list ->
 		let count = ref (List.length var_list) in
-		List.iter (fun (var_name, var_type, optional_init) ->
+		List.iter (fun (tvar, optional_init) ->
 			if (retval && !count==1) then
 				(match optional_init with
 				| None -> output "null()"
 				| Some expression -> gen_expression ctx true expression )
 			else begin
-            let type_name = (type_string var_type) in
+            let type_name = (type_string tvar.v_type) in
 				output (if type_name="Void" then "Dynamic" else type_name );
-				output (" " ^ (keyword_remap var_name) );
+				output (" " ^ (keyword_remap tvar.v_name) );
 				(match optional_init with
 				| None -> ()
 				| Some expression -> output " = "; gen_expression ctx true expression);
@@ -1438,13 +1438,13 @@ and gen_expression ctx retval expression =
 				if (!count > 0) then begin output ";\n"; output_i "" end
 			end
 		) var_list
-	| TFor (var_name, var_type, init, loop) ->
-		output ("for(::cpp::FastIterator_obj< " ^  (type_string var_type) ^
-             " > *__it = ::cpp::CreateFastIterator< "^(type_string var_type) ^ " >(");
+	| TFor (tvar, init, loop) ->
+		output ("for(::cpp::FastIterator_obj< " ^  (type_string tvar.v_type) ^
+             " > *__it = ::cpp::CreateFastIterator< "^(type_string tvar.v_type) ^ " >(");
 		gen_expression ctx true init;
 		output (");  __it->hasNext(); )");
 		ctx.ctx_writer#begin_block;
-		output_i ( (type_string var_type) ^ " " ^ (keyword_remap var_name) ^ " = __it->next();\n" );
+		output_i ( (type_string tvar.v_type) ^ " " ^ (keyword_remap tvar.v_name) ^ " = __it->next();\n" );
 		output_i "";
 		gen_expression ctx false loop;
 		output ";\n";
@@ -1452,7 +1452,7 @@ and gen_expression ctx retval expression =
 		ctx.ctx_writer#end_block;
 	| TIf (condition, if_expr, optional_else_expr)  ->
 		(match optional_else_expr with
-		| Some else_expr -> 
+		| Some else_expr ->
 			if (retval) then begin
             output "(  (";
 				gen_expression ctx true condition;
@@ -1564,14 +1564,14 @@ and gen_expression ctx retval expression =
 	output ( (type_string condition.etype) ^ " " ^ tmp_var ^ " = " );
 	gen_expression ctx true condition;
 	output ";\n";
- 
+
         let use_if_statements = contains_break expression in
 
         let dump_condition = if (use_if_statements) then begin
 		let tmp_name = get_switch_var ctx in
 		output_i ( "int " ^ tmp_name ^ " = (" ^ tmp_var ^ ")->GetIndex();" );
                 let elif = ref "if" in
-                ( fun case_ids -> 
+                ( fun case_ids ->
 			output (!elif ^ " (" );
 			elif := "else if";
 			output (String.concat "||"
@@ -1623,15 +1623,15 @@ and gen_expression ctx retval expression =
 			ctx.ctx_writer#begin_block;
 			let seen_dynamic = ref false in
 			let else_str = ref "" in
-			List.iter (fun (name,t,expression) ->
-				let type_name = type_string t in
+			List.iter (fun (v,expression) ->
+				let type_name = type_string v.v_type in
 				if (type_name="Dynamic") then begin
 					seen_dynamic := true;
 					output_i !else_str;
 				end else
 					output_i (!else_str ^ "if (__e.IsClass< " ^ type_name ^ " >() )");
 				ctx.ctx_writer#begin_block;
-				output_i (type_name ^ " " ^ name ^ " = __e;");
+				output_i (type_name ^ " " ^ v.v_name ^ " = __e;");
 				(* Move this "inside" the catch call too ... *)
 				ctx.ctx_return_from_block <-return_from_internal_node;
 				gen_expression ctx false (to_block expression);
@@ -1694,20 +1694,20 @@ let default_value_string = function
 
 
 let generate_default_values ctx args prefix =
-  List.iter ( fun (name,o,arg_type) -> let type_str = type_string arg_type in
+  List.iter ( fun (v,o) -> let type_str = type_string v.v_type in
 	match o with
 	| Some TNull -> ()
 	| Some const when (type_str=="::String") ->
-		ctx.ctx_output ("if (" ^ name ^ " == null() ) "
-			^ name ^ "=" ^ (default_value_string const) ^ ");\n")
+		ctx.ctx_output ("if (" ^ v.v_name ^ " == null() ) "
+			^ v.v_name ^ "=" ^ (default_value_string const) ^ ");\n")
 	| Some const ->
-		ctx.ctx_output (type_str ^ " " ^ name ^ " = " ^ prefix ^ name ^ ".Default(" ^ 
+		ctx.ctx_output (type_str ^ " " ^ v.v_name ^ " = " ^ prefix ^ v.v_name ^ ".Default(" ^
 			(default_value_string const) ^ ");\n")
 	| _ -> () ) args;;
 
 
-let has_default_values args = 
-	List.exists ( fun (_,o,_) -> match o with
+let has_default_values args =
+	List.exists ( fun (_,o) -> match o with
             | Some TNull -> false
             | Some _ -> true
             | _ -> false ) args ;;
@@ -1716,7 +1716,7 @@ let has_default_values args =
   When a specialized class inherits from a templated class, the inherited class
   contains the specialized type, rather than the generic template (Dynamic) type.
   C++ needs the inhertied functions to have the same types as the base types.
- 
+
   use Codegen.fix_overrides
 *)
 (*
@@ -1729,7 +1729,7 @@ let rec inherit_temlpate_types class_def name is_static in_def =
 				let field = PMap.find name funcs in
 				match field.cf_expr with
 					| Some { eexpr = TFunction parent_def } ->
-						 inherit_temlpate_types super name is_static 
+						 inherit_temlpate_types super name is_static
 							{
 								tf_args = List.map2 (fun (n,_,_) (_,c,t) -> n,c,t) in_def.tf_args parent_def.tf_args;
 								tf_type = parent_def.tf_type;
@@ -1877,7 +1877,7 @@ let gen_member_def ctx class_def is_static is_extern is_interface field =
 				output ("Dynamic " ^ remap_name ^ "_dyn();\n" );
 			(*end else
 				output ("		virtual Dynamic " ^ remap_name ^ "_dyn() = 0;\n\n" );*)
-		| _ -> 
+		| _ ->
 			if (is_interface) then begin
 				(*
 				output "virtual ";
@@ -1894,7 +1894,7 @@ let gen_member_def ctx class_def is_static is_extern is_interface field =
 			output ("Dynamic " ^ remap_name ^ ";\n");
 			output (if is_static then "		static " else "		");
 			(* external mem  Dynamic & *)
-			output ("inline Dynamic &" ^ remap_name ^ "_dyn() " ^ "{return " ^ remap_name^ "; }\n") 
+			output ("inline Dynamic &" ^ remap_name ^ "_dyn() " ^ "{return " ^ remap_name^ "; }\n")
 		end else begin
 			let return_type = (type_string function_def.tf_type) in
 			if (not is_static) then output "virtual ";
@@ -1972,13 +1972,13 @@ let find_referenced_types ctx obj super_deps constructor_deps header_only =
 				| TTypeExpr type_def -> add_type (t_path type_def)
 				(* Must visit the types, Type.iter will visit the expressions ... *)
 				| TTry (e,catches) ->
-					List.iter (fun (_,catch_type,_) -> visit_type catch_type) catches
+					List.iter (fun (v,_) -> visit_type v.v_type) catches
 				(* Must visit the enum param types, Type.iter will visit the rest ... *)
 				| TMatch (_,_,cases,_) ->
 					List.iter (fun (case_ids,params,expression) ->
 						(match params with
 						| None -> ()
-						| Some l -> List.iter (fun (v,t) -> visit_type t) l  ) ) cases;
+						| Some l -> List.iter (function None -> () | Some v -> visit_type v.v_type) l  ) ) cases;
 				(* Must visit type too, Type.iter will visit the expressions ... *)
             | TNew  (klass,params,_) -> begin
                visit_type (TInst (klass,params));
@@ -1989,10 +1989,10 @@ let find_referenced_types ctx obj super_deps constructor_deps header_only =
                end
 				(* Must visit type too, Type.iter will visit the expressions ... *)
 				| TVars var_list ->
-					List.iter (fun (_, var_type, _) -> visit_type var_type ) var_list
+					List.iter (fun (v, _) -> visit_type v.v_type) var_list
 				(* Must visit args too, Type.iter will visit the expressions ... *)
 				| TFunction func_def ->
-					List.iter (fun (_,_,arg_type) -> visit_type arg_type) func_def.tf_args;
+					List.iter (fun (v,_) -> visit_type v.v_type) func_def.tf_args;
 				| _ -> ()
 			);
 			Type.iter visit_expression expression;
@@ -2048,7 +2048,7 @@ let find_referenced_types ctx obj super_deps constructor_deps header_only =
 let generate_main common_ctx member_types super_deps class_def boot_classes init_classes =
 	let base_dir = common_ctx.file in
 	(* main routine should be a single static function *)
-	let main_expression = 
+	let main_expression =
 		(match class_def.cl_ordered_statics with
 		| [{ cf_expr = Some expression }] -> expression;
 		| _ -> assert false ) in
@@ -2104,7 +2104,7 @@ let begin_header_file output_h def_string =
 	output_h "#include <hxcpp.h>\n";
 	output_h "#endif\n\n";;
 
-let end_header_file output_h def_string = 
+let end_header_file output_h def_string =
 	output_h ("\n#endif /* INCLUDED_" ^ def_string ^ " */ \n");;
 
 let new_placed_cpp_file common_ctx class_path =
@@ -2145,7 +2145,7 @@ let generate_enum_files common_ctx enum_def super_deps meta =
 	PMap.iter (fun _ constructor ->
 		let name = keyword_remap constructor.ef_name in
 		match constructor.ef_type with
-		| TFun (args,_) -> 
+		| TFun (args,_) ->
 			output_cpp (smart_class_name ^ "  " ^ class_name ^ "::" ^ name ^ "(" ^
 				(gen_tfun_arg_list args) ^")\n");
 			output_cpp ("	{ return hx::CreateEnum< " ^ class_name ^ " >(" ^ (str name) ^ "," ^
@@ -2213,7 +2213,7 @@ let generate_enum_files common_ctx enum_def super_deps meta =
 	output_cpp "static ::String sStaticFields[] = {\n";
 	let sorted =
 	   List.sort (fun f1 f2 -> (PMap.find f1 enum_def.e_constrs ).ef_index -
-				   (PMap.find f2 enum_def.e_constrs ).ef_index ) 
+				   (PMap.find f2 enum_def.e_constrs ).ef_index )
 			  (pmap_keys enum_def.e_constrs) in
 
  	List.iter (fun name -> output_cpp ("	" ^ (str name) ^ ",\n") ) sorted;
@@ -2306,7 +2306,7 @@ let generate_enum_files common_ctx enum_def super_deps meta =
 		let name = keyword_remap constructor.ef_name in
 		output_h ( "		static " ^  smart_class_name ^ " " ^ name );
 		match constructor.ef_type with
-		| TFun (args,_) -> 
+		| TFun (args,_) ->
 			output_h ( "(" ^ (gen_tfun_arg_list args) ^");\n");
 			output_h ( "		static Dynamic " ^ name ^ "_dyn();\n");
 		| _ ->
@@ -2349,7 +2349,7 @@ let generate_class_files common_ctx member_types super_deps constructor_deps cla
 					| TFun (args,_) -> List.map (fun (a,_,t) -> (type_string t,a) )  args
 					| _ ->  (match definition.cf_expr with
 						| Some { eexpr = TFunction function_def } ->
-							List.map (fun (name,o,arg_type) -> gen_arg_type_name name o arg_type "__o_")
+							List.map (fun (v,o) -> gen_arg_type_name v.v_name o v.v_type "__o_")
 									function_def.tf_args;
 						| _ -> [] )
 					)
@@ -2416,7 +2416,7 @@ let generate_class_files common_ctx member_types super_deps constructor_deps cla
 
 		output_cpp (ptr_name ^ " " ^ class_name ^ "::__new(" ^constructor_type_args ^")\n");
 
-		let create_result ext = 
+		let create_result ext =
 			if (ext) then
 				output_cpp ("{  " ^ ptr_name ^ " result = __CreateEmpty();\n")
 			else
@@ -2442,7 +2442,7 @@ let generate_class_files common_ctx member_types super_deps constructor_deps cla
 	end;
 
 	(match class_def.cl_init with
-	| Some expression -> 
+	| Some expression ->
 		output_cpp ("void " ^ class_name^ "::__init__()");
 		gen_expression (new_context common_ctx cpp_file debug) false (to_block expression);
 		output_cpp "\n\n";
@@ -2809,7 +2809,7 @@ let add_class_to_makefile makefile add_obj class_def =
 	output_string makefile ( obj_file ^ " : src/" ^ cpp ^ " " ^ (gen_deps deps) ^ "\n");
 	output_string makefile ("\t$(COMPILE) src/" ^ cpp ^ " $(OUT_FLAGS)$@\n\n");
 	output_string makefile (add_obj ^ " " ^ obj_file ^ "\n\n" );;
-	
+
 
 let kind_string = function
 	| KNormal -> "KNormal"
@@ -2896,7 +2896,7 @@ let write_build_options filename options =
 	Pervasives.ignore (Unix.close_process_in cmd);
 	writer#close;;
 
-let create_member_types common_ctx = 
+let create_member_types common_ctx =
 	let result = Hashtbl.create 0 in
 	let add_member class_name interface member =
 		match follow member.cf_type with
@@ -2922,7 +2922,7 @@ let create_member_types common_ctx =
 	result;;
 
 (* Builds inheritance tree, so header files can include parents defs.  *)
-let create_super_dependencies common_ctx = 
+let create_super_dependencies common_ctx =
 	let result = Hashtbl.create 0 in
 	List.iter (fun object_def ->
 		(match object_def with
@@ -2939,7 +2939,7 @@ let create_super_dependencies common_ctx =
 		) common_ctx.types;
 	result;;
 
-let create_constructor_dependencies common_ctx = 
+let create_constructor_dependencies common_ctx =
 	let result = Hashtbl.create 0 in
 	List.iter (fun object_def ->
 		(match object_def with

+ 55 - 61
genjs.ml

@@ -29,7 +29,7 @@ type ctx = {
 	mutable statics : (tclass * string * texpr) list;
 	mutable inits : texpr list;
 	mutable tabs : string;
-	mutable in_value : bool;
+	mutable in_value : tvar option;
 	mutable in_loop : bool;
 	mutable handle_break : bool;
 	mutable id_counter : int;
@@ -39,7 +39,7 @@ type ctx = {
 }
 
 let s_path ctx = function
-	| ([],p) -> 
+	| ([],p) ->
 		(match ctx.namespace with
 		| None -> p
 		| Some ns -> ns ^ "." ^ p)
@@ -66,12 +66,12 @@ let print ctx = ctx.separator <- false; Printf.kprintf (fun s -> Buffer.add_stri
 
 let unsupported p = error "This expression cannot be compiled to Javascript" p
 
-let newline ctx =	
+let newline ctx =
 	match Buffer.nth ctx.buf (Buffer.length ctx.buf - 1) with
-	| '}' | '{' | ':' when not ctx.separator -> print ctx "\n%s" ctx.tabs	
+	| '}' | '{' | ':' when not ctx.separator -> print ctx "\n%s" ctx.tabs
 	| _ -> print ctx ";\n%s" ctx.tabs
 
-let semicolon ctx =	
+let semicolon ctx =
 	match Buffer.nth ctx.buf (Buffer.length ctx.buf - 1) with
 	| '}' when not ctx.separator -> ()
 	| _ -> spr ctx ";"
@@ -86,10 +86,10 @@ let rec concat ctx s f = function
 
 let fun_block ctx f p =
 	let e = (match f.tf_expr with { eexpr = TBlock [{ eexpr = TBlock _ } as e] } -> e | e -> e) in
-	let e = List.fold_left (fun e (a,c,t) ->
+	let e = List.fold_left (fun e (a,c) ->
 		match c with
 		| None | Some TNull -> e
-		| Some c -> Codegen.concat (Codegen.set_default ctx.com a c t p) e
+		| Some c -> Codegen.concat (Codegen.set_default ctx.com a c p) e
 	) e f.tf_args in
 	if ctx.com.debug then
 		Codegen.stack_block ctx.stack ctx.current (fst ctx.curmethod) e
@@ -139,7 +139,7 @@ let handle_break ctx e =
 				spr ctx "} catch( e ) { if( e != \"__break__\" ) throw e; }";
 			)
 
-let this ctx = if ctx.in_value then "$this" else "this"
+let this ctx = match ctx.in_value with None -> "this" | Some _ -> "$this"
 
 let gen_constant ctx p = function
 	| TInt i -> print ctx "%ld" i
@@ -170,26 +170,26 @@ let rec gen_call ctx e el =
 			List.iter (fun p -> print ctx ","; gen_value ctx p) params;
 			spr ctx ")";
 		);
-	| TCall (x,_) , el when x.eexpr <> TLocal "__js__" ->
+	| TCall (x,_) , el when (match x.eexpr with TLocal { v_name = "__js__" } -> false | _ -> true) ->
 		spr ctx "(";
 		gen_value ctx e;
 		spr ctx ")";
 		spr ctx "(";
 		concat ctx "," (gen_value ctx) el;
 		spr ctx ")";
-	| TLocal "__new__" , { eexpr = TConst (TString cl) } :: params ->
+	| TLocal { v_name = "__new__" }, { eexpr = TConst (TString cl) } :: params ->
 		print ctx "new %s(" cl;
 		concat ctx "," (gen_value ctx) params;
 		spr ctx ")";
-	| TLocal "__new__" , e :: params ->
+	| TLocal { v_name = "__new__" }, e :: params ->
 		spr ctx "new ";
 		gen_value ctx e;
 		spr ctx "(";
 		concat ctx "," (gen_value ctx) params;
 		spr ctx ")";
-	| TLocal "__js__", [{ eexpr = TConst (TString code) }] ->
+	| TLocal { v_name = "__js__" }, [{ eexpr = TConst (TString code) }] ->
 		spr ctx (String.concat "\n" (ExtString.String.nsplit code "\r\n"))
-	| TLocal "__resources__", [] ->
+	| TLocal { v_name = "__resources__" }, [] ->
 		spr ctx "[";
 		concat ctx "," (fun (name,data) ->
 			spr ctx "{ ";
@@ -209,7 +209,7 @@ let rec gen_call ctx e el =
 and gen_expr ctx e =
 	match e.eexpr with
 	| TConst c -> gen_constant ctx e.epos c
-	| TLocal s -> spr ctx (ident s)
+	| TLocal v -> spr ctx (ident v.v_name)
 	| TEnumField (e,s) ->
 		print ctx "%s%s" (ctx.type_accessor (TEnumDecl e)) (field s)
 	| TArray (e1,e2) ->
@@ -240,7 +240,7 @@ and gen_expr ctx e =
 		gen_value ctx e;
 		spr ctx ")";
 	| TReturn eo ->
-		if ctx.in_value then unsupported e.epos;
+		if ctx.in_value <> None then unsupported e.epos;
 		(match eo with
 		| None ->
 			spr ctx "return"
@@ -263,7 +263,7 @@ and gen_expr ctx e =
 	| TFunction f ->
 		let old = ctx.in_value, ctx.in_loop in
 		let old_meth = ctx.curmethod in
-		ctx.in_value <- false;
+		ctx.in_value <- None;
 		ctx.in_loop <- false;
 		if snd ctx.curmethod then
 			ctx.curmethod <- (fst ctx.curmethod ^ "@" ^ string_of_int (Lexer.get_error_line e.epos), true)
@@ -288,8 +288,8 @@ and gen_expr ctx e =
 		()
 	| TVars vl ->
 		spr ctx "var ";
-		concat ctx ", " (fun (n,_,e) ->
-			spr ctx (ident n);
+		concat ctx ", " (fun (v,e) ->
+			spr ctx (ident v.v_name);
 			match e with
 			| None -> ()
 			| Some e ->
@@ -340,10 +340,10 @@ and gen_expr ctx e =
 		concat ctx ", " (fun (f,e) -> print ctx "%s : " (anon_field f); gen_value ctx e) fields;
 		spr ctx "}";
 		ctx.separator <- true
-	| TFor (v,_,it,e) ->
+	| TFor (v,it,e) ->
 		let handle_break = handle_break ctx e in
 		let it = (match it.eexpr with
-			| TLocal v -> v
+			| TLocal v -> v.v_name
 			| _ ->
 				let id = ctx.id_counter in
 				ctx.id_counter <- ctx.id_counter + 1;
@@ -356,7 +356,7 @@ and gen_expr ctx e =
 		print ctx "while( %s.hasNext() ) {" it;
 		let bend = open_block ctx in
 		newline ctx;
-		print ctx "var %s = %s.next()" (ident v) it;
+		print ctx "var %s = %s.next()" (ident v.v_name) it;
 		gen_block ctx e;
 		bend();
 		newline ctx;
@@ -365,7 +365,7 @@ and gen_expr ctx e =
 	| TTry (e,catchs) ->
 		spr ctx "try ";
 		gen_expr ctx e;
-		let vname = (match catchs with [(v,_,_)] -> v | _ ->
+		let vname = (match catchs with [(v,_)] -> v.v_name | _ ->
 			let id = ctx.id_counter in
 			ctx.id_counter <- ctx.id_counter + 1;
 			"$e" ^ string_of_int id
@@ -373,9 +373,9 @@ and gen_expr ctx e =
 		print ctx " catch( %s ) {" vname;
 		let bend = open_block ctx in
 		let last = ref false in
-		List.iter (fun (v,t,e) ->
+		List.iter (fun (v,e) ->
 			if !last then () else
-			let t = (match follow t with
+			let t = (match follow v.v_type with
 			| TEnum (e,_) -> Some (TEnumDecl e)
 			| TInst (c,_) -> Some (TClassDecl c)
 			| TFun _
@@ -390,9 +390,9 @@ and gen_expr ctx e =
 			match t with
 			| None ->
 				last := true;
-				if vname <> v then begin
+				if vname <> v.v_name then begin
 					newline ctx;
-					print ctx "var %s = %s" v vname;
+					print ctx "var %s = %s" v.v_name vname;
 				end;
 				gen_block ctx e;
 			| Some t ->
@@ -401,9 +401,9 @@ and gen_expr ctx e =
 				gen_value ctx (mk (TTypeExpr t) (mk_mono()) e.epos);
 				spr ctx ") ) {";
 				let bend = open_block ctx in
-				if vname <> v then begin
+				if vname <> v.v_name then begin
 					newline ctx;
-					print ctx "var %s = %s" v vname;
+					print ctx "var %s = %s" v.v_name vname;
 				end;
 				gen_block ctx e;
 				bend();
@@ -424,7 +424,7 @@ and gen_expr ctx e =
 			"???"
 		end else begin
 			let v = (match e.eexpr with
-				| TLocal v -> v
+				| TLocal v -> v.v_name
 				| _ ->
 					spr ctx "var $e = ";
 					gen_value ctx e;
@@ -444,7 +444,7 @@ and gen_expr ctx e =
 			| None -> ()
 			| Some l ->
 				let n = ref 1 in
-				let l = List.fold_left (fun acc (v,_) -> incr n; match v with None -> acc | Some v -> (v,!n) :: acc) [] l in
+				let l = List.fold_left (fun acc v -> incr n; match v with None -> acc | Some v -> (v.v_name,!n) :: acc) [] l in
 				newline ctx;
 				spr ctx "var ";
 				concat ctx ", " (fun (v,n) ->
@@ -515,33 +515,27 @@ and gen_block ctx e =
 and gen_value ctx e =
 	let assign e =
 		mk (TBinop (Ast.OpAssign,
-			mk (TLocal "$r") t_dynamic e.epos,
+			mk (TLocal (match ctx.in_value with None -> assert false | Some v -> v)) t_dynamic e.epos,
 			e
 		)) e.etype e.epos
 	in
-	let value block =
+	let value() =
 		let old = ctx.in_value, ctx.in_loop in
-		ctx.in_value <- true;
+		let r = alloc_var "$r" t_dynamic in
+		ctx.in_value <- Some r;
 		ctx.in_loop <- false;
 		spr ctx "(function($this) ";
-		let b = if block then begin
-			spr ctx "{";
-			let b = open_block ctx in
+		spr ctx "{";
+		let b = open_block ctx in
+		newline ctx;
+		spr ctx "var $r";
+		newline ctx;
+		(fun() ->
 			newline ctx;
-			spr ctx "var $r";
+			spr ctx "return $r";
+			b();
 			newline ctx;
-			b
-		end else
-			(fun() -> ())
-		in
-		(fun() ->
-			if block then begin
-				newline ctx;
-				spr ctx "return $r";
-				b();
-				newline ctx;
-				spr ctx "}";
-			end;
+			spr ctx "}";
 			ctx.in_value <- fst old;
 			ctx.in_loop <- snd old;
 			print ctx "(%s))" (this ctx)
@@ -575,13 +569,13 @@ and gen_value ctx e =
 	| TWhile _
 	| TThrow _ ->
 		(* value is discarded anyway *)
-		let v = value true in
+		let v = value() in
 		gen_expr ctx e;
 		v()
 	| TBlock [e] ->
 		gen_value ctx e
 	| TBlock el ->
-		let v = value true in
+		let v = value() in
 		let rec loop = function
 			| [] ->
 				spr ctx "return null";
@@ -609,24 +603,24 @@ and gen_value ctx e =
 		| None -> spr ctx "null"
 		| Some e -> gen_value ctx e);
 	| TSwitch (cond,cases,def) ->
-		let v = value true in
+		let v = value() in
 		gen_expr ctx (mk (TSwitch (cond,
 			List.map (fun (e1,e2) -> (e1,assign e2)) cases,
 			match def with None -> None | Some e -> Some (assign e)
 		)) e.etype e.epos);
 		v()
 	| TMatch (cond,enum,cases,def) ->
-		let v = value true in
+		let v = value() in
 		gen_expr ctx (mk (TMatch (cond,enum,
 			List.map (fun (constr,params,e) -> (constr,params,assign e)) cases,
 			match def with None -> None | Some e -> Some (assign e)
 		)) e.etype e.epos);
 		v()
 	| TTry (b,catchs) ->
-		let v = value true in
+		let v = value() in
 		let block e = mk (TBlock [e]) e.etype e.epos in
 		gen_expr ctx (mk (TTry (block (assign b),
-			List.map (fun (v,t,e) -> v, t , block (assign e)) catchs
+			List.map (fun (v,e) -> v, block (assign e)) catchs
 		)) e.etype e.epos);
 		v()
 
@@ -639,7 +633,7 @@ let generate_package_create ctx (p,_) =
 			(match acc with
 			| [] ->
 				print ctx "if(typeof %s=='undefined') %s = {}" p p;
-			| _ -> 
+			| _ ->
 				let p = String.concat "." (List.rev acc) ^ (field p) in
 		        print ctx "if(!%s) %s = {}" p p);
 			newline ctx;
@@ -649,7 +643,7 @@ let generate_package_create ctx (p,_) =
 
 let check_field_name c f =
 	match f.cf_name with
-	| "prototype" | "__proto__" | "constructor" -> 
+	| "prototype" | "__proto__" | "constructor" ->
 		error ("The field name '" ^ f.cf_name ^ "'  is not allowed in JS") (match f.cf_expr with None -> c.cl_pos | Some e -> e.epos);
 	| _ -> ()
 
@@ -745,7 +739,7 @@ let generate_enum ctx e =
 		print ctx "%s%s = " p (field f.ef_name);
 		(match f.ef_type with
 		| TFun (args,_) ->
-			let sargs = String.concat "," (List.map arg_name args) in
+			let sargs = String.concat "," (List.map (fun (n,_,_) -> n) args) in
 			print ctx "function(%s) { var $x = [\"%s\",%d,%s]; $x.__enum__ = %s; $x.toString = $estr; return $x; }" sargs f.ef_name f.ef_index sargs p;
 		| _ ->
 			print ctx "[\"%s\",%d]" f.ef_name f.ef_index;
@@ -790,7 +784,7 @@ let alloc_ctx com =
 		inits = [];
 		current = null_class;
 		tabs = "";
-		in_value = false;
+		in_value = None;
 		in_loop = false;
 		handle_break = false;
 		id_counter = 0;
@@ -822,7 +816,7 @@ let generate com =
 	newline ctx;
 	(match ctx.namespace with
 		| None -> ()
-		| Some ns -> 
+		| Some ns ->
 			print ctx "if(typeof %s=='undefined') %s = {}" ns ns;
 			newline ctx);
 	List.iter (generate_type ctx) com.types;
@@ -832,7 +826,7 @@ let generate com =
 	newline ctx;
 	(match ctx.namespace with
 		| None -> ()
-		| Some ns -> 
+		| Some ns ->
 			print ctx "js.Boot.__ns = '%s'" ns;
 			newline ctx);
 	if com.debug then begin

+ 28 - 107
genneko.ml

@@ -30,8 +30,6 @@ type context = {
 	mutable macros : bool;
 	mutable curclass : string;
 	mutable curmethod : string;
-	mutable locals : (string , bool) PMap.t;
-	mutable curblock : texpr list;
 	mutable inits : (tclass * texpr) list;
 }
 
@@ -80,57 +78,6 @@ let gen_global_name ctx path =
 		Hashtbl.add ctx.globals path name;
 		name
 
-let add_local ctx v p =
-	let rec loop flag e =
-		match e.eexpr with
-		| TLocal a ->
-			if flag && a = v then raise Exit
-		| TFunction f ->
-			if not (List.exists (fun (a,_,_) -> a = v) f.tf_args) then loop true f.tf_expr
-		| TVars l ->
-			if List.exists (fun (a,_,_) -> a = v) l then raise Not_found;
-			Type.iter (loop flag) e
-		| TFor (a,_,e1,e2) ->
-			loop flag e1;
-			if a <> v then loop flag e2
-		| TMatch (e,_,cases,eo) ->
-			loop flag e;
-			(match eo with None -> () | Some e -> loop flag e);
-			List.iter (fun (_,params,e) ->
-				match params with
-				| Some l when List.exists (fun (a,_) -> a = Some v) l -> ()
-				| _ -> loop flag e
-			) cases
-		| TBlock l ->
-			(try
-				List.iter (loop flag) l
-			with
-				Not_found -> ())
-		| TTry (e,catchs) ->
-			loop flag e;
-			List.iter (fun (a,_,e) -> if a <> v then loop flag e) catchs
-		| _ ->
-			Type.iter (loop flag) e
-	in
-	let isref = (try
-		List.iter (loop false) ctx.curblock;
-		false
-	with
-		| Not_found -> false
-		| Exit -> true
-	) in
-	ctx.locals <- PMap.add v isref ctx.locals;
-	isref
-
-let block ctx curblock =
-	let l = ctx.locals in
-	let b = ctx.curblock in
-	ctx.curblock <- curblock;
-	(fun() ->
-		ctx.locals <- l;
-		ctx.curblock <- b;
-	)
-
 let null p =
 	(EConst Null,p)
 
@@ -237,7 +184,7 @@ and gen_call ctx p e el =
 			this p;
 			array p (List.map (gen_expr ctx) el)
 		]
-	| TLocal "__resources__", [] ->
+	| TLocal { v_name = "__resources__" }, [] ->
 		call p (builtin p "array") (Hashtbl.fold (fun name data acc ->
 			(EObject [("name",gen_constant ctx e.epos (TString name));("data",gen_big_string ctx p data)],p) :: acc
 		) ctx.com.resources [])
@@ -257,12 +204,11 @@ and gen_expr ctx e =
 	match e.eexpr with
 	| TConst c ->
 		gen_constant ctx e.epos c
-	| TLocal s ->
-		let isref = try PMap.find s ctx.locals with Not_found -> false in
-		if isref then
-			(EArray (ident p s,int p 0),p)
+	| TLocal v ->
+		if v.v_capture then
+			(EArray (ident p v.v_name,int p 0),p)
 		else
-			ident p s
+			ident p v.v_name
 	| TEnumField (e,f) ->
 		field p (gen_type_path p e.e_path) f
 	| TArray (e1,e2) ->
@@ -304,65 +250,48 @@ and gen_expr ctx e =
 	| TUnop (op,flag,e) ->
 		gen_unop ctx p op flag e
 	| TVars vl ->
-		(EVars (List.map (fun (v,_,e) ->
-			let isref = add_local ctx v p in
+		(EVars (List.map (fun (v,e) ->
 			let e = (match e with
 				| None ->
-					if isref then
+					if v.v_capture then
 						Some (call p (builtin p "array") [null p])
 					else
 						None
 				| Some e ->
 					let e = gen_expr ctx e in
-					if isref then
+					if v.v_capture then
 						Some (call p (builtin p "array") [e])
 					else
 						Some e
 			) in
-			v , e
+			v.v_name , e
 		) vl),p)
 	| TFunction f ->
-		let b = block ctx [f.tf_expr] in
-		let inits = List.fold_left (fun acc (a,c,t) ->
+		let inits = List.fold_left (fun acc (a,c) ->
 			let acc = (match c with
 				| None | Some TNull -> acc
-				| Some c ->	gen_expr ctx (Codegen.set_default ctx.com a c t e.epos) :: acc
+				| Some c ->	gen_expr ctx (Codegen.set_default ctx.com a c e.epos) :: acc
 			) in
-			if add_local ctx a p then
-				(EBinop ("=",ident p a,call p (builtin p "array") [ident p a]),p) :: acc
+			if a.v_capture then
+				(EBinop ("=",ident p a.v_name,call p (builtin p "array") [ident p a.v_name]),p) :: acc
 			else
 				acc
 		) [] f.tf_args in
 		let e = gen_expr ctx f.tf_expr in
 		let e = (match inits with [] -> e | _ -> EBlock (List.rev (e :: inits)),p) in
-		let e = (EFunction (List.map arg_name f.tf_args, with_return e),p) in
-		b();
-		e
+		(EFunction (List.map arg_name f.tf_args, with_return e),p)
 	| TBlock el ->
-		let b = block ctx el in
-		let rec loop = function
-			| [] -> []
-			| e :: l ->
-				ctx.curblock <- l;
-				let e = gen_expr ctx e in
-				e :: loop l
-		in
-		let e = (EBlock (loop el), p) in
-		b();
-		e
-	| TFor (v, _, it, e) ->
+		(EBlock (List.map (gen_expr ctx) el), p)
+	| TFor (v, it, e) ->
 		let it = gen_expr ctx it in
-		let b = block ctx [e] in
-		let isref = add_local ctx v p in
 		let e = gen_expr ctx e in
-		b();
 		let next = call p (field p (ident p "@tmp") "next") [] in
-		let next = (if isref then call p (builtin p "array") [next] else next) in
+		let next = (if v.v_capture then call p (builtin p "array") [next] else next) in
 		(EBlock
 			[(EVars ["@tmp", Some it],p);
 			(EWhile (call p (field p (ident p "@tmp") "hasNext") [],
 				(EBlock [
-					(EVars [v, Some next],p);
+					(EVars [v.v_name, Some next],p);
 					e
 				],p)
 			,NormalWhile),p)]
@@ -374,9 +303,9 @@ and gen_expr ctx e =
 	| TTry (e,catchs) ->
 		let rec loop = function
 			| [] -> call p (builtin p "rethrow") [ident p "@tmp"]
-			| (v,t,e) :: l ->
+			| (v,e) :: l ->
 				let e2 = loop l in
-				let path = (match follow t with
+				let path = (match follow v.v_type with
 					| TInst (c,_) -> Some c.cl_path
 					| TEnum (e,_) -> Some e.e_path
 					| TDynamic _ -> None
@@ -386,14 +315,11 @@ and gen_expr ctx e =
 					| None -> (EConst True,p)
 					| Some path -> call p (field p (gen_type_path p (["neko"],"Boot")) "__instanceof") [ident p "@tmp"; gen_type_path p path]
 				) in
-				let b = block ctx [e] in
-				let isref = add_local ctx v p in
 				let id = ident p "@tmp" in
-				let id = (if isref then call p (builtin p "array") [id] else id) in
+				let id = (if v.v_capture then call p (builtin p "array") [id] else id) in
 				let e = gen_expr ctx e in
-				b();
 				(EIf (cond,(EBlock [
-					EVars [v,Some id],p;
+					EVars [v.v_name,Some id],p;
 					e;
 				],p),Some e2),p)
 		in
@@ -427,21 +353,18 @@ and gen_expr ctx e =
 			| None ->
 				gen_expr ctx e
 			| Some el ->
-				let b = block ctx [e] in
 				let count = ref (-1) in
-				let vars = List.fold_left (fun acc (v,_) ->
+				let vars = List.fold_left (fun acc v ->
 					incr count;
 					match v with
 					| None ->
 						acc
 					| Some v ->
-						let isref = add_local ctx v p in
 						let e = (EArray (ident p "@tmp",int p (!count)),p) in
-						let e = (if isref then call p (builtin p "array") [e] else e) in
-						(v , Some e) :: acc
+						let e = (if v.v_capture then call p (builtin p "array") [e] else e) in
+						(v.v_name , Some e) :: acc
 				) [] el in
 				let e = gen_expr ctx e in
-				b();
 				(EBlock [
 					(EVars ["@tmp",Some (field p (ident p "@tmp") "args")],p);
 					(match vars with [] -> null p | _ -> EVars vars,p);
@@ -535,7 +458,7 @@ let gen_class ctx c =
 	| Some f ->
 		(match follow f.cf_type with
 		| TFun (args,_) ->
-			let params = List.map arg_name args in
+			let params = List.map (fun (n,_,_) -> n) args in
 			gen_method ctx p f ["new",(EFunction (params,(EBlock [
 				(EVars ["@o",Some (call p (builtin p "new") [null p])],p);
 				(call p (builtin p "objsetproto") [ident p "@o"; clpath]);
@@ -598,7 +521,7 @@ let gen_enum_constr ctx path c =
 	let p = pos ctx c.ef_pos in
 	(EBinop ("=",field p path c.ef_name, match follow c.ef_type with
 		| TFun (params,_) ->
-			let params = List.map arg_name params in
+			let params = List.map (fun (n,_,_) -> n) params in
 			(EFunction (params,
 				(EBlock [
 					(EVars ["@tmp",Some (EObject [
@@ -766,8 +689,6 @@ let new_context com macros =
 		curclass = "$boot";
 		curmethod = "$init";
 		inits = [];
-		curblock = [];
-		locals = PMap.empty;
 	}
 
 let header() =
@@ -819,7 +740,7 @@ let build ctx types =
 let generate com libs =
 	let ctx = new_context com false in
 	let t = Common.timer "neko generation" in
-	let libs = (ENeko (generate_libs_init libs) , { psource = "<header>"; pline = 1; }) in	
+	let libs = (ENeko (generate_libs_init libs) , { psource = "<header>"; pline = 1; }) in
 	let el = build ctx com.types in
 	let emain = (match com.main with None -> [] | Some e -> [gen_expr ctx e]) in
 	let e = (EBlock ((header()) @ libs :: el @ emain), null_pos) in

+ 131 - 131
genphp.ml

@@ -97,7 +97,7 @@ let rec class_string klass suffix params =
 				| TInst ({ cl_path = [],"Float" },_)
 				| TEnum ({ e_path = [],"Bool" },_) -> "Dynamic"
 				| _ -> "/*NULL*/" ^ (type_string t) )
-			| _ -> assert false); 
+			| _ -> assert false);
 	(* Normal class *)
 	| _ -> (join_class_path klass.cl_path "::") ^ suffix
 	)
@@ -132,16 +132,16 @@ and type_string_suff suffix haxe_type =
 	| TDynamic haxe_type -> "Dynamic"
 	| TLazy func -> type_string_suff suffix ((!func)())
 	)
-and type_string haxe_type = 
+and type_string haxe_type =
 	type_string_suff "" haxe_type;;
 
 let debug_expression expression type_too =
 	"/* " ^ Type.s_expr_kind expression ^ (if (type_too) then " = " ^ (type_string expression.etype) else "") ^ " */";;
 
-let rec register_extern_required_path ctx path = 
+let rec register_extern_required_path ctx path =
 	if (List.exists(fun p -> p = path) ctx.extern_classes_with_init) && not (List.exists(fun p -> p = path) ctx.extern_required_paths) then
 		ctx.extern_required_paths <- path :: ctx.extern_required_paths
-		
+
 let s_expr_expr = Type.s_expr_kind
 
 let s_expr_name e =
@@ -149,7 +149,7 @@ let s_expr_name e =
 
 let s_type_name t =
 	s_type (print_context()) t
-	
+
 let rec is_uncertain_type t =
 	match follow t with
 	| TInst (c, _) -> c.cl_interface
@@ -238,23 +238,23 @@ haxe reserved words that match php ones: break, case, class, continue, default,
 	| "enddeclare" | "endfor" | "endforeach" | "endif" | "endswitch"
 	| "endwhile" | "eval" | "exit" | "foreach"| "global" | "include"
 	| "include_once" | "isset" | "list" | "namespace" | "print" | "require" | "require_once"
-	| "unset" | "use" | "__function__" | "__class__" | "__method__" | "final" 
+	| "unset" | "use" | "__function__" | "__class__" | "__method__" | "final"
 	| "php_user_filter" | "protected" | "abstract" | "__set" | "__get" | "__call"
 	| "clone" -> suf ^ n
 	| _ -> n
-	
+
 let s_ident_local n =
 	let suf = "h" in
 	match String.lowercase n with
-	| "globals" | "_server" | "_get" | "_post" | "_cookie" | "_files" 
+	| "globals" | "_server" | "_get" | "_post" | "_cookie" | "_files"
 	| "_env" | "_request" | "_session" -> suf ^ n
 	| _ -> n
-	
+
 let create_directory com ldir =
  	let atm_path = ref (String.create 0) in
  	atm_path := com.file;
  	if not (Sys.file_exists com.file) then (Unix.mkdir com.file 0o755);
- 	(List.iter (fun p -> atm_path := !atm_path ^ "/" ^ p; if not (Sys.file_exists !atm_path) then (Unix.mkdir !atm_path 0o755);) ldir)   
+ 	(List.iter (fun p -> atm_path := !atm_path ^ "/" ^ p; if not (Sys.file_exists !atm_path) then (Unix.mkdir !atm_path 0o755);) ldir)
 
 let write_resource dir name data =
 	let i = ref 0 in
@@ -268,7 +268,7 @@ let write_resource dir name data =
 	let ch = open_out_bin (rdir ^ "/" ^ name) in
 	output_string ch data;
 	close_out ch
-	
+
 let stack_init com use_add =
 	Codegen.stack_context_init com "GLOBALS['%s']" "GLOBALS['%e']" "»spos" "»tmp" use_add null_pos
 
@@ -354,7 +354,7 @@ let inc_extern_path ctx path =
 		pre ^ (slashes (List.length (fst ctx.path))) ^ name ^ ".extern.php"
 		| (pack,name) ->
 		pre ^ (slashes (List.length (fst ctx.path))) ^ String.concat "/" pack ^ "/" ^ name ^ ".extern.php"
-	
+
 let close ctx =
 	output_string ctx.ch "<?php\n";
 	List.iter (fun path ->
@@ -394,7 +394,7 @@ let escape_bin s =
 			Buffer.add_char b (Char.chr c)
 		| c when c < 32 ->
 			Buffer.add_string b (Printf.sprintf "\\x%.2X" c)
-		| c -> 
+		| c ->
 			Buffer.add_char b (Char.chr c)
 	done;
 	Buffer.contents b
@@ -424,17 +424,17 @@ let is_dynamic_method f =
 		| Var _ -> true
 		| Method MethDynamic -> true
 		| _ -> false)
-		
+
 let fun_block ctx f p =
 	let e = (match f.tf_expr with { eexpr = TBlock [{ eexpr = TBlock _ } as e] } -> e | e -> e) in
-	let e = List.fold_left (fun e (a,c,t) ->
+	let e = List.fold_left (fun e (v,c) ->
 		match c with
 		| None | Some TNull -> e
-		| Some c -> Codegen.concat (Codegen.set_default ctx.com a c t p) e
+		| Some c -> Codegen.concat (Codegen.set_default ctx.com v c p) e
 	) e f.tf_args in
 	if ctx.com.debug then begin
 		Codegen.stack_block ctx.stack ctx.curclass ctx.curmethod e
-	end else 
+	end else
 		mk_block e
 
 let rec gen_array_args ctx lst =
@@ -443,9 +443,9 @@ let rec gen_array_args ctx lst =
 	| h :: t ->
 		spr ctx "[";
 		gen_value ctx h;
-		spr ctx "]";				
+		spr ctx "]";
 		gen_array_args ctx t
-		
+
 and gen_call ctx e el =
 	let rec genargs lst =
 		(match lst with
@@ -476,45 +476,45 @@ and gen_call ctx e el =
 			concat ctx "," (gen_value ctx) params;
 			spr ctx ")";
 		);
-	| TLocal "__set__" , { eexpr = TConst (TString code) } :: el ->
+	| TLocal { v_name = "__set__" }, { eexpr = TConst (TString code) } :: el ->
 		print ctx "$%s" code;
 		genargs el;
-	| TLocal "__set__" , e :: el ->
+	| TLocal { v_name = "__set__" }, e :: el ->
 		gen_value ctx e;
 		genargs el;
-	| TLocal "__setfield__" , e :: (f :: el) ->
+	| TLocal { v_name = "__setfield__" }, e :: (f :: el) ->
 		gen_value ctx e;
 		spr ctx "->{";
 		gen_value ctx f;
 		spr ctx "}";
 		genargs el;
-	| TLocal "__field__" , e :: ({ eexpr = TConst (TString code) } :: el) ->
+	| TLocal { v_name = "__field__" }, e :: ({ eexpr = TConst (TString code) } :: el) ->
 		gen_value ctx e;
 		spr ctx "->";
 		spr ctx code;
 		gen_array_args ctx el;
-	| TLocal "__field__" , e :: (f :: el) ->
+	| TLocal { v_name = "__field__" }, e :: (f :: el) ->
 		gen_value ctx e;
 		spr ctx "->";
 		gen_value ctx f;
 		gen_array_args ctx el;
-	| TLocal "__var__" , { eexpr = TConst (TString code) } :: el ->
+	| TLocal { v_name = "__var__" }, { eexpr = TConst (TString code) } :: el ->
 		print ctx "$%s" code;
 		gen_array_args ctx el;
-	| TLocal "__var__" , e :: el ->
+	| TLocal { v_name = "__var__" }, e :: el ->
 		gen_value ctx e;
 		gen_array_args ctx el;
-	| TLocal "__call__" , { eexpr = TConst (TString code) } :: el ->
+	| TLocal { v_name = "__call__" }, { eexpr = TConst (TString code) } :: el ->
 		spr ctx code;
 		spr ctx "(";
 		concat ctx ", " (gen_value ctx) el;
 		spr ctx ")";
-	| TLocal "__php__", [{ eexpr = TConst (TString code) }] ->
+	| TLocal { v_name = "__php__" }, [{ eexpr = TConst (TString code) }] ->
 		spr ctx code
-	| TLocal "__instanceof__" ,  [e1;{ eexpr = TConst (TString t) }] ->
+	| TLocal { v_name = "__instanceof__" },  [e1;{ eexpr = TConst (TString t) }] ->
 		gen_value ctx e1;
 		print ctx " instanceof %s" t;
-	| TLocal "__physeq__" ,  [e1;e2] ->
+	| TLocal { v_name = "__physeq__" },  [e1;e2] ->
 		gen_value ctx e1;
 		spr ctx " === ";
 		gen_value ctx e2
@@ -710,9 +710,9 @@ and gen_field_access ctx isvar e s =
 	| TArrayDecl _
 	| TNew _ ->
 		spr ctx "_hx_deref(";
-		ctx.is_call <- false; 
+		ctx.is_call <- false;
 		gen_value ctx e;
-		spr ctx ")"; 
+		spr ctx ")";
 		gen_member_access ctx isvar e s
 	| _ ->
 		gen_expr ctx e;
@@ -727,10 +727,10 @@ and gen_dynamic_function ctx isstatic name f params p =
 	ctx.local_types <- List.map snd params @ ctx.local_types;
 	let byref = if (String.length name > 9 && String.sub name 0 9 = "__byref__") then "&" else "" in
 	print ctx "function %s%s(" byref name;
-	concat ctx ", " (fun (arg,o,t) ->
-	let arg = define_local ctx arg in
-		s_funarg ctx arg t p o;
-		) f.tf_args;
+	concat ctx ", " (fun (v,c) ->
+		let arg = define_local ctx v.v_name in
+		s_funarg ctx arg v.v_type p c;
+	) f.tf_args;
 	spr ctx ") {";
 
 	if (List.length f.tf_args) > 0 then begin
@@ -738,8 +738,8 @@ and gen_dynamic_function ctx isstatic name f params p =
 			print ctx " return call_user_func_array(self::$%s, array("  name
 		else
 			print ctx " return call_user_func_array($this->%s, array("  name;
-		concat ctx ", " (fun (arg,o,t) ->
-			spr ctx ("$" ^ arg)
+		concat ctx ", " (fun (v,_) ->
+			spr ctx ("$" ^ v.v_name)
 		) f.tf_args;
 		print ctx ")); }";
 	end else if isstatic then
@@ -766,9 +766,9 @@ and gen_function ctx name f params p =
 	ctx.local_types <- List.map snd params @ ctx.local_types;
 	let byref = if (String.length name > 9 && String.sub name 0 9 = "__byref__") then "&" else "" in
 	print ctx "function %s%s(" byref name;
-	concat ctx ", " (fun (arg,o,t) ->
-		let arg = define_local ctx arg in
-		s_funarg ctx arg t p o;
+	concat ctx ", " (fun (v,o) ->
+		let arg = define_local ctx v.v_name in
+		s_funarg ctx arg v.v_type p o;
 	) f.tf_args;
 	print ctx ") ";
 	gen_expr ctx (fun_block ctx f p);
@@ -777,7 +777,7 @@ and gen_function ctx name f params p =
 	ctx.inv_locals <- old_li;
 	ctx.local_types <- old_t
 
-	
+
 and gen_inline_function ctx f hasthis p =
 	ctx.nested_loops <- ctx.nested_loops - 1;
 	let old = ctx.in_value in
@@ -786,13 +786,13 @@ and gen_inline_function ctx f hasthis p =
 	let old_t = ctx.local_types in
 	ctx.in_value <- Some "closure";
 
-	let args a = List.map (fun (n,_,_) -> n) a in
+	let args a = List.map (fun (v,_) -> v.v_name) a in
 	let arguments = ref [] in
-	
+
 	if hasthis then begin arguments := "this" :: !arguments end;
-	
+
 	PMap.iter (fun n _ -> arguments := !arguments @ [n]) old_li;
-	
+
 	spr ctx "array(new _hx_lambda(array(";
 
 	let c = ref 0 in
@@ -804,16 +804,16 @@ and gen_inline_function ctx f hasthis p =
 	) (remove_internals !arguments);
 
 	spr ctx "), \"";
-	
-	spr ctx (inline_function ctx (args f.tf_args) hasthis (fun_block ctx f p)); 
+
+	spr ctx (inline_function ctx (args f.tf_args) hasthis (fun_block ctx f p));
 	print ctx "\"), 'execute')";
-	
+
 	ctx.in_value <- old;
 	ctx.locals <- old_l;
 	ctx.inv_locals <- old_li;
 	ctx.local_types <- old_t;
 	ctx.nested_loops <- ctx.nested_loops + 1;
-	
+
 and unset_locals ctx old_l =
 	let lst = ref [] in
 	PMap.iter (fun n _ ->
@@ -826,7 +826,7 @@ and unset_locals ctx old_l =
 		concat ctx "," (fun (s) -> spr ctx s; ) !lst;
 		spr ctx ")"
 	end
-	
+
 and gen_while_expr ctx e =
 	let old_loop = ctx.in_loop in
 	ctx.in_loop <- true;
@@ -848,14 +848,14 @@ and gen_while_expr ctx e =
 and gen_expr ctx e =
 	let in_block = ctx.in_block in
 	ctx.in_block <- false;
-	let restore_in_block ctx inb = 
-		if inb then ctx.in_block <- true 
+	let restore_in_block ctx inb =
+		if inb then ctx.in_block <- true
 	in
 	match e.eexpr with
 	| TConst c ->
 		gen_constant ctx e.epos c
-	| TLocal s ->
-		spr ctx ("$" ^ (try PMap.find s ctx.locals with Not_found -> (s_ident_local s)))
+	| TLocal v ->
+		spr ctx ("$" ^ (try PMap.find v.v_name ctx.locals with Not_found -> (s_ident_local v.v_name)))
 	| TEnumField (en,s) ->
 		(match (try PMap.find s en.e_constrs with Not_found -> error ("Unknown local " ^ s) e.epos).ef_type with
 		| TFun (args,_) -> print ctx "%s::%s" (s_path ctx en.e_path en.e_extern e.epos) (s_ident s)
@@ -879,7 +879,7 @@ and gen_expr ctx e =
 		let non_assoc = function
 			| (Ast.OpEq | Ast.OpNotEq | Ast.OpGt | Ast.OpGte | Ast.OpLt | Ast.OpLte) -> true
 			| _ -> false
-		in		
+		in
 		(match e1.eexpr with
 		| TBinop (op2,_,_) when non_assoc op && non_assoc op2 ->
 			gen_expr ctx { e with eexpr = TBinop (op,mk (TParenthesis e1) e1.etype e1.epos,e2) }
@@ -1046,7 +1046,7 @@ and gen_expr ctx e =
 			print ctx " %s " (Ast.s_binop op);
 			gen_value_op ctx e2;
 		));
-	| TField (e1,s) 
+	| TField (e1,s)
 	| TClosure (e1,s) ->
 		(match follow e.etype with
 		| TFun (args, _) ->
@@ -1055,15 +1055,15 @@ and gen_expr ctx e =
 	  		end else if is_in_dynamic_methods ctx e1 s then begin
 	  			gen_field_access ctx true e1 s;
 	  		end else begin
-				let ob ex = 
+				let ob ex =
 					(match ex with
 					| TTypeExpr t ->
 						print ctx "\"";
 						spr ctx (s_path ctx (t_path t) false e1.epos);
 						print ctx "\""
-					| _ -> 
+					| _ ->
 						gen_expr ctx e1) in
-				
+
 				spr ctx "(isset(";
 				gen_field_access ctx true e1 s;
 				spr ctx ") ? ";
@@ -1071,7 +1071,7 @@ and gen_expr ctx e =
 				spr ctx ": array(";
 				ob e1.eexpr;
 				print ctx ", \"%s\"))" (s_ident s);
-				
+
 			end)
 		| TMono _ ->
 			if ctx.is_call then
@@ -1091,7 +1091,7 @@ and gen_expr ctx e =
 		print ctx "_hx_qtype(\"%s\")" (s_path_haxe (t_path t))
 	| TParenthesis e ->
 		(match e.eexpr with
-		| TParenthesis _ 
+		| TParenthesis _
 		| TReturn _ ->
 			gen_value ctx e;
 		| _ ->
@@ -1147,17 +1147,17 @@ and gen_expr ctx e =
 			end) in
 		let remaining = ref (List.length el) in
 		let build e =
-			(match e.eexpr with 
+			(match e.eexpr with
 			| TBlock [] -> ()
 			| _ -> newline ctx);
 			if (in_block && !remaining = 1) then begin
 				(match e.eexpr with
 				| TIf _
 				| TSwitch _
-				| TThrow _ 
+				| TThrow _
 				| TWhile _
 				| TFor _
-				| TMatch _ 
+				| TMatch _
 				| TTry _
 				| TBreak
 				| TBlock _ ->
@@ -1168,17 +1168,17 @@ and gen_expr ctx e =
 					(match e1.eexpr with
 					| TIf _
 					| TSwitch _
-					| TThrow _ 
+					| TThrow _
 					| TWhile _
 					| TFor _
-					| TMatch _ 
+					| TMatch _
 					| TTry _
 					| TBlock _ -> ()
 					| _ ->
 						spr ctx "return "
 					);
 					gen_expr ctx e1;
-				| _ -> 
+				| _ ->
 					spr ctx "return ";
 					gen_value ctx e;
 				)
@@ -1194,7 +1194,7 @@ and gen_expr ctx e =
 		end;
 		bend();
 		newline ctx;
-		
+
 		cb();
 		print ctx "}";
 		b();
@@ -1236,13 +1236,13 @@ and gen_expr ctx e =
 		()
 	| TVars vl ->
 		spr ctx "$";
-		concat ctx ("; $") (fun (n,t,v) ->
+		concat ctx ("; $") (fun (v,e) ->
 			let restore = save_locals ctx in
-			let n = define_local ctx n in
+			let n = define_local ctx v.v_name in
 			let restore2 = save_locals ctx in
 			restore();
-			(match v with
-			| None -> 
+			(match e with
+			| None ->
 				print ctx "%s = null" (s_ident_local n)
 			| Some e ->
 				print ctx "%s = " (s_ident_local n);
@@ -1330,10 +1330,10 @@ and gen_expr ctx e =
 		spr ctx "_hx_anonymous(array(";
 		concat ctx ", " (fun (f,e) -> print ctx "\"%s\" => " f; gen_value ctx e) fields;
 		spr ctx "))"
-	| TFor (v,t,it,e) ->
+	| TFor (v,it,e) ->
 		let b = save_locals ctx in
 		let tmp = define_local ctx "»it" in
-		let v = define_local ctx v in
+		let v = define_local ctx v.v_name in
 		(match it.eexpr with
 		| TCall (e,_) ->
 			(match e.eexpr with
@@ -1372,13 +1372,13 @@ and gen_expr ctx e =
 		newline ctx;
 		print ctx "$%s = ($%s instanceof HException) ? $%s->e : $%s" evar ex ex ex;
 		old();
-		List.iter (fun (v,t,e) ->
-			let ev = define_local ctx v in
+		List.iter (fun (v,e) ->
+			let ev = define_local ctx v.v_name in
 			newline ctx;
 
 			let b = save_locals ctx in
 			if not !first then spr ctx "else ";
-			(match follow t with
+			(match follow v.v_type with
 			| TEnum (te,_) -> (match snd te.e_path with
 				| "Bool"   -> print ctx "if(is_bool($%s = $%s))" ev evar
 				| _ -> print ctx "if(($%s = $%s) instanceof %s)" ev evar (s_path ctx te.e_path te.e_extern e.epos));
@@ -1437,7 +1437,7 @@ and gen_expr ctx e =
 			| None | Some [] -> ()
 			| Some l ->
 				let n = ref (-1) in
-				let l = List.fold_left (fun acc (v,t) -> incr n; match v with None -> acc | Some v -> (v,t,!n) :: acc) [] l in
+				let l = List.fold_left (fun acc v -> incr n; match v with None -> acc | Some v -> (v.v_name,v.v_type,!n) :: acc) [] l in
 				match l with
 				| [] -> ()
 				| l ->
@@ -1451,7 +1451,7 @@ and gen_expr ctx e =
 			print ctx "break";
 			newline ctx;
 			b()
-		) cases;		
+		) cases;
 		(match def with
 		| None -> ()
 		| Some e ->
@@ -1511,7 +1511,7 @@ and gen_expr ctx e =
 		spr ctx ", ";
 		gen_expr ctx (mk (TTypeExpr t) (mk_texpr t) e1.epos);
 		spr ctx ")"
-		
+
 and argument_list_from_locals include_this in_var l =
 	let lst = ref [] in
 	if (include_this && in_var) then lst := "»this" :: !lst
@@ -1520,16 +1520,16 @@ and argument_list_from_locals include_this in_var l =
 		lst := !lst @ [n];
 	) l;
 	!lst
-	
+
 and remove_internals args =
 	List.filter (fun a -> a = "»this" or '»' <> String.get a 0) args;
-		
+
 and inline_block ctx e =
 		let index = ctx.inline_index in
 		ctx.inline_index <- ctx.inline_index + 1;
-		let block = { 
+		let block = {
 			iname = (s_path ctx ctx.curclass.cl_path ctx.curclass.cl_extern ctx.curclass.cl_pos) ^ "_" ^ string_of_int index;
-			iindex = index; 
+			iindex = index;
 			ihasthis = ctx.in_instance_method; (* param this *)
 			iarguments = [];
 			iexpr = e;
@@ -1537,7 +1537,7 @@ and inline_block ctx e =
 			iin_block = true;
 			iinv_locals = ctx.inv_locals;
 		} in
-		
+
 		print ctx "%s(" block.iname;
 		let in_value = (match ctx.in_value with Some _ -> true | _ -> false) in
 		(match remove_internals (argument_list_from_locals ctx.in_instance_method in_value ctx.locals) with
@@ -1545,15 +1545,15 @@ and inline_block ctx e =
 		| l -> print ctx "$%s" (String.concat ", $" l)
 		);
 		spr ctx ")";
-		
+
 		ctx.inline_methods <- ctx.inline_methods @ [block]
-		
+
 and inline_function ctx args hasthis e =
 		let index = ctx.inline_index in
 		ctx.inline_index <- ctx.inline_index + 1;
-		let block = { 
+		let block = {
 			iname = (s_path ctx ctx.curclass.cl_path ctx.curclass.cl_extern ctx.curclass.cl_pos) ^ "_" ^ string_of_int index;
-			iindex = index; 
+			iindex = index;
 			ihasthis = hasthis; (* param this *)
 			iarguments = args;
 			iexpr = e;
@@ -1561,7 +1561,7 @@ and inline_function ctx args hasthis e =
 			iin_block = false;
 			iinv_locals = ctx.inv_locals;
 		} in
-		
+
 		ctx.inline_methods <- ctx.inline_methods @ [block];
 		block.iname
 and gen_value ctx e =
@@ -1596,7 +1596,7 @@ and gen_value ctx e =
 	| TThrow _
 	| TSwitch _
 	| TFor _
-	| TMatch _ 
+	| TMatch _
 	| TIf _
 	| TTry _ ->
 		inline_block ctx e
@@ -1620,7 +1620,7 @@ let generate_self_method ctx rights m static setter =
 			print ctx "%s function %s() { return call_user_func($this->%s); }" rights (s_ident m) (s_ident m)
 	);
 	newline ctx
-	
+
 let generate_field ctx static f =
 	newline ctx;
 	ctx.locals <- PMap.empty;
@@ -1638,7 +1638,7 @@ let generate_field ctx static f =
 		if is_dynamic_method f then
 			gen_dynamic_function ctx static (s_ident f.cf_name) fd f.cf_params p
 		else
-			gen_function ctx (s_ident f.cf_name) fd f.cf_params p		
+			gen_function ctx (s_ident f.cf_name) fd f.cf_params p
 	| _ ->
 		if ctx.curclass.cl_interface then
 			match follow f.cf_type with
@@ -1680,7 +1680,7 @@ let generate_field ctx static f =
 			let name = s_ident f.cf_name in
 			if static then
 				(match f.cf_kind with
-				| Var _ -> 
+				| Var _ ->
 					(match follow f.cf_type with
 					| TFun _
 					| TDynamic _ ->
@@ -1713,13 +1713,13 @@ let generate_static_field_assign ctx path f =
 			| TConst _ -> ()
 			| TFunction fd ->
 				(match f.cf_kind with
-				| Var _ when 
+				| Var _ when
 						(match follow f.cf_type with
 						| TFun _
 						| TDynamic _ ->
 							true;
 						| _ ->
-							false) -> 
+							false) ->
 					newline ctx;
 					print ctx "%s::$%s = " (s_path ctx path false p) (s_ident f.cf_name);
 					gen_value ctx e
@@ -1739,22 +1739,22 @@ let rec super_has_dynamic c =
 	| Some (csup, _) -> (match csup.cl_dynamic with
 		| Some _ -> true
 		| _ -> super_has_dynamic csup)
-				
+
 let generate_inline_method ctx c m =
 	(match ctx.inline_methods with
 	| [] -> ()
 	| h :: t -> ctx.inline_methods <- t
 	);
 	ctx.curclass <- c;
-	
+
 	let old = save_locals ctx in
 	ctx.in_value <- Some m.iname;
 	ctx.in_block <- m.iin_block;
-	ctx.in_loop <- false; 
+	ctx.in_loop <- false;
 	ctx.locals <- m.ilocals;
 	ctx.inv_locals <- m.iinv_locals;
-	
-	newline ctx;	
+
+	newline ctx;
 	print ctx "function %s(" m.iname;
 	(* arguments *)
 	let in_value = (match ctx.in_value with Some _ -> true | _ -> false) in
@@ -1764,10 +1764,10 @@ let generate_inline_method ctx c m =
 	| h :: t when h = "this" -> "»this" :: t
 	| _ -> arguments
 	in
-	
+
 	let marguments = List.map (define_local ctx) m.iarguments in
 	let arguments =  (List.map (fun a -> "&$" ^ a) arguments) @ (List.map (fun a -> "$" ^ a) marguments) in
-	
+
 	(match arguments with
 	| [] -> ()
 	| l  -> spr ctx (String.concat ", " arguments)
@@ -1776,7 +1776,7 @@ let generate_inline_method ctx c m =
 	ctx.nested_loops <- ctx.nested_loops - 1;
 	let block = open_block ctx in
 	newline ctx;
-	
+
 	(* blocks *)
 	if ctx.com.debug then begin
 		print ctx "\t$GLOBALS['%s']->push('%s:lambda_%d')" "%s" (s_path_haxe c.cl_path) m.iindex;
@@ -1790,7 +1790,7 @@ let generate_inline_method ctx c m =
 	ctx.nested_loops <- ctx.nested_loops + 1;
 	newline ctx;
 	spr ctx "}"
-	
+
 let generate_class ctx c =
 	let requires_constructor = ref true in
 	ctx.curclass <- c;
@@ -1809,7 +1809,7 @@ let generate_class ctx c =
 		concat ctx ", " (fun (i,_) ->
 		print ctx "%s" (s_path ctx i.cl_path i.cl_extern c.cl_pos)) l);
 	spr ctx "{";
-	
+
 	let get_dynamic_methods = List.filter is_dynamic_method c.cl_ordered_fields in
 
 	if not ctx.curclass.cl_interface then ctx.dynamic_methods <- get_dynamic_methods;
@@ -1848,7 +1848,7 @@ let generate_class ctx c =
 
 	cl();
 	newline ctx;
-		
+
 	if PMap.exists "__toString" c.cl_fields then
 		()
 	else if PMap.exists "toString" c.cl_fields && (not c.cl_interface) && (not c.cl_extern) then begin
@@ -1858,10 +1858,10 @@ let generate_class ctx c =
 		print ctx "\tfunction __toString() { return '%s'; }" ((s_path_haxe c.cl_path)) ;
 		newline ctx
 	end;
-	
+
 	print ctx "}"
-	
-	
+
+
 let createmain com e =
 	let filename = match com.php_front with None -> "index.php" | Some n -> n in
 	let ctx = {
@@ -1936,28 +1936,28 @@ let generate_enum ctx e =
 			print ctx "public static $%s" c.ef_name;
 	) e.e_constrs;
 	newline ctx;
-	
+
 	spr ctx "public static $__constructors = array(";
-	
+
 	let first = ref true in
 	PMap.iter (fun _ c ->
 		if not !first then spr ctx ", ";
 		print ctx "%d => '%s'" c.ef_index c.ef_name;
 		first := false;
 	) e.e_constrs;
-	
+
 	spr ctx ")";
-	
+
 	newline ctx;
-	
+
 	(match Codegen.build_metadata ctx.com (TEnumDecl e) with
 	| None -> ()
 	| Some _ ->
 		spr ctx "public static $__meta__";
 		newline ctx);
-	
+
 	pack();
-	
+
 	print ctx "}";
 
 	PMap.iter (fun _ c ->
@@ -1970,7 +1970,7 @@ let generate_enum ctx e =
 	) e.e_constrs;
 
 	newline ctx;
-	
+
 	match Codegen.build_metadata ctx.com (TEnumDecl e) with
 	| None -> ()
 	| Some e ->
@@ -1982,12 +1982,12 @@ let generate com =
 	let all_dynamic_methods = ref [] in
 	let extern_classes_with_init = ref [] in
 	let php_lib_path = (match com.php_lib with None -> "lib" | Some n -> n) in
- 	create_directory com (Str.split (Str.regexp "/")  php_lib_path);    
+ 	create_directory com (Str.split (Str.regexp "/")  php_lib_path);
 	(* check for methods with the same name but different case *)
 	let check_class_fields c =
 		let lc_names = ref [] in
 		let special_cases = ["toString"] in
-		let loop c lst static = 
+		let loop c lst static =
 			let in_special_cases name =
 				(List.exists (fun n -> String.lowercase n = name) (special_cases @ c.cl_overrides))
 			in
@@ -1996,8 +1996,8 @@ let generate com =
 				let prefixed_name s = (if s then "s_" else "i_") ^ name in
 				match cf.cf_kind, cf.cf_expr with
 				| (Method _, Some e) when not (in_special_cases name) ->
-					(try 
-						let lc = List.find (fun n -> 
+					(try
+						let lc = List.find (fun n ->
 							let n = snd n in
 							if static then
 								(n = (prefixed_name false))
@@ -2011,7 +2011,7 @@ let generate com =
 					()
 			) lst
 		in
-		let rec _check_class_fields cl = 
+		let rec _check_class_fields cl =
 			(match cl.cl_super with
 			| Some (s,_) -> _check_class_fields s
 			| _ -> ());
@@ -2044,12 +2044,12 @@ let generate com =
 				}) (List.filter is_dynamic_method lst)
 			in
 			all_dynamic_methods := dynamic_methods_names c.cl_ordered_fields @ !all_dynamic_methods;
-			
+
 			if c.cl_extern then
 				(match c.cl_init with
 				| Some _ ->
 					extern_classes_with_init := c.cl_path :: !extern_classes_with_init;
-				| _ -> 
+				| _ ->
 					())
 			else
 				all_dynamic_methods := dynamic_methods_names c.cl_ordered_statics @ !all_dynamic_methods;
@@ -2070,9 +2070,9 @@ let generate com =
 				let ctx = init com php_lib_path c.cl_path (if c.cl_interface then 2 else 0) in
 				ctx.extern_classes_with_init <- !extern_classes_with_init;
 				ctx.all_dynamic_methods <- !all_dynamic_methods;
-				
+
 				generate_class ctx c;
-				
+
 				(match c.cl_init with
 				| None -> ()
 				| Some e ->
@@ -2085,16 +2085,16 @@ let generate com =
 					newline ctx;
 					print ctx "$%s = new _hx_array(array())" ctx.stack.Codegen.stack_exc_var;
 				end;
-				
+
 				let rec loop l =
 					match l with
 					| [] -> ()
-					| h :: _ -> 
+					| h :: _ ->
 						generate_inline_method ctx c h;
 						loop ctx.inline_methods
 				in
 				loop ctx.inline_methods;
-				newline ctx;				
+				newline ctx;
 				close ctx
 		| TEnumDecl e ->
 			if e.e_extern then

+ 5 - 5
genswf.ml

@@ -605,16 +605,16 @@ let build_dependencies t =
 			List.iter add_type pl;
 			List.iter add_expr el;
 		| TFunction f ->
-			List.iter (fun (_,_,t) -> add_type t) f.tf_args;
+			List.iter (fun (v,_) -> add_type v.v_type) f.tf_args;
 			add_type f.tf_type;
 			add_expr f.tf_expr;
-		| TFor (_,t,e1,e2) ->
-			add_type t;
+		| TFor (v,e1,e2) ->
+			add_type v.v_type;
 			add_expr e1;
 			add_expr e2;
 		| TVars vl ->
-			List.iter (fun (_,t,e) ->
-				add_type t;
+			List.iter (fun (v,e) ->
+				add_type v.v_type;
 				match e with
 				| None -> ()
 				| Some e -> add_expr e

+ 70 - 64
genswf8.ml

@@ -58,7 +58,6 @@ type context = {
 	mutable static_init : bool;
 
 	(* loops *)
-	mutable cur_block : texpr list;
 	mutable breaks : (unit -> unit) list;
 	mutable continues : (int -> unit) list;
 	mutable loop_stack : int;
@@ -401,11 +400,9 @@ let begin_func ctx need_super need_args args =
 let open_block ctx =
 	let old_regs = ctx.regs in
 	let old_rcount = ctx.reg_count in
-	let old_block = ctx.cur_block in
 	(fun() ->
 		ctx.regs <- old_regs;
 		ctx.reg_count <- old_rcount;
-		ctx.cur_block <- old_block;
 	)
 
 let begin_loop ctx =
@@ -447,10 +444,10 @@ let segment ctx =
 (* -------------------------------------------------------------- *)
 (* Generation Helpers *)
 
-let define_var ctx v ef exprs =
-	if ctx.flash6 || List.exists (Codegen.local_find false v) exprs || ctx.static_init then begin
-		push ctx [VStr (v,false)];
-		ctx.regs <- PMap.add v NoReg ctx.regs;
+let define_var ctx v ef =
+	if ctx.flash6 || v.v_capture || ctx.static_init then begin
+		push ctx [VStr (v.v_name,false)];
+		ctx.regs <- PMap.add v.v_name NoReg ctx.regs;
 		match ef with
 		| None ->
 			write ctx ALocalVar
@@ -459,7 +456,7 @@ let define_var ctx v ef exprs =
 			write ctx ALocalAssign
 	end else begin
 		let r = alloc_reg ctx in
-		ctx.regs <- PMap.add v (Reg r) ctx.regs;
+		ctx.regs <- PMap.add v.v_name (Reg r) ctx.regs;
 		match ef with
 		| None -> ()
 		| Some f ->
@@ -470,8 +467,8 @@ let define_var ctx v ef exprs =
 let alloc_tmp ctx =
 	let r = alloc_reg ctx in
 	if ctx.flash6 then
-		let name = "$" ^ string_of_int r in
-		define_var ctx name None [];
+		let name = "$" ^ string_of_int r in		
+		define_var ctx (alloc_var name t_dynamic) None;
 		TmpVar (name,r);
 	else
 		TmpReg r
@@ -578,11 +575,11 @@ let rec gen_access ?(read_write=false) ctx forcall e =
 			VarStr
 		end else
 			VarReg 1
-	| TLocal "__arguments__" ->
+	| TLocal { v_name = "__arguments__" } ->
 		push ctx [VStr ("arguments",true)];
 		VarStr
-	| TLocal s ->
-		access_local ctx s
+	| TLocal v ->
+		access_local ctx v.v_name
 	| TField (e2,f) ->
 		gen_expr ctx true e2;
 		if read_write then write ctx ADup;
@@ -602,9 +599,9 @@ let rec gen_access ?(read_write=false) ctx forcall e =
 		push ctx [VStr (f,is_protected ctx e.etype f)];
 		VarClosure
 	| TArray (ea,eb) ->
-		if read_write then 
-			try 
-				let r = (match ea.eexpr with TLocal l -> (match PMap.find l ctx.regs with Reg r -> r | _ -> raise Not_found) | _ -> raise Not_found) in
+		if read_write then
+			try
+				let r = (match ea.eexpr with TLocal l -> (match PMap.find l.v_name ctx.regs with Reg r -> r | _ -> raise Not_found) | _ -> raise Not_found) in
 				push ctx [VReg r];
 				gen_expr ctx true eb;
 				write ctx ADup;
@@ -644,7 +641,7 @@ and gen_access_rw ctx e =
 	match e.eexpr with
 	| TField ({ eexpr = TLocal _ },_) | TArray ({ eexpr = TLocal _ },{ eexpr = TConst _ }) | TArray ({ eexpr = TLocal _ },{ eexpr = TLocal _ }) ->
 		ignore(gen_access ctx false e);
-		gen_access ctx false e		
+		gen_access ctx false e
 	| TField _ | TArray _ ->
 		gen_access ~read_write:true ctx false e
 	| _ ->
@@ -656,10 +653,10 @@ and gen_try_catch ctx retval e catchs =
 	gen_expr ctx retval e;
 	let end_try = start_try() in
 	let end_throw = ref true in
-	let jumps = List.map (fun (name,t,e) ->
+	let jumps = List.map (fun (v,e) ->
 		if not !end_throw then
 			(fun () -> ())
-		else let t = (match follow t with
+		else let t = (match follow v.v_type with
 			| TEnum (e,_) -> Some (TEnumDecl e)
 			| TInst (c,_) -> Some (TClassDecl c)
 			| TFun _
@@ -683,7 +680,7 @@ and gen_try_catch ctx retval e catchs =
 			cjmp ctx
 		) in
 		let block = open_block ctx in
-		define_var ctx name (Some (fun() -> push ctx [VReg 0])) [e];
+		define_var ctx v (Some (fun() -> push ctx [VReg 0]));
 		gen_expr ctx retval e;
 		block();
 		if retval then ctx.stack_size <- ctx.stack_size - 1;
@@ -754,16 +751,16 @@ and gen_match ctx retval e cases def =
 		let nregs = ctx.reg_count in
 		List.iter (fun j -> j()) jl;
 		let n = ref 1 in
-		List.iter (fun (a,t) ->
+		List.iter (fun v ->
 			incr n;
-			match a with
+			match v with
 			| None -> ()
-			| Some a ->
-				define_var ctx a (Some (fun() ->
+			| Some v ->
+				define_var ctx v (Some (fun() ->
 					get_tmp ctx renum;
 					push ctx [VInt !n];
 					write ctx AObjGet
-				)) [e]
+				))
 		) (match args with None -> [] | Some l -> l);
 		gen_expr ctx retval e;
 		if retval then ctx.stack_size <- ctx.stack_size - 1;
@@ -858,49 +855,50 @@ and gen_unop ctx retval op flag e =
 		let k = gen_access_rw ctx e in
 		getvar ctx k;
 		(* store preincr value for later access *)
-		if retval && flag = Postfix then write ctx (ASetReg 0);		
+		if retval && flag = Postfix then write ctx (ASetReg 0);
 		write ctx (match op with Increment -> AIncrement | Decrement -> ADecrement | _ -> assert false);
 		setvar ~retval:(retval && flag = Prefix) ctx k;
 		if retval && flag = Postfix then push ctx [VReg 0]
 
 and gen_call ctx e el =
-	match e.eexpr, el with
-	| TLocal "__instanceof__" ,  [e1;e2] ->
+	let loc = match e.eexpr with TLocal v -> v.v_name | _ -> "" in
+	match loc, el with
+	| "__instanceof__" ,  [e1;e2] ->
 		gen_expr ctx true e1;
 		gen_expr ctx true e2;
 		write ctx AInstanceOf
-	| TLocal "__typeof__" , [e] ->
+	| "__typeof__" , [e] ->
 		gen_expr ctx true e;
 		write ctx ATypeOf
-	| TLocal "__delete__" , [e1; e2] ->
+	| "__delete__" , [e1; e2] ->
 		gen_expr ctx true e1;
 		gen_expr ctx true e2;
 		write ctx ADeleteObj
-	| TLocal "__random__" , [e] ->
+	| "__random__" , [e] ->
 		gen_expr ctx true e;
 		write ctx ARandom
-	| TLocal "__trace__" , [e] ->
+	| "__trace__" , [e] ->
 		gen_expr ctx true e;
 		write ctx ATrace
-	| TLocal "__eval__" , [e] ->
+	| "__eval__" , [e] ->
 		gen_expr ctx true e;
 		write ctx AEval
-	| TLocal "__gettimer__", [] ->
+	| "__gettimer__", [] ->
 		write ctx AGetTimer
-	| TLocal "__undefined__", [] ->
-		push ctx [VUndefined]		
-	| TLocal "__geturl__" , url :: target :: post ->
+	| "__undefined__", [] ->
+		push ctx [VUndefined]
+	| "__geturl__" , url :: target :: post ->
 		gen_expr ctx true url;
 		gen_expr ctx true target;
 		write ctx (AGetURL2 (match post with [] -> 0 | [{ eexpr = TConst (TString "GET") }] -> 1 | _ -> 2))
-	| TLocal "__new__", e :: el ->
+	| "__new__", e :: el ->
 		let nargs = List.length el in
 		List.iter (gen_expr ctx true) (List.rev el);
 		push ctx [VInt nargs];
 		let k = gen_access ctx true e in
 		new_call ctx k nargs
-	| TLocal "__keys__", [e2]
-	| TLocal "__hkeys__", [e2] ->
+	| "__keys__", [e2]
+	| "__hkeys__", [e2] ->
 		let r = alloc_tmp ctx in
 		push ctx [VInt 0; VStr ("Array",true)];
 		new_call ctx VarStr 0;
@@ -914,7 +912,7 @@ and gen_call ctx e el =
 		push ctx [VNull];
 		write ctx AEqual;
 		let jump_end = cjmp ctx in
-		if e.eexpr = TLocal "__hkeys__" then begin
+		if loc = "__hkeys__" then begin
 			push ctx [VInt 1; VInt 1; VReg 0; VStr ("substr",true)];
 			call ctx VarObj 1;
 		end else begin
@@ -929,19 +927,19 @@ and gen_call ctx e el =
 		jump_end();
 		get_tmp ctx r;
 		free_tmp ctx r e2.epos;
-	| TLocal "__physeq__" ,  [e1;e2] ->
+	| "__physeq__" ,  [e1;e2] ->
 		gen_expr ctx true e1;
 		gen_expr ctx true e2;
 		write ctx APhysEqual;
-	| TLocal "__unprotect__", [{ eexpr = TConst (TString s) }] ->
+	| "__unprotect__", [{ eexpr = TConst (TString s) }] ->
 		push ctx [VStr (s,false)]
-	| TLocal "__resources__", [] ->
+	| "__resources__", [] ->
 		let count = ref 0 in
 		Hashtbl.iter (fun name data ->
 			incr count;
 			push ctx [VStr ("name",false);VStr (name,true)];
 			(* if the data contains \0 or is not UTF8 valid, encode into bytes *)
-			(try 
+			(try
 				(try ignore(String.index data '\000'); raise Exit; with Not_found -> ());
 				UTF8.validate data;
 				push ctx [VStr ("str",false)];
@@ -954,7 +952,7 @@ and gen_call ctx e el =
 			ctx.stack_size <- ctx.stack_size - 4;
 		) ctx.com.resources;
 		init_array ctx !count
-	| TLocal "__FSCommand2__", l ->
+	| "__FSCommand2__", l ->
 		let nargs = List.length l in
 		List.iter (gen_expr ctx true) (List.rev l);
 		push ctx [VInt nargs];
@@ -988,10 +986,8 @@ and gen_expr_2 ctx retval e =
 			| [] ->
 				if retval then push ctx [VNull]
 			| [e] ->
-				ctx.cur_block <- [];
 				gen_expr ctx retval e
 			| e :: l ->
-				ctx.cur_block <- l;
 				gen_expr ctx false e;
 				loop l
 		in
@@ -999,8 +995,8 @@ and gen_expr_2 ctx retval e =
 		loop el;
 		b()
 	| TVars vl ->
-		List.iter (fun (v,t,e) ->
-			define_var ctx v (match e with None -> None | Some e -> Some (fun() -> gen_expr ctx true e)) ctx.cur_block
+		List.iter (fun (v,e) ->
+			define_var ctx v (match e with None -> None | Some e -> Some (fun() -> gen_expr ctx true e))
 		) vl;
 		if retval then push ctx [VNull]
 	| TArrayDecl el ->
@@ -1019,7 +1015,18 @@ and gen_expr_2 ctx retval e =
 		let block = open_block ctx in
 		let old_in_loop = ctx.in_loop in
 		let old_meth = ctx.curmethod in
-		let reg_super = Codegen.local_find true "super" f.tf_expr in
+		let rec loop e =
+			match e.eexpr with
+			| TConst TSuper -> raise Exit
+			| _ -> Type.iter loop e
+		in
+		let reg_super = try loop f.tf_expr; false with Exit -> true in
+		let rec loop e =
+			match e.eexpr with
+			| TLocal { v_name = "__arguments__" } -> raise Exit
+			| _ -> Type.iter loop e
+		in
+		let reg_args = try loop f.tf_expr; false with Exit -> true in
 		if snd ctx.curmethod then
 			ctx.curmethod <- (fst ctx.curmethod ^ "@" ^ string_of_int (Lexer.get_error_line e.epos), true)
 		else
@@ -1033,25 +1040,25 @@ and gen_expr_2 ctx retval e =
 		ctx.reg_count <- (if reg_super then 2 else 1);
 		ctx.in_loop <- false;
 		let pargs = ref [] in
-		let rargs = List.map (fun (a,_,t) ->
-			let no_reg = ctx.flash6 || Codegen.local_find false a f.tf_expr in
+		let rargs = List.map (fun (v,_) ->
+			let no_reg = ctx.flash6 || v.v_capture in
 			if no_reg then begin
-				ctx.regs <- PMap.add a NoReg ctx.regs;
-				pargs := unprotect a :: !pargs;
-				0 , a
+				ctx.regs <- PMap.add v.v_name NoReg ctx.regs;
+				pargs := unprotect v.v_name :: !pargs;
+				0 , v.v_name
 			end else begin
 				let r = alloc_reg ctx in
-				ctx.regs <- PMap.add a (Reg r) ctx.regs;
+				ctx.regs <- PMap.add v.v_name (Reg r) ctx.regs;
 				pargs := false :: !pargs;
 				r , ""
 			end
 		) f.tf_args in
-		let tf = begin_func ctx reg_super (Codegen.local_find true "__arguments__" f.tf_expr) rargs in
+		let tf = begin_func ctx reg_super reg_args rargs in
 		ctx.fun_pargs <- (ctx.code_pos, List.rev !pargs) :: ctx.fun_pargs;
-		List.iter (fun (a,c,t) ->
+		List.iter (fun (v,c) ->
 			match c with
 			| None | Some TNull -> ()
-			| Some c -> gen_expr ctx false (Codegen.set_default ctx.com a c t e.epos)
+			| Some c -> gen_expr ctx false (Codegen.set_default ctx.com v c e.epos)
 		) f.tf_args;
 		if ctx.com.debug then begin
 			gen_expr ctx false (ctx.stack.Codegen.stack_push ctx.curclass (fst ctx.curmethod));
@@ -1161,7 +1168,7 @@ and gen_expr_2 ctx retval e =
 		gen_expr ctx retval (Codegen.default_cast ctx.com e1 t e.etype e.epos)
 	| TMatch (e,_,cases,def) ->
 		gen_match ctx retval e cases def
-	| TFor (v,_,it,e) ->
+	| TFor (v,it,e) ->
 		gen_expr ctx true it;
 		let r = alloc_tmp ctx in
 		set_tmp ctx r;
@@ -1181,12 +1188,12 @@ and gen_expr_2 ctx retval e =
 			get_tmp ctx r;
 			push ctx [VStr ("next",false)];
 			call ctx VarObj 0;
-		)) [e];
+		));
 		gen_expr ctx false e;
 		j_begin false;
 		j_end();
 		loop_end cont_pos;
-		if retval then getvar ctx (access_local ctx v);
+		if retval then getvar ctx (access_local ctx v.v_name);
 		b();
 		free_tmp ctx r null_pos
 
@@ -1507,7 +1514,6 @@ let generate com =
 		regs = PMap.empty;
 		reg_count = 0;
 		reg_max = 0;
-		cur_block = [];
 		breaks = [];
 		continues = [];
 		loop_stack = 0;

+ 82 - 84
genswf9.ml

@@ -83,14 +83,13 @@ type context = {
 	mutable last_line : int;
 	mutable last_file : string;
 	(* per-function *)
-	mutable locals : (string,local) PMap.t;
+	mutable locals : (int,tvar * local) PMap.t;
 	mutable code : hl_opcode DynArray.t;
 	mutable infos : code_infos;
 	mutable trys : try_infos list;
 	mutable breaks : (unit -> unit) list;
 	mutable continues : (int -> unit) list;
 	mutable in_static : bool;
-	mutable curblock : texpr list;
 	mutable block_vars : (hl_slot * string * hl_name option) list;
 	mutable used_vars : (string , pos) PMap.t;
 	mutable try_scope_reg : register option;
@@ -238,7 +237,7 @@ let classify ctx t =
 	| TEnum (e,_) ->
 		let rec loop = function
 			| [] -> KType (type_id ctx t)
-			| (":fakeEnum",[Ast.EConst (Type n),_],_) :: _ ->				
+			| (":fakeEnum",[Ast.EConst (Type n),_],_) :: _ ->
 				(match n with
 				| "Int" -> KInt
 				| "UInt" -> KUInt
@@ -388,8 +387,10 @@ let pop ctx n =
 	loop n;
 	ctx.infos.istack <- old
 
-let define_local ctx ?(init=false) name t el p =
-	let l = (if List.exists (Codegen.local_find false name) el then begin
+let define_local ctx ?(init=false) v p =
+	let name = v.v_name in
+	let t = v.v_type in
+	let l = (if v.v_capture then begin
 			let topt = type_opt ctx t in
 			let pos = (try
 				let slot , _ , t = (List.find (fun (_,x,_) -> name = x) ctx.block_vars) in
@@ -408,12 +409,12 @@ let define_local ctx ?(init=false) name t el p =
 			r.rinit <- init;
 			LReg r
 	) in
-	ctx.locals <- PMap.add name l ctx.locals
+	ctx.locals <- PMap.add v.v_id (v,l) ctx.locals
 
 let is_set v = (Obj.magic v) = Write
 
-let gen_local_access ctx name p (forset : 'a)  : 'a access =
-	match (try PMap.find name ctx.locals with Not_found -> error ("Unbound variable " ^ name) p) with
+let gen_local_access ctx v p (forset : 'a)  : 'a access =
+	match snd (try PMap.find v.v_id ctx.locals with Not_found -> error ("Unbound variable " ^ v.v_name) p) with
 	| LReg r ->
 		VReg r
 	| LScope n ->
@@ -423,8 +424,8 @@ let gen_local_access ctx name p (forset : 'a)  : 'a access =
 		if is_set forset then write ctx (HFindProp p);
 		VGlobal p
 
-let get_local_register ctx name =
-	match (try PMap.find name ctx.locals with Not_found -> LScope 0) with
+let get_local_register ctx v =
+	match (try snd (PMap.find v.v_id ctx.locals) with Not_found -> LScope 0) with
 	| LReg r -> Some r
 	| _ -> None
 
@@ -483,12 +484,10 @@ let getvar ctx (acc : read access) =
 	| VScope n ->
 		write ctx (HGetSlot n)
 
-let open_block ctx el retval =
+let open_block ctx retval =
 	let old_stack = ctx.infos.istack in
 	let old_regs = DynArray.map (fun r -> r.rused) ctx.infos.iregs in
 	let old_locals = ctx.locals in
-	let old_block = ctx.curblock in
-	ctx.curblock <- el;
 	(fun() ->
 		if ctx.infos.istack <> old_stack + (if retval then 1 else 0) then assert false;
 		let rcount = DynArray.length old_regs + 1 in
@@ -499,7 +498,6 @@ let open_block ctx el retval =
 				r.rused <- false
 		) ctx.infos.iregs;
 		ctx.locals <- old_locals;
-		ctx.curblock <- old_block;
 	)
 
 let begin_branch ctx =
@@ -575,12 +573,12 @@ let end_fun ctx args dparams tret =
 	{
 		hlmt_index = 0;
 		hlmt_ret = type_void ctx tret;
-		hlmt_args = List.map (fun (_,_,t) -> type_opt ctx t) args;
+		hlmt_args = List.map (fun (v,_) -> type_opt ctx v.v_type) args;
 		hlmt_native = false;
 		hlmt_var_args = false;
 		hlmt_debug_name = None;
 		hlmt_dparams = dparams;
-		hlmt_pnames = if ctx.swc || ctx.debugger then Some (List.map (fun (n,_,_) -> Some n) args) else None;
+		hlmt_pnames = if ctx.swc || ctx.debugger then Some (List.map (fun (v,_) -> Some v.v_name) args) else None;
 		hlmt_new_block = false;
 		hlmt_unused_flag = false;
 		hlmt_arguments_defined = false;
@@ -614,11 +612,11 @@ let begin_fun ctx args tret el stat p =
 		| _ -> Type.iter find_this e
 	in
 	let this_reg = try List.iter find_this el; false with Exit -> true in
-	ctx.locals <- PMap.foldi (fun name l acc ->
+	ctx.locals <- PMap.foldi (fun _ (v,l) acc ->
 		match l with
 		| LReg _ -> acc
-		| LScope _ -> PMap.add name (LGlobal (ident name)) acc
-		| LGlobal _ -> PMap.add name l acc
+		| LScope _ -> PMap.add v.v_id (v,LGlobal (ident v.v_name)) acc
+		| LGlobal _ -> PMap.add v.v_id (v,l) acc
 	) ctx.locals PMap.empty;
 
 	let dparams = ref None in
@@ -629,7 +627,7 @@ let begin_fun ctx args tret el stat p =
 			(match c with
 			| TInt i -> if kind = KUInt then HVUInt i else HVInt i
 			| TFloat s -> HVFloat (float_of_string s)
-			| TBool b -> HVBool b			
+			| TBool b -> HVBool b
 			| TNull -> error ("In Flash9, null can't be used as basic type " ^ s_type (print_context()) t) p
 			| _ -> assert false)
 		| _, Some TNull -> HVNone
@@ -645,12 +643,13 @@ let begin_fun ctx args tret el stat p =
 		) in
 		match !dparams with
 		| None -> if c <> None then dparams := Some [v]
-		| Some l -> dparams := Some (v :: l)		
+		| Some l -> dparams := Some (v :: l)
 	in
 
-	List.iter (fun (name,c,t) ->
-		define_local ctx name ~init:true t el p;		
-		match gen_local_access ctx name null_pos Write with
+	List.iter (fun (v,c) ->
+		let t = v.v_type in
+		define_local ctx v ~init:true p;
+		match gen_local_access ctx v null_pos Write with
 		| VReg r ->
 			make_constant_value r c t
 		| acc ->
@@ -662,7 +661,7 @@ let begin_fun ctx args tret el stat p =
 
 	let dparams = (match !dparams with None -> None | Some l -> Some (List.rev l)) in
 	let args, varargs = (match args with
-		| ["__arguments__",_,_] -> [], true
+		| [{ v_name = "__arguments__" },_] -> [], true
 		| _ -> args, false
 	) in
 	let rec loop_try e =
@@ -783,8 +782,8 @@ let use_var ctx f p =
 
 let gen_access ctx e (forset : 'a) : 'a access =
 	match e.eexpr with
-	| TLocal i ->
-		gen_local_access ctx i e.epos forset
+	| TLocal v ->
+		gen_local_access ctx v e.epos forset
 	| TField (e1,f) | TClosure (e1,f) ->
 		let id, k, closure = property ctx f e1.etype in
 		if closure && not ctx.for_call then error "In Flash9, this method cannot be accessed this way : please define a local function" e1.epos;
@@ -818,7 +817,7 @@ let gen_access ctx e (forset : 'a) : 'a access =
 			else
 				VCast (id,classify ctx e.etype)
 		)
-	| TArray ({ eexpr = TLocal "__global__" },{ eexpr = TConst (TString s) }) ->
+	| TArray ({ eexpr = TLocal { v_name = "__global__" } },{ eexpr = TConst (TString s) }) ->
 		let path = parse_path s in
 		let id = type_path ctx path in
 		if is_set forset then write ctx HGetGlobalScope;
@@ -836,8 +835,8 @@ let gen_access ctx e (forset : 'a) : 'a access =
 
 let gen_expr_twice ctx e =
 	match e.eexpr with
-	| TLocal l ->
-		(match get_local_register ctx l with
+	| TLocal v ->
+		(match get_local_register ctx v with
 		| Some r ->
 			write ctx (HReg r.rid);
 			write ctx (HReg r.rid);
@@ -862,7 +861,7 @@ let gen_access_rw ctx e : (read access * write access) =
 		let r = gen_access ctx e Read in
 		r, w
 	| TArray (e,eindex) ->
-		let r = (match e.eexpr with TLocal l -> get_local_register ctx l | _ -> None) in
+		let r = (match e.eexpr with TLocal v -> get_local_register ctx v | _ -> None) in
 		(match r with
 		| None ->
 			let r = alloc_reg ctx (classify ctx e.etype) in
@@ -932,19 +931,17 @@ let rec gen_expr_content ctx retval e =
 			| [] ->
 				if retval then write ctx HNull
 			| [e] ->
-				ctx.curblock <- [];
 				gen_expr ctx retval e
 			| e :: l ->
-				ctx.curblock <- l;
 				gen_expr ctx false e;
 				loop l
 		in
-		let b = open_block ctx [] retval in
+		let b = open_block ctx retval in
 		loop el;
 		b();
 	| TVars vl ->
-		List.iter (fun (v,t,ei) ->
-			define_local ctx v t ctx.curblock e.epos;
+		List.iter (fun (v,ei) ->
+			define_local ctx v e.epos;
 			(match ei with
 			| None -> ()
 			| Some e ->
@@ -1031,8 +1028,9 @@ let rec gen_expr_content ctx retval e =
 		let jend = jump ctx J3Always in
 		let rec loop ncases = function
 			| [] -> []
-			| (ename,t,e) :: l ->
-				let b = open_block ctx [e] retval in
+			| (v,e) :: l ->
+				let b = open_block ctx retval in
+				let t = v.v_type in
 				ctx.trys <- {
 					tr_pos = p;
 					tr_end = pend;
@@ -1046,15 +1044,15 @@ let rec gen_expr_content ctx retval e =
 				write ctx (HReg (match ctx.try_scope_reg with None -> assert false | Some r -> r.rid));
 				write ctx HScope;
 				(* store the exception into local var, using a tmp register if needed *)
-				define_local ctx ename t [e] e.epos;
-				let r = (match try PMap.find ename ctx.locals with Not_found -> assert false with
+				define_local ctx v e.epos;
+				let r = (match snd (try PMap.find v.v_id ctx.locals with Not_found -> assert false) with
 					| LReg _ -> None
 					| _ ->
 						let r = alloc_reg ctx (classify ctx t) in
 						set_reg ctx r;
 						Some r
 				) in
-				let acc = gen_local_access ctx ename e.epos Write in
+				let acc = gen_local_access ctx v e.epos Write in
 				(match r with None -> () | Some r -> write ctx (HReg r.rid));
 				setvar ctx acc None;
 				(* ----- *)
@@ -1066,11 +1064,11 @@ let rec gen_expr_content ctx retval e =
 				in
 				let has_call = (try call_loop e; false with Exit -> true) in
 				if has_call then begin
-					getvar ctx (gen_local_access ctx ename e.epos Read);
+					getvar ctx (gen_local_access ctx v e.epos Read);
 					write ctx (HAsType (type_path ctx (["flash";"errors"],"Error")));
 					let j = jump ctx J3False in
 					getvar ctx (VGlobal (type_path ctx (["flash"],"Boot")));
-					getvar ctx (gen_local_access ctx ename e.epos Read);
+					getvar ctx (gen_local_access ctx v e.epos Read);
 					setvar ctx (VId (ident "lastError")) None;
 					j();
 				end;
@@ -1087,13 +1085,13 @@ let rec gen_expr_content ctx retval e =
 		List.iter (fun j -> j()) loops;
 		branch();
 		jend()
-	| TFor (v,t,it,e) ->
+	| TFor (v,it,e) ->
 		gen_expr ctx true it;
 		let r = alloc_reg ctx KDynamic in
 		set_reg ctx r;
 		let branch = begin_branch ctx in
-		let b = open_block ctx [e] retval in
-		define_local ctx v t [e] e.epos;
+		let b = open_block ctx retval in
+		define_local ctx v e.epos;
 		let end_loop = begin_loop ctx in
 		let continue_pos = ctx.infos.ipos in
 		let start = jump_back ctx in
@@ -1228,17 +1226,17 @@ let rec gen_expr_content ctx retval e =
 			let j = jump ctx J3Always in
 			List.iter case cl;
 			pop_value ctx retval;
-			let b = open_block ctx [e] retval in
+			let b = open_block ctx retval in
 			(match params with
 			| None -> ()
 			| Some l ->
 				let p = ref (-1) in
-				List.iter (fun (name,t) ->
+				List.iter (fun v ->
 					incr p;
-					match name with
+					match v with
 					| None -> ()
 					| Some v ->
-						define_local ctx v t [e] e.epos;
+						define_local ctx v e.epos;
 						let acc = gen_local_access ctx v e.epos Write in
 						write ctx (HReg rparams.rid);
 						write ctx (HSmallInt !p);
@@ -1286,23 +1284,23 @@ let rec gen_expr_content ctx retval e =
 
 and gen_call ctx retval e el r =
 	match e.eexpr , el with
-	| TLocal "__is__" , [e;t] ->
+	| TLocal { v_name = "__is__" }, [e;t] ->
 		gen_expr ctx true e;
 		gen_expr ctx true t;
 		write ctx (HOp A3OIs)
-	| TLocal "__as__" , [e;t] ->
+	| TLocal { v_name = "__as__" }, [e;t] ->
 		gen_expr ctx true e;
 		gen_expr ctx true t;
 		write ctx (HOp A3OAs)
-	| TLocal "__int__", [e] ->
+	| TLocal { v_name = "__int__" }, [e] ->
 		gen_expr ctx true e;
 		write ctx HToInt
-	| TLocal "__float__", [e] ->
+	| TLocal { v_name = "__float__" }, [e] ->
 		gen_expr ctx true e;
 		write ctx HToNumber
-	| TLocal "__hkeys__" , [e2]
-	| TLocal "__foreach__", [e2]
-	| TLocal "__keys__" , [e2] ->
+	| TLocal { v_name = "__hkeys__" }, [e2]
+	| TLocal { v_name = "__foreach__" }, [e2]
+	| TLocal { v_name = "__keys__" }, [e2] ->
 		let racc = alloc_reg ctx (KType (type_path ctx ([],"Array"))) in
 		let rcounter = alloc_reg ctx KInt in
 		let rtmp = alloc_reg ctx KDynamic in
@@ -1317,14 +1315,15 @@ and gen_call ctx retval e el r =
 		write ctx (HReg racc.rid);
 		write ctx (HReg rtmp.rid);
 		write ctx (HReg rcounter.rid);
-		if e.eexpr = TLocal "__foreach__" then
+		(match e.eexpr with
+		| TLocal { v_name = "__foreach__" } ->
 			write ctx HForEach
-		else
+		| TLocal { v_name = "__hkeys__" } ->
 			write ctx HForIn;
-		if e.eexpr = TLocal "__hkeys__" then begin
 			write ctx (HSmallInt 1);
 			write ctx (HCallProperty (as3 "substr",1));
-		end;
+		| _ ->
+			write ctx HForIn);
 		write ctx (HCallPropVoid (as3 "push",1));
 		start();
 		write ctx (HNext (rtmp.rid,rcounter.rid));
@@ -1333,26 +1332,26 @@ and gen_call ctx retval e el r =
 		free_reg ctx rtmp;
 		free_reg ctx rcounter;
 		free_reg ctx racc;
-	| TLocal "__new__" , e :: el ->
+	| TLocal { v_name = "__new__" }, e :: el ->
 		gen_expr ctx true e;
 		List.iter (gen_expr ctx true) el;
 		write ctx (HConstruct (List.length el))
-	| TLocal "__delete__" , [o;f] ->
+	| TLocal { v_name = "__delete__" }, [o;f] ->
 		gen_expr ctx true o;
 		gen_expr ctx true f;
 		write ctx (HDeleteProp dynamic_prop);
-	| TLocal "__unprotect__" , [e] ->
+	| TLocal { v_name = "__unprotect__" }, [e] ->
 		write ctx (HGetLex (type_path ctx (["flash"],"Boot")));
 		gen_expr ctx true e;
 		write ctx (HCallProperty (ident "__unprotect__",1));
-	| TLocal "__typeof__", [e] ->
+	| TLocal { v_name = "__typeof__" }, [e] ->
 		gen_expr ctx true e;
 		write ctx HTypeof
-	| TLocal "__in__", [e; f] ->
+	| TLocal { v_name = "__in__" }, [e; f] ->
 		gen_expr ctx true e;
 		gen_expr ctx true f;
 		write ctx (HOp A3OIn)
-	| TLocal "__resources__", [] ->
+	| TLocal { v_name = "__resources__" }, [] ->
 		let count = ref 0 in
 		Hashtbl.iter (fun name data ->
 			incr count;
@@ -1363,7 +1362,7 @@ and gen_call ctx retval e el r =
 			write ctx (HObject 2);
 		) ctx.com.resources;
 		write ctx (HArray !count)
-	| TLocal "__vmem_set__", [{ eexpr = TConst (TInt code) };e1;e2] ->
+	| TLocal { v_name = "__vmem_set__" }, [{ eexpr = TConst (TInt code) };e1;e2] ->
 		gen_expr ctx true e2;
 		gen_expr ctx true e1;
 		write ctx (HOp (match code with
@@ -1374,7 +1373,7 @@ and gen_call ctx retval e el r =
 			| 4l -> A3OMemSetDouble
 			| _ -> assert false
 		))
-	| TLocal "__vmem_get__", [{ eexpr = TConst (TInt code) };e] ->
+	| TLocal { v_name = "__vmem_get__" }, [{ eexpr = TConst (TInt code) };e] ->
 		gen_expr ctx true e;
 		write ctx (HOp (match code with
 			| 0l -> A3OMemGet8
@@ -1384,7 +1383,7 @@ and gen_call ctx retval e el r =
 			| 4l -> A3OMemGetDouble
 			| _ -> assert false
 		))
-	| TLocal "__vmem_sign__", [{ eexpr = TConst (TInt code) };e] ->
+	| TLocal { v_name = "__vmem_sign__" }, [{ eexpr = TConst (TInt code) };e] ->
 		gen_expr ctx true e;
 		write ctx (HOp (match code with
 			| 0l -> A3OSign1
@@ -1392,12 +1391,12 @@ and gen_call ctx retval e el r =
 			| 2l -> A3OSign16
 			| _ -> assert false
 		))
-	| TLocal "__vector__", [ep] ->
+	| TLocal { v_name = "__vector__" }, [ep] ->
 		gen_type ctx (type_id ctx r);
 		write ctx HGetGlobalScope;
 		gen_expr ctx true ep;
 		write ctx (HCallStack 1)
-	| TArray ({ eexpr = TLocal "__global__" },{ eexpr = TConst (TString s) }), _ ->
+	| TArray ({ eexpr = TLocal { v_name = "__global__" } },{ eexpr = TConst (TString s) }), _ ->
 		(match gen_access ctx e Read with
 		| VGlobal id ->
 			write ctx (HFindPropStrict id);
@@ -1464,7 +1463,7 @@ and gen_unop ctx retval op flag e =
 	| Increment
 	| Decrement ->
 		let incr = (op = Increment) in
-		let r = (match e.eexpr with TLocal n -> get_local_register ctx n | _ -> None) in
+		let r = (match e.eexpr with TLocal v -> get_local_register ctx v | _ -> None) in
 		match r with
 		| Some r when r.rtype = KInt ->
 			if not r.rinit then r.rcond <- true;
@@ -1663,15 +1662,15 @@ let generate_method ctx fdata stat =
 
 let generate_construct ctx fdata c =
 	(* make all args optional to allow no-param constructor *)
-	let cargs = List.map (fun (a,c,t) -> 
+	let cargs = List.map (fun (v,c) ->
 		let c = (match c with Some _ -> c | None ->
-			Some (match classify ctx t with
+			Some (match classify ctx v.v_type with
 			| KInt | KUInt -> TInt 0l
 			| KFloat -> TFloat "0"
 			| KBool -> TBool false
-			| KType _ | KDynamic | KNone -> TNull)			
+			| KType _ | KDynamic | KNone -> TNull)
 		) in
-		a,c,t
+		v,c
 	) fdata.tf_args in
 	let f = begin_fun ctx cargs fdata.tf_type [ethis;fdata.tf_expr] false fdata.tf_expr.epos in
 	(* if skip_constructor, then returns immediatly *)
@@ -1704,13 +1703,13 @@ let generate_construct ctx fdata c =
 	write ctx HRetVoid;
 	f() , List.length fdata.tf_args
 
-let rec is_const e = 
+let rec is_const e =
 	match e.eexpr with
 	| TConst _ -> true
 	| TArrayDecl el | TBlock el -> List.for_all is_const el
 	| TObjectDecl fl -> List.for_all (fun (_,e) -> is_const e) fl
 	| TParenthesis e -> is_const e
-	| TFunction _ -> true		
+	| TFunction _ -> true
 	| _ -> false
 
 let generate_class_statics ctx c const =
@@ -1896,7 +1895,7 @@ let generate_field_kind ctx f c stat =
 			) args;
 			let dparams = (match !dparams with None -> None | Some l -> Some (List.rev l)) in
 			Some (HFMethod {
-				hlm_type = end_fun ctx (List.map (fun (a,opt,t) -> a, (if opt then Some TNull else None), t) args) dparams tret;
+				hlm_type = end_fun ctx (List.map (fun (a,opt,t) -> alloc_var a t, (if opt then Some TNull else None)) args) dparams tret;
 				hlm_final = false;
 				hlm_override = false;
 				hlm_kind = MK3Normal;
@@ -1998,7 +1997,7 @@ let generate_class ctx c =
 			hlf_metas = extract_meta f.cf_meta;
 		}
 	) c.cl_ordered_statics in
-	let statics = if not (need_init ctx c) then statics else  
+	let statics = if not (need_init ctx c) then statics else
 		{
 			hlf_name = ident "init__";
 			hlf_slot = (incr st_field_count; !st_field_count);
@@ -2034,7 +2033,7 @@ let generate_class ctx c =
 let generate_enum ctx e meta =
 	let name_id = type_path ctx e.e_path in
 	let api = ctx.com.basic in
-	let f = begin_fun ctx [("tag",None,api.tstring);("index",None,api.tint);("params",None,mk_mono())] api.tvoid [ethis] false e.e_pos in
+	let f = begin_fun ctx [alloc_var "tag" api.tstring, None;alloc_var "index" api.tint, None;alloc_var "params" (mk_mono()), None] api.tvoid [ethis] false e.e_pos in
 	let tag_id = ident "tag" in
 	let index_id = ident "index" in
 	let params_id = ident "params" in
@@ -2063,7 +2062,7 @@ let generate_enum ctx e meta =
 			hlf_slot = !st_count;
 			hlf_kind = (match f.ef_type with
 				| TFun (args,_) ->
-					let fdata = begin_fun ctx (List.map (fun (a,opt,t) -> a, (if opt then Some TNull else None), t) args) (TEnum (e,[])) [] true f.ef_pos in
+					let fdata = begin_fun ctx (List.map (fun (a,opt,t) -> alloc_var a t, (if opt then Some TNull else None)) args) (TEnum (e,[])) [] true f.ef_pos in
 					write ctx (HFindPropStrict name_id);
 					write ctx (HString f.ef_name);
 					write ctx (HInt f.ef_index);
@@ -2184,7 +2183,6 @@ let generate com boot_name =
 		trys = [];
 		breaks = [];
 		continues = [];
-		curblock = [];
 		block_vars = [];
 		used_vars = PMap.empty;
 		in_static = false;

+ 9 - 9
interp.ml

@@ -3177,7 +3177,7 @@ and decode_type t =
 	| 4, [pl; r] -> TFun (List.map (fun p -> dec_string (field p "name"), dec_bool (field p "opt"), decode_type (field p "t")) (dec_array pl), decode_type r)
 	| 5, [a] -> TAnon (decode_ref a)
 	| 6, [VNull] -> t_dynamic
-	| 6, [t] -> TDynamic (decode_type t)	
+	| 6, [t] -> TDynamic (decode_type t)
 	| _ -> raise Invalid_expr
 
 and encode_texpr e =
@@ -3259,9 +3259,9 @@ let rec make_ast e =
 		| TType (t,pl) ->
 			tpath t.t_path (List.map mk_type pl)
 		| TFun (args,ret) ->
-			CTFunction (List.map (fun (_,_,t) -> mk_type t) args, mk_type ret)			
+			CTFunction (List.map (fun (_,_,t) -> mk_type t) args, mk_type ret)
 		| TAnon a ->
-			CTAnonymous (PMap.foldi (fun _ f acc -> 
+			CTAnonymous (PMap.foldi (fun _ f acc ->
 				{
 					cff_name = f.cf_name;
 					cff_kind = FVar (mk_ot f.cf_type,None);
@@ -3284,7 +3284,7 @@ let rec make_ast e =
 	((match e.eexpr with
 	| TConst c ->
 		EConst (mk_const c)
-	| TLocal s -> EConst (Ident s)
+	| TLocal v -> EConst (Ident v.v_name)
 	| TEnumField (en,f) -> EField (mk_path en.e_path e.epos,f)
 	| TArray (e1,e2) -> EArray (make_ast e1,make_ast e2)
 	| TBinop (op,e1,e2) -> EBinop (op, make_ast e1, make_ast e2)
@@ -3296,13 +3296,13 @@ let rec make_ast e =
 	| TCall (e,el) -> ECall (make_ast e,List.map make_ast el)
 	| TNew (c,pl,el) -> ENew ((match mk_type (TInst (c,pl)) with CTPath p -> p | _ -> assert false),List.map make_ast el)
 	| TUnop (op,p,e) -> EUnop (op,p,make_ast e)
-	| TFunction f -> 
-		let arg (n,c,t) = n, false, mk_ot t, (match c with None -> None | Some c -> Some (EConst (mk_const c),e.epos)) in
+	| TFunction f ->
+		let arg (v,c) = v.v_name, false, mk_ot v.v_type, (match c with None -> None | Some c -> Some (EConst (mk_const c),e.epos)) in
 		EFunction (None,{ f_params = []; f_args = List.map arg f.tf_args; f_type = mk_ot f.tf_type; f_expr = Some (make_ast f.tf_expr) })
 	| TVars vl ->
-		EVars (List.map (fun (n,t,e) -> n, mk_ot t, eopt e) vl)
+		EVars (List.map (fun (v,e) -> v.v_name, mk_ot v.v_type, eopt e) vl)
 	| TBlock el -> EBlock (List.map make_ast el)
-	| TFor (n,t,it,e) -> EFor (n,make_ast it,make_ast e)
+	| TFor (v,it,e) -> EFor (v.v_name,make_ast it,make_ast e)
 	| TIf (e,e1,e2) -> EIf (make_ast e,make_ast e1,eopt e2)
 	| TWhile (e1,e2,flag) -> EWhile (make_ast e1, make_ast e2, flag)
 	| TSwitch (e,cases,def) -> ESwitch (make_ast e,List.map (fun (vl,e) -> List.map make_ast vl, make_ast e) cases,eopt def)
@@ -3311,7 +3311,7 @@ let rec make_ast e =
 			assert false
 		in
 		ESwitch (make_ast e,List.map scases cases,eopt def)
-	| TTry (e,catches) -> ETry (make_ast e,List.map (fun (n,t,e) -> n, mk_type t, make_ast e) catches)
+	| TTry (e,catches) -> ETry (make_ast e,List.map (fun (v,e) -> v.v_name, mk_type v.v_type, make_ast e) catches)
 	| TReturn e -> EReturn (eopt e)
 	| TBreak -> EBreak
 	| TContinue -> EContinue

+ 2 - 1
main.ml

@@ -608,7 +608,8 @@ try
 		let filters = [
 			if com.foptimize then Optimizer.reduce_expression ctx else Optimizer.sanitize ctx;
 			Codegen.check_local_vars_init;
-			Codegen.block_vars com;
+			Codegen.captured_vars com;
+			Codegen.rename_local_vars com;
 		] in
 		Codegen.post_process com filters;
 		Common.add_filter com (fun() -> List.iter (Codegen.on_generate ctx) com.types);

+ 144 - 121
optimizer.ml

@@ -24,15 +24,14 @@ open Typecore
 (* ---------------------------------------------------------------------- *)
 (* INLINING *)
 
+type in_local = {
+	i_var : tvar;
+	i_subst : tvar;
+	mutable i_write : bool;
+	mutable i_read : int;
+}
+
 let rec type_inline ctx cf f ethis params tret p =
-	let locals = save_locals ctx in
-	let hcount = Hashtbl.create 0 in
-	let lsets = Hashtbl.create 0 in
-	let pnames = List.map (fun (name,_,t) ->
-		let name = add_local ctx name t in
-		Hashtbl.add hcount name (ref 0);
-		(name,t)
-	) f.tf_args in
 	(* type substitution on both class and function type parameters *)
 	let has_params, map_type =
 		let rec get_params c pl =
@@ -52,88 +51,123 @@ let rec type_inline ctx cf f ethis params tret p =
 		let tparams = fst tparams @ cf.cf_params in
 		tparams <> [], apply_params tparams tmonos
 	in
+	(* locals substitution *)
+	let locals = Hashtbl.create 0 in
+	let local v =
+		try
+			Hashtbl.find locals v.v_id
+		with Not_found ->
+			let i = {
+				i_var = v;
+				i_subst = alloc_var v.v_name v.v_type;
+				i_write = false;
+				i_read = 0;
+			} in
+			Hashtbl.add locals v.v_id i;
+			Hashtbl.add locals i.i_subst.v_id i;
+			i
+	in	
+	let read_local v = 
+		try 
+			Hashtbl.find locals v.v_id 
+		with Not_found ->
+			{
+				i_var = v;
+				i_subst = v;
+				i_write = false;
+				i_read = 0;
+			}
+	in
 	(* use default values for null/unset arguments *)
 	let rec loop pl al =
 		match pl, al with
 		| [], [] -> []
-		| e :: pl, (name, opt, t) :: al ->
-			if is_nullable t && is_null e.etype then Hashtbl.add lsets name (); (* force coerce *)
+		| e :: pl, (v, opt) :: al ->
+			(*
+				if we pass a Null<T> var to an inlined method that needs a T.
+				we need to force a local var to be created on some platforms.				
+			*)
+			if is_nullable v.v_type && is_null e.etype && (match ctx.com.platform with Flash9 | Cpp -> true | _ -> false) then (local v).i_write <- true;
 			(match e.eexpr, opt with
-			| TConst TNull , Some c -> mk (TConst c) (map_type t) e.epos
+			| TConst TNull , Some c -> mk (TConst c) v.v_type e.epos
 			| _ -> e) :: loop pl al
-		| [], (_,opt,t) :: al ->
+		| [], (v,opt) :: al ->
 			(match opt with
 			| None -> assert false
-			| Some c -> mk (TConst c) (map_type t) p) :: loop [] al
+			| Some c -> mk (TConst c) v.v_type p) :: loop [] al
 		| _ :: _, [] ->
 			assert false
 	in
-	let params = loop params f.tf_args in
+	(*
+		Build the expr/var subst list
+	*)
 	let ethis = (match ethis.eexpr with TConst TSuper -> { ethis with eexpr = TConst TThis } | _ -> ethis) in
-	let vthis = gen_local ctx ethis.etype in
-	let this_count = ref 0 in
-	let local i =
-		let i = (try PMap.find i ctx.locals_map with Not_found -> i) in
-		(try incr (Hashtbl.find hcount i) with Not_found -> ());
-		i
-	in
+	let vthis = alloc_var "_this" ethis.etype in
+	let inlined_vars = List.map2 (fun e (v,_) -> local v, e) (ethis :: loop params f.tf_args) ((vthis,None) :: f.tf_args) in
+	(*
+		here, we try to eliminate final returns from the expression tree.
+		However, this is not entirely correct since we don't yet correctly propagate
+		the type of returned expressions upwards ("return" expr itself being Dynamic).
+
+		We also substitute variables with fresh ones that might be renamed at later stage.
+	*)
 	let opt f = function
 		| None -> None
 		| Some e -> Some (f e)
 	in
-	let inlined_vars = List.map2 (fun (n,t) e -> n,(t,e)) ((vthis,ethis.etype) :: pnames) (ethis :: params) in
 	let has_vars = ref false in
-	(*
-		here, we try to eliminate final returns from the expression tree.
-		However, this is not entirely correct since we don't yet correctly propagate
-		the type of returned expressions upwards ("return" expr itself being Dynamic)
-	*)
+	let in_loop = ref false in
 	let rec map term e =
 		let po = e.epos in
 		let e = { e with epos = p } in
 		match e.eexpr with
-		| TLocal s ->
-			{ e with eexpr = TLocal (local s) }
+		| TLocal v ->
+			let l = read_local v in
+			l.i_read <- l.i_read + if !in_loop then 2 else 1;
+			{ e with eexpr = TLocal l.i_subst }
 		| TConst TThis ->
-			incr this_count;
-			{ e with eexpr = TLocal vthis }
+			let l = read_local vthis in
+			l.i_read <- l.i_read + if !in_loop then 2 else 1;
+			{ e with eexpr = TLocal l.i_subst }
 		| TVars vl ->
 			has_vars := true;
-			let vl = List.map (fun (v,t,e) ->
-				let e = opt (map false) e in
-				add_local ctx v t,t,e
+			let vl = List.map (fun (v,e) ->				
+				(local v).i_subst,opt (map false) e
 			) vl in
 			{ e with eexpr = TVars vl }
 		| TReturn eo ->
 			if not term then error "Cannot inline a not final return" po;
 			(match eo with
-			| None -> mk (TConst TNull) (mk_mono()) p
+			| None -> mk (TConst TNull) f.tf_type p
 			| Some e -> map term e)
-		| TFor (v,t,e1,e2) ->
+		| TFor (v,e1,e2) ->
+			let i = local v in
 			let e1 = map false e1 in
-			let old = save_locals ctx in
-			let v = add_local ctx v t in
+			let old = !in_loop in
+			in_loop := true;
 			let e2 = map false e2 in
-			old();
-			{ e with eexpr = TFor (v,t,e1,e2) }
+			in_loop := old;
+			{ e with eexpr = TFor (i.i_subst,e1,e2) }
+		| TWhile (cond,eloop,flag) ->
+			let cond = map false cond in
+			let old = !in_loop in
+			in_loop := true;
+			let eloop = map false eloop in
+			in_loop := old;
+			{ e with eexpr = TWhile (cond,eloop,flag) }			
 		| TMatch (v,en,cases,def) ->
 			let term, t = (match def with Some d when term -> true, ref d.etype | _ -> false, ref e.etype) in
 			let cases = List.map (fun (i,vl,e) ->
-				let old = save_locals ctx in
-				let vl = opt (List.map (fun (n,t) -> opt (fun n -> add_local ctx n t) n, t)) vl in
+				let vl = opt (List.map (fun v -> opt (fun v -> (local v).i_subst) v)) vl in
 				let e = map term e in
 				if is_null e.etype then t := e.etype;
-				old();
 				i, vl, e
 			) cases in
 			{ e with eexpr = TMatch (map false v,en,cases,opt (map term) def); etype = !t }
 		| TTry (e1,catches) ->
-			{ e with eexpr = TTry (map term e1,List.map (fun (v,t,e) ->
-				let old = save_locals ctx in
-				let v = add_local ctx v t in
+			{ e with eexpr = TTry (map term e1,List.map (fun (v,e) ->
 				let e = map term e in
-				old();
-				v,t,e
+				(local v).i_subst,e
 			) catches) }
 		| TBlock l ->
 			let old = save_locals ctx in
@@ -161,74 +195,54 @@ let rec type_inline ctx cf f ethis params tret p =
 			{ e with eexpr = TIf(econd,eif,Some eelse); etype = if is_null eif.etype then eif.etype else eelse.etype }
 		| TParenthesis _ | TIf (_,_,Some _) | TSwitch (_,_,Some _) ->
 			Type.map_expr (map term) e
-		| TUnop (op,pref,({ eexpr = TLocal s } as e1)) ->
-			(match op with
-			| Increment | Decrement -> Hashtbl.add lsets (local s) ()
-			| _ -> ());
-			{ e with eexpr = TUnop (op,pref,map false e1) }
-		| TBinop (op,({ eexpr = TLocal s } as e1),e2) ->
-			(match op with
-			| OpAssign | OpAssignOp _ -> Hashtbl.add lsets (local s) ()
-			| _ -> ());
-			{ e with eexpr = TBinop (op,map false e1,map false e2) }
+		| TUnop ((Increment|Decrement),_,{ eexpr = TLocal v }) ->
+			(read_local v).i_write <- true;
+			Type.map_expr (map false) e
+		| TBinop ((OpAssign | OpAssignOp _),{ eexpr = TLocal v },_) ->
+			(read_local v).i_write <- true;
+			Type.map_expr (map false) e;
 		| TConst TSuper ->
 			error "Cannot inline function containing super" po
 		| TFunction _ ->
 			error "Cannot inline functions containing closures" po
-		| TCall ({ eexpr = TLocal s },el) ->
-			(*
-				Let's inline a local function call.
-				This is the only place where we can do it since it's required to track locals
-				of both original calling context and inlined function.
-				Since it's a bit early inlining, we also have to make sure that this local will not be writable.
-			*)
-			(try
-				let _, ef = List.assoc (local s) inlined_vars in
-				match ef.eexpr, follow ef.etype with
-				| TFunction func, TFun (_,rt) ->
-					let cf = mk_field "" ef.etype e.epos in
-					let inl = (try type_inline ctx cf func ethis el rt e.epos with Error (Custom _,_) -> None) in
-					(match inl with
-					| None -> raise Not_found
-					| Some e -> map term e (* loop *))
-				| _ -> raise Not_found
-			with Not_found ->
-				Type.map_expr (map false) e)
 		| _ ->
 			Type.map_expr (map false) e
 	in
 	let e = map true f.tf_expr in
-	locals();
+	(*
+		if variables are not written and used with a const value, let's substitute
+		with the actual value, either create a temp var
+	*)
 	let subst = ref PMap.empty in
-	Hashtbl.add hcount vthis this_count;
-	let vars = List.map (fun (n,(t,e)) ->
-		let flag = not (Hashtbl.mem lsets n) && (match e.eexpr with
-			| TLocal _ | TConst _ | TFunction _ -> true
-			| _ ->
-				let used = !(Hashtbl.find hcount n) in
-				used <= 1
+	let vars = List.fold_left (fun acc (i,e) ->
+		let flag = (match e.eexpr with
+			| TLocal _ | TConst _ -> not i.i_write
+			| TFunction _ -> if i.i_write then error "Cannot modify a closure parameter inside inline method" p; true
+			| _ -> not i.i_write && i.i_read <= 1
 		) in
-		if not flag && (match e.eexpr with TFunction _ -> true | _ -> false) then error "Cannot modify a closure parameter inside inline method" p;
-		(n,t,e,flag)
-	) inlined_vars in
-	let vars = List.fold_left (fun acc (n,t,e,flag) ->
 		if flag then begin
-			subst := PMap.add n e !subst;
+			subst := PMap.add i.i_subst.v_id e !subst;
 			acc
 		end else
-			(n,t,Some e) :: acc
-	) [] vars in
+			(i.i_subst,Some e) :: acc
+	) [] inlined_vars in
 	let subst = !subst in
 	let rec inline_params e =
 		match e.eexpr with
-		| TLocal s -> (try PMap.find s subst with Not_found -> e)
+		| TLocal v -> (try PMap.find v.v_id subst with Not_found -> e)
 		| _ -> Type.map_expr inline_params e
 	in
 	let e = (if PMap.is_empty subst then e else inline_params e) in
 	let init = (match vars with [] -> None | l -> Some (mk (TVars (List.rev l)) ctx.t.tvoid p)) in
-	if Common.defined ctx.com "js" && (init <> None || !has_vars) then
+	(*
+		If we have local variables and returning a value, then this will result in
+		unoptimized JS code, so let's instead skip inlining.
+
+		This could be fixed with better post process code cleanup (planed)
+	*)
+	if Common.platform ctx.com Js && (init <> None || !has_vars) then begin
 		None
-	else
+	end else
 		let wrap e =
 			(* we can't mute the type of the expression because it is not correct to do so *)
 			if e.etype == tret then
@@ -252,9 +266,18 @@ let rec type_inline ctx cf f ethis params tret p =
 				this is very expensive since we are building the substitution list for
 				every expression, but hopefully in such cases the expression size is small
 			*)
-			let rec map_expr_type e = Type.map_expr_type map_expr_type map_type e in
+			let vars = Hashtbl.create 0 in
+			let map_var v =
+				if not (Hashtbl.mem vars v.v_id) then begin
+					Hashtbl.add vars v.v_id ();
+					v.v_type <- map_type v.v_type;
+				end;
+				v
+			in
+			let rec map_expr_type e = Type.map_expr_type map_expr_type map_type map_var e in
 			Some (map_expr_type e)
 
+
 (* ---------------------------------------------------------------------- *)
 (* LOOPS *)
 
@@ -276,19 +299,16 @@ let optimize_for_loop ctx i e1 e2 p =
 			| TBinop (OpAssign,{ eexpr = TLocal l },_)
 			| TBinop (OpAssignOp _,{ eexpr = TLocal l },_)
 			| TUnop (Increment,_,{ eexpr = TLocal l })
-			| TUnop (Decrement,_,{ eexpr = TLocal l })  when l = i ->
+			| TUnop (Decrement,_,{ eexpr = TLocal l })  when l == i ->
 				error "Loop variable cannot be modified" e.epos
-			| TFunction f when List.exists (fun (l,_,_) -> l = i) f.tf_args ->
-				e
-			| TFor (k,_,_,_) when k = i ->
-				e
 			| _ ->
-				Type.map_expr check e
+				Type.iter check e
 		in
-		let e2 = check (type_expr ctx e2 false) in
+		let e2 = type_expr ctx e2 false in
+		check e2;
 		let etmp = mk (TLocal tmp) t_int p in
 		let incr = mk (TUnop (Increment,Postfix,etmp)) t_int p in
-		let init = mk (TVars [i,t_int,Some incr]) t_void p in
+		let init = mk (TVars [i,Some incr]) t_void p in
 		let block = match e2.eexpr with
 			| TBlock el -> mk (TBlock (init :: el)) t_void e2.epos
 			| _ -> mk (TBlock [init;e2]) t_void p
@@ -299,7 +319,7 @@ let optimize_for_loop ctx i e1 e2 p =
 		(match max with
 		| None ->
 			lblock [
-				mk (TVars [tmp,t_int,Some i1]) t_void p;
+				mk (TVars [tmp,Some i1]) t_void p;
 				mk (TWhile (
 					mk (TBinop (OpLt, etmp, { i2 with etype = t_int })) ctx.t.tbool p,
 					block,
@@ -308,7 +328,7 @@ let optimize_for_loop ctx i e1 e2 p =
 			]
 		| Some max ->
 			lblock [
-				mk (TVars [tmp,t_int,Some i1;max,t_int,Some i2]) t_void p;
+				mk (TVars [tmp,Some i1;max,Some i2]) t_void p;
 				mk (TWhile (
 					mk (TBinop (OpLt, etmp, mk (TLocal max) t_int p)) ctx.t.tbool p,
 					block,
@@ -323,17 +343,17 @@ let optimize_for_loop ctx i e1 e2 p =
 			| TLocal _ -> e1, []
 			| _ ->
 				let atmp = gen_local ctx e1.etype in
-				mk (TLocal atmp) e1.etype e1.epos, [atmp,e1.etype,Some e1]
+				mk (TLocal atmp) e1.etype e1.epos, [atmp,Some e1]
 		) in
 		let iexpr = mk (TLocal index) t_int p in
 		let e2 = type_expr ctx e2 false in
-		let aget = mk (TVars [i,pt,Some (mk (TArray (arr,iexpr)) pt p)]) t_void p in
+		let aget = mk (TVars [i,Some (mk (TArray (arr,iexpr)) pt p)]) t_void p in
 		let incr = mk (TUnop (Increment,Prefix,iexpr)) t_int p in
 		let block = match e2.eexpr with
 			| TBlock el -> mk (TBlock (aget :: incr :: el)) t_void e2.epos
 			| _ -> mk (TBlock [aget;incr;e2]) t_void p
 		in
-		let ivar = index, t_int, Some (mk (TConst (TInt 0l)) t_int p) in
+		let ivar = index, Some (mk (TConst (TInt 0l)) t_int p) in
 		lblock [
 			mk (TVars (ivar :: avars)) t_void p;
 			mk (TWhile (
@@ -348,14 +368,14 @@ let optimize_for_loop ctx i e1 e2 p =
 		let cell = gen_local ctx tcell in
 		let cexpr = mk (TLocal cell) tcell p in
 		let e2 = type_expr ctx e2 false in
-		let evar = mk (TVars [i,t,Some (mk (TField (cexpr,"elt")) t p)]) t_void p in
+		let evar = mk (TVars [i,Some (mk (TField (cexpr,"elt")) t p)]) t_void p in
 		let enext = mk (TBinop (OpAssign,cexpr,mk (TField (cexpr,"next")) tcell p)) tcell p in
 		let block = match e2.eexpr with
 			| TBlock el -> mk (TBlock (evar :: enext :: el)) t_void e2.epos
 			| _ -> mk (TBlock [evar;enext;e2]) t_void p
 		in
 		lblock [
-			mk (TVars [cell,tcell,Some (mk (TField (e1,"head")) tcell p)]) t_void p;
+			mk (TVars [cell,Some (mk (TField (e1,"head")) tcell p)]) t_void p;
 			mk (TWhile (
 				mk (TBinop (OpNotEq, cexpr, mk (TConst TNull) tcell p)) ctx.t.tbool p,
 				block,
@@ -419,7 +439,7 @@ let sanitize_expr e =
 		| TVars _	(* needs to be put into blocks *)
 		| TFor _	(* a temp var is needed for holding iterator *)
 		| TMatch _	(* a temp var is needed for holding enum *)
-		| TCall ({ eexpr = TLocal "__js__" },_) (* we never know *)
+		| TCall ({ eexpr = TLocal { v_name = "__js__" } },_) (* we never know *)
 			-> block e
 		| _ -> e
 	in
@@ -428,7 +448,7 @@ let sanitize_expr e =
 		match e.eexpr with
 		| TIf (_,_,None) -> true
 		| TWhile (_,e,NormalWhile) -> has_if e
-		| TFor (_,_,_,e) -> has_if e
+		| TFor (_,_,e) -> has_if e
 		| _ -> false
 	in
 	match e.eexpr with
@@ -465,9 +485,9 @@ let sanitize_expr e =
 		let e1 = parent e1 in
 		let e2 = complex e2 in
 		{ e with eexpr = TWhile (e1,e2,flag) }
-	| TFor (v,t,e1,e2) ->
+	| TFor (v,e1,e2) ->
 		let e2 = complex e2 in
-		{ e with eexpr = TFor (v,t,e1,e2) }
+		{ e with eexpr = TFor (v,e1,e2) }
 	| TFunction f ->
 		(match f.tf_expr.eexpr with
 		| TBlock _ -> e
@@ -480,7 +500,7 @@ let sanitize_expr e =
 		if need_parent e1 then { e with eexpr = TArray(parent e1,e2) } else e
 	| TTry (e1,catches) ->
 		let e1 = block e1 in
-		let catches = List.map (fun (v,t,e) -> v, t, block e) catches in
+		let catches = List.map (fun (v,e) -> v, block e) catches in
 		{ e with eexpr = TTry (e1,catches) }
 	| TSwitch (e1,cases,def) ->
 		let e1 = parent e1 in
@@ -658,11 +678,14 @@ let rec reduce_loop ctx e =
 				e
 		| _ -> e
 		)
-	(*
-		disable : we need to call type_inline, but it requires to have good locals.
-		instead it's directly done in type_inline while inlining a function-parameter
-		| TCall ({ eexpr = TFunction func } as ef,el) ->
-	*)
+	| TCall ({ eexpr = TFunction func } as ef,el) ->
+		let cf = mk_field "" ef.etype e.epos in
+		let ethis = mk (TConst TThis) t_dynamic e.epos in
+		let rt = (match follow ef.etype with TFun (_,rt) -> rt | _ -> assert false) in
+		let inl = (try type_inline ctx cf func ethis el rt e.epos with Error (Custom _,_) -> None) in
+		(match inl with
+		| None -> reduce_expr ctx e
+		| Some e -> reduce_loop ctx e)
 	| _ ->
 		reduce_expr ctx e)
 

+ 49 - 30
type.ml

@@ -65,8 +65,15 @@ and tconstant =
 	| TThis
 	| TSuper
 
+and tvar = {
+	v_id : int;
+	mutable v_name : string;
+	mutable v_type : t;
+	mutable v_capture : bool;
+}
+
 and tfunc = {
-	tf_args : (string * tconstant option * t) list;
+	tf_args : (tvar * tconstant option) list;
 	tf_type : t;
 	tf_expr : texpr;
 }
@@ -85,7 +92,7 @@ and tanon = {
 
 and texpr_expr =
 	| TConst of tconstant
-	| TLocal of string
+	| TLocal of tvar
 	| TEnumField of tenum * string
 	| TArray of texpr * texpr
 	| TBinop of Ast.binop * texpr * texpr
@@ -99,14 +106,14 @@ and texpr_expr =
 	| TNew of tclass * tparams * texpr list
 	| TUnop of Ast.unop * Ast.unop_flag * texpr
 	| TFunction of tfunc
-	| TVars of (string * t * texpr option) list
+	| TVars of (tvar * texpr option) list
 	| TBlock of texpr list
-	| TFor of string * t * texpr * texpr
+	| TFor of tvar * texpr * texpr
 	| TIf of texpr * texpr * texpr option
 	| TWhile of texpr * texpr * Ast.while_flag
 	| TSwitch of texpr * (texpr list * texpr) list * texpr option
-	| TMatch of texpr * (tenum * tparams) * (int list * (string option * t) list option * texpr) list * texpr option
-	| TTry of texpr * (string * t * texpr) list
+	| TMatch of texpr * (tenum * tparams) * (int list * tvar option list option * texpr) list * texpr option
+	| TTry of texpr * (tvar * texpr) list
 	| TReturn of texpr option
 	| TBreak
 	| TContinue
@@ -205,6 +212,10 @@ type module_def = {
 	mtypes : module_type list;
 }
 
+let alloc_var =
+	let uid = ref 0 in
+	(fun n t -> incr uid; { v_name = n; v_type = t; v_id = !uid; v_capture = false })
+
 let mk e t p = { eexpr = e; etype = t; epos = p }
 
 let mk_block e =
@@ -251,7 +262,7 @@ let null_class =
 	c.cl_private <- true;
 	c
 
-let arg_name (name,_,_) = name
+let arg_name (a,_) = a.v_name
 
 let t_private = function
 	| TClassDecl c -> c.cl_private
@@ -871,7 +882,7 @@ let iter f e =
 		()
 	| TArray (e1,e2)
 	| TBinop (_,e1,e2)
-	| TFor (_,_,e1,e2)
+	| TFor (_,e1,e2)
 	| TWhile (e1,e2,_) ->
 		f e1;
 		f e2;
@@ -892,7 +903,7 @@ let iter f e =
 		f e;
 		List.iter f el
 	| TVars vl ->
-		List.iter (fun (_,_,e) -> match e with None -> () | Some e -> f e) vl
+		List.iter (fun (_,e) -> match e with None -> () | Some e -> f e) vl
 	| TFunction fu ->
 		f fu.tf_expr
 	| TIf (e,e1,e2) ->
@@ -909,7 +920,7 @@ let iter f e =
 		(match def with None -> () | Some e -> f e)
 	| TTry (e,catches) ->
 		f e;
-		List.iter (fun (_,_,e) -> f e) catches
+		List.iter (fun (_,e) -> f e) catches
 	| TReturn eo ->
 		(match eo with None -> () | Some e -> f e)
 
@@ -926,8 +937,8 @@ let map_expr f e =
 		{ e with eexpr = TArray (f e1,f e2) }
 	| TBinop (op,e1,e2) ->
 		{ e with eexpr = TBinop (op,f e1,f e2) }
-	| TFor (v,t,e1,e2) ->
-		{ e with eexpr = TFor (v,t,f e1,f e2) }
+	| TFor (v,e1,e2) ->
+		{ e with eexpr = TFor (v,f e1,f e2) }
 	| TWhile (e1,e2,flag) ->
 		{ e with eexpr = TWhile (f e1,f e2,flag) }
 	| TThrow e1 ->
@@ -951,7 +962,7 @@ let map_expr f e =
 	| TCall (e1,el) ->
 		{ e with eexpr = TCall (f e1, List.map f el) }
 	| TVars vl ->
-		{ e with eexpr = TVars (List.map (fun (v,t,e) -> v , t , match e with None -> None | Some e -> Some (f e)) vl) }
+		{ e with eexpr = TVars (List.map (fun (v,e) -> v , match e with None -> None | Some e -> Some (f e)) vl) }
 	| TFunction fu ->
 		{ e with eexpr = TFunction { fu with tf_expr = f fu.tf_expr } }
 	| TIf (ec,e1,e2) ->
@@ -961,13 +972,13 @@ let map_expr f e =
 	| TMatch (e1,t,cases,def) ->
 		{ e with eexpr = TMatch (f e1, t, List.map (fun (cl,params,e) -> cl, params, f e) cases, match def with None -> None | Some e -> Some (f e)) }
 	| TTry (e1,catches) ->
-		{ e with eexpr = TTry (f e1, List.map (fun (v,t,e) -> v, t, f e) catches) }
+		{ e with eexpr = TTry (f e1, List.map (fun (v,e) -> v, f e) catches) }
 	| TReturn eo ->
 		{ e with eexpr = TReturn (match eo with None -> None | Some e -> Some (f e)) }
 	| TCast (e1,t) ->
 		{ e with eexpr = TCast (f e1,t) }
 
-let map_expr_type f ft e =
+let map_expr_type f ft fv e =
 	match e.eexpr with
 	| TConst _
 	| TLocal _
@@ -980,8 +991,8 @@ let map_expr_type f ft e =
 		{ e with eexpr = TArray (f e1,f e2); etype = ft e.etype }
 	| TBinop (op,e1,e2) ->
 		{ e with eexpr = TBinop (op,f e1,f e2); etype = ft e.etype }
-	| TFor (v,t,e1,e2) ->
-		{ e with eexpr = TFor (v,ft t,f e1,f e2); etype = ft e.etype }
+	| TFor (v,e1,e2) ->
+		{ e with eexpr = TFor (fv v,f e1,f e2); etype = ft e.etype }
 	| TWhile (e1,e2,flag) ->
 		{ e with eexpr = TWhile (f e1,f e2,flag); etype = ft e.etype }
 	| TThrow e1 ->
@@ -1008,11 +1019,11 @@ let map_expr_type f ft e =
 	| TCall (e1,el) ->
 		{ e with eexpr = TCall (f e1, List.map f el); etype = ft e.etype }
 	| TVars vl ->
-		{ e with eexpr = TVars (List.map (fun (v,t,e) -> v , ft t , match e with None -> None | Some e -> Some (f e)) vl); etype = ft e.etype }
+		{ e with eexpr = TVars (List.map (fun (v,e) -> fv v, match e with None -> None | Some e -> Some (f e)) vl); etype = ft e.etype }
 	| TFunction fu ->
 		let fu = {
 			tf_expr = f fu.tf_expr;
-			tf_args = List.map (fun (n,o,t) -> n, o, ft t) fu.tf_args;
+			tf_args = List.map (fun (v,o) -> fv v, o) fu.tf_args;
 			tf_type = ft fu.tf_type;
 		} in
 		{ e with eexpr = TFunction fu; etype = ft e.etype }
@@ -1021,9 +1032,16 @@ let map_expr_type f ft e =
 	| TSwitch (e1,cases,def) ->
 		{ e with eexpr = TSwitch (f e1, List.map (fun (el,e2) -> List.map f el, f e2) cases, match def with None -> None | Some e -> Some (f e)); etype = ft e.etype }
 	| TMatch (e1,(en,pl),cases,def) ->
-		{ e with eexpr = TMatch (f e1, (en,List.map ft pl), List.map (fun (cl,params,e) -> cl, params, f e) cases, match def with None -> None | Some e -> Some (f e)); etype = ft e.etype }
+		let map_case (cl,params,e) =
+			let params = match params with
+				| None -> None
+				| Some l -> Some (List.map (function None -> None | Some v -> Some (fv v)) l)
+			in
+			cl, params, f e
+		in
+		{ e with eexpr = TMatch (f e1, (en,List.map ft pl), List.map map_case cases, match def with None -> None | Some e -> Some (f e)); etype = ft e.etype }
 	| TTry (e1,catches) ->
-		{ e with eexpr = TTry (f e1, List.map (fun (v,t,e) -> v, ft t, f e) catches); etype = ft e.etype }
+		{ e with eexpr = TTry (f e1, List.map (fun (v,e) -> fv v, f e) catches); etype = ft e.etype }
 	| TReturn eo ->
 		{ e with eexpr = TReturn (match eo with None -> None | Some e -> Some (f e)); etype = ft e.etype }
 	| TCast (e1,t) ->
@@ -1048,7 +1066,7 @@ let s_expr_kind e =
 	| TFunction _ -> "Function"
 	| TVars _ -> "Vars"
 	| TBlock _ -> "Block"
-	| TFor (_,_,_,_) -> "For"
+	| TFor (_,_,_) -> "For"
 	| TIf (_,_,_) -> "If"
 	| TWhile (_,_,_) -> "While"
 	| TSwitch (_,_,_) -> "Switch"
@@ -1073,11 +1091,12 @@ let rec s_expr s_type e =
 		| TThis -> "this"
 		| TSuper -> "super"
 	in
+	let s_var v = v.v_name ^ ":" ^ string_of_int v.v_id in
 	let str = (match e.eexpr with
 	| TConst c ->
 		"Const " ^ s_const c
-	| TLocal s ->
-		"Local " ^ s
+	| TLocal v ->
+		"Local " ^ s_var v
 	| TEnumField (e,f) ->
 		sprintf "EnumField %s.%s" (s_type_path e.e_path) f
 	| TArray (e1,e2) ->
@@ -1105,14 +1124,14 @@ let rec s_expr s_type e =
 		| Prefix -> sprintf "(%s %s)" (s_unop op) (loop e)
 		| Postfix -> sprintf "(%s %s)" (loop e) (s_unop op))
 	| TFunction f ->
-		let args = slist (fun (n,o,t) -> sprintf "%s : %s%s" n (s_type t) (match o with None -> "" | Some c -> " = " ^ s_const c)) f.tf_args in
+		let args = slist (fun (v,o) -> sprintf "%s : %s%s" (s_var v) (s_type v.v_type) (match o with None -> "" | Some c -> " = " ^ s_const c)) f.tf_args in
 		sprintf "Function(%s) : %s = %s" args (s_type f.tf_type) (loop f.tf_expr)
 	| TVars vl ->
-		sprintf "Vars %s" (slist (fun (v,t,eo) -> sprintf "%s : %s%s" v (s_type t) (match eo with None -> "" | Some e -> " = " ^ loop e)) vl)
+		sprintf "Vars %s" (slist (fun (v,eo) -> sprintf "%s : %s%s" (s_var v) (s_type v.v_type) (match eo with None -> "" | Some e -> " = " ^ loop e)) vl)
 	| TBlock el ->
 		sprintf "Block {\n%s}" (String.concat "" (List.map (fun e -> sprintf "%s;\n" (loop e)) el))
-	| TFor (v,t,econd,e) ->
-		sprintf "For (%s : %s in %s,%s)" v (s_type t) (loop econd) (loop e)
+	| TFor (v,econd,e) ->
+		sprintf "For (%s : %s in %s,%s)" (s_var v) (s_type v.v_type) (loop econd) (loop e)
 	| TIf (e,e1,e2) ->
 		sprintf "If (%s,%s%s)" (loop e) (loop e1) (match e2 with None -> "" | Some e -> "," ^ loop e)
 	| TWhile (econd,e,flag) ->
@@ -1122,11 +1141,11 @@ let rec s_expr s_type e =
 	| TSwitch (e,cases,def) ->
 		sprintf "Switch (%s,(%s)%s)" (loop e) (slist (fun (cl,e) -> sprintf "case %s: %s" (slist loop cl) (loop e)) cases) (match def with None -> "" | Some e -> "," ^ loop e)
 	| TMatch (e,(en,tparams),cases,def) ->
-		let args vl = slist (fun (so,t) -> sprintf "%s : %s" (match so with None -> "_" | Some s -> s) (s_type t)) vl in
+		let args vl = slist (function None -> "_" | Some v -> sprintf "%s : %s" (s_var v) (s_type v.v_type)) vl in
 		let cases = slist (fun (il,vl,e) -> sprintf "case %s%s : %s" (slist string_of_int il) (match vl with None -> "" | Some vl -> sprintf "(%s)" (args vl)) (loop e)) cases in
 		sprintf "Match %s (%s,(%s)%s)" (s_type (TEnum (en,tparams))) (loop e) cases (match def with None -> "" | Some e -> "," ^ loop e)
 	| TTry (e,cl) ->
-		sprintf "Try %s(%s) " (loop e) (slist (fun (v,t,e) -> sprintf "catch( %s : %s ) %s" v (s_type t) (loop e)) cl)
+		sprintf "Try %s(%s) " (loop e) (slist (fun (v,e) -> sprintf "catch( %s : %s ) %s" (s_var v) (s_type v.v_type) (loop e)) cl)
 	| TReturn None ->
 		"Return"
 	| TReturn (Some e) ->

+ 9 - 27
typecore.ml

@@ -73,9 +73,7 @@ and typer = {
 	mutable in_loop : bool;
 	mutable in_display : bool;
 	mutable ret : t;
-	mutable locals : (string, t) PMap.t;
-	mutable locals_map : (string, string) PMap.t;
-	mutable locals_map_inv : (string, string) PMap.t;
+	mutable locals : (string, tvar) PMap.t;
 	mutable opened : anon_status ref list;
 	mutable param_type : t option;
 }
@@ -169,34 +167,18 @@ let exc_protect f =
 
 let save_locals ctx =
 	let locals = ctx.locals in
-	let map = ctx.locals_map in
-	let inv = ctx.locals_map_inv in
-	(fun() ->
-		ctx.locals <- locals;
-		ctx.locals_map <- map;
-		ctx.locals_map_inv <- inv;
-	)
-
-let add_local ctx v t =
-	let rec loop n =
-		let nv = (if n = 0 then v else v ^ string_of_int n) in
-		if PMap.mem nv ctx.locals || PMap.mem nv ctx.locals_map_inv then
-			loop (n+1)
-		else begin
-			ctx.locals <- PMap.add v t ctx.locals;
-			if n <> 0 then begin
-				ctx.locals_map <- PMap.add v nv ctx.locals_map;
-				ctx.locals_map_inv <- PMap.add nv v ctx.locals_map_inv;
-			end;
-			nv
-		end
-	in
-	loop 0
+	(fun() -> ctx.locals <- locals)
+
+let add_local ctx n t =
+	let v = alloc_var n t in
+	ctx.locals <- PMap.add n v ctx.locals;
+	v
 
 let gen_local ctx t =
+	(* ensure that our generated local does not mask an existing one *)
 	let rec loop n =
 		let nv = (if n = 0 then "_g" else "_g" ^ string_of_int n) in
-		if PMap.mem nv ctx.locals || PMap.mem nv ctx.locals_map_inv then
+		if PMap.mem nv ctx.locals then
 			loop (n+1)
 		else
 			nv

+ 9 - 12
typeload.ml

@@ -435,7 +435,7 @@ let rec return_flow ctx e =
 		(match def with None -> () | Some e -> return_flow e)
 	| TTry (e,cases) ->
 		return_flow e;
-		List.iter (fun (_,_,e) -> return_flow e) cases;
+		List.iter (fun (_,e) -> return_flow e) cases;
 	| _ ->
 		error()
 
@@ -535,8 +535,7 @@ let type_function ctx args ret static constr f p =
 				| TConst c -> Some c
 				| _ -> display_error ctx "Parameter default value should be constant" p; None
 		) in
-		let n = add_local ctx n t in
-		n, c, t
+		add_local ctx n t, c
 	) args in
 	let old_ret = ctx.ret in
 	let old_static = ctx.in_static in
@@ -794,15 +793,15 @@ let init_class ctx c p herits fields =
 		| None ->
 			if ctx.com.verbose then print_endline ("Remove method " ^ (s_type_path c.cl_path) ^ "." ^ cf.cf_name);
 			remove_field cf stat
-		| _ -> ()) 
+		| _ -> ())
 	in
-	let remove_var_if_unreferenced cf stat = (fun () ->	
+	let remove_var_if_unreferenced cf stat = (fun () ->
 		if not (has_meta ":?keep" cf.cf_meta) then begin
 			if ctx.com.verbose then print_endline ("Remove var " ^ (s_type_path c.cl_path) ^ "." ^ cf.cf_name);
 			remove_field cf stat
 		end)
 	in
-	
+
 	(* ----------------------- COMPLETION ----------------------------- *)
 
 	let display_file = if ctx.com.display then String.lowercase (Common.get_full_path p.pfile) = String.lowercase (!Parser.resume_display).pfile else false in
@@ -925,7 +924,7 @@ let init_class ctx c p herits fields =
 			let params = !params in
 			if inline && c.cl_interface then error "You can't declare inline methods in interfaces" p;
 			let is_macro = (is_macro && stat) || has_meta ":macro" f.cff_meta in
-			let f, stat, fd = if not is_macro || stat then 
+			let f, stat, fd = if not is_macro || stat then
 				f, stat, fd
 			else if ctx.in_macro then
 				(* non-static macros methods are turned into static when we are running the macro *)
@@ -1012,7 +1011,7 @@ let init_class ctx c p herits fields =
 					(fun() -> ())
 				end else begin
 					cf.cf_type <- TLazy r;
-					(fun() -> 
+					(fun() ->
 						if not (keep f stat) then begin
 							delay ctx (remove_method_if_unreferenced cf stat)
 						end else
@@ -1087,7 +1086,7 @@ let init_class ctx c p herits fields =
 						loop l
 				| _ -> error "Invalid require identifier" p
 			in
-			loop conds			
+			loop conds
 		| _ :: l ->
 			check_require l
 	in
@@ -1274,8 +1273,6 @@ let type_module ctx m tdecls loadp =
 		ret = ctx.ret;
 		current = m;
 		locals = PMap.empty;
-		locals_map = PMap.empty;
-		locals_map_inv = PMap.empty;
 		local_types = ctx.g.std.mtypes @ m.mtypes;
 		local_using = [];
 		type_params = [];
@@ -1415,7 +1412,7 @@ let type_module ctx m tdecls loadp =
 			| _ -> assert false);
 	) tdecls;
 	(* PASS 3 : type checking, delayed until all modules and types are built *)
-	List.iter (delay ctx) (List.rev (!delays));	
+	List.iter (delay ctx) (List.rev (!delays));
 	m
 
 let parse_module ctx m p =

+ 44 - 41
typer.ml

@@ -25,7 +25,7 @@ open Typecore
 (* TOOLS *)
 
 type switch_mode =
-	| CMatch of (tenum_field * (string option * t) list option * pos)
+	| CMatch of (tenum_field * (string * t) option list option * pos)
 	| CExpr of texpr
 
 type access_mode =
@@ -195,10 +195,8 @@ let unify_call_params ctx name el args p inline =
 	loop [] el args []
 
 let type_local ctx i p =
-	(* local lookup *)
-	let t = PMap.find i ctx.locals in
-	let i = (try PMap.find i ctx.locals_map with Not_found -> i) in
-	mk (TLocal i) t p
+	let v = PMap.find i ctx.locals in
+	mk (TLocal v) v.v_type p
 
 let rec type_module_type ctx t tparams p =
 	match t with
@@ -295,7 +293,10 @@ let make_call ctx e params t p =
 		(match f.cf_expr with
 		| Some { eexpr = TFunction fd } ->
 			(match Optimizer.type_inline ctx f fd ethis params t p with
-			| None -> raise Exit
+			| None -> 
+				(match cl with
+				| Some { cl_extern = true } -> error "Inline could not be done" p
+				| _ -> raise Exit)
 			| Some e -> e)
 		| _ ->
 			error "Recursive inline is not supported" p)
@@ -313,14 +314,16 @@ let rec acc_get ctx g p =
 		| TFun (_ :: args,ret) ->
 			let tcallb = TFun (args,ret) in
 			let twrap = TFun ([("_e",false,e.etype)],tcallb) in
-			let ecall = make_call ctx et (List.map (fun (n,_,t) -> mk (TLocal n) t p) (("_e",false,e.etype) :: args)) ret p in
+			let args = List.map (fun (n,_,t) -> alloc_var n t) args in
+			let ve = alloc_var "_e" e.etype in
+			let ecall = make_call ctx et (List.map (fun v -> mk (TLocal v) v.v_type p) (ve :: args)) ret p in
 			let ecallb = mk (TFunction {
-				tf_args = List.map (fun (n,_,t) -> n,None,t) args;
+				tf_args = List.map (fun v -> v,None) args;
 				tf_type = ret;
 				tf_expr = mk (TReturn (Some ecall)) t_dynamic p;
 			}) tcallb p in
 			let ewrap = mk (TFunction {
-				tf_args = [("_e",None,e.etype)];
+				tf_args = [ve,None];
 				tf_type = tcallb;
 				tf_expr = mk (TReturn (Some ecallb)) t_dynamic p;
 			}) twrap p in
@@ -528,7 +531,8 @@ let type_ident ctx i is_type p mode =
 		AKExpr e
 	with Not_found ->
 		if ctx.untyped then
-			AKExpr (mk (TLocal i) (mk_mono()) p)
+			let t = mk_mono() in
+			AKExpr (mk (TLocal (alloc_var i t)) t p)
 		else begin
 			if ctx.in_static && PMap.mem i ctx.curclass.cl_fields then error ("Cannot access " ^ i ^ " in static function") p;
 			raise (Error (Unknown_ident i,p))
@@ -677,7 +681,7 @@ let rec type_binop ctx op e1 e2 p =
 			unify ctx e2.etype e1.etype p;
 			check_assign ctx e1;
 			(match e1.eexpr , e2.eexpr with
-			| TLocal i1 , TLocal i2
+			| TLocal i1 , TLocal i2 when i1 == i2 -> error "Assigning a value to itself" p
 			| TField ({ eexpr = TConst TThis },i1) , TField ({ eexpr = TConst TThis },i2) when i1 = i2 ->
 				error "Assigning a value to itself" p
 			| _ , _ -> ());
@@ -703,11 +707,11 @@ let rec type_binop ctx op e1 e2 p =
 			let l = save_locals ctx in
 			let v = gen_local ctx e.etype in
 			let ev = mk (TLocal v) e.etype p in
-			let get = type_binop ctx op (EField ((EConst (Ident v),p),f),p) e2 p in
+			let get = type_binop ctx op (EField ((EConst (Ident v.v_name),p),f),p) e2 p in
 			unify ctx get.etype t p;
 			l();
 			mk (TBlock [
-				mk (TVars [v,e.etype,Some e]) ctx.t.tvoid p;
+				mk (TVars [v,Some e]) ctx.t.tvoid p;
 				make_call ctx (mk (TField (ev,m)) (tfun [t] t) p) [get] t p
 			]) t p
 		| AKInline _ | AKUsing _ | AKMacro _ ->
@@ -889,25 +893,25 @@ and type_unop ctx op flag e p =
 		let ev = mk (TLocal v) e.etype p in
 		let op = (match op with Increment -> OpAdd | Decrement -> OpSub | _ -> assert false) in
 		let one = (EConst (Int "1"),p) in
-		let eget = (EField ((EConst (Ident v),p),f),p) in
+		let eget = (EField ((EConst (Ident v.v_name),p),f),p) in
 		match flag with
 		| Prefix ->
 			let get = type_binop ctx op eget one p in
 			unify ctx get.etype t p;
 			l();
 			mk (TBlock [
-				mk (TVars [v,e.etype,Some e]) ctx.t.tvoid p;
+				mk (TVars [v,Some e]) ctx.t.tvoid p;
 				make_call ctx (mk (TField (ev,m)) (tfun [t] t) p) [get] t p
 			]) t p
 		| Postfix ->
 			let v2 = gen_local ctx t in
 			let ev2 = mk (TLocal v2) t p in
 			let get = type_expr ctx eget in
-			let plusone = type_binop ctx op (EConst (Ident v2),p) one p in
+			let plusone = type_binop ctx op (EConst (Ident v2.v_name),p) one p in
 			unify ctx get.etype t p;
 			l();
 			mk (TBlock [
-				mk (TVars [v,e.etype,Some e; v2,t,Some get]) ctx.t.tvoid p;
+				mk (TVars [v,Some e; v2,Some get]) ctx.t.tvoid p;
 				make_call ctx (mk (TField (ev,m)) (tfun [plusone.etype] t) p) [plusone] t p;
 				ev2
 			]) t p
@@ -962,7 +966,7 @@ and type_switch ctx e cases def need_val p =
 				| [None] -> List.map (fun _ -> None) l
 				| _ -> error ("This constructor requires " ^ string_of_int (List.length l) ^ " arguments") p
 			) in
-			Some (List.map2 (fun p (_,_,t) -> p, apply_params en.e_types params t) pl l)
+			Some (List.map2 (fun p (_,_,t) -> match p with None -> None | Some p -> Some (p, apply_params en.e_types params t)) pl l)
 		| TEnum _ ->
 			if pl <> [] then error "This constructor does not require any argument" p;
 			None
@@ -1038,9 +1042,11 @@ and type_switch ctx e cases def need_val p =
 			let l2 = (match p2 with None -> [] | Some l -> l) in
 			let rec loop = function
 				| [] , [] -> true
-				| (n,_) :: l , [] | [] , (n,_) :: l -> n = None && loop (l,[])
-				| (n1,t1) :: l1, (n2,t2) :: l2 ->
-					n1 = n2 && (n1 = None || type_iseq t1 t2) && loop (l1,l2)
+				| None :: l , [] | [] , None :: l -> loop (l,[])
+				| None :: l1, None :: l2 -> loop (l1,l2)
+				| Some (n1,t1) :: l1, Some (n2,t2) :: l2 ->
+					n1 = n2 && type_iseq t1 t2 && loop (l1,l2)
+				| _ -> false
 			in
 			loop (l1,l2)
 		in
@@ -1061,10 +1067,10 @@ and type_switch ctx e cases def need_val p =
 					| None -> None
 					| Some l ->
 						let has = ref false in
-						let l = List.map (fun (p,t) ->
-							match p with
-							| None -> None, t
-							| Some v -> has := true; Some (add_local ctx v t), t
+						let l = List.map (fun v ->
+							match v with
+							| None -> None
+							| Some (v,t) -> has := true; Some (add_local ctx v t)
 						) l in
 						if !has then Some l else None
 				) in
@@ -1301,14 +1307,11 @@ and type_expr ctx ?(need_val=true) (e,p) =
 						unify ctx e.etype t p;
 						Some e
 				) in
-				let v = add_local ctx v t in
-				v , t , e
+				add_local ctx v t, e
 			with
 				Error (e,p) ->
 					display_error ctx (error_msg e) p;
-					let t = t_dynamic in
-					let v = add_local ctx v t in
-					v , t, None
+					add_local ctx v t_dynamic, None
 		) vl in
 		mk (TVars vl) ctx.t.tvoid p
 	| EFor (i,e1,e2) ->
@@ -1343,7 +1346,7 @@ and type_expr ctx ?(need_val=true) (e,p) =
 					)
 				) in
 				let e2 = type_expr ~need_val:false ctx e2 in
-				mk (TFor (i,pt,e1,e2)) ctx.t.tvoid p
+				mk (TFor (i,e1,e2)) ctx.t.tvoid p
 		) in
 		ctx.in_loop <- old_loop;
 		old_locals();
@@ -1433,7 +1436,7 @@ and type_expr ctx ?(need_val=true) (e,p) =
 			locals();
 			if need_val then unify ctx e.etype e1.etype e.epos;
 			if PMap.mem name ctx.locals then error ("Local variable " ^ name ^ " is preventing usage of this type here") e.epos;
-			v , t , e
+			v , e
 		) catches in
 		mk (TTry (e1,catches)) (if not need_val then ctx.t.tvoid else e1.etype) p
 	| EThrow e ->
@@ -1498,7 +1501,7 @@ and type_expr ctx ?(need_val=true) (e,p) =
 		let e = mk (TFunction f) ft p in
 		(match vname with
 		| None -> e
-		| Some v -> mk (TVars [v,ft,Some e]) ctx.t.tvoid p)
+		| Some v -> mk (TVars [v,Some e]) ctx.t.tvoid p)
 	| EUntyped e ->
 		let old = ctx.untyped in
 		ctx.untyped <- true;
@@ -1625,10 +1628,11 @@ and type_call ctx e el p =
 				match args, params with
 				| _ , [] ->
 					let k = ref 0 in
-					let fun_arg = ("f",None,e.etype) in
-					let first_args = List.map (fun t -> incr k; "a" ^ string_of_int !k, None, t) (List.rev eargs) in
-					let missing_args = List.map (fun (_,opt,t) -> incr k; "a" ^ string_of_int !k, (if opt then Some TNull else None), t) args in
-					let vexpr (v,_,t) = mk (TLocal v) t p in
+					let fun_args l = List.map (fun (v,c) -> v.v_name, c<>None, v.v_type) l in
+					let fun_arg = alloc_var "f" e.etype,None in
+					let first_args = List.map (fun t -> incr k; alloc_var ("a" ^ string_of_int !k) t, None) (List.rev eargs) in
+					let missing_args = List.map (fun (_,opt,t) -> incr k; alloc_var ("a" ^ string_of_int !k) t, (if opt then Some TNull else None)) args in
+					let vexpr (v,_) = mk (TLocal v) v.v_type p in
 					let func = mk (TFunction {
 						tf_args = missing_args;
 						tf_type = ret;
@@ -1656,7 +1660,8 @@ and type_call ctx e el p =
 	| (EConst (Ident "__unprotect__"),_) , [(EConst (String _),_) as e] ->
 		let e = type_expr ctx e in
 		if Common.defined ctx.com "flash" then
-			mk (TCall (mk (TLocal "__unprotect__") (tfun [e.etype] e.etype) p,[e])) e.etype e.epos
+			let t = tfun [e.etype] e.etype in
+			mk (TCall (mk (TLocal (alloc_var "__unprotect__" t)) t p,[e])) e.etype e.epos
 		else
 			e
 	| (EConst (Ident "super"),sp) , el ->
@@ -1718,7 +1723,7 @@ and type_call ctx e el p =
 			| _ ->
 				(* member-macro call : since we will make a static call, let's found the actual class and not its subclass *)
 				(match follow ethis.etype with
-				| TInst (c,_) ->					
+				| TInst (c,_) ->
 					let rec loop c =
 						if PMap.mem f.cf_name c.cl_fields then
 							match ctx.g.do_macro ctx MExpr c.cl_path f.cf_name (Interp.make_ast ethis :: el) p with
@@ -2279,8 +2284,6 @@ let rec create com =
 		in_macro = Common.defined com "macro";
 		ret = mk_mono();
 		locals = PMap.empty;
-		locals_map = PMap.empty;
-		locals_map_inv = PMap.empty;
 		local_types = [];
 		local_using = [];
 		type_params = [];