Browse Source

- php: fixed String.charCodeAt
- php: minor optimization (removed foreach from std code)
- php: implemented haxe.Stack
- php: changed exception handler to use haXe call stack
- php: changed special vars to use the » prefix instead of __
- php: fixed use of reserved keywords for var names
- php: List iterator is now class based (faster)

Franco Ponticelli 16 years ago
parent
commit
df6efc5678
13 changed files with 319 additions and 145 deletions
  1. 7 0
      doc/CHANGES.txt
  2. 170 43
      genphp.ml
  3. 1 15
      std/List.hx
  4. 1 1
      std/Reflect.hx
  5. 11 12
      std/Type.hx
  6. 13 1
      std/haxe/Stack.hx
  7. 2 2
      std/haxe/io/Bytes.hx
  8. 0 8
      std/haxe/io/BytesBuffer.hx
  9. 16 0
      std/haxe/xml/Proxy.hx
  10. 92 57
      std/php/Boot.hx
  11. 2 2
      std/php/Lib.hx
  12. 1 1
      std/php/PhpXml__.hx
  13. 3 3
      std/php/Web.hx

+ 7 - 0
doc/CHANGES.txt

@@ -41,6 +41,13 @@ TODO :
 	flash9 : fixed bug with SWC output and recursive types
 	flash8 : fixed inversed arguments in __new__
 	neko : added neko.net.Socket.setFastSend
+	php: fixed String.charCodeAt
+	php: minor optimization (removed foreach from std code)
+	php: implemented haxe.Stack
+	php: changed exception handler to use haXe call stack
+	php: changed special vars to use the » prefix instead of __
+	php: fixed use of reserved keywords for var names
+	php: List iterator is now class based (faster)
 
 2009-03-22: 2.03
 	optimized Type.enumEq : use index instead of tag comparison for neko/flash9/php

+ 170 - 43
genphp.ml

