Simon Krajewski пре 11 година
родитељ
комит
b0b0dde32b
9 измењених фајлова са 109 додато и 313 уклоњено
  1. 1 1
      Makefile
  2. 1 2
      ast.ml
  3. 0 1
      common.ml
  4. 18 175
      genjs.ml
  5. 1 11
      main.ml
  6. 69 101
      std/Math.hx
  7. 5 5
      std/js/Boot.hx
  8. 10 12
      std/js/_std/Reflect.hx
  9. 4 5
      std/js/_std/Std.hx

+ 1 - 1
Makefile

@@ -115,7 +115,7 @@ gencs.cmx: type.cmx lexer.cmx gencommon.cmx common.cmx codegen.cmx ast.cmx
 
 genjava.cmx: type.cmx gencommon.cmx common.cmx codegen.cmx ast.cmx
 
-genjs.cmx: type.cmx optimizer.cmx lexer.cmx common.cmx codegen.cmx ast.cmx typecore.cmx
+genjs.cmx: type.cmx optimizer.cmx lexer.cmx common.cmx codegen.cmx ast.cmx
 
 genneko.cmx: type.cmx lexer.cmx common.cmx codegen.cmx ast.cmx
 

+ 1 - 2
ast.ml

@@ -58,7 +58,6 @@ module Meta = struct
 		| EnumConstructorParam
 		| Exhaustive
 		| Expose
-		| ShallowExpose
 		| Extern
 		| FakeEnum
 		| File
@@ -693,4 +692,4 @@ let rec s_expr (e,_) =
 	| EArrayDecl el -> "[" ^ (String.concat "," (List.map s_expr el)) ^ "]"
 	| EObjectDecl fl -> "{" ^ (String.concat "," (List.map (fun (n,e) -> n ^ ":" ^ (s_expr e)) fl)) ^ "}"
 	| EBinop (op,e1,e2) -> s_expr e1 ^ s_binop op ^ s_expr e2
-	| _ -> "'???'"
+	| _ -> "'???'"

+ 0 - 1
common.ml

@@ -330,7 +330,6 @@ module MetaInfo = struct
 		| EnumConstructorParam -> ":enumConstructorParam",("Used internally to annotate GADT type parameters",[UsedOn TClass; Internal])
 		| Exhaustive -> ":exhaustive",("",[Internal])
 		| Expose -> ":expose",("Makes the class available on the window object",[HasParam "?Name=Class path";UsedOn TClass;Platform Js])
-		| ShallowExpose -> ":shallowExpose",("Similar to @:expose meta. Instead of being exposed on the window object, the class will be made available to the surrounding scope of the haxe generated closure instead",[HasParam "?Name=Class path";UsedOn TClass;Platform Js])
 		| Extern -> ":extern",("Marks the field as extern so it is not generated",[UsedOn TClassField])
 		| FakeEnum -> ":fakeEnum",("Treat enum as collection of values of the specified type",[HasParam "Type name";UsedOn TEnum])
 		| File -> ":file",("Includes a given binary file into the target Swf and associates it with the class (must extend flash.utils.ByteArray)",[HasParam "File path";UsedOn TClass;Platform Flash])

+ 18 - 175
genjs.ml

@@ -23,7 +23,6 @@
 open Ast
 open Type
 open Common
-open Typecore
 
 type pos = Ast.pos
 
@@ -60,21 +59,6 @@ type ctx = {
 	mutable found_expose : bool;
 }
 
-type object_store = {
-	os_name : string;
-	mutable os_fields : object_store list;
-}
-
-let get_shallow ctx path meta =
-	if not ctx.js_modern then []
-	else try
-		let (_, args, pos) = Meta.get Meta.ShallowExpose meta in
-		(match args with
-			| [ EConst (String s), _ ] -> [s]
-			| [] -> [path]
-			| _ -> error "Invalid @:shallowExpose parameters" pos)
-	with Not_found -> []
-
 let dot_path = Ast.s_type_path
 
 let flat_path (p,s) =
@@ -260,7 +244,7 @@ let newline ctx =
 let newprop ctx =
 	match Buffer.nth ctx.buf (Buffer.length ctx.buf - 1) with
 	| '{' -> print ctx "\n%s" ctx.tabs
-	| _ -> print ctx ",\n%s" ctx.tabs
+	| _ -> print ctx "\n%s," ctx.tabs
 
 let semicolon ctx =
 	match Buffer.nth ctx.buf (Buffer.length ctx.buf - 1) with
@@ -401,7 +385,7 @@ let rec gen_call ctx e el in_value =
 		concat ctx "," (gen_value ctx) params;
 		spr ctx ")";
 	| TLocal { v_name = "__js__" }, [{ eexpr = TConst (TString code) }] ->
-		spr ctx (String.concat "\n" (ExtString.String.nsplit code "\r\n")); ctx.separator <- false;
+		spr ctx (String.concat "\n" (ExtString.String.nsplit code "\r\n"))
 	| TLocal { v_name = "__instanceof__" },  [o;t] ->
 		spr ctx "(";
 		gen_value ctx o;
@@ -427,16 +411,6 @@ let rec gen_call ctx e el in_value =
 			spr ctx "}"
 		) (Hashtbl.fold (fun name data acc -> (name,data) :: acc) ctx.com.resources []);
 		spr ctx "]";
-	| TLocal { v_name = "__js__teq" } , [x;y] ->
-		spr ctx "(";
-		gen_value ctx x;
-		spr ctx ") === ";
-		gen_value ctx y;
-	| TLocal { v_name = "__js__tne" } , [x;y] ->
-		spr ctx "(";
-		gen_value ctx x;
-		spr ctx ") !== ";
-		gen_value ctx y;
 	| TLocal { v_name = "`trace" }, [e;infos] ->
 		if has_feature ctx "haxe.Log.trace" then begin
 			let t = (try List.find (fun t -> t_path t = (["haxe"],"Log")) ctx.com.types with _ -> assert false) in
@@ -888,7 +862,6 @@ let generate_package_create ctx (p,_) =
 				else
 					print ctx "if(!%s) %s = {}" p p
 			);
-			ctx.separator <- true;
 			newline ctx;
 			loop (p :: acc) l
 	in
@@ -917,8 +890,8 @@ let gen_class_static_field ctx c f =
 			let path = (s_path ctx c.cl_path) ^ (static_field f.cf_name) in
 			ctx.id_counter <- 0;
 			print ctx "%s = " path;
-			(match (get_shallow ctx path f.cf_meta) with [s] -> print ctx "$__hx_shallows.%s = " s | _ -> ());
 			gen_value ctx e;
+			ctx.separator <- false;
 			newline ctx;
 			handle_expose ctx path f.cf_meta
 		| _ ->
@@ -944,17 +917,6 @@ let gen_class_field ctx c f =
 		gen_value ctx e;
 		ctx.separator <- false
 
-let generate_class___name__ ctx c =
-	if has_feature ctx "js.Boot.isClass" then begin
-		let p = s_path ctx c.cl_path in
-		print ctx "%s.__name__ = " p;
-		if has_feature ctx "Type.getClassName" then
-			print ctx "[%s]" (String.concat "," (List.map (fun s -> Printf.sprintf "\"%s\"" (Ast.s_escape s)) (fst c.cl_path @ [snd c.cl_path])))
-		else
-			print ctx "true";
-		newline ctx;
-	end
-
 let generate_class ctx c =
 	ctx.current <- c;
 	ctx.id_counter <- 0;
@@ -971,17 +933,23 @@ let generate_class ctx c =
 		print ctx "%s = " p
 	else
 		print ctx "%s = $hxClasses[\"%s\"] = " p (dot_path c.cl_path);
-	(match (get_shallow ctx p c.cl_meta) with [s] -> print ctx "$__hx_shallows.%s = " s | _ -> ());
 	(match c.cl_constructor with
 	| Some { cf_expr = Some e } -> gen_expr ctx e
-	| _ -> (print ctx "function() { }"); ctx.separator <- true);
+	| _ -> print ctx "function() { }");
 	newline ctx;
 	if ctx.js_modern && hxClasses then begin
 		print ctx "$hxClasses[\"%s\"] = %s" (dot_path c.cl_path) p;
 		newline ctx;
 	end;
 	handle_expose ctx p c.cl_meta;