@@ -1,12 +1,3 @@
-(*
-TODO:
-
-- debug version
-- runtime check for undefined fields
-OPTIMIZATION
-- replace eval for statements with functions/inlines
-- replace closures (eval) with functions
-*)
 (*
  *  haXe/PHP Compiler
  *  Copyright (c)2008 Franco Ponticelli
@@ -40,7 +31,9 @@ type context = {
 	ch : out_channel;
 	buf : Buffer.t;
 	path : path;
+	stack : Codegen.stack_context;
 	mutable curclass : tclass;
+	mutable curmethod : string;
 	mutable tabs : string;
 	mutable in_value : string option;
 	mutable in_loop : bool;
@@ -60,6 +53,106 @@ type context = {
 	mutable cwd : string;
 }
 
+let join_class_path path separator =
+	let result = match fst path, snd path with
+	| [], s -> s
+	| el, s -> String.concat separator el ^ separator ^ s in
+	if (String.contains result '+') then begin
+		let idx = String.index result '+' in
+		(String.sub result 0 idx) ^ (String.sub result (idx+1) ((String.length result) - idx -1 ) )
+	end else
+		result;;
+
+(*  Get a string to represent a type.
+	 The "suffix" will be nothing or "_obj", depending if we want the name of the
+	 pointer class or the pointee (_obj class *)
+let rec class_string klass suffix params =
+	(match klass.cl_path with
+	(* Array class *)
+	|  ([],"Array") -> (snd klass.cl_path) ^ suffix ^ "<" ^ (String.concat ","
+					 (List.map type_string  params) ) ^ " >"
+	| _ when klass.cl_kind=KTypeParameter -> "Dynamic"
+	|  ([],"#Int") -> "/* # */int"
+	|  (["haxe";"io"],"Unsigned_char__") -> "unsigned char"
+	|  ([],"Class") -> "Class"
+	|  ([],"Null") -> (match params with
+			| [t] ->
+				(match follow t with
+				| TInst ({ cl_path = [],"Int" },_)
+				| TInst ({ cl_path = [],"Float" },_)
+				| TEnum ({ e_path = [],"Bool" },_) -> "Dynamic"
+				| _ -> "/*NULL*/" ^ (type_string t) )
+			| _ -> assert false); 
+	(* Normal class *)
+	| _ -> (join_class_path klass.cl_path "::") ^ suffix
+	)
+and type_string_suff suffix haxe_type =
+	(match haxe_type with
+	| TMono r -> (match !r with None -> "Dynamic" | Some t -> type_string_suff suffix t)
+	| TEnum ({ e_path = ([],"Void") },[]) -> "Void"
+	| TEnum ({ e_path = ([],"Bool") },[]) -> "bool"
+	| TInst ({ cl_path = ([],"Float") },[]) -> "double"
+	| TInst ({ cl_path = ([],"Int") },[]) -> "int"
+	| TEnum (enum,params) ->  (join_class_path enum.e_path "::") ^ suffix
+	| TInst (klass,params) ->  (class_string klass suffix params)
+	| TType (type_def,params) ->
+		(match type_def.t_path with
+		| [] , "Null" ->
+			(match params with
+			| [t] ->
+				(match follow t with
+				| TInst ({ cl_path = [],"Int" },_)
+				| TInst ({ cl_path = [],"Float" },_)
+				| TEnum ({ e_path = [],"Bool" },_) -> "Dynamic"
+				| _ -> type_string_suff suffix t)
+			| _ -> assert false);
+		| [] , "Array" ->
+			(match params with
+			| [t] -> "Array<" ^ (type_string (follow t) ) ^ " >"
+			| _ -> assert false)
+		| _ ->  type_string_suff suffix (apply_params type_def.t_types params type_def.t_type)
+		)
+	| TFun (args,haxe_type) -> "Dynamic"
+	| TAnon anon -> "Dynamic"
+	| TDynamic haxe_type -> "Dynamic"
+	| TLazy func -> type_string_suff suffix ((!func)())
+	)
+and type_string haxe_type = 
+	type_string_suff "" haxe_type;;
+
+let debug_expression expression type_too =
+	"/* " ^
+	(match expression.eexpr with
+	| TConst _ -> "TConst"
+	| TLocal _ -> "TLocal"
+	| TEnumField _ -> "TEnumField"
+	| TArray (_,_) -> "TArray"
+	| TBinop (_,_,_) -> "TBinop"
+	| TField (_,_) -> "TField"
+	| TClosure _ -> "TClosure"
+	| TTypeExpr _ -> "TTypeExpr"
+	| TParenthesis _ -> "TParenthesis"
+	| TObjectDecl _ -> "TObjectDecl"
+	| TArrayDecl _ -> "TArrayDecl"
+	| TCall (_,_) -> "TCall"
+	| TNew (_,_,_) -> "TNew"
+	| TUnop (_,_,_) -> "TUnop"
+	| TFunction _ -> "TFunction"
+	| TVars _ -> "TVars"
+	| TBlock _ -> "TBlock"
+	| TFor (_,_,_,_) -> "TFor"
+	| TIf (_,_,_) -> "TIf"
+	| TWhile (_,_,_) -> "TWhile"
+	| TSwitch (_,_,_) -> "TSwitch"
+	| TMatch (_,_,_,_) -> "TMatch"
+	| TTry (_,_) -> "TTry"
+	| TReturn _ -> "TReturn"
+	| TBreak -> "TBreak"
+	| TContinue -> "TContinue"
+	| TThrow _ -> "TThrow" ) ^
+	(if (type_too) then " = " ^ (type_string expression.etype) else "") ^
+	" */";;
+
 let rec escphp n =
 	if n = 0 then "" else if n = 1 then "\\" else ("\\\\" ^ escphp (n-1))
 
@@ -195,9 +288,16 @@ haxe reserved words that match php ones: break, case, class, continue, default,
 	| "endwhile" | "eval" | "exit" | "foreach"| "global" | "include"
 	| "include_once" | "isset" | "list" | "print" | "require" | "require_once"
 	| "unset" | "use" | "__FUNCTION__" | "__CLASS__" | "__METHOD__" | "final" 
-	| "php_user_filter" | "protected" | "abstract" 
+	| "php_user_filter" | "protected" | "abstract" | "__set" | "__get" | "__call"
 	| "clone" -> suf ^ n
 	| _ -> n
+	
+let s_ident_local n =
+	let suf = "h" in
+	match n with
+	| "GLOBALS" | "_SERVER" | "_GET" | "_POST" | "_COOKIE" | "_FILES" 
+	| "_ENV" | "_REQUEST" | "_SESSION" -> suf ^ n
+	| _ -> n
 
 let write_resource dir name data =
 	let i = ref 0 in
@@ -211,6 +311,9 @@ 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
 
 let init com cwd path def_type =
 	let rec create acc = function
@@ -231,6 +334,7 @@ let init com cwd path def_type =
 	Hashtbl.add imports (snd path) [fst path];
 	{
 		com = com;
+		stack = stack_init com false;
 		tabs = "";
 		ch = ch;
 		path = path;
@@ -242,6 +346,7 @@ let init com cwd path def_type =
 		extern_required_paths = [];
 		extern_classes_with_init = [];
 		curclass = null_class;
+		curmethod = "";
 		locals = PMap.empty;
 		inv_locals = PMap.empty;
 		local_types = [];
@@ -305,7 +410,7 @@ let save_locals ctx =
 
 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
+	let name = (if n = 1 then s_ident_local l else s_ident_local (l ^ string_of_int n)) in
 	if PMap.mem name ctx.inv_locals then
 		loop (n+1)
 	else begin
@@ -345,12 +450,12 @@ let handle_break ctx e =
 				ctx.handle_break <- snd old;
 				newline ctx;
 				let p = escphp ctx.quotes in
-				print ctx "} catch(Exception %s$e) { if( %s$e->getMessage() != %s\"__break__%s\" ) throw %s$e; }" p p p p p;
+				print ctx "} catch(_hx_break_exception %s$»e){}" p;
 			)
 
 let this ctx =
 	let p = escphp ctx.quotes in
-	if ctx.in_value <> None then (p ^ "$__this") else (p ^ "$this")
+	if ctx.in_value <> None then (p ^ "$»this") else (p ^ "$this")
 
 let escape_bin s quotes =
 	let b = Buffer.create 0 in
@@ -378,6 +483,8 @@ let gen_constant ctx p = function
 
 let s_funarg ctx arg t p c =
 	let byref = if (String.length arg > 7 && String.sub arg 0 7 = "byref__") then "&" else "" in
+	print ctx "%s%s$%s" byref (escphp ctx.quotes) (s_ident_local arg)
+(*
 	(match t with
 	| TInst (cl,_) ->
 		(match cl.cl_path with
@@ -398,6 +505,7 @@ let s_funarg ctx arg t p c =
 	| _ ->
 		print ctx "%s%s$%s" byref (escphp ctx.quotes) arg;
 	)
+*)
 
 let is_in_dynamic_methods ctx e s =
 	List.exists (fun dm ->
@@ -409,6 +517,7 @@ let is_dynamic_method f =
 	(match f.cf_set with
 		| MethodAccess true -> 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) ->
@@ -416,6 +525,9 @@ let fun_block ctx f p =
 		| None | Some TNull -> e
 		| Some c -> Codegen.concat (Codegen.set_default ctx.com a c t 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 
 		mk_block e
 
 let gen_function_header ctx name f params p =
@@ -549,6 +661,17 @@ and gen_call ctx e el =
 		spr ctx ", array(";
 		concat ctx ", " (gen_value ctx) el;
 		spr ctx "))"
+(*
+	| TField (ex,name), el ->
+		spr ctx (debug_expression ex true);
+		ctx.is_call <- true;
+		spr ctx "call_user_func_array(";
+		gen_value ctx e;
+		ctx.is_call <- false;
+		spr ctx ", array(";
+		concat ctx ", " (gen_value ctx) el;
+		spr ctx "))"
+*)
 	| _ ->
 		ctx.is_call <- true;
 		gen_value ctx e;
@@ -850,7 +973,8 @@ and gen_expr ctx e =
 	| TConst c ->
 		gen_constant ctx e.epos c
 	| TLocal s ->
-		spr ctx ((escphp ctx.quotes) ^ "$" ^ (try PMap.find s ctx.locals with Not_found -> error ("Unknown local " ^ s) e.epos))
+		spr ctx ((escphp ctx.quotes) ^ "$" ^ (try PMap.find s ctx.locals with Not_found -> (s_ident_local s)))
+(*		spr ctx ((escphp ctx.quotes) ^ "$" ^ (s_ident_local s)) *)
 	| 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)
@@ -873,7 +997,7 @@ and gen_expr ctx e =
 			(match e.eexpr with
 			| TArray(te1, te2) ->
 				gen_value ctx te1;
-				spr ctx "->__a[";
+				spr ctx "->»a[";
 				gen_value ctx te2;
 				spr ctx "]";
 			| _ ->
@@ -882,7 +1006,7 @@ and gen_expr ctx e =
 			(match e.eexpr with
 			| TArray(te1, te2) ->
 				gen_value ctx te1;
-				spr ctx "->__a[";
+				spr ctx "->»a[";
 				gen_value ctx te2;
 				spr ctx "]";
 			| TField (e1,s) ->
@@ -1100,8 +1224,7 @@ and gen_expr ctx e =
 			);
 	| TBreak ->
 		if not ctx.in_loop then unsupported e.epos;
-		let p = escphp ctx.quotes in
-		if ctx.handle_break then print ctx "throw new Exception(%s\"__break__%s\")" p p else spr ctx "break"
+		if ctx.handle_break then spr ctx "throw new _hx_break_exception()" else spr ctx "break"
 	| TContinue ->
 		if not ctx.in_loop then unsupported e.epos;
 		spr ctx "continue"
@@ -1156,9 +1279,12 @@ and gen_expr ctx e =
 		b();
 	| TFunction f ->
 		let old = ctx.in_value, ctx.in_loop in
+		let old_meth = ctx.curmethod in
 		ctx.in_value <- None;
 		ctx.in_loop <- false;
+		ctx.curmethod <- ctx.curmethod ^ "@" ^ string_of_int (Lexer.find_line_index ctx.com.lines e.epos);
 		gen_inline_function ctx f [] e.epos;
+		ctx.curmethod <- old_meth;
 		ctx.in_value <- fst old;
 		ctx.in_loop <- snd old;
 	| TCall (ec,el) ->
@@ -1193,9 +1319,9 @@ and gen_expr ctx e =
 			let n = define_local ctx n in
 			match v with
 			| None -> 
-				print ctx "%s = null" n
+				print ctx "%s = null" (s_ident_local n)
 			| Some e ->
-				print ctx "%s = " n;
+				print ctx "%s = " (s_ident_local n);
 				gen_value ctx e
 		) vl;
 	| TNew (c,_,el) ->
@@ -1234,7 +1360,7 @@ and gen_expr ctx e =
 		(match e.eexpr with
 		| TArray(te1, te2) ->
 			gen_value ctx te1;
-			spr ctx "->__a[";
+			spr ctx "->»a[";
 			gen_value ctx te2;
 			spr ctx "]";
 		| TField (e1,s) ->
@@ -1245,7 +1371,7 @@ and gen_expr ctx e =
 		(match e.eexpr with
 		| TArray(te1, te2) ->
 			gen_value ctx te1;
-			spr ctx "->__a[";
+			spr ctx "->»a[";
 			gen_value ctx te2;
 			spr ctx "]";
 		| TField (e1,s) ->
@@ -1275,7 +1401,7 @@ and gen_expr ctx e =
 	| TFor (v,t,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 = define_local ctx "»it" in
 		let v = define_local ctx v in
 		let p = escphp ctx.quotes in
 		print ctx "%s$%s = " p tmp;
@@ -1293,7 +1419,7 @@ and gen_expr ctx e =
 	| TTry (e,catchs) ->
 		spr ctx "try ";
 		gen_expr ctx (mk_block e);
-		let ex = define_local ctx "__e__" in
+		let ex = define_local ctx "»e" in
 		print ctx "catch(Exception %s$%s) {" (escphp ctx.quotes) ex;
 		let p = escphp ctx.quotes in
 		let first = ref true in
@@ -1341,7 +1467,7 @@ and gen_expr ctx e =
 			print ctx " else throw %s$%s; }" (escphp ctx.quotes) ex;
 	| TMatch (e,_,cases,def) ->
 		let b = save_locals ctx in
-		let tmp = define_local ctx "__t__" in
+		let tmp = define_local ctx "»t" in
 		print ctx "%s$%s = " (escphp ctx.quotes) tmp;
 		gen_value ctx e;
 		newline ctx;
@@ -1409,14 +1535,14 @@ 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 v -> "»r")) t_dynamic e.epos,
 			e
 		)) e.etype e.epos
 	in
 	let value bl =
 		let old = ctx.in_value, ctx.in_loop in
 		let locs = save_locals ctx in
-		let tmp = define_local ctx "__r__" in
+		let tmp = define_local ctx "»r" in
 		ctx.in_value <- Some tmp;
 		ctx.in_loop <- false;
 		let b =
@@ -1424,7 +1550,7 @@ and gen_value ctx e =
 			print ctx "eval(%s\"" (escphp ctx.quotes);
 			ctx.quotes <- (ctx.quotes + 1);
 			let p = (escphp ctx.quotes) in
-			print ctx "if(isset(%s$this)) %s$__this =& %s$this;" p p p;
+			print ctx "if(isset(%s$this)) %s$»this =& %s$this;" p p p;
 			let b = open_block ctx in
 			b
 		end else
@@ -1538,17 +1664,6 @@ 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 rec field_exists_in_hierarchy cl name =
-	if PMap.exists name cl.cl_fields then true
-	else (
-		match cl.cl_super with
-		| Some (c,_) -> 
-			field_exists_in_hierarchy c name
-		| None -> 
-			false
-	)
-	
 	
 let generate_field ctx static f =
 	newline ctx;
@@ -1558,7 +1673,10 @@ let generate_field ctx static f =
 	let p = ctx.curclass.cl_pos in
 	match f.cf_expr with
 	| Some { eexpr = TFunction fd } ->
-		if static && field_exists_in_hierarchy ctx.curclass f.cf_name then error ("Can't redeclare method (PHP limitation): " ^ f.cf_name) ctx.curclass.cl_pos;
+		if f.cf_name = "__construct" then
+			ctx.curmethod <- "new"
+		else
+			ctx.curmethod <- f.cf_name;
 		spr ctx (rights ^ " ");
 		(match f.cf_set with
 		| MethodAccess true ->
@@ -1643,6 +1761,7 @@ let rec super_has_dynamic c =
 let generate_class ctx c =
 	let requires_constructor = ref true in
 	ctx.curclass <- c;
+(*	ctx.curmethod <- ("new",true); *)
 	ctx.local_types <- List.map snd c.cl_types;
 
 	print ctx "%s %s " (if c.cl_interface then "interface" else "class") (s_path ctx c.cl_path c.cl_extern c.cl_pos);
@@ -1684,12 +1803,12 @@ let generate_class ctx c =
 	(match c.cl_dynamic with
 		| Some _ when not c.cl_interface && not (super_has_dynamic c) ->
 			newline ctx;
-			spr ctx "private $__dynamics = array();\n\tpublic function &__get($n) {\n\t\tif(isset($this->__dynamics[$n]))\n\t\t\treturn $this->__dynamics[$n];\n\t}\n\tpublic function __set($n, $v) {\n\t\t$this->__dynamics[$n] = $v;\n\t}\n\tpublic function __call($n, $a) {\n\t\tif(is_callable($this->__dynamics[$n]))\n\t\t\treturn call_user_func_array($this->__dynamics[$n], $a);\n\t\tthrow new HException(\"Unable to call «\".$n.\"»\");\n\t}"
+			spr ctx "private $»dynamics = array();\n\tpublic function &__get($n) {\n\t\tif(isset($this->»dynamics[$n]))\n\t\t\treturn $this->»dynamics[$n];\n\t}\n\tpublic function __set($n, $v) {\n\t\t$this->»dynamics[$n] = $v;\n\t}\n\tpublic function __call($n, $a) {\n\t\tif(is_callable($this->»dynamics[$n]))\n\t\t\treturn call_user_func_array($this->»dynamics[$n], $a);\n\t\tthrow new HException(\"Unable to call «\".$n.\"»\");\n\t}"
 		| Some _
 		| _ ->
 			if List.length ctx.dynamic_methods > 0 then begin
 				newline ctx;
-				spr ctx "public function __call($m, $a) {\n\t\tif(isset($this->$m) && is_callable($this->$m))\n\t\t\treturn call_user_func_array($this->$m, $a);\n\t\telse if(isset($this->__dynamics[$m]) && is_callable($this->__dynamics[$m]))\n\t\t\treturn call_user_func_array($this->__dynamics[$m], $a);\n\t\telse\n\t\t\tthrow new HException('Unable to call «'.$m.'»');\n\t}";
+				spr ctx "public function __call($m, $a) {\n\t\tif(isset($this->$m) && is_callable($this->$m))\n\t\t\treturn call_user_func_array($this->$m, $a);\n\t\telse if(isset($this->»dynamics[$m]) && is_callable($this->»dynamics[$m]))\n\t\t\treturn call_user_func_array($this->»dynamics[$m], $a);\n\t\telse\n\t\t\tthrow new HException('Unable to call «'.$m.'»');\n\t}";
 			end;
 	);
 
@@ -1709,11 +1828,12 @@ let generate_class ctx c =
 	end;
 	
 	print ctx "}"
-
+	
 let createmain com c =
 	let filename = match com.php_front with None -> "index.php" | Some n -> n in
 	let ctx = {
 		com = com;
+		stack = stack_init com false;
 		tabs = "";
 		ch = open_out (com.file ^ "/" ^ filename);
 		path = ([], "");
@@ -1725,6 +1845,7 @@ let createmain com c =
 		extern_required_paths = [];
 		extern_classes_with_init = [];
 		curclass = null_class;
+		curmethod = "";
 		locals = PMap.empty;
 		inv_locals = PMap.empty;
 		local_types = [];
@@ -1853,6 +1974,12 @@ let generate com =
 					gen_expr ctx e);
 				List.iter (generate_static_field_assign ctx c.cl_path) c.cl_ordered_statics;
 				newline ctx;
+				if c.cl_path = (["php"], "Boot") & com.debug then begin
+					print ctx "$%s = new _hx_array(array())" ctx.stack.Codegen.stack_var;
+					newline ctx;
+					print ctx "$%s = new _hx_array(array())" ctx.stack.Codegen.stack_exc_var;
+					newline ctx;
+				end;
 				close ctx);
 		| TEnumDecl e ->
 			if e.e_extern then

+ 1 - 15
std/List.hx

@@ -189,21 +189,7 @@ class List<T> {
 	**/
 	public function iterator() : Iterator<T> {
 #if php
-		var it = null;
-		it = untyped {
-			h : h,
-			hasNext : function() {
-				return __php__("$it->h != null");
-			},
-			next : function() {
-				if(__php__("$it->h == null"))
-					return null;
-				var x = __php__("$it->h[0]");
-				it.h = __php__("$it->h[1]");
-				return x;
-			}
-		};
-		return cast it;
+		return untyped __call__("new _hx_list_iterator", h);
 #else
 		return cast {
 			h : h,

+ 1 - 1
std/Reflect.hx

@@ -117,7 +117,7 @@ class Reflect {
 				else if(args.length == 1) return __call__("call_user_func", field(o, func), args[0]);
 				else return __call__("call_user_func", field(o, func), args[0], args[1]);
 			}
-			return __php__("call_user_func_array(is_callable($func) ? $func : array($o, $func) , $args == null ? array() : $args->__a)");
+			return __php__("call_user_func_array(is_callable($func) ? $func : array($o, $func) , $args == null ? array() : $args->»a)");
 		#elseif cpp
          var s:String = func;
          return untyped o.__Field(s).__Run(args);

+ 11 - 12
std/Type.hx

@@ -324,7 +324,7 @@ class Type {
 			if(cl.__qname__ == 'String') return args[0];
 			var c = cl.__rfl__();
 			if(c == null) return null;
-			return __php__("$inst = $c->getConstructor() ? $c->newInstanceArgs($args->__a) : $c->newInstanceArgs()");
+			return __php__("$inst = $c->getConstructor() ? $c->newInstanceArgs($args->»a) : $c->newInstanceArgs()");
 		#elseif cpp
 			if (cl!=null)
 				return cl.mConstructArgs(args);
@@ -449,17 +449,16 @@ class Type {
 			untyped __php__("
 			$rfl = $c->__rfl__();
 			if($rfl === null) return new _hx_array(array());
-			$ms = $rfl->getMethods();
-			$ps = $rfl->getProperties();
 			$r = array();
 			$internals = array('__construct', '__call', '__get', '__set', '__isset', '__unset', '__toString');
-			foreach($ms as $m) {
+			$ms = $rfl->getMethods();
+			while(list(, $m) = each($ms)) {
 				$n = $m->getName();
 				if(!$m->isStatic() && ! in_array($n, $internals)) $r[] = $n;
 			}
-			foreach($ps as $p)
-				if(!$p->isStatic()) $r[] = $p->getName();
-			");
+			$ps = $rfl->getProperties();
+			while(list(, $p) = each($ps))
+				if(!$p->isStatic()) $r[] = $p->getName()");
 			return untyped __php__("new _hx_array(array_values(array_unique($r)))");
 		#elseif cpp
 			return untyped c.GetInstanceFields();
@@ -502,11 +501,11 @@ class Type {
 			$rfl = $c->__rfl__();
 			if($rfl === null) return new _hx_array(array());
 			$ms = $rfl->getMethods();
-			$ps = $rfl->getProperties();
 			$r = array();
-			foreach($ms as $m)
+			while(list(, $m) = each($ms))
 				if($m->isStatic()) $r[] = $m->getName();
-			foreach($ps as $p)
+			$ps = $rfl->getProperties();
+			while(list(, $p) = each($ps))
 				if($p->isStatic()) $r[] = $p->getName();
 			");
 			return untyped __php__("new _hx_array($r)");
@@ -540,9 +539,9 @@ class Type {
 			var rfl = __php__("new ReflectionClass($e->__tname__)");
 			var sps : ArrayAccess<Dynamic> = rfl.getStaticProperties();
 //			var r : ArrayAccess<String> = __call__('array');
-			__php__("$r = array(); foreach($sps as $k => $v) $r[] = $k");
+			__php__("$r = array(); while(list($k) = each($sps)) $r[] = $k");
 			sps = rfl.getMethods();
-			__php__("foreach($sps as $m) { $n = $m->getName(); if($n != '__construct' && $n != '__toString') $r[] = $n; }");
+			__php__("while(list(, $m) = each($sps)) { $n = $m->getName(); if($n != '__construct' && $n != '__toString') $r[] = $n; }");
 			return __php__("new _hx_array($r)");
 		#elseif cpp
 			return untyped e.GetClassFields();

+ 13 - 1
std/haxe/Stack.hx

@@ -54,6 +54,8 @@ class Stack {
 			return a;
 		#elseif (flash || js)
 			return makeStack("$s");
+		#elseif php
+			return makeStack("%s");
 		#else
 			return [];
 		#end
@@ -83,8 +85,10 @@ class Stack {
 				i--;
 			}
 			return a;
-		#elseif (flash ||js)
+		#elseif (flash || js)
 			return makeStack("$e");
+		#elseif php
+			return makeStack("%e");
 		#else
 			return [];
 		#end
@@ -172,6 +176,14 @@ class Stack {
 				m.unshift(Method(d[0],d[1]));
 			}
 			return m;
+		#elseif php
+			var a : Array<String> = untyped __php__("$GLOBALS[$s]");
+			var m = new Array();
+			for( i in 0...a.length - ((s == "%s") ? 2 : 0)) {
+				var d = a[i].split("::");
+				m.unshift(Method(d[0],d[1]));
+			}
+			return m;
 		#else
 			return null;
 		#end

+ 2 - 2
std/haxe/io/Bytes.hx

@@ -157,7 +157,7 @@ class Bytes {
 		#elseif php
 		// TODO: test me
 		return untyped __call__("substr", b, pos, len);
-//		return untyped __call__("call_user_func_array", "pack", __call__("array_merge", __call__("array", "C*"), __call__("array_slice", b.__a, pos, len)));
+//		return untyped __call__("call_user_func_array", "pack", __call__("array_merge", __call__("array", "C*"), __call__("array_slice", b.»a, pos, len)));
 		#elseif cpp
 		var result:String="";
 		untyped __global__.__hxcpp_string_of_bytes(b,result,pos,len);
@@ -198,7 +198,7 @@ class Bytes {
 		#elseif php
 		// TODO: test me
 		return cast b;
-//		return untyped __call__("call_user_func_array", "pack", __call__("array_merge", __call__("array", "C*"), b.__a));
+//		return untyped __call__("call_user_func_array", "pack", __call__("array_merge", __call__("array", "C*"), b.»a));
 		#else
 		return readString(0,length);
 		#end

+ 0 - 8
std/haxe/io/BytesBuffer.hx

@@ -73,7 +73,6 @@ class BytesBuffer {
 		b.writeBytes(src.getData());
 		#elseif php
 		b += cast src.getData();
-//		b = untyped __call__("new _hx_array", __call__("array_merge", b.__a, src.getData().__a));
 		#else
 		var b1 = b;
 		var b2 = src.getData();
@@ -92,13 +91,6 @@ class BytesBuffer {
 		b.writeBytes(src.getData(),pos,len);
 		#elseif php
 		b += untyped __call__("substr", src.b, pos, len);
-/*
-		try {
-			b = untyped __call__("new _hx_array", __call__("array_merge", b.__a, __call__("array_slice", src.getData().__a, pos, len)));
-		} catch(e : Dynamic) {
-			throw Error.OutsideBounds;
-		}
-*/
 		#else
 		var b1 = b;
 		var b2 = src.getData();

+ 16 - 0
std/haxe/xml/Proxy.hx

@@ -42,6 +42,7 @@ package haxe.xml;
 	// in your XML, and completion works as well
 	]
 **/
+/*
 class Proxy<Const,T> {
 
 	var __f : String -> T;
@@ -55,3 +56,18 @@ class Proxy<Const,T> {
 	}
 
 }
+*/
+
+class Proxy<Const,T> {
+
+	dynamic function __f(s : String) : T { return null; }
+
+	public function new(f) {
+		this.__f = f;
+	}
+
+	public function resolve(k) : T {
+		return __f(k);
+	}
+
+}

+ 92 - 57
std/php/Boot.hx

@@ -15,63 +15,64 @@ function _hx_add($a, $b) {
 	}
 }
 		
-function _hx_anonymous($p = array()) {
+function _hx_anonymous($arr = array()) {
 	$o = new _hx_anonymous();
-	foreach($p as $k => $v)
+	reset($arr);
+	while(list($k, $v) = each($arr))
 		$o->$k = $v;
 	return $o;
 }
 
 class _hx_array implements ArrayAccess {
-	var $__a;
+	var $»a;
 	var $length;
 	function __construct($a = array()) {
-		$this->__a = $a;
+		$this->»a = $a;
 		$this->length = count($a);
 	}
 
 	function concat($a) {
-		return new _hx_array(array_merge($this->__a, $a->__a));
+		return new _hx_array(array_merge($this->»a, $a->»a));
 	}
 
 	function copy() {
-		return new _hx_array($this->__a);
+		return new _hx_array($this->»a);
 	}
 
 	function &get($index) {
-		if(isset($this->__a[$index])) return $this->__a[$index];
+		if(isset($this->»a[$index])) return $this->»a[$index];
 		return null;
 	}
 
 	function insert($pos, $x) {
-		array_splice($this->__a, $pos, 0, array($x));
+		array_splice($this->»a, $pos, 0, array($x));
 		$this->length++;
 	}
 
 	function iterator() {
-		return new _hx_array_iterator($this->__a);
+		return new _hx_array_iterator($this->»a);
 	}
 
 	function join($sep) {
-		return implode($this->__a, $sep);
+		return implode($this->»a, $sep);
 	}
 
 	function pop() {
-		$r = array_pop($this->__a);
-		$this->length = count($this->__a);
+		$r = array_pop($this->»a);
+		$this->length = count($this->»a);
 		return $r;
 	}
 
 	function push($x) {
-		$this->__a[] = $x;
+		$this->»a[] = $x;
 		$this->length++;
 	}
 
 	function remove($x) {
-		for($i = 0; $i < count($this->__a); $i++)
-			if($this->__a[$i] === $x) {
-				unset($this->__a[$i]);
-				$this->__a = array_values($this->__a);
+		for($i = 0; $i < count($this->»a); $i++)
+			if($this->»a[$i] === $x) {
+				unset($this->»a[$i]);
+				$this->»a = array_values($this->»a);
 				$this->length--;
 				return true;
 			}
@@ -79,8 +80,8 @@ class _hx_array implements ArrayAccess {
 	}
 
 	function removeAt($pos) {
-		if(array_key_exists($pos, $this->__a)) {
-			unset($this->__a[$pos]);
+		if(array_key_exists($pos, $this->»a)) {
+			unset($this->»a[$pos]);
 			$this->length--;
 			return true;
 		} else
@@ -88,35 +89,35 @@ class _hx_array implements ArrayAccess {
 	}
 
 	function reverse() {
-		$this->__a = array_reverse($this->__a, false);
+		$this->»a = array_reverse($this->»a, false);
 	}
 
 	function shift() {
-		$r = array_shift($this->__a);
-		$this->length = count($this->__a);
+		$r = array_shift($this->»a);
+		$this->length = count($this->»a);
 		return $r;
 	}
 
 	function slice($pos, $end) {
 		if($end == null)
-			return new _hx_array(array_slice($this->__a, $pos));
+			return new _hx_array(array_slice($this->»a, $pos));
 		else
-			return new _hx_array(array_slice($this->__a, $pos, $end-$pos));
+			return new _hx_array(array_slice($this->»a, $pos, $end-$pos));
 	}
 
 	function sort($f) {
-		usort($this->__a, $f);
+		usort($this->»a, $f);
 	}
 
 	function splice($pos, $len) {
 		if($len < 0) $len = 0;
-		$nh = new _hx_array(array_splice($this->__a, $pos, $len));
-		$this->length = count($this->__a);
+		$nh = new _hx_array(array_splice($this->»a, $pos, $len));
+		$this->length = count($this->»a);
 		return $nh;
 	}
 
 	function toString() {
-		return '['.implode($this->__a, ', ').']';
+		return '['.implode($this->»a, ', ').']';
 	}
 
 	function __toString() {
@@ -124,26 +125,26 @@ class _hx_array implements ArrayAccess {
 	}
 
 	function unshift($x) {
-		array_unshift($this->__a, $x);
+		array_unshift($this->»a, $x);
 		$this->length++;
 	}
 
 	// ArrayAccess methods:
 	function offsetExists($offset) {
-		return isset($this->__a[$offset]);
+		return isset($this->»a[$offset]);
 	}
 
 	function offsetGet($offset) {
-		if(isset($this->__a[$offset])) return $this->__a[$offset];
+		if(isset($this->»a[$offset])) return $this->»a[$offset];
 		return null;
 	}
 
 	function offsetSet($offset, $value) {
 		if($this->length <= $offset) {
-			$this->__a = array_merge($this->__a, array_fill(0, $offset+1-$this->length, null));
+			$this->»a = array_merge($this->»a, array_fill(0, $offset+1-$this->length, null));
 			$this->length = $offset+1;
 		}
-		return $this->__a[$offset] = $value;
+		return $this->»a[$offset] = $value;
 	}
 
 	function offsetUnset($offset) {
@@ -152,20 +153,20 @@ class _hx_array implements ArrayAccess {
 }
 
 class _hx_array_iterator {
-	private $a;
-	private $i;
+	private $»a;
+	private $»i;
 	public function __construct($a) {
-		$this->__a = $a;
-		$this->i = 0;
+		$this->»a = $a;
+		$this->»i = 0;
 	}
 
 	public function next() {
 		if(!$this->hasNext()) return null;
-		return $this->__a[$this->i++];
+		return $this->»a[$this->»i++];
 	}
 
 	public function hasNext() {
-		return $this->i < count($this->__a);
+		return $this->»i < count($this->»a);
 	}
 }
 
@@ -177,8 +178,10 @@ function _hx_array_assign($a, $i, $v) {
 	return $a[$i] = $v;
 }
 
+class _hx_break_exception extends Exception {}
+
 function _hx_char_code_at($s, $pos) {
-	if(empty($s) || $pos >= strlen($s)) return null;
+	if($pos < 0 || $pos >= strlen($s)) return null;
 	return ord($s{$pos});
 }
 
@@ -204,7 +207,7 @@ function _hx_equal($x, $y) {
 
 function _hx_error_handler($errno, $errmsg, $filename, $linenum, $vars) {
 	$msg = $errmsg . ' (errno: ' . $errno . ') in ' . $filename . ' at line #' . $linenum;
-	$e = new HException($msg, $errmsg, $errno, _hx_anonymous(array('fileName' => 'Boot.hx', 'lineNumber' => 41, 'className' => 'php.Boot', 'methodName' => '__error_handler')));
+	$e = new HException($msg, $errmsg, $errno, _hx_anonymous(array('fileName' => 'Boot.hx', 'lineNumber' => __LINE__, 'className' => 'php.Boot', 'methodName' => '_hx_error_handler')));
 	$e->setFile($filename);
 	$e->setLine($linenum);
 	throw $e;
@@ -212,8 +215,25 @@ function _hx_error_handler($errno, $errmsg, $filename, $linenum, $vars) {
 }
 
 function _hx_exception_handler($e) {
-	$msg = '<pre>Uncaught exception: <b>' . $e->getMessage() . '</b>\nin file: <b>' . $e->getFile() . '</b> line <b>' . $e->getLine() . '</b>\n\n' . $e->getTraceAsString() . '</pre>';
-	die($msg);
+	if(0 == strncasecmp(PHP_SAPI, 'cli', 3)) {
+		$msg   = $e-> getMessage();
+		$nl    = \"\\n\";
+		$pre   = '';
+		$post  = '';
+	} else {
+		$msg   = '<b>' . $e-> getMessage() . '</b>';
+		$nl    = \"<br />\";
+		$pre   = '<pre>';
+		$post  = '</pre>';
+	}
+	if(isset($GLOBALS['%s'])) {
+		$stack = '';
+		$i = $GLOBALS['%s']->length;
+		while(--$i >= 0)
+			$stack .= 'Called from '.$GLOBALS['%s'][$i].$nl;
+		die($pre.'uncaught exception: '.$msg.$nl.$nl.$stack.$post);
+	} else
+		die($pre.'uncaught exception: '.$msg.$nl.$nl.'in file: '.$e->getFile().' line '.$e->getLine().$nl.$e->getTraceAsString().$post);
 }
 
 function _hx_explode($delimiter, $s) {
@@ -318,6 +338,24 @@ function _hx_len($o) {
 	return is_string($o) ? strlen($o) : $o->length;
 }
 
+class _hx_list_iterator {
+	private $»h;
+	public function __construct($h) {
+		$this->»h = $h;
+	}
+
+	public function next() {
+		if($this->»h == null) return null;
+		$x = $this->»h[0];
+		$this->»h = $this->»h[1];
+		return $x;
+	}
+
+	public function hasNext() {
+		return $this->»h != null;
+	}
+}
+
 function _hx_null() {
 	return null;
 }
@@ -476,12 +514,7 @@ function _hx_ttype($n) {
 
 class _hx_anonymous extends stdClass {
 	public function __call($m, $a) {
-		$v = $this->$m;
-		try {
-			return call_user_func_array($v, $a);
-		} catch(Exception $e) {
-			throw new HException('Unable to call «'.$m.'»');
-		}
+		return call_user_func_array($this->$m, $a);
 	}
 
 	public function __set($n, $v) {
@@ -508,7 +541,7 @@ class _hx_anonymous extends stdClass {
 		$b = '{ ';
 		$properties = $rfl->getProperties();
 		$first = true;
-		foreach($properties as $prop) {
+		while(list(, $prop) = each($properties)) {
 			if($first)
 				$first = false;
 			else
@@ -610,11 +643,13 @@ class _hx_lambda {
 
 	public $params = array();
 	public function execute() {
-		$__this =& $this->scope;
-		foreach(array_keys($this->locals) as ${'%k'})
-			${${'%k'}} =& $this->locals[${'%k'}];
-		for(${'%i'} = 0; ${'%i'} < count($this->args); ${'%i'}++)
-			${$this->args[${'%i'}]} =& $this->params[${'%i'}];
+		$»arr = array_keys($this->locals);
+		while($»k = current($»arr)) {
+			${$»k} =& $this->locals[$»k];
+			next($»arr);
+		}
+		for($»i = 0; $»i < count($this->args); $»i++)
+			${$this->args[$»i]} =& $this->params[$»i];
 		return eval($this->body);
 	}
 
@@ -705,7 +740,7 @@ $_hx_autload_cache_file = $_hx_libdir . '/../cache/haxe_autoload.php';
 if(!file_exists($_hx_autload_cache_file)) {
 	function _hx_build_paths($d, &$_hx_types_array, $pack) {
 		$h = opendir($d);
-		while (false !== ($f = readdir($h))) {
+		while(false !== ($f = readdir($h))) {
 			$p = $d.'/'.$f;
 			if($f == '.' || $f == '..')
 				continue;
@@ -780,4 +815,4 @@ function _hx_autoload($name) {
 
 spl_autoload_register('_hx_autoload')");
 	}
-}
+}

+ 2 - 2
std/php/Lib.hx

@@ -49,7 +49,7 @@ class Lib {
 	}
 
 	public static inline function toPhpArray(a : Array<Dynamic>) : NativeArray {
-		return untyped a.__a;
+		return untyped __php__("$a->»a");
 	}
 
 	public static inline function toHaxeArray(a : NativeArray) : Array<Dynamic> {
@@ -58,7 +58,7 @@ class Lib {
 
 	public static function hashOfAssociativeArray<T>(arr : NativeArray) : Hash<T> {
 		var h = new Hash<T>();
-		untyped __php__("foreach($arr as $k => $v) $h->set($k, $v)");
+		untyped __php__("reset($arr); while(list($k, $v) = each($arr)) $h->set($k, $v)");
 		return h;
 	}
 

+ 1 - 1
std/php/PhpXml__.hx

@@ -49,7 +49,7 @@ class PhpXml__ {
 	private static var build : PhpXml__;
 	private static function __start_element_handler(parser : Dynamic, name : String, attribs : ArrayAccess<String>) {
 		var node = createElement(name);
-		untyped __php__("foreach($attribs as $key => $value) $node->set($key, $value)");
+		untyped __php__("while(list($k, $v) = each($attribs)) $node->set($k, $v)");
 		build.addChild(node);
 		build = node;
 	}

+ 3 - 3
std/php/Web.hx

@@ -13,7 +13,7 @@ class Web {
 		#if force_std_separator
 		var a : NativeArray = untyped __php__("$_POST");
 		if(untyped __call__("get_magic_quotes_gpc"))
-			untyped __php__("foreach($a as $k => $v) $a[$k] = stripslashes((string)$v)");
+			untyped __php__("reset($a); while(list($k, $v) = each($a)) $a[$k] = stripslashes((string)$v)");
 		var h = Lib.hashOfAssociativeArray(a);
 		var params = getParamsString();
 		if( params == "" )
@@ -27,7 +27,7 @@ class Web {
 		#else
 		var a : NativeArray = untyped __php__("array_merge($_GET, $_POST)");
 		if(untyped __call__("get_magic_quotes_gpc"))
-			untyped __php__("foreach($a as $k => $v) $a[$k] = stripslashes((string)$v)");
+			untyped __php__("reset($a); while(list($k, $v) = each($a)) $a[$k] = stripslashes((string)$v)");
 		return Lib.hashOfAssociativeArray(a);
 		#end
 	}
@@ -62,7 +62,7 @@ class Web {
             var data = post.get(param);
             var k = 0, v = "";
             if (untyped __call__("is_array", data)) {
-                untyped __php__(" foreach($data as $k=>$v) { ");
+                untyped __php__(" reset($data); while(list($k, $v) = each($data)) { ");
                 res[k] = v;
                 untyped __php__(" } ");
             }