-	generate_class___name__ ctx c;
+	if has_feature ctx "js.Boot.isClass" then begin
+		print ctx "%s.__name__ = " p;
+		if has_feature ctx "Type.getClassName" then
+			print ctx "[%s]" (String.concat "," (List.map (fun s -> Printf.sprintf "\"%s\"" (Ast.s_escape s)) (fst c.cl_path @ [snd c.cl_path])))
+		else
+			print ctx "true";
+		newline ctx;
+	end;
 	(match c.cl_implements with
 	| [] -> ()
 	| l ->
@@ -1038,7 +1006,7 @@ let generate_class ctx c =
 
 		bend();
 		print ctx "\n}";
-		(match c.cl_super with None -> ctx.separator <- true | _ -> print ctx ")");
+		(match c.cl_super with None -> () | _ -> print ctx ")");
 		newline ctx
 	end
 
@@ -1054,7 +1022,6 @@ let generate_enum ctx e =
 	print ctx "{";
 	if has_feature ctx "js.Boot.isEnum" then print ctx " __ename__ : %s," (if has_feature ctx "Type.getEnumName" then "[" ^ String.concat "," ename ^ "]" else "true");
 	print ctx " __constructs__ : [%s] }" (String.concat "," (List.map (fun s -> Printf.sprintf "\"%s\"" s) e.e_names));
-	ctx.separator <- true;
 	newline ctx;
 	List.iter (fun n ->
 		let f = PMap.find n e.e_constrs in
@@ -1063,7 +1030,6 @@ let generate_enum ctx e =
 		| TFun (args,_) ->
 			let sargs = String.concat "," (List.map (fun (n,_,_) -> ident 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;
-			ctx.separator <- true;
 		| _ ->
 			print ctx "[\"%s\",%d]" f.ef_name f.ef_index;
 			newline ctx;
@@ -1091,8 +1057,6 @@ let generate_type ctx = function
 		| None -> ()
 		| Some e ->
 			ctx.inits <- e :: ctx.inits);
-		(* Special case, want to add Math.__name__ only when required, handle here since Math is extern *)
-		if c.cl_path = ([], "Math") then generate_class___name__ ctx c;
 		if not c.cl_extern then
 			generate_class ctx c
 		else if not ctx.js_flatten && Meta.has Meta.InitPackage c.cl_meta then
@@ -1145,70 +1109,6 @@ let gen_single_expr ctx e expr =
 	ctx.id_counter <- 0;
 	str
 
-let mk_local tctx n t pos =
-	mk (TLocal (try PMap.find n tctx.locals with _ -> add_local tctx n t)) t pos
-
-let optimize_stdis tctx equal triple o t recurse =
-	let pos = o.epos in
-	let stringt = tctx.Typecore.com.basic.tstring in
-	let boolt = tctx.Typecore.com.basic.tbool in
-	let intt = tctx.Typecore.com.basic.tint in
-	let tostring t = let pstring = (Common.add_feature tctx.Typecore.com "Std.is"; mk_local tctx "$ObjectPrototypeToString" t_dynamic pos) in
-					let pstring = mk (TField (pstring, FDynamic ("call"))) (tfun [o.etype] stringt) pos in
-					let psof = mk (TCall (pstring, [o])) stringt pos in
-					mk (TBinop (equal, psof, (mk (TConst (TString t)) stringt pos))) boolt pos
-	in match t.eexpr with
-		| TTypeExpr (TAbstractDecl ({ a_path = [],"Bool" })) -> tostring "[object Boolean]"
-		| TTypeExpr (TAbstractDecl ({ a_path = [],"Float" })) -> tostring "[object Number]"
-		| TTypeExpr (TClassDecl ({ cl_path = [],"String" })) -> tostring "[object String]"
-		| TTypeExpr (TAbstractDecl ({ a_path = [],"Int" })) ->
-			(* need to use ===/!==, not ==/!= so tast is a bit more annoying, we leave this to the generator *)
-			let teq = mk_local tctx triple (tfun [intt; intt] boolt) pos in
-			let lhs = mk (TBinop (Ast.OpOr, o, mk (TConst (TInt Int32.zero)) intt pos)) intt pos in
-			mk (TCall (teq, [lhs; o])) boolt pos
-		| TTypeExpr (TClassDecl ({ cl_path = [],"Array" })) -> tostring "[object Array]"
-		| _ -> recurse
-
-let optimize_stdstring tctx v recurse =
-	let pos = v.epos in
-	let stringt = tctx.Typecore.com.basic.tstring in
-	let stringv = mk (TBinop (Ast.OpAdd, mk (TConst (TString "")) stringt pos, v)) stringt pos in
-	match (follow v.etype) with
-		| TInst ({ cl_path = [],"String" }, []) -> v
-		| TAbstract ({ a_path = [],"Float" }, []) -> stringv
-		| TAbstract ({ a_path = [],"Int" }, []) -> stringv
-		| TAbstract ({ a_path = [],"Bool" }, []) -> stringv
-		| _ -> recurse
-
-let rec optimize_call tctx e = let recurse = optimize tctx e in
-	match e.eexpr with
-	| TUnop (Ast.Not, _, { eexpr = TCall (ce, el) }) -> (match ce.eexpr, el with
-		(* Catch Std.is call, even if it was inlined *)
-		| TField ({ eexpr = TTypeExpr (TClassDecl ({ cl_path = ["js"], "Boot" })) }, FStatic (_, ({ cf_name = "__instanceof" }))), [o;t] ->
-			optimize_stdis tctx Ast.OpNotEq "__js__tne" o t recurse
-		| TField ({ eexpr = TTypeExpr (TClassDecl ({ cl_path = [],"Std" })) }, FStatic (_, ({ cf_name = "is" }))), [o;t] ->
-			optimize_stdis tctx Ast.OpNotEq "__js__tne" o t recurse
-		| _ -> recurse)
-	| TCall (ce, el) -> (match ce.eexpr, el with
-		(* Catch Std.is call, even if it was inlined *)
-		| TField ({ eexpr = TTypeExpr (TClassDecl ({ cl_path = ["js"], "Boot" })) }, FStatic (_, ({ cf_name = "__instanceof" }))), [o;t] ->
-			optimize_stdis tctx Ast.OpEq "__js__teq" o t recurse
-		| TField ({ eexpr = TTypeExpr (TClassDecl ({ cl_path = [],"Std" })) }, FStatic (_, ({ cf_name = "is" }))), [o;t] ->
-			optimize_stdis tctx Ast.OpEq "__js__teq" o t recurse
-		(* Catch Std.int when not inlined, if it was inlined there's no optimisation to be made *)
-		| TField ({ eexpr = TTypeExpr (TClassDecl ({ cl_path = [], "Std" })) }, FStatic (_, ({ cf_name = "int" }))), [v] ->
-			mk (TBinop (Ast.OpOr, v, mk (TConst (TInt Int32.zero)) tctx.Typecore.com.basic.tint v.epos)) tctx.Typecore.com.basic.tbool v.epos
-		(* Catch Std.string, even if it was inlined *)
-		| TField ({ eexpr = TTypeExpr (TClassDecl ({ cl_path = [], "Std" })) }, FStatic (_, ({ cf_name = "string" }))), [v] ->
-			optimize_stdstring tctx v recurse
-		| TField ({ eexpr = TTypeExpr (TClassDecl ({ cl_path = ["js"], "Boot" })) }, FStatic (_, ({ cf_name = "__string_rec" }))), [v; { eexpr = TConst (TString "") }] ->
-			optimize_stdstring tctx v recurse
-		| _ -> recurse)
-	| _ -> recurse
-
-and optimize tctx e =
-	Type.map_expr (optimize_call tctx) e
-
 let generate com =
 	let t = Common.timer "generate js" in
 	(match com.js_gen with
@@ -1219,52 +1119,11 @@ let generate com =
 	if has_feature ctx "Class" || has_feature ctx "Type.getClassName" then add_feature ctx "js.Boot.isClass";
 	if has_feature ctx "Enum" || has_feature ctx "Type.getEnumName" then add_feature ctx "js.Boot.isEnum";
 
-	let shallows = List.concat (List.map (fun t ->
-		match t with
-			| TClassDecl c ->
-				let path = s_path ctx c.cl_path in
-				let class_shallows = get_shallow ctx path c.cl_meta in
-				let static_shallows = List.map (fun f ->
-					get_shallow ctx (path ^ static_field f.cf_name) f.cf_meta
-				) c.cl_ordered_statics in
-				List.concat (class_shallows :: static_shallows)
-			| _ -> []
-		) com.types) in
-	let anyShallowExposed = shallows <> [] in
-	let smap = ref (PMap.create String.compare) in
-	let shallowObject = { os_name = ""; os_fields = [] } in
-	List.iter (fun path -> (
-		let parts = ExtString.String.nsplit path "." in
-		let rec loop p pre = match p with
-			| f :: g :: ls ->
-				let path = match pre with "" -> f | pre -> (pre ^ "." ^ f) in
-				if not (PMap.exists path !smap) then (
-					let elts = { os_name = f; os_fields = [] } in
-					smap := PMap.add path elts !smap;
-					let cobject = match pre with "" -> shallowObject | pre -> PMap.find pre !smap in
-					cobject.os_fields <- elts :: cobject.os_fields
-				);
-				loop (g :: ls) path;
-			| _ -> ()
-		in loop parts "";
-	)) shallows;
-
 	if ctx.js_modern then begin
 		(* Additional ES5 strict mode keywords. *)
 		List.iter (fun s -> Hashtbl.replace kwds s ()) [ "arguments"; "eval" ];
 
-		(* Wrap output in a closure. Exposing shallowExpose types to outside of closure *)
-		if anyShallowExposed then (
-			print ctx "var $__hx_shallows = ";
-			let rec print_obj { os_fields = fields } = (
-				print ctx "{";
-				concat ctx "," (fun ({ os_name = name } as f) -> print ctx "%s" (name ^ ":"); print_obj f) fields;
-				print ctx "}"
-			) in
-			print_obj shallowObject;
-			ctx.separator <- true;
-			newline ctx
-		);
+		(* Wrap output in a closure. *)
 		print ctx "(function () { \"use strict\"";
 		newline ctx;
 	end;
@@ -1284,7 +1143,7 @@ let generate com =
 	);
 	if List.exists (function TClassDecl { cl_extern = false; cl_super = Some _ } -> true | _ -> false) com.types then begin
 		print ctx "function $extend(from, fields) {
-	function Inherit() {} Inherit.prototype = from; var proto = new Inherit();
+	function inherit() {}; inherit.prototype = from; var proto = new inherit();
 	for (var name in fields) proto[name] = fields[name];
 	if( fields.toString !== Object.prototype.toString ) proto.toString = fields.toString;
 	return proto;
@@ -1305,12 +1164,14 @@ let generate com =
 	if has_feature ctx "use.$iterator" then begin
 		add_feature ctx "use.$bind";
 		print ctx "function $iterator(o) { if( o instanceof Array ) return function() { return HxOverrides.iter(o); }; return typeof(o.iterator) == 'function' ? $bind(o,o.iterator) : o.iterator; }";
+		ctx.separator <- true;
 		newline ctx;
 	end;
 	if has_feature ctx "use.$bind" then begin
 		print ctx "var $_, $fid = 0";
 		newline ctx;
 		print ctx "function $bind(o,m) { if( m == null ) return null; if( m.__id__ == null ) m.__id__ = $fid++; var f; if( o.hx__closures__ == null ) o.hx__closures__ = {}; else f = o.hx__closures__[m.__id__]; if( f == null ) { f = function(){ return f.method.apply(f.scope, arguments); }; f.scope = o; f.method = m; o.hx__closures__[m.__id__] = f; } return f; }";
+		ctx.separator <- true;
 		newline ctx;
 	end;
 	List.iter (gen_block ~after:true ctx) (List.rev ctx.inits);
@@ -1319,7 +1180,7 @@ let generate com =
 	| None -> ()
 	| Some e -> gen_expr ctx e; newline ctx);
 	if ctx.found_expose then begin
-		(* TODO(bruno): Remove runtime branching when standard node haxelib is available *)
+        (* TODO(bruno): Remove runtime branching when standard node haxelib is available *)
 		print ctx
 "function $hxExpose(src, path) {
 	var o = typeof window != \"undefined\" ? window : exports;
@@ -1336,24 +1197,6 @@ let generate com =
 	if ctx.js_modern then begin
 		print ctx "})()";
 		newline ctx;
-		if anyShallowExposed then begin
-			let rec print_obj { os_fields = fields } = (
-				print ctx "{";
-				concat ctx "," (fun f-> print ctx "%s" (f.os_name ^ ":"); print_obj f) fields;
-				print ctx "}"
-			) in
-			List.iter (fun f ->
-				print ctx "var %s = " f.os_name;
-				print_obj f;
-				ctx.separator <- true;
-				newline ctx
-			) shallowObject.os_fields;
-			List.iter (fun path ->
-				if not (ExtString.String.contains path '.') then print ctx "var ";
-				print ctx "%s" (path ^ " = $__hx_shallows." ^ path);
-				newline ctx;
-			) shallows;
-		end
 	end;
 	if com.debug then write_mappings ctx else (try Sys.remove (com.file ^ ".map") with _ -> ());
 	let ch = open_out_bin com.file in

+ 1 - 11
main.ml

@@ -1214,21 +1214,11 @@ try
 		com.main <- main;
 		com.types <- types;
 		com.modules <- modules;
-		let foldMap = List.fold_left (fun f g x -> g (f x)) (fun x -> x) in
 		let filters = [
 			Codegen.Abstract.handle_abstract_casts tctx;
 			(match com.platform with Cpp -> Codegen.handle_side_effects com (Typecore.gen_local tctx) | _ -> fun e -> e);
 			Codegen.promote_complex_rhs com;
-			if com.foptimize then foldMap (
-				let reduce_expression = Optimizer.reduce_expression tctx in
-				let inline_constructors = Optimizer.inline_constructors tctx in
-				match com.platform with
-					| Js -> [inline_constructors;
-							 Genjs.optimize tctx;
-							 reduce_expression]
-					| _ -> [inline_constructors;
-							reduce_expression]
-			) else Optimizer.sanitize tctx;
+			if com.foptimize then (fun e -> Optimizer.reduce_expression tctx (Optimizer.inline_constructors tctx e)) else Optimizer.sanitize tctx;
 			Codegen.check_local_vars_init;
 			Codegen.captured_vars com;
 			Codegen.rename_local_vars com;

+ 69 - 101
std/Math.hx

@@ -23,219 +23,203 @@
 	This class defines mathematical functions and constants.
 **/
 #if cpp @:include("hxMath") #end
-@:keepInit
 extern class Math
 {
 	static var PI(default,null) : Float;
-
+	
 	/**
 		A special Float constant which denotes negative infinity.
-
+		
 		For example, this is the result of -1.0 / 0.0.
-
+		
 		Operations with NEGATIVE_INFINITY as an operand may result in
 		Operations with NEGATIVE_INFINITY as an operand may result in
 		NEGATIVE_INFINITY, POSITIVE_INFINITY or NaN. For detailed information,
 		see ...
-
+		
 		If this constant is converted to an Int, e.g. through Std.int(), the
 		result is unspecified.
 	**/
-#if js
-	static var NEGATIVE_INFINITY(get, null) : Float;
-	static inline function get_NEGATIVE_INFINITY() : Float return untyped __define_feature__("Math.INF/NAN", $Number).NEGATIVE_INFINITY;
-#else
 	static var NEGATIVE_INFINITY(default, null) : Float;
-#end
 	/**
 		A special Float constant which denotes negative infinity.
-
+		
 		For example, this is the result of 1.0 / 0.0.
-
+		
 		Operations with POSITIVE_INFINITY as an operand may result in
 		NEGATIVE_INFINITY, POSITIVE_INFINITY or NaN. For detailed information,
 		see ...
-
+	
 		If this constant is converted to an Int, e.g. through Std.int(), the
 		result is unspecified.
 	**/
-#if js
-	static var POSITIVE_INFINITY(get, null) : Float;
-	static inline function get_POSITIVE_INFINITY() : Float return untyped __define_feature__("Math.INF/NAN", $Number).POSITIVE_INFINITY;
-#else
-	static var POSITIVE_INFINITY(default, null) : Float;
-#end
+	static var POSITIVE_INFINITY(default,null) : Float;
 
 	/**
 		A special Float constant which denotes an invalid number.
-
+		
 		NaN stands for "Not a Number". It occurs when a mathematically incorrect
 		operation is executed, such as taking the square root of a negative
 		number: Math.sqrt(-1).
-
+		
 		All further operations with NaN as an operand will result in NaN.
-
+		
 		If this constant is converted to an Int, e.g. through Std.int(), the
 		result is unspecified.
-
+		
 		In order to test if a value is NaN, you should use Math.isNaN() function.
-
+		
 		(Php) In PHP versions prior to 5.3.1 VC 9 there may be unexpected
 		results when performing arithmetic operations with NaN on Windows, see:
 			https://bugs.php.net/bug.php?id=42143
 	**/
-#if js
-	static var NaN(get, null) : Float;
-	static inline function get_NaN() : Float return untyped __define_feature__("Math.INF/NAN", $Number).NaN;
-#else
 	static var NaN(default, null) : Float;
-#end
 
 	/**
 		Returns the absolute value of `v`.
-
+		
 		If `v` is positive or 0, the result is unchanged. Otherwise the result
 		is -`v`.
-
+		
 		If `v` is NEGATIVE_INFINITY or POSITIVE_INFINITY, the result is
 		POSITIVE_INFINITY.
-
+		
 		If `v` is NaN, the result is NaN.
 	**/
 	static function abs(v:Float):Float;
-
+	
 	/**
 		Returns the smaller of values `a` and `b`.
-
+		
 		If `a` or `b` are NaN, the result is NaN.
-
+		
 		If `a` or `b` are NEGATIVE_INFINITY, the result is NEGATIVE_INFINITY.
-
+		
 		If `a` and `b` are POSITIVE_INFINITY, the result is POSITIVE_INFINITY.
 	**/
 	static function min(a:Float, b:Float):Float;
-
+	
 	/**
 		Returns the greater of values `a` and `b`.
-
+		
 		If `a` or `b` are NaN, the result is NaN.
-
+		
 		If `a` or `b` are POSITIVE_INFINITY, the result is POSITIVE_INFINITY.
-
+		
 		If `a` and `b` are NEGATIVE_INFINITY, the result is NEGATIVE_INFINITY.
 	**/
 	static function max(a:Float, b:Float):Float;
-
+	
 	/**
 		Returns the trigonometric sine of `v`.
-
+		
 		The unit of `v` is radians.
-
+		
 		If `v` is NaN or infinite, the result is NaN.
 	**/
 	static function sin(v:Float):Float;
-
+	
 	/**
 		Returns the trigonometric cosine of `v`.
-
+		
 		The unit of `v` is radians.
-
+		
 		If `v` is NaN or infinite, the result is NaN.
 	**/
 	static function cos(v:Float):Float;
-
+	
 	// TODO
 	static function tan(v:Float):Float;
 	static function asin(v:Float):Float;
 	static function acos(v:Float):Float;
 	static function atan(v:Float):Float;
 	static function atan2(y:Float, x:Float):Float;
-
+	
 	/**
 		Returns Euler's number, raised to the power of `v`.
-
+		
 		exp(1.0) is approximately 2.718281828459.
-
+		
 		If `v` is POSITIVE_INFINITY, the result is POSITIVE_INFINITY.
-
+		
 		If `v` is NEGATIVE_INFINITY, the result is 0.0.
-
+		
 		If `v` is NaN, the result is NaN.
 	**/
 	static function exp(v:Float):Float;
-
+	
 	/**
 		Returns the natural logarithm of `v`.
-
+		
 		If `v` is negative (including NEGATIVE_INFINITY) or NaN, the result is
 		NaN.
-
+		
 		If `v` is POSITIVE_INFINITY, the result is POSITIVE_INFINITY.
-
+		
 		If `v` is 0.0, the result is NEGATIVE_INFINITY.
-
+		
 		This is the inverse operation of exp, i.e. log(exp(v)) == v always
 		holds.
 	**/
 	static function log(v:Float):Float;
-
+	
 	// TODO
 	// http://docs.oracle.com/javase/1.4.2/docs/api/java/lang/Math.html#pow(double, double) <-- wtf?
 	static function pow(v:Float, exp:Float):Float;
-
+	
 	/**
 		Returns the square root of `v`.
-
+		
 		If `v` is negative (including NEGATIVE_INFINITY) or NaN, the result is
 		NaN.
-
+		
 		If `v` is POSITIVE_INFINITY, the result is POSITIVE_INFINITY.
-
+		
 		If `v` is 0.0, the result is 0.0.
 	**/
 	static function sqrt(v:Float):Float;
-
+	
 	/**
 		Rounds `v` to the nearest Int value.
 
 		If v is outside of the signed Int32 range, or is NaN, NEGATIVE_INFINITY or POSITIVE_INFINITY, the result is unspecified.
-
+		
 		TODO: need spec
 	**/
 	static function round(v:Float):Int;
-
+	
 	/**
 		Returns the largest Int value that is not greater than `v`.
-
-		If v is outside of the signed Int32 range, or is NaN, NEGATIVE_INFINITY or POSITIVE_INFINITY, the result is unspecified.
-
+		
+		If v is outside of the signed Int32 range, or is NaN, NEGATIVE_INFINITY or POSITIVE_INFINITY, the result is unspecified.		
+		
 		TODO: need spec
 	**/
 	static function floor(v:Float):Int;
-
+	
 	/**
 		Returns the smallest Int value that is not less than `v`.
 
 		If v is outside of the signed Int32 range, or is NaN, NEGATIVE_INFINITY or POSITIVE_INFINITY, the result is unspecified.
-
+		
 		TODO: need spec
 	**/
 	static function ceil(v:Float):Int;
-
+	
 	/**
 		Returns a pseudo-random number which is greater than or equal to 0.0,
 		and less than 1.0.
 	**/
 	static function random() : Float;
-
+	
 	#if ((flash9 && !as3) || cpp)
-
+	
 	static function ffloor( v : Float ) : Float;
 	static function fceil( v : Float ) : Float;
 	static function fround( v : Float ) : Float;
-
+	
 	#else
-
+	
 	static inline function ffloor( v : Float ) : Float {
 		return floor(v);
 	}
@@ -247,60 +231,45 @@ extern class Math
 	static inline function fround( v : Float ) : Float {
 		return round(v);
 	}
-
+	
 	#end
-
+	
 
 	/**
 		Tells if `f` is a finite number.
-
+		
 		If `f` is POSITIVE_INFINITY, NEGATIVE_INFINITY or NaN, the result is
 		false.
-
+		
 		Otherwise the result is true.
 	**/
-#if js
-	static inline function isFinite( f : Float ) : Bool return untyped __define_feature__("Math.isFinite", $isFinite)(f);
-#else
 	static function isFinite( f : Float ) : Bool;
-#end
-
+	
 	/**
 		Tells if `f` is not a valid number.
-
+		
 		If `f` is NaN, the result is true.
-
+		
 		Otherwise the result is false. In particular, both POSITIVE_INFINITY and
 		NEGATIVE_INFINITY are not considered NaN.
 	**/
-#if js
-	static inline function isNaN( f : Float ) : Bool return untyped __define_feature__("Math.isNaN", $isNaN)(f);
-#else
 	static function isNaN( f : Float ) : Bool;
-#end
 
 	private static function __init__() : Void untyped {
 	#if flash9
 		NaN = __global__["Number"].NaN;
 		NEGATIVE_INFINITY = __global__["Number"].NEGATIVE_INFINITY;
 		POSITIVE_INFINITY = __global__["Number"].POSITIVE_INFINITY;
-	#elseif flash
+	#else
 		Math.__name__ = ["Math"];
 		Math.NaN = Number["NaN"];
 		Math.NEGATIVE_INFINITY = Number["NEGATIVE_INFINITY"];
 		Math.POSITIVE_INFINITY = Number["POSITIVE_INFINITY"];
-	#else
-		__js__("Math").NaN = Number["NaN"];
-		__js__("Math").NEGATIVE_INFINITY = Number["NEGATIVE_INFINITY"];
-		__js__("Math").POSITIVE_INFINITY = Number["POSITIVE_INFINITY"];
 	#end
 	#if js
 		__feature__("Type.resolveClass",$hxClasses['Math'] = Math);
-		__feature__("Math.INF/NAN", __js__("var $Number = Number"));
-		__feature__("Math.isFinite",__js__("var $isFinite = isFinite"));
-		__feature__("Math.isNaN",__js__("var $isNaN = isNaN"));
 	#end
-		#if js __js__("Math") #else Math #end.isFinite = function(i) {
+		Math.isFinite = function(i) {
 			return
 			#if flash9
 			__global__["isFinite"](i);
@@ -312,7 +281,7 @@ extern class Math
 			false;
 			#end
 		};
-		#if js __js__("Math") #else Math #end.isNaN = function(i) {
+		Math.isNaN = function(i) {
 			return
 			#if flash9
 			__global__["isNaN"](i);
@@ -329,4 +298,3 @@ extern class Math
 }
 
 
-

+ 5 - 5
std/js/Boot.hx

@@ -122,7 +122,7 @@ class Boot {
 				var str = "{\n";
 				s += "\t";
 				var hasp = (o.hasOwnProperty != null);
-				__js__("for( var k in o ) {");
+				__js__("for( var k in o ) { ");
 					if( hasp && !o.hasOwnProperty(k) )
 						__js__("continue");
 					if( k == "prototype" || k == "__class__" || k == "__super__" || k == "__interfaces__" || k == "__properties__" )
@@ -166,11 +166,11 @@ class Boot {
 		case Int:
 			return (untyped __js__("(o|0) === o"));
 		case Float:
-			return (untyped __define_feature__("Std.is", $ObjectPrototypeToString)).call(o) == "[object Number]";
+			return (untyped __js__("typeof"))(o) == "number";
 		case Bool:
-			return (untyped __define_feature__("Std.is", $ObjectPrototypeToString)).call(o) == "[object Boolean]";
+			return (untyped __js__("typeof"))(o) == "boolean";
 		case String:
-			return (untyped __define_feature__("Std.is", $ObjectPrototypeToString)).call(o) == "[object String]";
+			return (untyped __js__("typeof"))(o) == "string";
 		case Dynamic:
 			return true;
 		default:
@@ -178,7 +178,7 @@ class Boot {
 				// Check if o is an instance of a Haxe class
 				if( (untyped __js__("typeof"))(cl) == "function" ) {
 					if( untyped __js__("o instanceof cl") ) {
-						if( (untyped __define_feature__("Std.is", $ObjectPrototypeToString)).call(o) == "[object Array]" )
+						if( cl == Array )
 							return (o.__enum__ == null);
 						return true;
 					}

+ 10 - 12
std/js/_std/Reflect.hx

@@ -19,12 +19,11 @@
  * FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER
  * DEALINGS IN THE SOFTWARE.
  */
-@:coreApi
-@:keepInit
-class Reflect {
+@:coreApi class Reflect {
 
-	public static inline function hasField( o : Dynamic, field : String ) : Bool
-		return untyped __define_feature__("hasOwnProperty", $hasOwnProperty).call(o, field);
+	public static function hasField( o : Dynamic, field : String ) : Bool {
+		return untyped __js__('Object').prototype.hasOwnProperty.call(o, field);
+	}
 
 	public inline static function field( o : Dynamic, field : String ) : Dynamic untyped {
 		var v = null;
@@ -35,8 +34,9 @@ class Reflect {
 		return v;
 	}
 
-	public inline static function setField( o : Dynamic, field : String, value : Dynamic ) : Void
-		untyped o[field] = value;
+	public inline static function setField( o : Dynamic, field : String, value : Dynamic ) : Void untyped {
+		o[field] = value;
+	}
 
 	public static inline function getProperty( o : Dynamic, field : String ) : Dynamic untyped {
 		var tmp;
@@ -55,8 +55,9 @@ class Reflect {
 	public static function fields( o : Dynamic ) : Array<String> {
 		var a = [];
 		if (o != null) untyped {
+			var hasOwnProperty = __js__('Object').prototype.hasOwnProperty;
 			__js__("for( var f in o ) {");
-			if( f != "__id__" && f != "hx__closures__" && __define_feature__("hasOwnProperty", $hasOwnProperty).call(o, f) ) a.push(f);
+			if( f != "__id__" && f != "hx__closures__" && hasOwnProperty.call(o, f) ) a.push(f);
 			__js__("}");
 		}
 		return a;
@@ -84,7 +85,7 @@ class Reflect {
 		var t = __js__("typeof(v)");
 		return (t == "string" || (t == "object" && v.__enum__ == null)) || (t == "function" && (js.Boot.isClass(v) || js.Boot.isEnum(v)) != null);
 	}
-
+	
 	public static function isEnumValue( v : Dynamic ) : Bool {
 		return v != null && v.__enum__ != null;
 	}
@@ -110,7 +111,4 @@ class Reflect {
 		};
 	}
 
-	static function __init__() : Void {
-		untyped __feature__("hasOwnProperty", __js__("var $hasOwnProperty = Object.prototype.hasOwnProperty"));
-	}
 }

+ 4 - 5
std/js/_std/Std.hx

@@ -24,19 +24,19 @@ import js.Boot;
 @:keepInit
 @:coreApi class Std {
 
-	public inline static function is( v : Dynamic, t : Dynamic ) : Bool {
+	public static inline function is( v : Dynamic, t : Dynamic ) : Bool {
 		return untyped js.Boot.__instanceof(v,t);
 	}
-
+	
 	public static inline function instance<T>( v : { }, c : Class<T> ) : T {
 		return untyped __instanceof__(v, c) ? cast v : null;
 	}
 
-	public inline static function string( s : Dynamic ) : String {
+	public static function string( s : Dynamic ) : String {
 		return untyped js.Boot.__string_rec(s,"");
 	}
 
-	public inline static function int( x : Float ) : Int {
+	public static inline function int( x : Float ) : Int {
 		return cast(x) | 0;
 	}
 
@@ -110,7 +110,6 @@ import js.Boot;
 					return a;
 				}
 		);
-        __feature__("Std.is", __js__("var $ObjectPrototypeToString = Object.prototype.toString"));
 	}
 
 }