2
0
Эх сурвалжийг харах

[java] Added minimal std lib; fixed issue #1451 ;added support for override detection in java-lib; added correct overload check override implementation (only count arguments, not return types); many -java-lib related fixed

Caue Waneck 12 жил өмнө
parent
commit
4b6395882b
40 өөрчлөгдсөн 11321 нэмэгдсэн , 233 устгасан
  1. 1 1
      common.ml
  2. 121 29
      genjava.ml
  3. 486 0
      std/cs/_std/StringMap.hx
  4. 6 0
      std/java/Boot.hx
  5. 3 2
      std/java/_std/sys/io/Process.hx
  6. 111 0
      std/java/internal/Exception.hx
  7. 4 2
      std/java/internal/Exceptions.hx
  8. 45 0
      std/java/io/Closeable.hx
  9. 291 0
      std/java/io/Console.hx
  10. 59 0
      std/java/io/EOFException.hx
  11. 44 0
      std/java/io/Flushable.hx
  12. 91 0
      std/java/io/IOException.hx
  13. 14 13
      std/java/io/NativeInput.hx
  14. 11 10
      std/java/io/NativeOutput.hx
  15. 759 0
      std/java/io/PrintWriter.hx
  16. 170 0
      std/java/io/Serializable.hx
  17. 266 0
      std/java/io/Writer.hx
  18. 119 0
      std/java/lang/Appendable.hx
  19. 73 0
      std/java/lang/AutoCloseable.hx
  20. 377 0
      std/java/lang/Byte.hx
  21. 108 0
      std/java/lang/CharSequence.hx
  22. 54 0
      std/java/lang/Cloneable.hx
  23. 137 0
      std/java/lang/Comparable.hx
  24. 853 0
      std/java/lang/Double.hx
  25. 185 0
      std/java/lang/Enum.hx
  26. 111 0
      std/java/lang/Exception.hx
  27. 798 0
      std/java/lang/Float.hx
  28. 796 0
      std/java/lang/Integer.hx
  29. 44 0
      std/java/lang/Iterable.hx
  30. 830 0
      std/java/lang/Long.hx
  31. 1366 0
      std/java/lang/Math.hx
  32. 106 114
      std/java/lang/Number.hx
  33. 106 0
      std/java/lang/RuntimeException.hx
  34. 387 0
      std/java/lang/Short.hx
  35. 175 0
      std/java/lang/StackTraceElement.hx
  36. 619 55
      std/java/lang/Throwable.hx
  37. 1528 0
      std/java/util/Locale.hx
  38. 21 1
      tests/unit/TestJava.hx
  39. 32 1
      tests/unit/native_java/src/haxe/test/Base.java
  40. 14 5
      typeload.ml

+ 1 - 1
common.ml

@@ -120,7 +120,7 @@ type context = {
 	mutable php_lib : string option;
 	mutable php_lib : string option;
 	mutable php_prefix : string option;
 	mutable php_prefix : string option;
 	mutable swf_libs : (string * (unit -> Swf.swf) * (unit -> ((string list * string),As3hl.hl_class) Hashtbl.t)) list;
 	mutable swf_libs : (string * (unit -> Swf.swf) * (unit -> ((string list * string),As3hl.hl_class) Hashtbl.t)) list;
-	mutable java_libs : (string * (unit -> unit) * (unit -> ((string list * string) list)) * ((string list * string) -> JData.jclass option)) list;
+	mutable java_libs : (string * (unit -> unit) * (unit -> ((string list * string) list)) * ((string list * string) -> ((JData.jclass * string * string) option))) list;
 	mutable js_gen : (unit -> unit) option;
 	mutable js_gen : (unit -> unit) option;
 	(* typing *)
 	(* typing *)
 	mutable basic : basic_types;
 	mutable basic : basic_types;

+ 121 - 29
genjava.ml

@@ -20,6 +20,7 @@
  * DEALINGS IN THE SOFTWARE.
  * DEALINGS IN THE SOFTWARE.
  *)
  *)
 
 
+open JData
 open Unix
 open Unix
 open Ast
 open Ast
 open Common
 open Common
@@ -153,7 +154,7 @@ struct
         | TField( _, FStatic({ cl_path = (["java";"lang"], "Math") }, { cf_name = "POSITIVE_INFINITY" }) ) ->
         | TField( _, FStatic({ cl_path = (["java";"lang"], "Math") }, { cf_name = "POSITIVE_INFINITY" }) ) ->
           mk_static_field_access_infer float_cl "POSITIVE_INFINITY" e.epos []
           mk_static_field_access_infer float_cl "POSITIVE_INFINITY" e.epos []
         | TField( _, FStatic({ cl_path = (["java";"lang"], "Math") }, { cf_name = "isNaN"}) ) ->
         | TField( _, FStatic({ cl_path = (["java";"lang"], "Math") }, { cf_name = "isNaN"}) ) ->
-          mk_static_field_access_infer float_cl "isNaN" e.epos []
+          mk_static_field_access_infer float_cl "_isNaN" e.epos []
         | TCall( ({ eexpr = TField( (_ as ef), FStatic({ cl_path = (["java";"lang"], "Math") }, { cf_name = ("ffloor" as f) }) ) } as fe), p)
         | TCall( ({ eexpr = TField( (_ as ef), FStatic({ cl_path = (["java";"lang"], "Math") }, { cf_name = ("ffloor" as f) }) ) } as fe), p)
         | TCall( ({ eexpr = TField( (_ as ef), FStatic({ cl_path = (["java";"lang"], "Math") }, { cf_name = ("fround" as f) }) ) } as fe), p)
         | TCall( ({ eexpr = TField( (_ as ef), FStatic({ cl_path = (["java";"lang"], "Math") }, { cf_name = ("fround" as f) }) ) } as fe), p)
         | TCall( ({ eexpr = TField( (_ as ef), FStatic({ cl_path = (["java";"lang"], "Math") }, { cf_name = ("fceil" as f) }) ) } as fe), p) ->
         | TCall( ({ eexpr = TField( (_ as ef), FStatic({ cl_path = (["java";"lang"], "Math") }, { cf_name = ("fceil" as f) }) ) } as fe), p) ->
@@ -165,7 +166,7 @@ struct
         | TCall( ( { eexpr = TField( _, FStatic({ cl_path = (["java";"lang"], "Math") }, { cf_name = "isFinite" }) ) } as efield ), [v]) ->
         | TCall( ( { eexpr = TField( _, FStatic({ cl_path = (["java";"lang"], "Math") }, { cf_name = "isFinite" }) ) } as efield ), [v]) ->
           { e with eexpr =
           { e with eexpr =
             TUnop(Ast.Not, Ast.Prefix, {
             TUnop(Ast.Not, Ast.Prefix, {
-              e with eexpr = TCall( mk_static_field_access_infer float_cl "isInfinite" efield.epos [], [run v] )
+              e with eexpr = TCall( mk_static_field_access_infer float_cl "_isInfinite" efield.epos [], [run v] )
             })
             })
           }
           }
         (* end of math changes *)
         (* end of math changes *)
@@ -1068,6 +1069,14 @@ let configure gen =
           write w "( ";
           write w "( ";
           expr_s w e1; write w ( " " ^ (Ast.s_binop op) ^ " " ); expr_s w e2;
           expr_s w e1; write w ( " " ^ (Ast.s_binop op) ^ " " ); expr_s w e2;
           write w " )"
           write w " )"
+        | TField (e, FStatic(_, cf)) when Meta.has Meta.Native cf.cf_meta ->
+          let rec loop meta = match meta with
+            | (Meta.Native, [EConst (String s), _],_) :: _ ->
+              expr_s w e; write w "."; write_field w s
+            | _ :: tl -> loop tl
+            | [] -> expr_s w e; write w "."; write_field w (cf.cf_name)
+          in
+          loop cf.cf_meta
         | TField (e, s) ->
         | TField (e, s) ->
           expr_s w e; write w "."; write_field w (field_name s)
           expr_s w e; write w "."; write_field w (field_name s)
         | TTypeExpr (TClassDecl { cl_path = (["haxe"], "Int32") }) ->
         | TTypeExpr (TClassDecl { cl_path = (["haxe"], "Int32") }) ->
@@ -2063,6 +2072,16 @@ let configure gen =
 (* end of configure function *)
 (* end of configure function *)
 
 
 let before_generate con =
 let before_generate con =
+  let java_ver = try
+      int_of_string (PMap.find "java_ver" con.defines)
+    with | Not_found ->
+      7
+  in
+  let rec loop i =
+    Common.raw_define con ("java" ^ (string_of_int i));
+    if i > 0 then loop (i - 1)
+  in
+  loop java_ver;
   ()
   ()
 
 
 let generate con =
 let generate con =
@@ -2093,12 +2112,12 @@ type java_lib_ctx = {
   jcur_pack : string list;
   jcur_pack : string list;
 }
 }
 
 
-let lookup_jclass ctx path =
+let lookup_jclass com path =
   List.fold_left (fun acc (_,_,_,get_raw_class) ->
   List.fold_left (fun acc (_,_,_,get_raw_class) ->
     match acc with
     match acc with
     | None -> get_raw_class path
     | None -> get_raw_class path
     | Some p -> Some p
     | Some p -> Some p
-  ) None ctx.jcom.java_libs
+  ) None com.java_libs
 
 
 exception ConversionError of string * pos
 exception ConversionError of string * pos
 
 
@@ -2158,8 +2177,8 @@ and convert_signature ctx p jsig =
   | TObject ( (["java";"lang"], "Class"), args ) -> mk_type_path ctx ([], "Class") (List.map (convert_arg ctx p) args)
   | TObject ( (["java";"lang"], "Class"), args ) -> mk_type_path ctx ([], "Class") (List.map (convert_arg ctx p) args)
   (** other types *)
   (** other types *)
   | TObject ( path, [] ) ->
   | TObject ( path, [] ) ->
-    (match lookup_jclass ctx path with
-    | Some jcl -> mk_type_path ctx path (List.map (fun _ -> convert_arg ctx p TAny) jcl.ctypes)
+    (match lookup_jclass ctx.jcom path with
+    | Some (jcl, _, _) -> mk_type_path ctx path (List.map (fun _ -> convert_arg ctx p TAny) jcl.ctypes)
     | None -> mk_type_path ctx path [])
     | None -> mk_type_path ctx path [])
   | TObject ( path, args ) -> mk_type_path ctx path (List.map (convert_arg ctx p) args)
   | TObject ( path, args ) -> mk_type_path ctx path (List.map (convert_arg ctx p) args)
   | TArray (jsig, _) -> mk_type_path ctx (["java"], "NativeArray") [ TPType (convert_signature ctx p jsig) ]
   | TArray (jsig, _) -> mk_type_path ctx (["java"], "NativeArray") [ TPType (convert_signature ctx p jsig) ]
@@ -2189,6 +2208,21 @@ let convert_param ctx p param =
 
 
 let get_type_path ctx ct = match ct with | CTPath p -> p | _ -> assert false
 let get_type_path ctx ct = match ct with | CTPath p -> p | _ -> assert false
 
 
+let is_override field =
+  List.exists (function
+    (* TODO: pass anotations as @:meta *)
+    | AttrVisibleAnnotations ann ->
+      List.exists (function
+        | { ann_type = TObject( (["java";"lang"], "Override"), [] ) } ->
+            true
+        | _ -> false
+      ) ann
+    | _ -> false
+  ) field.jf_attributes
+
+let mk_override field =
+  { field with jf_attributes = ((AttrVisibleAnnotations [{ ann_type = TObject( (["java";"lang"], "Override"), [] ); ann_elements = [] }]) :: field.jf_attributes) }
+
 let convert_java_enum ctx p pe =
 let convert_java_enum ctx p pe =
   let meta = ref [Meta.Native, [EConst (String (real_java_path ctx pe.cpath) ), p], p ] in
   let meta = ref [Meta.Native, [EConst (String (real_java_path ctx pe.cpath) ), p], p ] in
   let data = ref [] in
   let data = ref [] in
@@ -2291,12 +2325,20 @@ let convert_java_field ctx p jc field =
         })
         })
       | _ -> error "Method signature was expected" p
       | _ -> error "Method signature was expected" p
   in
   in
+  let cff_name, cff_meta =
+    if String.get cff_name 0 = '%' then
+      let name = (String.sub cff_name 1 (String.length cff_name - 1)) in
+      "_" ^ name,
+      (Meta.Native, [EConst (String (name) ), cff_pos], cff_pos) :: !cff_meta
+    else
+      cff_name, !cff_meta
+  in
 
 
   {
   {
     cff_name = cff_name;
     cff_name = cff_name;
     cff_doc = cff_doc;
     cff_doc = cff_doc;
     cff_pos = cff_pos;
     cff_pos = cff_pos;
-    cff_meta = !cff_meta;
+    cff_meta = cff_meta;
     cff_access = !cff_access;
     cff_access = !cff_access;
     cff_kind = kind
     cff_kind = kind
   }
   }
@@ -2394,9 +2436,9 @@ let add_java_lib com file =
         let real_path = file ^ "/" ^ (String.concat "." pack) ^ "/" ^ name ^ ".class" in
         let real_path = file ^ "/" ^ (String.concat "." pack) ^ "/" ^ name ^ ".class" in
         try
         try
           let data = Std.input_file ~bin:true real_path in
           let data = Std.input_file ~bin:true real_path in
-          Some (IO.input_string data), real_path, real_path
+          Some(JReader.parse_class (IO.input_string data), real_path, real_path)
         with
         with
-          | _ -> None, real_path, real_path), (fun () -> ()), (fun () -> let ret = ref [] in get_classes_dir [] file ret; !ret)
+          | _ -> None), (fun () -> ()), (fun () -> let ret = ref [] in get_classes_dir [] file ret; !ret)
     | _ -> (* open zip file *)
     | _ -> (* open zip file *)
       let zip = Zip.open_in file in
       let zip = Zip.open_in file in
       let closed = ref false in
       let closed = ref false in
@@ -2406,23 +2448,87 @@ let add_java_lib com file =
           let location = (String.concat "/" (pack @ [name]) ^ ".class") in
           let location = (String.concat "/" (pack @ [name]) ^ ".class") in
           let entry = Zip.find_entry zip location in
           let entry = Zip.find_entry zip location in
           let data = Zip.read_entry zip entry in
           let data = Zip.read_entry zip entry in
-          Some (IO.input_string data), file, file ^ "@" ^ location
+          Some(JReader.parse_class (IO.input_string data), file, file ^ "@" ^ location)
         with
         with
           | Not_found ->
           | Not_found ->
-            None, file, file),
+            None),
       (fun () -> closed := true; Zip.close_in zip),
       (fun () -> closed := true; Zip.close_in zip),
       (fun () -> get_classes_zip zip)
       (fun () -> get_classes_zip zip)
   in
   in
+  let cached_types = Hashtbl.create 12 in
+  let get_raw_class path =
+    try
+      Hashtbl.find cached_types path
+    with | Not_found ->
+      match get_raw_class path with
+      | None ->
+          Hashtbl.add cached_types path None;
+          None
+      | Some (i, p1, p2) ->
+          let ret = Some (i, p1, p2) in
+          Hashtbl.add cached_types path ret;
+          ret
+  in
   let rec build path p outer =
   let rec build path p outer =
     match get_raw_class path, path with
     match get_raw_class path, path with
-    | (None, _, _), ([], c) -> build (["haxe";"root"], c) p outer
-    | (None, _, _), _ -> None
-    | (Some i, real_path, pos_path), _ ->
+    | None, ([], c) -> build (["haxe";"root"], c) p outer
+    | None, _ -> None
+    | Some (cls, real_path, pos_path), _ ->
         let outer = Option.default (fst path @ [snd path]) outer in
         let outer = Option.default (fst path @ [snd path]) outer in
         let ctx =  create_ctx com outer in
         let ctx =  create_ctx com outer in
       try
       try
         let pos = { pfile = pos_path; pmin = 0; pmax = 0; } in
         let pos = { pfile = pos_path; pmin = 0; pmax = 0; } in
-        let cls = JReader.parse_class i in
+        (* search static / non-static name clash *)
+        let nonstatics = ref [] in
+        List.iter (fun f ->
+          if not(List.mem JStatic f.jf_flags) then nonstatics := f :: !nonstatics
+        ) (cls.cfields @ cls.cmethods);
+        let cmethods = ref cls.cmethods in
+        let rec loop cls =
+          match cls.csuper with
+            | TObject ((["java";"lang"],"Object"), _) -> ()
+            | TObject (path, _) ->
+                (match lookup_jclass com path with
+                | None -> ()
+                | Some (cls,_,_) ->
+                  List.iter (fun f -> if not (List.mem JStatic f.jf_flags) then nonstatics := f :: !nonstatics) (cls.cfields @ cls.cmethods);
+                  cmethods := List.map (fun jm ->
+                    if not(List.mem JStatic jm.jf_flags) && not (is_override jm) && List.exists (fun msup ->
+                      msup.jf_name = jm.jf_name && not(List.mem JStatic msup.jf_flags) && match msup.jf_vmsignature, jm.jf_vmsignature with
+                      | TMethod(a1,_), TMethod(a2,_) -> a1 = a2
+                      | _ -> false
+                    ) cls.cmethods then
+                      mk_override jm
+                    else
+                      jm
+                  ) !cmethods;
+                  loop cls)
+            | _ -> ()
+        in
+        loop cls;
+        let map_field f =
+          let change = match f.jf_name with
+          | "callback" | "cast" | "extern" | "function" | "in" | "typedef" | "using" | "var" | "untyped" | "inline" -> true
+          | _ when List.mem JStatic f.jf_flags && List.exists (fun f2 -> f.jf_name = f2.jf_name) !nonstatics -> true
+          | _ -> false
+          in
+          if change then
+            { f with jf_name = "%" ^ f.jf_name }
+          else
+            f
+        in
+        (* change static fields that have the same name as methods *)
+        let cfields = List.map map_field cls.cfields in
+        let cmethods = List.map map_field !cmethods in
+        (* take off variable fields that have the same name as methods *)
+        let filter_field f f2 = f != f2 && (List.mem JStatic f.jf_flags = List.mem JStatic f2.jf_flags) && f.jf_name = f2.jf_name && f2.jf_kind <> f.jf_kind in
+        let cfields = List.filter (fun f ->
+          if List.mem JStatic f.jf_flags then
+            not (List.exists (filter_field f) cmethods)
+          else
+            not (List.exists (filter_field f) !nonstatics)) cfields
+        in
+        let cls = { cls with cfields = cfields; cmethods = cmethods } in
         let pack = match fst path with | ["haxe";"root"] -> [] | p -> p in
         let pack = match fst path with | ["haxe";"root"] -> [] | p -> p in
 
 
         let ppath = path in
         let ppath = path in
@@ -2450,20 +2556,6 @@ let add_java_lib com file =
     | Some r -> r
     | Some r -> r
   in
   in
 
 
-  let cached_types = Hashtbl.create 12 in
-  let get_raw_class path =
-    try
-      Hashtbl.find cached_types path
-    with | Not_found ->
-      match get_raw_class path with
-      | (None, _ ,_) ->
-          Hashtbl.add cached_types path None;
-          None
-      | (Some i, _, _) ->
-          let ret = JReader.parse_class i in
-          Hashtbl.add cached_types path (Some ret);
-          Some ret
-  in
 
 
   (* TODO: add_dependency m mdep *)
   (* TODO: add_dependency m mdep *)
   com.load_extern_type <- com.load_extern_type @ [build];
   com.load_extern_type <- com.load_extern_type @ [build];

+ 486 - 0
std/cs/_std/StringMap.hx

@@ -0,0 +1,486 @@
+/*
+ * Copyright (C)2005-2012 Haxe Foundation
+ *
+ * Permission is hereby granted, free of charge, to any person obtaining a
+ * copy of this software and associated documentation files (the "Software"),
+ * to deal in the Software without restriction, including without limitation
+ * the rights to use, copy, modify, merge, publish, distribute, sublicense,
+ * and/or sell copies of the Software, and to permit persons to whom the
+ * Software is furnished to do so, subject to the following conditions:
+ *
+ * The above copyright notice and this permission notice shall be included in
+ * all copies or substantial portions of the Software.
+ *
+ * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
+ * IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
+ * FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
+ * AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
+ * LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
+ * FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER
+ * DEALINGS IN THE SOFTWARE.
+ */
+import cs.NativeArray;
+
+class StringMap<T>
+{
+	@:extern private static inline var HASH_UPPER = 0.77;
+	@:extern private static inline var FLAG_EMPTY = 0;
+	@:extern private static inline var FLAG_DEL = 1;
+
+	/**
+	 * This is the most important structure here and the reason why it's so fast.
+	 * It's an array of all the hashes contained in the table. These hashes cannot be 0 nor 1,
+	 * which stand for "empty" and "deleted" states.
+	 *
+	 * The lookup algorithm will keep looking until a 0 or the key wanted is found;
+	 * The insertion algorithm will do the same but will also break when FLAG_DEL is found;
+	 */
+	private var hashes:NativeArray<HashType>;
+	private var _keys:NativeArray<String>;
+	private var vals:NativeArray<T>;
+
+	private var nBuckets:Int;
+	private var size:Int;
+	private var nOccupied:Int;
+	private var upperBound:Int;
+
+	private var cachedKey:String;
+	private var cachedIndex:Int;
+
+#if DEBUG_HASHTBL
+	private var totalProbes:Int;
+	private var probeTimes:Int;
+	private var sameHash:Int;
+	private var maxProbe:Int;
+#end
+
+	public function new() : Void
+	{
+		cachedIndex = -1;
+	}
+
+	public function set( key : String, value : T ) : Void
+	{
+		var x:Int, k:Int;
+		if (nOccupied >= upperBound)
+		{
+			if (nBuckets > (size << 1))
+				resize(nBuckets - 1); //clear "deleted" elements
+			else
+				resize(nBuckets + 2);
+		}
+
+		var hashes = hashes, keys = _keys, hashes = hashes;
+		{
+			var mask = (nBuckets == 0) ? 0 : nBuckets - 1;
+			var site = x = nBuckets;
+			k = hash(key);
+			var i = k & mask, nProbes = 0;
+
+			//for speed up
+			if (isEither(hashes[i])) {
+				x = i;
+			} else {
+				//var inc = getInc(k, mask);
+				var last = i, flag;
+				while(! (isEither(flag = hashes[i]) || (flag == k && _keys[i] == key)) )
+				{
+					i = (i + ++nProbes) & mask;
+#if DEBUG_HASHTBL
+					probeTimes++;
+					if (i == last)
+						throw "assert";
+#end
+				}
+				x = i;
+			}
+
+#if DEBUG_HASHTBL
+			if (nProbes > maxProbe)
+				maxProbe = nProbes;
+			totalProbes++;
+#end
+		}
+
+		var flag = hashes[x];
+		if (isEmpty(flag))
+		{
+			keys[x] = key;
+			vals[x] = value;
+			hashes[x] = k;
+			size++;
+			nOccupied++;
+		} else if (isDel(flag)) {
+			keys[x] = key;
+			vals[x] = value;
+			hashes[x] = k;
+			size++;
+		} else {
+			assert(_keys[x] == key);
+			vals[x] = value;
+		}
+
+		cachedIndex = x;
+		cachedKey = key;
+	}
+
+	@:final private function lookup( key : String ) : Int
+	{
+		if (nBuckets != 0)
+		{
+			var hashes = hashes, keys = _keys;
+
+			var mask = nBuckets - 1, hash = hash(key), k = hash, nProbes = 0;
+			var i = k & mask;
+			var last = i, flag;
+			//var inc = getInc(k, mask);
+			while (!isEmpty(flag = hashes[i]) && (isDel(flag) || flag != k || keys[i] != key))
+			{
+				i = (i + ++nProbes) & mask;
+#if DEBUG_HASHTBL
+				probeTimes++;
+				if (i == last)
+					throw "assert";
+#end
+			}
+
+#if DEBUG_HASHTBL
+			if (nProbes > maxProbe)
+				maxProbe = nProbes;
+			totalProbes++;
+#end
+			return isEither(flag) ? -1 : i;
+		}
+
+		return -1;
+	}
+
+	@:final @:private function resize(newNBuckets:Int) : Void
+	{
+		//This function uses 0.25*n_bucktes bytes of working space instead of [sizeof(key_t+val_t)+.25]*n_buckets.
+		var newHash = null;
+		var j = 1;
+		{
+			newNBuckets = roundUp(newNBuckets);
+			if (newNBuckets < 4) newNBuckets = 4;
+			if (size >= (newNBuckets * HASH_UPPER + 0.5)) /* requested size is too small */
+			{
+				j = 0;
+			} else { /* hash table size to be changed (shrink or expand); rehash */
+				var nfSize = newNBuckets;
+				newHash = new NativeArray( nfSize );
+				if (nBuckets < newNBuckets) //expand
+				{
+					var k = new NativeArray(newNBuckets);
+					if (_keys != null)
+						arrayCopy(_keys, 0, k, 0, nBuckets);
+					_keys = k;
+
+					var v = new NativeArray(newNBuckets);
+					if (vals != null)
+						arrayCopy(vals, 0, v, 0, nBuckets);
+					vals = v;
+				} //otherwise shrink
+			}
+		}
+
+		if (j != 0)
+		{ //rehashing is required
+			//resetting cache
+			cachedKey = null;
+			cachedIndex = -1;
+
+			j = -1;
+			var nBuckets = nBuckets, _keys = _keys, vals = vals, hashes = hashes;
+
+			var newMask = newNBuckets - 1;
+			while (++j < nBuckets)
+			{
+				var k;
+				if (!isEither(k = hashes[j]))
+				{
+					var key = _keys[j];
+					var val = vals[j];
+
+					hashes[j] = FLAG_DEL;
+					while (true) /* kick-out process; sort of like in Cuckoo hashing */
+					{
+						var nProbes = 0;
+						//var inc = getInc(k, newMask);
+						var i = k & newMask;
+
+						while (!isEmpty(newHash[i]))
+							i = (i + ++nProbes) & newMask;
+
+						newHash[i] = k;
+
+						if (i < nBuckets && !isEither(k = hashes[i])) /* kick out the existing element */
+						{
+							{
+								var tmp = _keys[i];
+								_keys[i] = key;
+								key = tmp;
+							}
+							{
+								var tmp = vals[i];
+								vals[i] = val;
+								val = tmp;
+							}
+
+							hashes[i] = FLAG_DEL; /* mark it as deleted in the old hash table */
+						} else { /* write the element and jump out of the loop */
+							_keys[i] = key;
+							vals[i] = val;
+							break;
+						}
+					}
+				}
+			}
+
+			if (nBuckets > newNBuckets) /* shrink the hash table */
+			{
+				{
+					var k = new NativeArray(newNBuckets);
+					arrayCopy(_keys, 0, k, 0, newNBuckets);
+					this._keys = k;
+				}
+				{
+					var v = new NativeArray(newNBuckets);
+					arrayCopy(vals, 0, v, 0, newNBuckets);
+					this.vals = v;
+				}
+			}
+
+			this.hashes = newHash;
+			this.nBuckets = newNBuckets;
+			this.nOccupied = size;
+			this.upperBound = Std.int(newNBuckets * HASH_UPPER + .5);
+		}
+	}
+
+	public function get( key : String ) : Null<T>
+	{
+		var idx = -1;
+		if (cachedKey == key && ( (idx = cachedIndex) != -1 ))
+		{
+			return vals[idx];
+		}
+
+		idx = lookup(key);
+		if (idx != -1)
+		{
+			cachedKey = key;
+			cachedIndex = idx;
+
+			return vals[idx];
+		}
+
+		return null;
+	}
+
+	private function getDefault( key : String, def : T ) : T
+	{
+		var idx = -1;
+		if (cachedKey == key && ( (idx = cachedIndex) != -1 ))
+		{
+			return vals[idx];
+		}
+
+		idx = lookup(key);
+		if (idx != -1)
+		{
+			cachedKey = key;
+			cachedIndex = idx;
+
+			return vals[idx];
+		}
+
+		return def;
+	}
+
+	public function exists( key : String ) : Bool
+	{
+		var idx = -1;
+		if (cachedKey == key && ( (idx = cachedIndex) != -1 ))
+		{
+			return true;
+		}
+
+		idx = lookup(key);
+		if (idx != -1)
+		{
+			cachedKey = key;
+			cachedIndex = idx;
+
+			return true;
+		}
+
+		return false;
+	}
+
+	public function remove( key : String ) : Bool
+	{
+		var idx = -1;
+		if (! (cachedKey == key && ( (idx = cachedIndex) != -1 )))
+		{
+			idx = lookup(key);
+		}
+
+		if (idx == -1)
+		{
+			return false;
+		} else {
+			if (cachedKey == key)
+				cachedIndex = -1;
+
+			hashes[idx] = FLAG_EMPTY;
+			_keys[idx] = null;
+			vals[idx] = null;
+			--size;
+
+			return true;
+		}
+	}
+
+	/**
+		Returns an iterator of all keys in the hashtable.
+		Implementation detail: Do not set() any new value while iterating, as it may cause a resize, which will break iteration
+	**/
+	public function keys() : Iterator<String>
+	{
+		var i = 0;
+		var len = nBuckets;
+		return {
+			hasNext: function() {
+				for (j in i...len)
+				{
+					if (!isEither(hashes[j]))
+					{
+						i = j;
+						return true;
+					}
+				}
+				return false;
+			},
+			next: function() {
+				var ret = _keys[i];
+				cachedIndex = i;
+				cachedKey = ret;
+
+				i = i + 1;
+				return ret;
+			}
+		};
+	}
+
+	/**
+		Returns an iterator of all values in the hashtable.
+		Implementation detail: Do not set() any new value while iterating, as it may cause a resize, which will break iteration
+	**/
+	public function iterator() : Iterator<T>
+	{
+		var i = 0;
+		var len = nBuckets;
+		return {
+			hasNext: function() {
+				for (j in i...len)
+				{
+					if (!isEither(hashes[j]))
+					{
+						i = j;
+						return true;
+					}
+				}
+				return false;
+			},
+			next: function() {
+				var ret = vals[i];
+				i = i + 1;
+				return ret;
+			}
+		};
+	}
+
+	/**
+		Returns an displayable representation of the hashtable content.
+	**/
+
+	public function toString() : String {
+		var s = new StringBuf();
+		s.add("{");
+		var it = keys();
+		for( i in it ) {
+			s.add(i);
+			s.add(" => ");
+			s.add(Std.string(get(i)));
+			if( it.hasNext() )
+				s.add(", ");
+		}
+		s.add("}");
+		return s.toString();
+	}
+
+	@:extern private static inline function roundUp(x:Int):Int
+	{
+		--x;
+		x |= (x) >>> 1;
+		x |= (x) >>> 2;
+		x |= (x) >>> 4;
+		x |= (x) >>> 8;
+		x |= (x) >>> 16;
+		return ++x;
+	}
+
+	@:extern private static inline function getInc(k:Int, mask:Int):Int //return 1 for linear probing
+		return (((k) >> 3 ^ (k) << 3) | 1) & (mask)
+
+	@:extern private static inline function isEither(v:HashType):Bool
+		return (v & 0xFFFFFFFE) == 0
+
+	@:extern private static inline function isEmpty(v:HashType):Bool
+		return v == FLAG_EMPTY
+
+	@:extern private static inline function isDel(v:HashType):Bool
+		return v == FLAG_DEL
+
+	//guarantee: Whatever this function is, it will never return 0 nor 1
+	@:extern private static inline function hash(s:String):HashType
+	{
+		var k:Int = untyped s.GetHashCode();
+		//k *= 357913941;
+		//k ^= k << 24;
+		//k += ~357913941;
+		//k ^= k >> 31;
+		//k ^= k << 31;
+
+		k = (k+0x7ed55d16) + (k<<12);
+		k = (k^0xc761c23c) ^ (k>>19);
+		k = (k+0x165667b1) + (k<<5);
+		k = (k+0xd3a2646c) ^ (k<<9);
+		k = (k+0xfd7046c5) + (k<<3);
+		k = (k^0xb55a4f09) ^ (k>>16);
+
+		var ret = k;
+		if (isEither(ret))
+		{
+			if (ret == 0)
+				ret = 2;
+			else
+				ret = 0xFFFFFFFF;
+		}
+
+		return ret;
+	}
+
+	@:extern private static inline function arrayCopy(sourceArray:cs.system.Array, sourceIndex:Int, destinationArray:cs.system.Array, destinationIndex:Int, length:Int):Void
+		cs.system.Array.Copy(sourceArray, sourceIndex, destinationArray, destinationIndex, length)
+
+	@:extern private static inline function assert(x:Bool):Void
+	{
+#if DEBUG_HASHTBL
+		if (!x) throw "assert failed";
+#end
+	}
+}
+
+private typedef HashType = Int;

+ 6 - 0
std/java/Boot.hx

@@ -35,6 +35,12 @@ import java.lang.Boolean;
 import java.lang.Character;
 import java.lang.Character;
 import java.lang.Class;
 import java.lang.Class;
 import java.lang.Number;
 import java.lang.Number;
+import java.lang.Byte;
+import java.lang.Double;
+import java.lang.Float;
+import java.lang.Integer;
+import java.lang.Long;
+import java.lang.Short;
 import java.lang.Throwable;
 import java.lang.Throwable;
 import java.internal.StringExt;
 import java.internal.StringExt;
 import java.internal.FieldLookup;
 import java.internal.FieldLookup;

+ 3 - 2
std/java/_std/sys/io/Process.hx

@@ -23,7 +23,8 @@ package sys.io;
 import haxe.io.Bytes;
 import haxe.io.Bytes;
 import haxe.io.BytesInput;
 import haxe.io.BytesInput;
 import haxe.io.Eof;
 import haxe.io.Eof;
-import java.io.Exceptions;
+import java.io.IOException;
+import java.io.EOFException;
 import java.NativeArray;
 import java.NativeArray;
 
 
 @:coreApi
 @:coreApi
@@ -153,4 +154,4 @@ private class ProcessInput extends java.io.NativeInput
 			throw haxe.io.Error.Custom(e);
 			throw haxe.io.Error.Custom(e);
 		}
 		}
 	}
 	}
-}
+}

+ 111 - 0
std/java/internal/Exception.hx

@@ -0,0 +1,111 @@
+package java.lang;
+/*
+* Copyright (c) 1994, 2011, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* The class {@code Exception} and its subclasses are a form of
+* {@code Throwable} that indicates conditions that a reasonable
+* application might want to catch.
+*
+* <p>The class {@code Exception} and any subclasses that are not also
+* subclasses of {@link RuntimeException} are <em>checked
+* exceptions</em>.  Checked exceptions need to be declared in a
+* method or constructor's {@code throws} clause if they can be thrown
+* by the execution of the method or constructor and propagate outside
+* the method or constructor boundary.
+*
+* @author  Frank Yellin
+* @see     java.lang.Error
+* @jls 11.2 Compile-Time Checking of Exceptions
+* @since   JDK1.0
+*/
+@:require(java0) extern class Exception extends java.lang.Throwable
+{
+	/**
+	* Constructs a new exception with {@code null} as its detail message.
+	* The cause is not initialized, and may subsequently be initialized by a
+	* call to {@link #initCause}.
+	*/
+	@:overload public function new() : Void;
+	
+	/**
+	* Constructs a new exception with the specified detail message.  The
+	* cause is not initialized, and may subsequently be initialized by
+	* a call to {@link #initCause}.
+	*
+	* @param   message   the detail message. The detail message is saved for
+	*          later retrieval by the {@link #getMessage()} method.
+	*/
+	@:overload public function new(message : String) : Void;
+	
+	/**
+	* Constructs a new exception with the specified detail message and
+	* cause.  <p>Note that the detail message associated with
+	* {@code cause} is <i>not</i> automatically incorporated in
+	* this exception's detail message.
+	*
+	* @param  message the detail message (which is saved for later retrieval
+	*         by the {@link #getMessage()} method).
+	* @param  cause the cause (which is saved for later retrieval by the
+	*         {@link #getCause()} method).  (A <tt>null</tt> value is
+	*         permitted, and indicates that the cause is nonexistent or
+	*         unknown.)
+	* @since  1.4
+	*/
+	@:require(java4) @:overload public function new(message : String, cause : java.lang.Throwable) : Void;
+	
+	/**
+	* Constructs a new exception with the specified cause and a detail
+	* message of <tt>(cause==null ? null : cause.toString())</tt> (which
+	* typically contains the class and detail message of <tt>cause</tt>).
+	* This constructor is useful for exceptions that are little more than
+	* wrappers for other throwables (for example, {@link
+	* java.security.PrivilegedActionException}).
+	*
+	* @param  cause the cause (which is saved for later retrieval by the
+	*         {@link #getCause()} method).  (A <tt>null</tt> value is
+	*         permitted, and indicates that the cause is nonexistent or
+	*         unknown.)
+	* @since  1.4
+	*/
+	@:require(java4) @:overload public function new(cause : java.lang.Throwable) : Void;
+	
+	/**
+	* Constructs a new exception with the specified detail message,
+	* cause, suppression enabled or disabled, and writable stack
+	* trace enabled or disabled.
+	*
+	* @param  message the detail message.
+	* @param cause the cause.  (A {@code null} value is permitted,
+	* and indicates that the cause is nonexistent or unknown.)
+	* @param enableSuppression whether or not suppression is enabled
+	*                          or disabled
+	* @param writableStackTrace whether or not the stack trace should
+	*                           be writable
+	* @since 1.7
+	*/
+	@:require(java7) @:overload private function new(message : String, cause : java.lang.Throwable, enableSuppression : Bool, writableStackTrace : Bool) : Void;
+	
+	
+}

+ 4 - 2
std/java/internal/Exceptions.hx

@@ -21,6 +21,8 @@
  */
  */
 package java.internal;
 package java.internal;
 import java.lang.Throwable;
 import java.lang.Throwable;
+import java.lang.RuntimeException;
+import java.lang.Exception;
 
 
 @:nativeGen @:keep @:native("haxe.lang.HaxeException") private class HaxeException extends RuntimeException
 @:nativeGen @:keep @:native("haxe.lang.HaxeException") private class HaxeException extends RuntimeException
 {
 {
@@ -44,7 +46,7 @@ import java.lang.Throwable;
 		return obj;
 		return obj;
 	}
 	}
 
 
-	public function toString():String
+	@:overload override public function toString():String
 	{
 	{
 		return "Haxe Exception: " + obj;
 		return "Haxe Exception: " + obj;
 	}
 	}
@@ -61,4 +63,4 @@ import java.lang.Throwable;
 
 
 		return new HaxeException(obj, null, null);
 		return new HaxeException(obj, null, null);
 	}
 	}
-}
+}

+ 45 - 0
std/java/io/Closeable.hx

@@ -0,0 +1,45 @@
+package java.io;
+/*
+* Copyright (c) 2003, 2010, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* A {@code Closeable} is a source or destination of data that can be closed.
+* The close method is invoked to release resources that the object is
+* holding (such as open files).
+*
+* @since 1.5
+*/
+@:require(java5) extern interface Closeable extends java.lang.AutoCloseable
+{
+	/**
+	* Closes this stream and releases any system resources associated
+	* with it. If the stream is already closed then invoking this
+	* method has no effect.
+	*
+	* @throws IOException if an I/O error occurs
+	*/
+	@:overload public function close() : Void;
+	
+	
+}

+ 291 - 0
std/java/io/Console.hx

@@ -0,0 +1,291 @@
+package java.io;
+/*
+* Copyright (c) 2005, 2011, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* Methods to access the character-based console device, if any, associated
+* with the current Java virtual machine.
+*
+* <p> Whether a virtual machine has a console is dependent upon the
+* underlying platform and also upon the manner in which the virtual
+* machine is invoked.  If the virtual machine is started from an
+* interactive command line without redirecting the standard input and
+* output streams then its console will exist and will typically be
+* connected to the keyboard and display from which the virtual machine
+* was launched.  If the virtual machine is started automatically, for
+* example by a background job scheduler, then it will typically not
+* have a console.
+* <p>
+* If this virtual machine has a console then it is represented by a
+* unique instance of this class which can be obtained by invoking the
+* {@link java.lang.System#console()} method.  If no console device is
+* available then an invocation of that method will return <tt>null</tt>.
+* <p>
+* Read and write operations are synchronized to guarantee the atomic
+* completion of critical operations; therefore invoking methods
+* {@link #readLine()}, {@link #readPassword()}, {@link #format format()},
+* {@link #printf printf()} as well as the read, format and write operations
+* on the objects returned by {@link #reader()} and {@link #writer()} may
+* block in multithreaded scenarios.
+* <p>
+* Invoking <tt>close()</tt> on the objects returned by the {@link #reader()}
+* and the {@link #writer()} will not close the underlying stream of those
+* objects.
+* <p>
+* The console-read methods return <tt>null</tt> when the end of the
+* console input stream is reached, for example by typing control-D on
+* Unix or control-Z on Windows.  Subsequent read operations will succeed
+* if additional characters are later entered on the console's input
+* device.
+* <p>
+* Unless otherwise specified, passing a <tt>null</tt> argument to any method
+* in this class will cause a {@link NullPointerException} to be thrown.
+* <p>
+* <b>Security note:</b>
+* If an application needs to read a password or other secure data, it should
+* use {@link #readPassword()} or {@link #readPassword(String, Object...)} and
+* manually zero the returned character array after processing to minimize the
+* lifetime of sensitive data in memory.
+*
+* <blockquote><pre>
+* Console cons;
+* char[] passwd;
+* if ((cons = System.console()) != null &&
+*     (passwd = cons.readPassword("[%s]", "Password:")) != null) {
+*     ...
+*     java.util.Arrays.fill(passwd, ' ');
+* }
+* </pre></blockquote>
+*
+* @author  Xueming Shen
+* @since   1.6
+*/
+@:require(java6) extern class Console implements java.io.Flushable
+{
+	/**
+	* Retrieves the unique {@link java.io.PrintWriter PrintWriter} object
+	* associated with this console.
+	*
+	* @return  The printwriter associated with this console
+	*/
+	@:overload public function writer() : java.io.PrintWriter;
+	
+	/**
+	* Retrieves the unique {@link java.io.Reader Reader} object associated
+	* with this console.
+	* <p>
+	* This method is intended to be used by sophisticated applications, for
+	* example, a {@link java.util.Scanner} object which utilizes the rich
+	* parsing/scanning functionality provided by the <tt>Scanner</tt>:
+	* <blockquote><pre>
+	* Console con = System.console();
+	* if (con != null) {
+	*     Scanner sc = new Scanner(con.reader());
+	*     ...
+	* }
+	* </pre></blockquote>
+	* <p>
+	* For simple applications requiring only line-oriented reading, use
+	* <tt>{@link #readLine}</tt>.
+	* <p>
+	* The bulk read operations {@link java.io.Reader#read(char[]) read(char[]) },
+	* {@link java.io.Reader#read(char[], int, int) read(char[], int, int) } and
+	* {@link java.io.Reader#read(java.nio.CharBuffer) read(java.nio.CharBuffer)}
+	* on the returned object will not read in characters beyond the line
+	* bound for each invocation, even if the destination buffer has space for
+	* more characters. A line bound is considered to be any one of a line feed
+	* (<tt>'\n'</tt>), a carriage return (<tt>'\r'</tt>), a carriage return
+	* followed immediately by a linefeed, or an end of stream.
+	*
+	* @return  The reader associated with this console
+	*/
+	@:overload public function reader() : java.io.Reader;
+	
+	/**
+	* Writes a formatted string to this console's output stream using
+	* the specified format string and arguments.
+	*
+	* @param  fmt
+	*         A format string as described in <a
+	*         href="../util/Formatter.html#syntax">Format string syntax</a>
+	*
+	* @param  args
+	*         Arguments referenced by the format specifiers in the format
+	*         string.  If there are more arguments than format specifiers, the
+	*         extra arguments are ignored.  The number of arguments is
+	*         variable and may be zero.  The maximum number of arguments is
+	*         limited by the maximum dimension of a Java array as defined by
+	*         <cite>The Java&trade; Virtual Machine Specification</cite>.
+	*         The behaviour on a
+	*         <tt>null</tt> argument depends on the <a
+	*         href="../util/Formatter.html#syntax">conversion</a>.
+	*
+	* @throws  IllegalFormatException
+	*          If a format string contains an illegal syntax, a format
+	*          specifier that is incompatible with the given arguments,
+	*          insufficient arguments given the format string, or other
+	*          illegal conditions.  For specification of all possible
+	*          formatting errors, see the <a
+	*          href="../util/Formatter.html#detail">Details</a> section
+	*          of the formatter class specification.
+	*
+	* @return  This console
+	*/
+	@:overload public function format(fmt : String, args : java.NativeArray<Dynamic>) : Console;
+	
+	/**
+	* A convenience method to write a formatted string to this console's
+	* output stream using the specified format string and arguments.
+	*
+	* <p> An invocation of this method of the form <tt>con.printf(format,
+	* args)</tt> behaves in exactly the same way as the invocation of
+	* <pre>con.format(format, args)</pre>.
+	*
+	* @param  format
+	*         A format string as described in <a
+	*         href="../util/Formatter.html#syntax">Format string syntax</a>.
+	*
+	* @param  args
+	*         Arguments referenced by the format specifiers in the format
+	*         string.  If there are more arguments than format specifiers, the
+	*         extra arguments are ignored.  The number of arguments is
+	*         variable and may be zero.  The maximum number of arguments is
+	*         limited by the maximum dimension of a Java array as defined by
+	*         <cite>The Java&trade; Virtual Machine Specification</cite>.
+	*         The behaviour on a
+	*         <tt>null</tt> argument depends on the <a
+	*         href="../util/Formatter.html#syntax">conversion</a>.
+	*
+	* @throws  IllegalFormatException
+	*          If a format string contains an illegal syntax, a format
+	*          specifier that is incompatible with the given arguments,
+	*          insufficient arguments given the format string, or other
+	*          illegal conditions.  For specification of all possible
+	*          formatting errors, see the <a
+	*          href="../util/Formatter.html#detail">Details</a> section of the
+	*          formatter class specification.
+	*
+	* @return  This console
+	*/
+	@:overload public function printf(format : String, args : java.NativeArray<Dynamic>) : Console;
+	
+	/**
+	* Provides a formatted prompt, then reads a single line of text from the
+	* console.
+	*
+	* @param  fmt
+	*         A format string as described in <a
+	*         href="../util/Formatter.html#syntax">Format string syntax</a>.
+	*
+	* @param  args
+	*         Arguments referenced by the format specifiers in the format
+	*         string.  If there are more arguments than format specifiers, the
+	*         extra arguments are ignored.  The maximum number of arguments is
+	*         limited by the maximum dimension of a Java array as defined by
+	*         <cite>The Java&trade; Virtual Machine Specification</cite>.
+	*
+	* @throws  IllegalFormatException
+	*          If a format string contains an illegal syntax, a format
+	*          specifier that is incompatible with the given arguments,
+	*          insufficient arguments given the format string, or other
+	*          illegal conditions.  For specification of all possible
+	*          formatting errors, see the <a
+	*          href="../util/Formatter.html#detail">Details</a> section
+	*          of the formatter class specification.
+	*
+	* @throws IOError
+	*         If an I/O error occurs.
+	*
+	* @return  A string containing the line read from the console, not
+	*          including any line-termination characters, or <tt>null</tt>
+	*          if an end of stream has been reached.
+	*/
+	@:overload public function readLine(fmt : String, args : java.NativeArray<Dynamic>) : String;
+	
+	/**
+	* Reads a single line of text from the console.
+	*
+	* @throws IOError
+	*         If an I/O error occurs.
+	*
+	* @return  A string containing the line read from the console, not
+	*          including any line-termination characters, or <tt>null</tt>
+	*          if an end of stream has been reached.
+	*/
+	@:overload public function readLine() : String;
+	
+	/**
+	* Provides a formatted prompt, then reads a password or passphrase from
+	* the console with echoing disabled.
+	*
+	* @param  fmt
+	*         A format string as described in <a
+	*         href="../util/Formatter.html#syntax">Format string syntax</a>
+	*         for the prompt text.
+	*
+	* @param  args
+	*         Arguments referenced by the format specifiers in the format
+	*         string.  If there are more arguments than format specifiers, the
+	*         extra arguments are ignored.  The maximum number of arguments is
+	*         limited by the maximum dimension of a Java array as defined by
+	*         <cite>The Java&trade; Virtual Machine Specification</cite>.
+	*
+	* @throws  IllegalFormatException
+	*          If a format string contains an illegal syntax, a format
+	*          specifier that is incompatible with the given arguments,
+	*          insufficient arguments given the format string, or other
+	*          illegal conditions.  For specification of all possible
+	*          formatting errors, see the <a
+	*          href="../util/Formatter.html#detail">Details</a>
+	*          section of the formatter class specification.
+	*
+	* @throws IOError
+	*         If an I/O error occurs.
+	*
+	* @return  A character array containing the password or passphrase read
+	*          from the console, not including any line-termination characters,
+	*          or <tt>null</tt> if an end of stream has been reached.
+	*/
+	@:overload public function readPassword(fmt : String, args : java.NativeArray<Dynamic>) : java.NativeArray<java.StdTypes.Char16>;
+	
+	/**
+	* Reads a password or passphrase from the console with echoing disabled
+	*
+	* @throws IOError
+	*         If an I/O error occurs.
+	*
+	* @return  A character array containing the password or passphrase read
+	*          from the console, not including any line-termination characters,
+	*          or <tt>null</tt> if an end of stream has been reached.
+	*/
+	@:overload public function readPassword() : java.NativeArray<java.StdTypes.Char16>;
+	
+	/**
+	* Flushes the console and forces any buffered output to be written
+	* immediately .
+	*/
+	@:overload public function flush() : Void;
+	
+	
+}

+ 59 - 0
std/java/io/EOFException.hx

@@ -0,0 +1,59 @@
+package java.io;
+/*
+* Copyright (c) 1995, 2008, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* Signals that an end of file or end of stream has been reached
+* unexpectedly during input.
+* <p>
+* This exception is mainly used by data input streams to signal end of
+* stream. Note that many other input operations return a special value on
+* end of stream rather than throwing an exception.
+* <p>
+*
+* @author  Frank Yellin
+* @see     java.io.DataInputStream
+* @see     java.io.IOException
+* @since   JDK1.0
+*/
+@:require(java0) extern class EOFException extends java.io.IOException
+{
+	/**
+	* Constructs an <code>EOFException</code> with <code>null</code>
+	* as its error detail message.
+	*/
+	@:overload public function new() : Void;
+	
+	/**
+	* Constructs an <code>EOFException</code> with the specified detail
+	* message. The string <code>s</code> may later be retrieved by the
+	* <code>{@link java.lang.Throwable#getMessage}</code> method of class
+	* <code>java.lang.Throwable</code>.
+	*
+	* @param   s   the detail message.
+	*/
+	@:overload public function new(s : String) : Void;
+	
+	
+}

+ 44 - 0
std/java/io/Flushable.hx

@@ -0,0 +1,44 @@
+package java.io;
+/*
+* Copyright (c) 2004, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* A <tt>Flushable</tt> is a destination of data that can be flushed.  The
+* flush method is invoked to write any buffered output to the underlying
+* stream.
+*
+* @since 1.5
+*/
+@:require(java5) extern interface Flushable
+{
+	/**
+	* Flushes this stream by writing any buffered output to the underlying
+	* stream.
+	*
+	* @throws IOException If an I/O error occurs
+	*/
+	@:overload public function flush() : Void;
+	
+	
+}

+ 91 - 0
std/java/io/IOException.hx

@@ -0,0 +1,91 @@
+package java.io;
+/*
+* Copyright (c) 1994, 2006, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* Signals that an I/O exception of some sort has occurred. This
+* class is the general class of exceptions produced by failed or
+* interrupted I/O operations.
+*
+* @author  unascribed
+* @see     java.io.InputStream
+* @see     java.io.OutputStream
+* @since   JDK1.0
+*/
+@:require(java0) extern class IOException extends java.lang.Exception
+{
+	/**
+	* Constructs an {@code IOException} with {@code null}
+	* as its error detail message.
+	*/
+	@:overload public function new() : Void;
+	
+	/**
+	* Constructs an {@code IOException} with the specified detail message.
+	*
+	* @param message
+	*        The detail message (which is saved for later retrieval
+	*        by the {@link #getMessage()} method)
+	*/
+	@:overload public function new(message : String) : Void;
+	
+	/**
+	* Constructs an {@code IOException} with the specified detail message
+	* and cause.
+	*
+	* <p> Note that the detail message associated with {@code cause} is
+	* <i>not</i> automatically incorporated into this exception's detail
+	* message.
+	*
+	* @param message
+	*        The detail message (which is saved for later retrieval
+	*        by the {@link #getMessage()} method)
+	*
+	* @param cause
+	*        The cause (which is saved for later retrieval by the
+	*        {@link #getCause()} method).  (A null value is permitted,
+	*        and indicates that the cause is nonexistent or unknown.)
+	*
+	* @since 1.6
+	*/
+	@:require(java6) @:overload public function new(message : String, cause : java.lang.Throwable) : Void;
+	
+	/**
+	* Constructs an {@code IOException} with the specified cause and a
+	* detail message of {@code (cause==null ? null : cause.toString())}
+	* (which typically contains the class and detail message of {@code cause}).
+	* This constructor is useful for IO exceptions that are little more
+	* than wrappers for other throwables.
+	*
+	* @param cause
+	*        The cause (which is saved for later retrieval by the
+	*        {@link #getCause()} method).  (A null value is permitted,
+	*        and indicates that the cause is nonexistent or unknown.)
+	*
+	* @since 1.6
+	*/
+	@:require(java6) @:overload public function new(cause : java.lang.Throwable) : Void;
+	
+	
+}

+ 14 - 13
std/java/io/NativeInput.hx

@@ -24,7 +24,8 @@ import haxe.Int64;
 import haxe.io.Bytes;
 import haxe.io.Bytes;
 import haxe.io.Eof;
 import haxe.io.Eof;
 import haxe.io.Input;
 import haxe.io.Input;
-import java.io.Exceptions;
+import java.io.IOException;
+import java.io.EOFException;
 
 
 @:native('haxe.java.io.NativeInput') class NativeInput extends Input
 @:native('haxe.java.io.NativeInput') class NativeInput extends Input
 {
 {
@@ -33,52 +34,52 @@ import java.io.Exceptions;
 	{
 	{
 		this.stream = stream;
 		this.stream = stream;
 	}
 	}
-	
-	override public function readByte():Int 
+
+	override public function readByte():Int
 	{
 	{
 		try
 		try
 		{
 		{
 			return stream.read();
 			return stream.read();
-		} 
+		}
 		catch (e:EOFException) {
 		catch (e:EOFException) {
 			throw new Eof();
 			throw new Eof();
 		}
 		}
-		
+
 		catch (e:IOException) {
 		catch (e:IOException) {
 			throw haxe.io.Error.Custom(e);
 			throw haxe.io.Error.Custom(e);
 		}
 		}
 	}
 	}
-	
-	override public function readBytes(s:Bytes, pos:Int, len:Int):Int 
+
+	override public function readBytes(s:Bytes, pos:Int, len:Int):Int
 	{
 	{
 		var ret = 0;
 		var ret = 0;
 		try
 		try
 		{
 		{
 			ret = stream.read(s.getData(), pos, len);
 			ret = stream.read(s.getData(), pos, len);
 		}
 		}
-		
+
 		catch (e:EOFException) {
 		catch (e:EOFException) {
 			throw new Eof();
 			throw new Eof();
 		}
 		}
-		
+
 		catch (e:IOException) {
 		catch (e:IOException) {
 			throw haxe.io.Error.Custom(e);
 			throw haxe.io.Error.Custom(e);
 		}
 		}
-		
+
 		if (ret == -1)
 		if (ret == -1)
 			throw new Eof();
 			throw new Eof();
 		return ret;
 		return ret;
 	}
 	}
-	
+
 	override public function close():Void
 	override public function close():Void
 	{
 	{
 		try
 		try
 		{
 		{
 			stream.close();
 			stream.close();
 		}
 		}
-		
+
 		catch (e:IOException) {
 		catch (e:IOException) {
 			throw haxe.io.Error.Custom(e);
 			throw haxe.io.Error.Custom(e);
 		}
 		}
 	}
 	}
-}
+}

+ 11 - 10
std/java/io/NativeOutput.hx

@@ -24,7 +24,8 @@ import haxe.Int64;
 import haxe.io.Bytes;
 import haxe.io.Bytes;
 import haxe.io.Eof;
 import haxe.io.Eof;
 import haxe.io.Output;
 import haxe.io.Output;
-import java.io.Exceptions;
+import java.io.IOException;
+import java.io.EOFException;
 
 
 @:native('haxe.java.io.NativeOutput') class NativeOutput extends Output
 @:native('haxe.java.io.NativeOutput') class NativeOutput extends Output
 {
 {
@@ -33,44 +34,44 @@ import java.io.Exceptions;
 	{
 	{
 		this.stream = stream;
 		this.stream = stream;
 	}
 	}
-	
-	override public function writeByte(c:Int):Void 
+
+	override public function writeByte(c:Int):Void
 	{
 	{
 		try
 		try
 		{
 		{
 			stream.write(c);
 			stream.write(c);
 		}
 		}
-		
+
 		catch (e:EOFException) {
 		catch (e:EOFException) {
 			throw new Eof();
 			throw new Eof();
 		}
 		}
-		
+
 		catch (e:IOException) {
 		catch (e:IOException) {
 			throw haxe.io.Error.Custom(e);
 			throw haxe.io.Error.Custom(e);
 		}
 		}
 	}
 	}
-	
+
 	override public function close():Void
 	override public function close():Void
 	{
 	{
 		try
 		try
 		{
 		{
 			stream.close();
 			stream.close();
 		}
 		}
-		
+
 		catch (e:IOException) {
 		catch (e:IOException) {
 			throw haxe.io.Error.Custom(e);
 			throw haxe.io.Error.Custom(e);
 		}
 		}
 	}
 	}
-	
+
 	override public function flush():Void
 	override public function flush():Void
 	{
 	{
 		try
 		try
 		{
 		{
 			stream.flush();
 			stream.flush();
 		}
 		}
-		
+
 		catch (e:IOException) {
 		catch (e:IOException) {
 			throw haxe.io.Error.Custom(e);
 			throw haxe.io.Error.Custom(e);
 		}
 		}
 	}
 	}
-}
+}

+ 759 - 0
std/java/io/PrintWriter.hx

@@ -0,0 +1,759 @@
+package java.io;
+/*
+* Copyright (c) 1996, 2011, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* Prints formatted representations of objects to a text-output stream.  This
+* class implements all of the <tt>print</tt> methods found in {@link
+* PrintStream}.  It does not contain methods for writing raw bytes, for which
+* a program should use unencoded byte streams.
+*
+* <p> Unlike the {@link PrintStream} class, if automatic flushing is enabled
+* it will be done only when one of the <tt>println</tt>, <tt>printf</tt>, or
+* <tt>format</tt> methods is invoked, rather than whenever a newline character
+* happens to be output.  These methods use the platform's own notion of line
+* separator rather than the newline character.
+*
+* <p> Methods in this class never throw I/O exceptions, although some of its
+* constructors may.  The client may inquire as to whether any errors have
+* occurred by invoking {@link #checkError checkError()}.
+*
+* @author      Frank Yellin
+* @author      Mark Reinhold
+* @since       JDK1.1
+*/
+@:require(java1) extern class PrintWriter extends java.io.Writer
+{
+	/**
+	* The underlying character-output stream of this
+	* <code>PrintWriter</code>.
+	*
+	* @since 1.2
+	*/
+	@:require(java2) private var out : java.io.Writer;
+	
+	/**
+	* Creates a new PrintWriter, without automatic line flushing.
+	*
+	* @param  out        A character-output stream
+	*/
+	@:overload public function new(out : java.io.Writer) : Void;
+	
+	/**
+	* Creates a new PrintWriter.
+	*
+	* @param  out        A character-output stream
+	* @param  autoFlush  A boolean; if true, the <tt>println</tt>,
+	*                    <tt>printf</tt>, or <tt>format</tt> methods will
+	*                    flush the output buffer
+	*/
+	@:overload public function new(out : java.io.Writer, autoFlush : Bool) : Void;
+	
+	/**
+	* Creates a new PrintWriter, without automatic line flushing, from an
+	* existing OutputStream.  This convenience constructor creates the
+	* necessary intermediate OutputStreamWriter, which will convert characters
+	* into bytes using the default character encoding.
+	*
+	* @param  out        An output stream
+	*
+	* @see java.io.OutputStreamWriter#OutputStreamWriter(java.io.OutputStream)
+	*/
+	@:overload public function new(out : java.io.OutputStream) : Void;
+	
+	/**
+	* Creates a new PrintWriter from an existing OutputStream.  This
+	* convenience constructor creates the necessary intermediate
+	* OutputStreamWriter, which will convert characters into bytes using the
+	* default character encoding.
+	*
+	* @param  out        An output stream
+	* @param  autoFlush  A boolean; if true, the <tt>println</tt>,
+	*                    <tt>printf</tt>, or <tt>format</tt> methods will
+	*                    flush the output buffer
+	*
+	* @see java.io.OutputStreamWriter#OutputStreamWriter(java.io.OutputStream)
+	*/
+	@:overload public function new(out : java.io.OutputStream, autoFlush : Bool) : Void;
+	
+	/**
+	* Creates a new PrintWriter, without automatic line flushing, with the
+	* specified file name.  This convenience constructor creates the necessary
+	* intermediate {@link java.io.OutputStreamWriter OutputStreamWriter},
+	* which will encode characters using the {@linkplain
+	* java.nio.charset.Charset#defaultCharset() default charset} for this
+	* instance of the Java virtual machine.
+	*
+	* @param  fileName
+	*         The name of the file to use as the destination of this writer.
+	*         If the file exists then it will be truncated to zero size;
+	*         otherwise, a new file will be created.  The output will be
+	*         written to the file and is buffered.
+	*
+	* @throws  FileNotFoundException
+	*          If the given string does not denote an existing, writable
+	*          regular file and a new regular file of that name cannot be
+	*          created, or if some other error occurs while opening or
+	*          creating the file
+	*
+	* @throws  SecurityException
+	*          If a security manager is present and {@link
+	*          SecurityManager#checkWrite checkWrite(fileName)} denies write
+	*          access to the file
+	*
+	* @since  1.5
+	*/
+	@:require(java5) @:overload public function new(fileName : String) : Void;
+	
+	/**
+	* Creates a new PrintWriter, without automatic line flushing, with the
+	* specified file name and charset.  This convenience constructor creates
+	* the necessary intermediate {@link java.io.OutputStreamWriter
+	* OutputStreamWriter}, which will encode characters using the provided
+	* charset.
+	*
+	* @param  fileName
+	*         The name of the file to use as the destination of this writer.
+	*         If the file exists then it will be truncated to zero size;
+	*         otherwise, a new file will be created.  The output will be
+	*         written to the file and is buffered.
+	*
+	* @param  csn
+	*         The name of a supported {@linkplain java.nio.charset.Charset
+	*         charset}
+	*
+	* @throws  FileNotFoundException
+	*          If the given string does not denote an existing, writable
+	*          regular file and a new regular file of that name cannot be
+	*          created, or if some other error occurs while opening or
+	*          creating the file
+	*
+	* @throws  SecurityException
+	*          If a security manager is present and {@link
+	*          SecurityManager#checkWrite checkWrite(fileName)} denies write
+	*          access to the file
+	*
+	* @throws  UnsupportedEncodingException
+	*          If the named charset is not supported
+	*
+	* @since  1.5
+	*/
+	@:require(java5) @:overload public function new(fileName : String, csn : String) : Void;
+	
+	/**
+	* Creates a new PrintWriter, without automatic line flushing, with the
+	* specified file.  This convenience constructor creates the necessary
+	* intermediate {@link java.io.OutputStreamWriter OutputStreamWriter},
+	* which will encode characters using the {@linkplain
+	* java.nio.charset.Charset#defaultCharset() default charset} for this
+	* instance of the Java virtual machine.
+	*
+	* @param  file
+	*         The file to use as the destination of this writer.  If the file
+	*         exists then it will be truncated to zero size; otherwise, a new
+	*         file will be created.  The output will be written to the file
+	*         and is buffered.
+	*
+	* @throws  FileNotFoundException
+	*          If the given file object does not denote an existing, writable
+	*          regular file and a new regular file of that name cannot be
+	*          created, or if some other error occurs while opening or
+	*          creating the file
+	*
+	* @throws  SecurityException
+	*          If a security manager is present and {@link
+	*          SecurityManager#checkWrite checkWrite(file.getPath())}
+	*          denies write access to the file
+	*
+	* @since  1.5
+	*/
+	@:require(java5) @:overload public function new(file : java.io.File) : Void;
+	
+	/**
+	* Creates a new PrintWriter, without automatic line flushing, with the
+	* specified file and charset.  This convenience constructor creates the
+	* necessary intermediate {@link java.io.OutputStreamWriter
+	* OutputStreamWriter}, which will encode characters using the provided
+	* charset.
+	*
+	* @param  file
+	*         The file to use as the destination of this writer.  If the file
+	*         exists then it will be truncated to zero size; otherwise, a new
+	*         file will be created.  The output will be written to the file
+	*         and is buffered.
+	*
+	* @param  csn
+	*         The name of a supported {@linkplain java.nio.charset.Charset
+	*         charset}
+	*
+	* @throws  FileNotFoundException
+	*          If the given file object does not denote an existing, writable
+	*          regular file and a new regular file of that name cannot be
+	*          created, or if some other error occurs while opening or
+	*          creating the file
+	*
+	* @throws  SecurityException
+	*          If a security manager is present and {@link
+	*          SecurityManager#checkWrite checkWrite(file.getPath())}
+	*          denies write access to the file
+	*
+	* @throws  UnsupportedEncodingException
+	*          If the named charset is not supported
+	*
+	* @since  1.5
+	*/
+	@:require(java5) @:overload public function new(file : java.io.File, csn : String) : Void;
+	
+	/**
+	* Flushes the stream.
+	* @see #checkError()
+	*/
+	@:overload override public function flush() : Void;
+	
+	/**
+	* Closes the stream and releases any system resources associated
+	* with it. Closing a previously closed stream has no effect.
+	*
+	* @see #checkError()
+	*/
+	@:overload override public function close() : Void;
+	
+	/**
+	* Flushes the stream if it's not closed and checks its error state.
+	*
+	* @return <code>true</code> if the print stream has encountered an error,
+	*          either on the underlying output stream or during a format
+	*          conversion.
+	*/
+	@:overload public function checkError() : Bool;
+	
+	/**
+	* Indicates that an error has occurred.
+	*
+	* <p> This method will cause subsequent invocations of {@link
+	* #checkError()} to return <tt>true</tt> until {@link
+	* #clearError()} is invoked.
+	*/
+	@:overload private function setError() : Void;
+	
+	/**
+	* Clears the error state of this stream.
+	*
+	* <p> This method will cause subsequent invocations of {@link
+	* #checkError()} to return <tt>false</tt> until another write
+	* operation fails and invokes {@link #setError()}.
+	*
+	* @since 1.6
+	*/
+	@:require(java6) @:overload private function clearError() : Void;
+	
+	/**
+	* Writes a single character.
+	* @param c int specifying a character to be written.
+	*/
+	@:overload override public function write(c : Int) : Void;
+	
+	/**
+	* Writes A Portion of an array of characters.
+	* @param buf Array of characters
+	* @param off Offset from which to start writing characters
+	* @param len Number of characters to write
+	*/
+	@:overload override public function write(buf : java.NativeArray<java.StdTypes.Char16>, off : Int, len : Int) : Void;
+	
+	/**
+	* Writes an array of characters.  This method cannot be inherited from the
+	* Writer class because it must suppress I/O exceptions.
+	* @param buf Array of characters to be written
+	*/
+	@:overload override public function write(buf : java.NativeArray<java.StdTypes.Char16>) : Void;
+	
+	/**
+	* Writes a portion of a string.
+	* @param s A String
+	* @param off Offset from which to start writing characters
+	* @param len Number of characters to write
+	*/
+	@:overload override public function write(s : String, off : Int, len : Int) : Void;
+	
+	/**
+	* Writes a string.  This method cannot be inherited from the Writer class
+	* because it must suppress I/O exceptions.
+	* @param s String to be written
+	*/
+	@:overload override public function write(s : String) : Void;
+	
+	/**
+	* Prints a boolean value.  The string produced by <code>{@link
+	* java.lang.String#valueOf(boolean)}</code> is translated into bytes
+	* according to the platform's default character encoding, and these bytes
+	* are written in exactly the manner of the <code>{@link
+	* #write(int)}</code> method.
+	*
+	* @param      b   The <code>boolean</code> to be printed
+	*/
+	@:overload public function print(b : Bool) : Void;
+	
+	/**
+	* Prints a character.  The character is translated into one or more bytes
+	* according to the platform's default character encoding, and these bytes
+	* are written in exactly the manner of the <code>{@link
+	* #write(int)}</code> method.
+	*
+	* @param      c   The <code>char</code> to be printed
+	*/
+	@:overload public function print(c : java.StdTypes.Char16) : Void;
+	
+	/**
+	* Prints an integer.  The string produced by <code>{@link
+	* java.lang.String#valueOf(int)}</code> is translated into bytes according
+	* to the platform's default character encoding, and these bytes are
+	* written in exactly the manner of the <code>{@link #write(int)}</code>
+	* method.
+	*
+	* @param      i   The <code>int</code> to be printed
+	* @see        java.lang.Integer#toString(int)
+	*/
+	@:overload public function print(i : Int) : Void;
+	
+	/**
+	* Prints a long integer.  The string produced by <code>{@link
+	* java.lang.String#valueOf(long)}</code> is translated into bytes
+	* according to the platform's default character encoding, and these bytes
+	* are written in exactly the manner of the <code>{@link #write(int)}</code>
+	* method.
+	*
+	* @param      l   The <code>long</code> to be printed
+	* @see        java.lang.Long#toString(long)
+	*/
+	@:overload public function print(l : haxe.Int64) : Void;
+	
+	/**
+	* Prints a floating-point number.  The string produced by <code>{@link
+	* java.lang.String#valueOf(float)}</code> is translated into bytes
+	* according to the platform's default character encoding, and these bytes
+	* are written in exactly the manner of the <code>{@link #write(int)}</code>
+	* method.
+	*
+	* @param      f   The <code>float</code> to be printed
+	* @see        java.lang.Float#toString(float)
+	*/
+	@:overload public function print(f : Single) : Void;
+	
+	/**
+	* Prints a double-precision floating-point number.  The string produced by
+	* <code>{@link java.lang.String#valueOf(double)}</code> is translated into
+	* bytes according to the platform's default character encoding, and these
+	* bytes are written in exactly the manner of the <code>{@link
+	* #write(int)}</code> method.
+	*
+	* @param      d   The <code>double</code> to be printed
+	* @see        java.lang.Double#toString(double)
+	*/
+	@:overload public function print(d : Float) : Void;
+	
+	/**
+	* Prints an array of characters.  The characters are converted into bytes
+	* according to the platform's default character encoding, and these bytes
+	* are written in exactly the manner of the <code>{@link #write(int)}</code>
+	* method.
+	*
+	* @param      s   The array of chars to be printed
+	*
+	* @throws  NullPointerException  If <code>s</code> is <code>null</code>
+	*/
+	@:overload public function print(s : java.NativeArray<java.StdTypes.Char16>) : Void;
+	
+	/**
+	* Prints a string.  If the argument is <code>null</code> then the string
+	* <code>"null"</code> is printed.  Otherwise, the string's characters are
+	* converted into bytes according to the platform's default character
+	* encoding, and these bytes are written in exactly the manner of the
+	* <code>{@link #write(int)}</code> method.
+	*
+	* @param      s   The <code>String</code> to be printed
+	*/
+	@:overload public function print(s : String) : Void;
+	
+	/**
+	* Prints an object.  The string produced by the <code>{@link
+	* java.lang.String#valueOf(Object)}</code> method is translated into bytes
+	* according to the platform's default character encoding, and these bytes
+	* are written in exactly the manner of the <code>{@link #write(int)}</code>
+	* method.
+	*
+	* @param      obj   The <code>Object</code> to be printed
+	* @see        java.lang.Object#toString()
+	*/
+	@:overload public function print(obj : Dynamic) : Void;
+	
+	/**
+	* Terminates the current line by writing the line separator string.  The
+	* line separator string is defined by the system property
+	* <code>line.separator</code>, and is not necessarily a single newline
+	* character (<code>'\n'</code>).
+	*/
+	@:overload public function println() : Void;
+	
+	/**
+	* Prints a boolean value and then terminates the line.  This method behaves
+	* as though it invokes <code>{@link #print(boolean)}</code> and then
+	* <code>{@link #println()}</code>.
+	*
+	* @param x the <code>boolean</code> value to be printed
+	*/
+	@:overload public function println(x : Bool) : Void;
+	
+	/**
+	* Prints a character and then terminates the line.  This method behaves as
+	* though it invokes <code>{@link #print(char)}</code> and then <code>{@link
+	* #println()}</code>.
+	*
+	* @param x the <code>char</code> value to be printed
+	*/
+	@:overload public function println(x : java.StdTypes.Char16) : Void;
+	
+	/**
+	* Prints an integer and then terminates the line.  This method behaves as
+	* though it invokes <code>{@link #print(int)}</code> and then <code>{@link
+	* #println()}</code>.
+	*
+	* @param x the <code>int</code> value to be printed
+	*/
+	@:overload public function println(x : Int) : Void;
+	
+	/**
+	* Prints a long integer and then terminates the line.  This method behaves
+	* as though it invokes <code>{@link #print(long)}</code> and then
+	* <code>{@link #println()}</code>.
+	*
+	* @param x the <code>long</code> value to be printed
+	*/
+	@:overload public function println(x : haxe.Int64) : Void;
+	
+	/**
+	* Prints a floating-point number and then terminates the line.  This method
+	* behaves as though it invokes <code>{@link #print(float)}</code> and then
+	* <code>{@link #println()}</code>.
+	*
+	* @param x the <code>float</code> value to be printed
+	*/
+	@:overload public function println(x : Single) : Void;
+	
+	/**
+	* Prints a double-precision floating-point number and then terminates the
+	* line.  This method behaves as though it invokes <code>{@link
+	* #print(double)}</code> and then <code>{@link #println()}</code>.
+	*
+	* @param x the <code>double</code> value to be printed
+	*/
+	@:overload public function println(x : Float) : Void;
+	
+	/**
+	* Prints an array of characters and then terminates the line.  This method
+	* behaves as though it invokes <code>{@link #print(char[])}</code> and then
+	* <code>{@link #println()}</code>.
+	*
+	* @param x the array of <code>char</code> values to be printed
+	*/
+	@:overload public function println(x : java.NativeArray<java.StdTypes.Char16>) : Void;
+	
+	/**
+	* Prints a String and then terminates the line.  This method behaves as
+	* though it invokes <code>{@link #print(String)}</code> and then
+	* <code>{@link #println()}</code>.
+	*
+	* @param x the <code>String</code> value to be printed
+	*/
+	@:overload public function println(x : String) : Void;
+	
+	/**
+	* Prints an Object and then terminates the line.  This method calls
+	* at first String.valueOf(x) to get the printed object's string value,
+	* then behaves as
+	* though it invokes <code>{@link #print(String)}</code> and then
+	* <code>{@link #println()}</code>.
+	*
+	* @param x  The <code>Object</code> to be printed.
+	*/
+	@:overload public function println(x : Dynamic) : Void;
+	
+	/**
+	* A convenience method to write a formatted string to this writer using
+	* the specified format string and arguments.  If automatic flushing is
+	* enabled, calls to this method will flush the output buffer.
+	*
+	* <p> An invocation of this method of the form <tt>out.printf(format,
+	* args)</tt> behaves in exactly the same way as the invocation
+	*
+	* <pre>
+	*     out.format(format, args) </pre>
+	*
+	* @param  format
+	*         A format string as described in <a
+	*         href="../util/Formatter.html#syntax">Format string syntax</a>.
+	*
+	* @param  args
+	*         Arguments referenced by the format specifiers in the format
+	*         string.  If there are more arguments than format specifiers, the
+	*         extra arguments are ignored.  The number of arguments is
+	*         variable and may be zero.  The maximum number of arguments is
+	*         limited by the maximum dimension of a Java array as defined by
+	*         <cite>The Java&trade; Virtual Machine Specification</cite>.
+	*         The behaviour on a
+	*         <tt>null</tt> argument depends on the <a
+	*         href="../util/Formatter.html#syntax">conversion</a>.
+	*
+	* @throws  IllegalFormatException
+	*          If a format string contains an illegal syntax, a format
+	*          specifier that is incompatible with the given arguments,
+	*          insufficient arguments given the format string, or other
+	*          illegal conditions.  For specification of all possible
+	*          formatting errors, see the <a
+	*          href="../util/Formatter.html#detail">Details</a> section of the
+	*          formatter class specification.
+	*
+	* @throws  NullPointerException
+	*          If the <tt>format</tt> is <tt>null</tt>
+	*
+	* @return  This writer
+	*
+	* @since  1.5
+	*/
+	@:require(java5) @:overload public function printf(format : String, args : java.NativeArray<Dynamic>) : PrintWriter;
+	
+	/**
+	* A convenience method to write a formatted string to this writer using
+	* the specified format string and arguments.  If automatic flushing is
+	* enabled, calls to this method will flush the output buffer.
+	*
+	* <p> An invocation of this method of the form <tt>out.printf(l, format,
+	* args)</tt> behaves in exactly the same way as the invocation
+	*
+	* <pre>
+	*     out.format(l, format, args) </pre>
+	*
+	* @param  l
+	*         The {@linkplain java.util.Locale locale} to apply during
+	*         formatting.  If <tt>l</tt> is <tt>null</tt> then no localization
+	*         is applied.
+	*
+	* @param  format
+	*         A format string as described in <a
+	*         href="../util/Formatter.html#syntax">Format string syntax</a>.
+	*
+	* @param  args
+	*         Arguments referenced by the format specifiers in the format
+	*         string.  If there are more arguments than format specifiers, the
+	*         extra arguments are ignored.  The number of arguments is
+	*         variable and may be zero.  The maximum number of arguments is
+	*         limited by the maximum dimension of a Java array as defined by
+	*         <cite>The Java&trade; Virtual Machine Specification</cite>.
+	*         The behaviour on a
+	*         <tt>null</tt> argument depends on the <a
+	*         href="../util/Formatter.html#syntax">conversion</a>.
+	*
+	* @throws  IllegalFormatException
+	*          If a format string contains an illegal syntax, a format
+	*          specifier that is incompatible with the given arguments,
+	*          insufficient arguments given the format string, or other
+	*          illegal conditions.  For specification of all possible
+	*          formatting errors, see the <a
+	*          href="../util/Formatter.html#detail">Details</a> section of the
+	*          formatter class specification.
+	*
+	* @throws  NullPointerException
+	*          If the <tt>format</tt> is <tt>null</tt>
+	*
+	* @return  This writer
+	*
+	* @since  1.5
+	*/
+	@:require(java5) @:overload public function printf(l : java.util.Locale, format : String, args : java.NativeArray<Dynamic>) : PrintWriter;
+	
+	/**
+	* Writes a formatted string to this writer using the specified format
+	* string and arguments.  If automatic flushing is enabled, calls to this
+	* method will flush the output buffer.
+	*
+	* <p> The locale always used is the one returned by {@link
+	* java.util.Locale#getDefault() Locale.getDefault()}, regardless of any
+	* previous invocations of other formatting methods on this object.
+	*
+	* @param  format
+	*         A format string as described in <a
+	*         href="../util/Formatter.html#syntax">Format string syntax</a>.
+	*
+	* @param  args
+	*         Arguments referenced by the format specifiers in the format
+	*         string.  If there are more arguments than format specifiers, the
+	*         extra arguments are ignored.  The number of arguments is
+	*         variable and may be zero.  The maximum number of arguments is
+	*         limited by the maximum dimension of a Java array as defined by
+	*         <cite>The Java&trade; Virtual Machine Specification</cite>.
+	*         The behaviour on a
+	*         <tt>null</tt> argument depends on the <a
+	*         href="../util/Formatter.html#syntax">conversion</a>.
+	*
+	* @throws  IllegalFormatException
+	*          If a format string contains an illegal syntax, a format
+	*          specifier that is incompatible with the given arguments,
+	*          insufficient arguments given the format string, or other
+	*          illegal conditions.  For specification of all possible
+	*          formatting errors, see the <a
+	*          href="../util/Formatter.html#detail">Details</a> section of the
+	*          Formatter class specification.
+	*
+	* @throws  NullPointerException
+	*          If the <tt>format</tt> is <tt>null</tt>
+	*
+	* @return  This writer
+	*
+	* @since  1.5
+	*/
+	@:require(java5) @:overload public function format(format : String, args : java.NativeArray<Dynamic>) : PrintWriter;
+	
+	/**
+	* Writes a formatted string to this writer using the specified format
+	* string and arguments.  If automatic flushing is enabled, calls to this
+	* method will flush the output buffer.
+	*
+	* @param  l
+	*         The {@linkplain java.util.Locale locale} to apply during
+	*         formatting.  If <tt>l</tt> is <tt>null</tt> then no localization
+	*         is applied.
+	*
+	* @param  format
+	*         A format string as described in <a
+	*         href="../util/Formatter.html#syntax">Format string syntax</a>.
+	*
+	* @param  args
+	*         Arguments referenced by the format specifiers in the format
+	*         string.  If there are more arguments than format specifiers, the
+	*         extra arguments are ignored.  The number of arguments is
+	*         variable and may be zero.  The maximum number of arguments is
+	*         limited by the maximum dimension of a Java array as defined by
+	*         <cite>The Java&trade; Virtual Machine Specification</cite>.
+	*         The behaviour on a
+	*         <tt>null</tt> argument depends on the <a
+	*         href="../util/Formatter.html#syntax">conversion</a>.
+	*
+	* @throws  IllegalFormatException
+	*          If a format string contains an illegal syntax, a format
+	*          specifier that is incompatible with the given arguments,
+	*          insufficient arguments given the format string, or other
+	*          illegal conditions.  For specification of all possible
+	*          formatting errors, see the <a
+	*          href="../util/Formatter.html#detail">Details</a> section of the
+	*          formatter class specification.
+	*
+	* @throws  NullPointerException
+	*          If the <tt>format</tt> is <tt>null</tt>
+	*
+	* @return  This writer
+	*
+	* @since  1.5
+	*/
+	@:require(java5) @:overload public function format(l : java.util.Locale, format : String, args : java.NativeArray<Dynamic>) : PrintWriter;
+	
+	/**
+	* Appends the specified character sequence to this writer.
+	*
+	* <p> An invocation of this method of the form <tt>out.append(csq)</tt>
+	* behaves in exactly the same way as the invocation
+	*
+	* <pre>
+	*     out.write(csq.toString()) </pre>
+	*
+	* <p> Depending on the specification of <tt>toString</tt> for the
+	* character sequence <tt>csq</tt>, the entire sequence may not be
+	* appended. For instance, invoking the <tt>toString</tt> method of a
+	* character buffer will return a subsequence whose content depends upon
+	* the buffer's position and limit.
+	*
+	* @param  csq
+	*         The character sequence to append.  If <tt>csq</tt> is
+	*         <tt>null</tt>, then the four characters <tt>"null"</tt> are
+	*         appended to this writer.
+	*
+	* @return  This writer
+	*
+	* @since  1.5
+	*/
+	@:require(java5) @:overload override public function append(csq : java.lang.CharSequence) : PrintWriter;
+	
+	/**
+	* Appends a subsequence of the specified character sequence to this writer.
+	*
+	* <p> An invocation of this method of the form <tt>out.append(csq, start,
+	* end)</tt> when <tt>csq</tt> is not <tt>null</tt>, behaves in
+	* exactly the same way as the invocation
+	*
+	* <pre>
+	*     out.write(csq.subSequence(start, end).toString()) </pre>
+	*
+	* @param  csq
+	*         The character sequence from which a subsequence will be
+	*         appended.  If <tt>csq</tt> is <tt>null</tt>, then characters
+	*         will be appended as if <tt>csq</tt> contained the four
+	*         characters <tt>"null"</tt>.
+	*
+	* @param  start
+	*         The index of the first character in the subsequence
+	*
+	* @param  end
+	*         The index of the character following the last character in the
+	*         subsequence
+	*
+	* @return  This writer
+	*
+	* @throws  IndexOutOfBoundsException
+	*          If <tt>start</tt> or <tt>end</tt> are negative, <tt>start</tt>
+	*          is greater than <tt>end</tt>, or <tt>end</tt> is greater than
+	*          <tt>csq.length()</tt>
+	*
+	* @since  1.5
+	*/
+	@:require(java5) @:overload override public function append(csq : java.lang.CharSequence, start : Int, end : Int) : PrintWriter;
+	
+	/**
+	* Appends the specified character to this writer.
+	*
+	* <p> An invocation of this method of the form <tt>out.append(c)</tt>
+	* behaves in exactly the same way as the invocation
+	*
+	* <pre>
+	*     out.write(c) </pre>
+	*
+	* @param  c
+	*         The 16-bit character to append
+	*
+	* @return  This writer
+	*
+	* @since 1.5
+	*/
+	@:require(java5) @:overload override public function append(c : java.StdTypes.Char16) : PrintWriter;
+	
+	
+}

+ 170 - 0
std/java/io/Serializable.hx

@@ -0,0 +1,170 @@
+package java.io;
+/*
+* Copyright (c) 1996, 2005, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* Serializability of a class is enabled by the class implementing the
+* java.io.Serializable interface. Classes that do not implement this
+* interface will not have any of their state serialized or
+* deserialized.  All subtypes of a serializable class are themselves
+* serializable.  The serialization interface has no methods or fields
+* and serves only to identify the semantics of being serializable. <p>
+*
+* To allow subtypes of non-serializable classes to be serialized, the
+* subtype may assume responsibility for saving and restoring the
+* state of the supertype's public, protected, and (if accessible)
+* package fields.  The subtype may assume this responsibility only if
+* the class it extends has an accessible no-arg constructor to
+* initialize the class's state.  It is an error to declare a class
+* Serializable if this is not the case.  The error will be detected at
+* runtime. <p>
+*
+* During deserialization, the fields of non-serializable classes will
+* be initialized using the public or protected no-arg constructor of
+* the class.  A no-arg constructor must be accessible to the subclass
+* that is serializable.  The fields of serializable subclasses will
+* be restored from the stream. <p>
+*
+* When traversing a graph, an object may be encountered that does not
+* support the Serializable interface. In this case the
+* NotSerializableException will be thrown and will identify the class
+* of the non-serializable object. <p>
+*
+* Classes that require special handling during the serialization and
+* deserialization process must implement special methods with these exact
+* signatures: <p>
+*
+* <PRE>
+* private void writeObject(java.io.ObjectOutputStream out)
+*     throws IOException
+* private void readObject(java.io.ObjectInputStream in)
+*     throws IOException, ClassNotFoundException;
+* private void readObjectNoData()
+*     throws ObjectStreamException;
+* </PRE>
+*
+* <p>The writeObject method is responsible for writing the state of the
+* object for its particular class so that the corresponding
+* readObject method can restore it.  The default mechanism for saving
+* the Object's fields can be invoked by calling
+* out.defaultWriteObject. The method does not need to concern
+* itself with the state belonging to its superclasses or subclasses.
+* State is saved by writing the individual fields to the
+* ObjectOutputStream using the writeObject method or by using the
+* methods for primitive data types supported by DataOutput.
+*
+* <p>The readObject method is responsible for reading from the stream and
+* restoring the classes fields. It may call in.defaultReadObject to invoke
+* the default mechanism for restoring the object's non-static and
+* non-transient fields.  The defaultReadObject method uses information in
+* the stream to assign the fields of the object saved in the stream with the
+* correspondingly named fields in the current object.  This handles the case
+* when the class has evolved to add new fields. The method does not need to
+* concern itself with the state belonging to its superclasses or subclasses.
+* State is saved by writing the individual fields to the
+* ObjectOutputStream using the writeObject method or by using the
+* methods for primitive data types supported by DataOutput.
+*
+* <p>The readObjectNoData method is responsible for initializing the state of
+* the object for its particular class in the event that the serialization
+* stream does not list the given class as a superclass of the object being
+* deserialized.  This may occur in cases where the receiving party uses a
+* different version of the deserialized instance's class than the sending
+* party, and the receiver's version extends classes that are not extended by
+* the sender's version.  This may also occur if the serialization stream has
+* been tampered; hence, readObjectNoData is useful for initializing
+* deserialized objects properly despite a "hostile" or incomplete source
+* stream.
+*
+* <p>Serializable classes that need to designate an alternative object to be
+* used when writing an object to the stream should implement this
+* special method with the exact signature: <p>
+*
+* <PRE>
+* ANY-ACCESS-MODIFIER Object writeReplace() throws ObjectStreamException;
+* </PRE><p>
+*
+* This writeReplace method is invoked by serialization if the method
+* exists and it would be accessible from a method defined within the
+* class of the object being serialized. Thus, the method can have private,
+* protected and package-private access. Subclass access to this method
+* follows java accessibility rules. <p>
+*
+* Classes that need to designate a replacement when an instance of it
+* is read from the stream should implement this special method with the
+* exact signature.<p>
+*
+* <PRE>
+* ANY-ACCESS-MODIFIER Object readResolve() throws ObjectStreamException;
+* </PRE><p>
+*
+* This readResolve method follows the same invocation rules and
+* accessibility rules as writeReplace.<p>
+*
+* The serialization runtime associates with each serializable class a version
+* number, called a serialVersionUID, which is used during deserialization to
+* verify that the sender and receiver of a serialized object have loaded
+* classes for that object that are compatible with respect to serialization.
+* If the receiver has loaded a class for the object that has a different
+* serialVersionUID than that of the corresponding sender's class, then
+* deserialization will result in an {@link InvalidClassException}.  A
+* serializable class can declare its own serialVersionUID explicitly by
+* declaring a field named <code>"serialVersionUID"</code> that must be static,
+* final, and of type <code>long</code>:<p>
+*
+* <PRE>
+* ANY-ACCESS-MODIFIER static final long serialVersionUID = 42L;
+* </PRE>
+*
+* If a serializable class does not explicitly declare a serialVersionUID, then
+* the serialization runtime will calculate a default serialVersionUID value
+* for that class based on various aspects of the class, as described in the
+* Java(TM) Object Serialization Specification.  However, it is <em>strongly
+* recommended</em> that all serializable classes explicitly declare
+* serialVersionUID values, since the default serialVersionUID computation is
+* highly sensitive to class details that may vary depending on compiler
+* implementations, and can thus result in unexpected
+* <code>InvalidClassException</code>s during deserialization.  Therefore, to
+* guarantee a consistent serialVersionUID value across different java compiler
+* implementations, a serializable class must declare an explicit
+* serialVersionUID value.  It is also strongly advised that explicit
+* serialVersionUID declarations use the <code>private</code> modifier where
+* possible, since such declarations apply only to the immediately declaring
+* class--serialVersionUID fields are not useful as inherited members. Array
+* classes cannot declare an explicit serialVersionUID, so they always have
+* the default computed value, but the requirement for matching
+* serialVersionUID values is waived for array classes.
+*
+* @author  unascribed
+* @see java.io.ObjectOutputStream
+* @see java.io.ObjectInputStream
+* @see java.io.ObjectOutput
+* @see java.io.ObjectInput
+* @see java.io.Externalizable
+* @since   JDK1.1
+*/
+extern interface Serializable
+{
+	
+}

+ 266 - 0
std/java/io/Writer.hx

@@ -0,0 +1,266 @@
+package java.io;
+/*
+* Copyright (c) 1996, 2005, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* Abstract class for writing to character streams.  The only methods that a
+* subclass must implement are write(char[], int, int), flush(), and close().
+* Most subclasses, however, will override some of the methods defined here in
+* order to provide higher efficiency, additional functionality, or both.
+*
+* @see Writer
+* @see   BufferedWriter
+* @see   CharArrayWriter
+* @see   FilterWriter
+* @see   OutputStreamWriter
+* @see     FileWriter
+* @see   PipedWriter
+* @see   PrintWriter
+* @see   StringWriter
+* @see Reader
+*
+* @author      Mark Reinhold
+* @since       JDK1.1
+*/
+@:require(java1) extern class Writer implements java.lang.Appendable implements java.io.Closeable implements java.io.Flushable
+{
+	/**
+	* The object used to synchronize operations on this stream.  For
+	* efficiency, a character-stream object may use an object other than
+	* itself to protect critical sections.  A subclass should therefore use
+	* the object in this field rather than <tt>this</tt> or a synchronized
+	* method.
+	*/
+	private var lock : Dynamic;
+	
+	/**
+	* Creates a new character-stream writer whose critical sections will
+	* synchronize on the writer itself.
+	*/
+	@:overload private function new() : Void;
+	
+	/**
+	* Creates a new character-stream writer whose critical sections will
+	* synchronize on the given object.
+	*
+	* @param  lock
+	*         Object to synchronize on
+	*/
+	@:overload private function new(lock : Dynamic) : Void;
+	
+	/**
+	* Writes a single character.  The character to be written is contained in
+	* the 16 low-order bits of the given integer value; the 16 high-order bits
+	* are ignored.
+	*
+	* <p> Subclasses that intend to support efficient single-character output
+	* should override this method.
+	*
+	* @param  c
+	*         int specifying a character to be written
+	*
+	* @throws  IOException
+	*          If an I/O error occurs
+	*/
+	@:overload public function write(c : Int) : Void;
+	
+	/**
+	* Writes an array of characters.
+	*
+	* @param  cbuf
+	*         Array of characters to be written
+	*
+	* @throws  IOException
+	*          If an I/O error occurs
+	*/
+	@:overload public function write(cbuf : java.NativeArray<java.StdTypes.Char16>) : Void;
+	
+	/**
+	* Writes a portion of an array of characters.
+	*
+	* @param  cbuf
+	*         Array of characters
+	*
+	* @param  off
+	*         Offset from which to start writing characters
+	*
+	* @param  len
+	*         Number of characters to write
+	*
+	* @throws  IOException
+	*          If an I/O error occurs
+	*/
+	@:overload @:abstract public function write(cbuf : java.NativeArray<java.StdTypes.Char16>, off : Int, len : Int) : Void;
+	
+	/**
+	* Writes a string.
+	*
+	* @param  str
+	*         String to be written
+	*
+	* @throws  IOException
+	*          If an I/O error occurs
+	*/
+	@:overload public function write(str : String) : Void;
+	
+	/**
+	* Writes a portion of a string.
+	*
+	* @param  str
+	*         A String
+	*
+	* @param  off
+	*         Offset from which to start writing characters
+	*
+	* @param  len
+	*         Number of characters to write
+	*
+	* @throws  IndexOutOfBoundsException
+	*          If <tt>off</tt> is negative, or <tt>len</tt> is negative,
+	*          or <tt>off+len</tt> is negative or greater than the length
+	*          of the given string
+	*
+	* @throws  IOException
+	*          If an I/O error occurs
+	*/
+	@:overload public function write(str : String, off : Int, len : Int) : Void;
+	
+	/**
+	* Appends the specified character sequence to this writer.
+	*
+	* <p> An invocation of this method of the form <tt>out.append(csq)</tt>
+	* behaves in exactly the same way as the invocation
+	*
+	* <pre>
+	*     out.write(csq.toString()) </pre>
+	*
+	* <p> Depending on the specification of <tt>toString</tt> for the
+	* character sequence <tt>csq</tt>, the entire sequence may not be
+	* appended. For instance, invoking the <tt>toString</tt> method of a
+	* character buffer will return a subsequence whose content depends upon
+	* the buffer's position and limit.
+	*
+	* @param  csq
+	*         The character sequence to append.  If <tt>csq</tt> is
+	*         <tt>null</tt>, then the four characters <tt>"null"</tt> are
+	*         appended to this writer.
+	*
+	* @return  This writer
+	*
+	* @throws  IOException
+	*          If an I/O error occurs
+	*
+	* @since  1.5
+	*/
+	@:require(java5) @:overload public function append(csq : java.lang.CharSequence) : Writer;
+	
+	/**
+	* Appends a subsequence of the specified character sequence to this writer.
+	* <tt>Appendable</tt>.
+	*
+	* <p> An invocation of this method of the form <tt>out.append(csq, start,
+	* end)</tt> when <tt>csq</tt> is not <tt>null</tt> behaves in exactly the
+	* same way as the invocation
+	*
+	* <pre>
+	*     out.write(csq.subSequence(start, end).toString()) </pre>
+	*
+	* @param  csq
+	*         The character sequence from which a subsequence will be
+	*         appended.  If <tt>csq</tt> is <tt>null</tt>, then characters
+	*         will be appended as if <tt>csq</tt> contained the four
+	*         characters <tt>"null"</tt>.
+	*
+	* @param  start
+	*         The index of the first character in the subsequence
+	*
+	* @param  end
+	*         The index of the character following the last character in the
+	*         subsequence
+	*
+	* @return  This writer
+	*
+	* @throws  IndexOutOfBoundsException
+	*          If <tt>start</tt> or <tt>end</tt> are negative, <tt>start</tt>
+	*          is greater than <tt>end</tt>, or <tt>end</tt> is greater than
+	*          <tt>csq.length()</tt>
+	*
+	* @throws  IOException
+	*          If an I/O error occurs
+	*
+	* @since  1.5
+	*/
+	@:require(java5) @:overload public function append(csq : java.lang.CharSequence, start : Int, end : Int) : Writer;
+	
+	/**
+	* Appends the specified character to this writer.
+	*
+	* <p> An invocation of this method of the form <tt>out.append(c)</tt>
+	* behaves in exactly the same way as the invocation
+	*
+	* <pre>
+	*     out.write(c) </pre>
+	*
+	* @param  c
+	*         The 16-bit character to append
+	*
+	* @return  This writer
+	*
+	* @throws  IOException
+	*          If an I/O error occurs
+	*
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public function append(c : java.StdTypes.Char16) : Writer;
+	
+	/**
+	* Flushes the stream.  If the stream has saved any characters from the
+	* various write() methods in a buffer, write them immediately to their
+	* intended destination.  Then, if that destination is another character or
+	* byte stream, flush it.  Thus one flush() invocation will flush all the
+	* buffers in a chain of Writers and OutputStreams.
+	*
+	* <p> If the intended destination of this stream is an abstraction provided
+	* by the underlying operating system, for example a file, then flushing the
+	* stream guarantees only that bytes previously written to the stream are
+	* passed to the operating system for writing; it does not guarantee that
+	* they are actually written to a physical device such as a disk drive.
+	*
+	* @throws  IOException
+	*          If an I/O error occurs
+	*/
+	@:overload @:abstract public function flush() : Void;
+	
+	/**
+	* Closes the stream, flushing it first. Once the stream has been closed,
+	* further write() or flush() invocations will cause an IOException to be
+	* thrown. Closing a previously closed stream has no effect.
+	*
+	* @throws  IOException
+	*          If an I/O error occurs
+	*/
+	@:overload @:abstract public function close() : Void;
+	
+	
+}

+ 119 - 0
std/java/lang/Appendable.hx

@@ -0,0 +1,119 @@
+package java.lang;
+/*
+* Copyright (c) 2003, 2004, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* An object to which <tt>char</tt> sequences and values can be appended.  The
+* <tt>Appendable</tt> interface must be implemented by any class whose
+* instances are intended to receive formatted output from a {@link
+* java.util.Formatter}.
+*
+* <p> The characters to be appended should be valid Unicode characters as
+* described in <a href="Character.html#unicode">Unicode Character
+* Representation</a>.  Note that supplementary characters may be composed of
+* multiple 16-bit <tt>char</tt> values.
+*
+* <p> Appendables are not necessarily safe for multithreaded access.  Thread
+* safety is the responsibility of classes that extend and implement this
+* interface.
+*
+* <p> Since this interface may be implemented by existing classes
+* with different styles of error handling there is no guarantee that
+* errors will be propagated to the invoker.
+*
+* @since 1.5
+*/
+@:require(java5) extern interface Appendable
+{
+	/**
+	* Appends the specified character sequence to this <tt>Appendable</tt>.
+	*
+	* <p> Depending on which class implements the character sequence
+	* <tt>csq</tt>, the entire sequence may not be appended.  For
+	* instance, if <tt>csq</tt> is a {@link java.nio.CharBuffer} then
+	* the subsequence to append is defined by the buffer's position and limit.
+	*
+	* @param  csq
+	*         The character sequence to append.  If <tt>csq</tt> is
+	*         <tt>null</tt>, then the four characters <tt>"null"</tt> are
+	*         appended to this Appendable.
+	*
+	* @return  A reference to this <tt>Appendable</tt>
+	*
+	* @throws  IOException
+	*          If an I/O error occurs
+	*/
+	@:overload public function append(csq : java.lang.CharSequence) : Appendable;
+	
+	/**
+	* Appends a subsequence of the specified character sequence to this
+	* <tt>Appendable</tt>.
+	*
+	* <p> An invocation of this method of the form <tt>out.append(csq, start,
+	* end)</tt> when <tt>csq</tt> is not <tt>null</tt>, behaves in
+	* exactly the same way as the invocation
+	*
+	* <pre>
+	*     out.append(csq.subSequence(start, end)) </pre>
+	*
+	* @param  csq
+	*         The character sequence from which a subsequence will be
+	*         appended.  If <tt>csq</tt> is <tt>null</tt>, then characters
+	*         will be appended as if <tt>csq</tt> contained the four
+	*         characters <tt>"null"</tt>.
+	*
+	* @param  start
+	*         The index of the first character in the subsequence
+	*
+	* @param  end
+	*         The index of the character following the last character in the
+	*         subsequence
+	*
+	* @return  A reference to this <tt>Appendable</tt>
+	*
+	* @throws  IndexOutOfBoundsException
+	*          If <tt>start</tt> or <tt>end</tt> are negative, <tt>start</tt>
+	*          is greater than <tt>end</tt>, or <tt>end</tt> is greater than
+	*          <tt>csq.length()</tt>
+	*
+	* @throws  IOException
+	*          If an I/O error occurs
+	*/
+	@:overload public function append(csq : java.lang.CharSequence, start : Int, end : Int) : Appendable;
+	
+	/**
+	* Appends the specified character to this <tt>Appendable</tt>.
+	*
+	* @param  c
+	*         The character to append
+	*
+	* @return  A reference to this <tt>Appendable</tt>
+	*
+	* @throws  IOException
+	*          If an I/O error occurs
+	*/
+	@:overload public function append(c : java.StdTypes.Char16) : Appendable;
+	
+	
+}

+ 73 - 0
std/java/lang/AutoCloseable.hx

@@ -0,0 +1,73 @@
+package java.lang;
+/*
+* Copyright (c) 2009, 2011, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* A resource that must be closed when it is no longer needed.
+*
+* @author Josh Bloch
+* @since 1.7
+*/
+@:require(java7) extern interface AutoCloseable
+{
+	/**
+	* Closes this resource, relinquishing any underlying resources.
+	* This method is invoked automatically on objects managed by the
+	* {@code try}-with-resources statement.
+	*
+	* <p>While this interface method is declared to throw {@code
+	* Exception}, implementers are <em>strongly</em> encouraged to
+	* declare concrete implementations of the {@code close} method to
+	* throw more specific exceptions, or to throw no exception at all
+	* if the close operation cannot fail.
+	*
+	* <p><em>Implementers of this interface are also strongly advised
+	* to not have the {@code close} method throw {@link
+	* InterruptedException}.</em>
+	*
+	* This exception interacts with a thread's interrupted status,
+	* and runtime misbehavior is likely to occur if an {@code
+	* InterruptedException} is {@linkplain Throwable#addSuppressed
+	* suppressed}.
+	*
+	* More generally, if it would cause problems for an
+	* exception to be suppressed, the {@code AutoCloseable.close}
+	* method should not throw it.
+	*
+	* <p>Note that unlike the {@link java.io.Closeable#close close}
+	* method of {@link java.io.Closeable}, this {@code close} method
+	* is <em>not</em> required to be idempotent.  In other words,
+	* calling this {@code close} method more than once may have some
+	* visible side effect, unlike {@code Closeable.close} which is
+	* required to have no effect if called more than once.
+	*
+	* However, implementers of this interface are strongly encouraged
+	* to make their {@code close} methods idempotent.
+	*
+	* @throws Exception if this resource cannot be closed
+	*/
+	@:overload public function close() : Void;
+	
+	
+}

+ 377 - 0
std/java/lang/Byte.hx

@@ -0,0 +1,377 @@
+package java.lang;
+/*
+* Copyright (c) 1996, 2009, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+*
+* The {@code Byte} class wraps a value of primitive type {@code byte}
+* in an object.  An object of type {@code Byte} contains a single
+* field whose type is {@code byte}.
+*
+* <p>In addition, this class provides several methods for converting
+* a {@code byte} to a {@code String} and a {@code String} to a {@code
+* byte}, as well as other constants and methods useful when dealing
+* with a {@code byte}.
+*
+* @author  Nakul Saraiya
+* @author  Joseph D. Darcy
+* @see     java.lang.Number
+* @since   JDK1.1
+*/
+@:require(java1) extern class Byte extends java.lang.Number implements java.lang.Comparable<Byte>
+{
+	/**
+	* A constant holding the minimum value a {@code byte} can
+	* have, -2<sup>7</sup>.
+	*/
+	public static var MIN_VALUE(default, null) : java.StdTypes.Int8;
+	
+	/**
+	* A constant holding the maximum value a {@code byte} can
+	* have, 2<sup>7</sup>-1.
+	*/
+	public static var MAX_VALUE(default, null) : java.StdTypes.Int8;
+	
+	/**
+	* The {@code Class} instance representing the primitive type
+	* {@code byte}.
+	*/
+	public static var TYPE(default, null) : Class<Byte>;
+	
+	/**
+	* Returns a new {@code String} object representing the
+	* specified {@code byte}. The radix is assumed to be 10.
+	*
+	* @param b the {@code byte} to be converted
+	* @return the string representation of the specified {@code byte}
+	* @see java.lang.Integer#toString(int)
+	*/
+	@:native('toString') @:overload public static function _toString(b : java.StdTypes.Int8) : String;
+	
+	/**
+	* Returns a {@code Byte} instance representing the specified
+	* {@code byte} value.
+	* If a new {@code Byte} instance is not required, this method
+	* should generally be used in preference to the constructor
+	* {@link #Byte(byte)}, as this method is likely to yield
+	* significantly better space and time performance since
+	* all byte values are cached.
+	*
+	* @param  b a byte value.
+	* @return a {@code Byte} instance representing {@code b}.
+	* @since  1.5
+	*/
+	@:require(java5) @:overload public static function valueOf(b : java.StdTypes.Int8) : Byte;
+	
+	/**
+	* Parses the string argument as a signed {@code byte} in the
+	* radix specified by the second argument. The characters in the
+	* string must all be digits, of the specified radix (as
+	* determined by whether {@link java.lang.Character#digit(char,
+	* int)} returns a nonnegative value) except that the first
+	* character may be an ASCII minus sign {@code '-'}
+	* (<code>'&#92;u002D'</code>) to indicate a negative value or an
+	* ASCII plus sign {@code '+'} (<code>'&#92;u002B'</code>) to
+	* indicate a positive value.  The resulting {@code byte} value is
+	* returned.
+	*
+	* <p>An exception of type {@code NumberFormatException} is
+	* thrown if any of the following situations occurs:
+	* <ul>
+	* <li> The first argument is {@code null} or is a string of
+	* length zero.
+	*
+	* <li> The radix is either smaller than {@link
+	* java.lang.Character#MIN_RADIX} or larger than {@link
+	* java.lang.Character#MAX_RADIX}.
+	*
+	* <li> Any character of the string is not a digit of the
+	* specified radix, except that the first character may be a minus
+	* sign {@code '-'} (<code>'&#92;u002D'</code>) or plus sign
+	* {@code '+'} (<code>'&#92;u002B'</code>) provided that the
+	* string is longer than length 1.
+	*
+	* <li> The value represented by the string is not a value of type
+	* {@code byte}.
+	* </ul>
+	*
+	* @param s         the {@code String} containing the
+	*                  {@code byte}
+	*                  representation to be parsed
+	* @param radix     the radix to be used while parsing {@code s}
+	* @return          the {@code byte} value represented by the string
+	*                   argument in the specified radix
+	* @throws          NumberFormatException If the string does
+	*                  not contain a parsable {@code byte}.
+	*/
+	@:overload public static function parseByte(s : String, radix : Int) : java.StdTypes.Int8;
+	
+	/**
+	* Parses the string argument as a signed decimal {@code
+	* byte}. The characters in the string must all be decimal digits,
+	* except that the first character may be an ASCII minus sign
+	* {@code '-'} (<code>'&#92;u002D'</code>) to indicate a negative
+	* value or an ASCII plus sign {@code '+'}
+	* (<code>'&#92;u002B'</code>) to indicate a positive value. The
+	* resulting {@code byte} value is returned, exactly as if the
+	* argument and the radix 10 were given as arguments to the {@link
+	* #parseByte(java.lang.String, int)} method.
+	*
+	* @param s         a {@code String} containing the
+	*                  {@code byte} representation to be parsed
+	* @return          the {@code byte} value represented by the
+	*                  argument in decimal
+	* @throws          NumberFormatException if the string does not
+	*                  contain a parsable {@code byte}.
+	*/
+	@:overload public static function parseByte(s : String) : java.StdTypes.Int8;
+	
+	/**
+	* Returns a {@code Byte} object holding the value
+	* extracted from the specified {@code String} when parsed
+	* with the radix given by the second argument. The first argument
+	* is interpreted as representing a signed {@code byte} in
+	* the radix specified by the second argument, exactly as if the
+	* argument were given to the {@link #parseByte(java.lang.String,
+	* int)} method. The result is a {@code Byte} object that
+	* represents the {@code byte} value specified by the string.
+	*
+	* <p> In other words, this method returns a {@code Byte} object
+	* equal to the value of:
+	*
+	* <blockquote>
+	* {@code new Byte(Byte.parseByte(s, radix))}
+	* </blockquote>
+	*
+	* @param s         the string to be parsed
+	* @param radix     the radix to be used in interpreting {@code s}
+	* @return          a {@code Byte} object holding the value
+	*                  represented by the string argument in the
+	*                  specified radix.
+	* @throws          NumberFormatException If the {@code String} does
+	*                  not contain a parsable {@code byte}.
+	*/
+	@:overload public static function valueOf(s : String, radix : Int) : Byte;
+	
+	/**
+	* Returns a {@code Byte} object holding the value
+	* given by the specified {@code String}. The argument is
+	* interpreted as representing a signed decimal {@code byte},
+	* exactly as if the argument were given to the {@link
+	* #parseByte(java.lang.String)} method. The result is a
+	* {@code Byte} object that represents the {@code byte}
+	* value specified by the string.
+	*
+	* <p> In other words, this method returns a {@code Byte} object
+	* equal to the value of:
+	*
+	* <blockquote>
+	* {@code new Byte(Byte.parseByte(s))}
+	* </blockquote>
+	*
+	* @param s         the string to be parsed
+	* @return          a {@code Byte} object holding the value
+	*                  represented by the string argument
+	* @throws          NumberFormatException If the {@code String} does
+	*                  not contain a parsable {@code byte}.
+	*/
+	@:overload public static function valueOf(s : String) : Byte;
+	
+	/**
+	* Decodes a {@code String} into a {@code Byte}.
+	* Accepts decimal, hexadecimal, and octal numbers given by
+	* the following grammar:
+	*
+	* <blockquote>
+	* <dl>
+	* <dt><i>DecodableString:</i>
+	* <dd><i>Sign<sub>opt</sub> DecimalNumeral</i>
+	* <dd><i>Sign<sub>opt</sub></i> {@code 0x} <i>HexDigits</i>
+	* <dd><i>Sign<sub>opt</sub></i> {@code 0X} <i>HexDigits</i>
+	* <dd><i>Sign<sub>opt</sub></i> {@code #} <i>HexDigits</i>
+	* <dd><i>Sign<sub>opt</sub></i> {@code 0} <i>OctalDigits</i>
+	* <p>
+	* <dt><i>Sign:</i>
+	* <dd>{@code -}
+	* <dd>{@code +}
+	* </dl>
+	* </blockquote>
+	*
+	* <i>DecimalNumeral</i>, <i>HexDigits</i>, and <i>OctalDigits</i>
+	* are as defined in section 3.10.1 of
+	* <cite>The Java&trade; Language Specification</cite>,
+	* except that underscores are not accepted between digits.
+	*
+	* <p>The sequence of characters following an optional
+	* sign and/or radix specifier ("{@code 0x}", "{@code 0X}",
+	* "{@code #}", or leading zero) is parsed as by the {@code
+	* Byte.parseByte} method with the indicated radix (10, 16, or 8).
+	* This sequence of characters must represent a positive value or
+	* a {@link NumberFormatException} will be thrown.  The result is
+	* negated if first character of the specified {@code String} is
+	* the minus sign.  No whitespace characters are permitted in the
+	* {@code String}.
+	*
+	* @param     nm the {@code String} to decode.
+	* @return   a {@code Byte} object holding the {@code byte}
+	*          value represented by {@code nm}
+	* @throws  NumberFormatException  if the {@code String} does not
+	*            contain a parsable {@code byte}.
+	* @see java.lang.Byte#parseByte(java.lang.String, int)
+	*/
+	@:overload public static function decode(nm : String) : Byte;
+	
+	/**
+	* Constructs a newly allocated {@code Byte} object that
+	* represents the specified {@code byte} value.
+	*
+	* @param value     the value to be represented by the
+	*                  {@code Byte}.
+	*/
+	@:overload public function new(value : java.StdTypes.Int8) : Void;
+	
+	/**
+	* Constructs a newly allocated {@code Byte} object that
+	* represents the {@code byte} value indicated by the
+	* {@code String} parameter. The string is converted to a
+	* {@code byte} value in exactly the manner used by the
+	* {@code parseByte} method for radix 10.
+	*
+	* @param s         the {@code String} to be converted to a
+	*                  {@code Byte}
+	* @throws           NumberFormatException If the {@code String}
+	*                  does not contain a parsable {@code byte}.
+	* @see        java.lang.Byte#parseByte(java.lang.String, int)
+	*/
+	@:overload public function new(s : String) : Void;
+	
+	/**
+	* Returns the value of this {@code Byte} as a
+	* {@code byte}.
+	*/
+	@:overload override public function byteValue() : java.StdTypes.Int8;
+	
+	/**
+	* Returns the value of this {@code Byte} as a
+	* {@code short}.
+	*/
+	@:overload override public function shortValue() : java.StdTypes.Int16;
+	
+	/**
+	* Returns the value of this {@code Byte} as an
+	* {@code int}.
+	*/
+	@:overload override public function intValue() : Int;
+	
+	/**
+	* Returns the value of this {@code Byte} as a
+	* {@code long}.
+	*/
+	@:overload override public function longValue() : haxe.Int64;
+	
+	/**
+	* Returns the value of this {@code Byte} as a
+	* {@code float}.
+	*/
+	@:overload override public function floatValue() : Single;
+	
+	/**
+	* Returns the value of this {@code Byte} as a
+	* {@code double}.
+	*/
+	@:overload override public function doubleValue() : Float;
+	
+	/**
+	* Returns a {@code String} object representing this
+	* {@code Byte}'s value.  The value is converted to signed
+	* decimal representation and returned as a string, exactly as if
+	* the {@code byte} value were given as an argument to the
+	* {@link java.lang.Byte#toString(byte)} method.
+	*
+	* @return  a string representation of the value of this object in
+	*          base&nbsp;10.
+	*/
+	@:overload public function toString() : String;
+	
+	/**
+	* Returns a hash code for this {@code Byte}; equal to the result
+	* of invoking {@code intValue()}.
+	*
+	* @return a hash code value for this {@code Byte}
+	*/
+	@:overload public function hashCode() : Int;
+	
+	/**
+	* Compares this object to the specified object.  The result is
+	* {@code true} if and only if the argument is not
+	* {@code null} and is a {@code Byte} object that
+	* contains the same {@code byte} value as this object.
+	*
+	* @param obj       the object to compare with
+	* @return          {@code true} if the objects are the same;
+	*                  {@code false} otherwise.
+	*/
+	@:overload public function equals(obj : Dynamic) : Bool;
+	
+	/**
+	* Compares two {@code Byte} objects numerically.
+	*
+	* @param   anotherByte   the {@code Byte} to be compared.
+	* @return  the value {@code 0} if this {@code Byte} is
+	*          equal to the argument {@code Byte}; a value less than
+	*          {@code 0} if this {@code Byte} is numerically less
+	*          than the argument {@code Byte}; and a value greater than
+	*           {@code 0} if this {@code Byte} is numerically
+	*           greater than the argument {@code Byte} (signed
+	*           comparison).
+	* @since   1.2
+	*/
+	@:require(java2) @:overload public function compareTo(anotherByte : Byte) : Int;
+	
+	/**
+	* Compares two {@code byte} values numerically.
+	* The value returned is identical to what would be returned by:
+	* <pre>
+	*    Byte.valueOf(x).compareTo(Byte.valueOf(y))
+	* </pre>
+	*
+	* @param  x the first {@code byte} to compare
+	* @param  y the second {@code byte} to compare
+	* @return the value {@code 0} if {@code x == y};
+	*         a value less than {@code 0} if {@code x < y}; and
+	*         a value greater than {@code 0} if {@code x > y}
+	* @since 1.7
+	*/
+	@:require(java7) @:overload public static function compare(x : java.StdTypes.Int8, y : java.StdTypes.Int8) : Int;
+	
+	/**
+	* The number of bits used to represent a {@code byte} value in two's
+	* complement binary form.
+	*
+	* @since 1.5
+	*/
+	@:require(java5) public static var SIZE(default, null) : Int;
+	
+	
+}

+ 108 - 0
std/java/lang/CharSequence.hx

@@ -0,0 +1,108 @@
+package java.lang;
+/*
+* Copyright (c) 2000, 2003, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* A <tt>CharSequence</tt> is a readable sequence of <code>char</code> values. This
+* interface provides uniform, read-only access to many different kinds of
+* <code>char</code> sequences.
+* A <code>char</code> value represents a character in the <i>Basic
+* Multilingual Plane (BMP)</i> or a surrogate. Refer to <a
+* href="Character.html#unicode">Unicode Character Representation</a> for details.
+*
+* <p> This interface does not refine the general contracts of the {@link
+* java.lang.Object#equals(java.lang.Object) equals} and {@link
+* java.lang.Object#hashCode() hashCode} methods.  The result of comparing two
+* objects that implement <tt>CharSequence</tt> is therefore, in general,
+* undefined.  Each object may be implemented by a different class, and there
+* is no guarantee that each class will be capable of testing its instances
+* for equality with those of the other.  It is therefore inappropriate to use
+* arbitrary <tt>CharSequence</tt> instances as elements in a set or as keys in
+* a map. </p>
+*
+* @author Mike McCloskey
+* @since 1.4
+* @spec JSR-51
+*/
+@:require(java4) extern interface CharSequence
+{
+	/**
+	* Returns the length of this character sequence.  The length is the number
+	* of 16-bit <code>char</code>s in the sequence.</p>
+	*
+	* @return  the number of <code>char</code>s in this sequence
+	*/
+	@:overload public function length() : Int;
+	
+	/**
+	* Returns the <code>char</code> value at the specified index.  An index ranges from zero
+	* to <tt>length() - 1</tt>.  The first <code>char</code> value of the sequence is at
+	* index zero, the next at index one, and so on, as for array
+	* indexing. </p>
+	*
+	* <p>If the <code>char</code> value specified by the index is a
+	* <a href="{@docRoot}/java/lang/Character.html#unicode">surrogate</a>, the surrogate
+	* value is returned.
+	*
+	* @param   index   the index of the <code>char</code> value to be returned
+	*
+	* @return  the specified <code>char</code> value
+	*
+	* @throws  IndexOutOfBoundsException
+	*          if the <tt>index</tt> argument is negative or not less than
+	*          <tt>length()</tt>
+	*/
+	@:overload public function charAt(index : Int) : java.StdTypes.Char16;
+	
+	/**
+	* Returns a new <code>CharSequence</code> that is a subsequence of this sequence.
+	* The subsequence starts with the <code>char</code> value at the specified index and
+	* ends with the <code>char</code> value at index <tt>end - 1</tt>.  The length
+	* (in <code>char</code>s) of the
+	* returned sequence is <tt>end - start</tt>, so if <tt>start == end</tt>
+	* then an empty sequence is returned. </p>
+	*
+	* @param   start   the start index, inclusive
+	* @param   end     the end index, exclusive
+	*
+	* @return  the specified subsequence
+	*
+	* @throws  IndexOutOfBoundsException
+	*          if <tt>start</tt> or <tt>end</tt> are negative,
+	*          if <tt>end</tt> is greater than <tt>length()</tt>,
+	*          or if <tt>start</tt> is greater than <tt>end</tt>
+	*/
+	@:overload public function subSequence(start : Int, end : Int) : CharSequence;
+	
+	/**
+	* Returns a string containing the characters in this sequence in the same
+	* order as this sequence.  The length of the string will be the length of
+	* this sequence. </p>
+	*
+	* @return  a string consisting of exactly this sequence of characters
+	*/
+	@:overload public function toString() : String;
+	
+	
+}

+ 54 - 0
std/java/lang/Cloneable.hx

@@ -0,0 +1,54 @@
+package java.lang;
+/*
+* Copyright (c) 1995, 2004, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* A class implements the <code>Cloneable</code> interface to
+* indicate to the {@link java.lang.Object#clone()} method that it
+* is legal for that method to make a
+* field-for-field copy of instances of that class.
+* <p>
+* Invoking Object's clone method on an instance that does not implement the
+* <code>Cloneable</code> interface results in the exception
+* <code>CloneNotSupportedException</code> being thrown.
+* <p>
+* By convention, classes that implement this interface should override
+* <tt>Object.clone</tt> (which is protected) with a public method.
+* See {@link java.lang.Object#clone()} for details on overriding this
+* method.
+* <p>
+* Note that this interface does <i>not</i> contain the <tt>clone</tt> method.
+* Therefore, it is not possible to clone an object merely by virtue of the
+* fact that it implements this interface.  Even if the clone method is invoked
+* reflectively, there is no guarantee that it will succeed.
+*
+* @author  unascribed
+* @see     java.lang.CloneNotSupportedException
+* @see     java.lang.Object#clone()
+* @since   JDK1.0
+*/
+@:require(java0) extern interface Cloneable
+{
+	
+}

+ 137 - 0
std/java/lang/Comparable.hx

@@ -0,0 +1,137 @@
+package java.lang;
+/*
+* Copyright (c) 1997, 2007, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* This interface imposes a total ordering on the objects of each class that
+* implements it.  This ordering is referred to as the class's <i>natural
+* ordering</i>, and the class's <tt>compareTo</tt> method is referred to as
+* its <i>natural comparison method</i>.<p>
+*
+* Lists (and arrays) of objects that implement this interface can be sorted
+* automatically by {@link Collections#sort(List) Collections.sort} (and
+* {@link Arrays#sort(Object[]) Arrays.sort}).  Objects that implement this
+* interface can be used as keys in a {@linkplain SortedMap sorted map} or as
+* elements in a {@linkplain SortedSet sorted set}, without the need to
+* specify a {@linkplain Comparator comparator}.<p>
+*
+* The natural ordering for a class <tt>C</tt> is said to be <i>consistent
+* with equals</i> if and only if <tt>e1.compareTo(e2) == 0</tt> has
+* the same boolean value as <tt>e1.equals(e2)</tt> for every
+* <tt>e1</tt> and <tt>e2</tt> of class <tt>C</tt>.  Note that <tt>null</tt>
+* is not an instance of any class, and <tt>e.compareTo(null)</tt> should
+* throw a <tt>NullPointerException</tt> even though <tt>e.equals(null)</tt>
+* returns <tt>false</tt>.<p>
+*
+* It is strongly recommended (though not required) that natural orderings be
+* consistent with equals.  This is so because sorted sets (and sorted maps)
+* without explicit comparators behave "strangely" when they are used with
+* elements (or keys) whose natural ordering is inconsistent with equals.  In
+* particular, such a sorted set (or sorted map) violates the general contract
+* for set (or map), which is defined in terms of the <tt>equals</tt>
+* method.<p>
+*
+* For example, if one adds two keys <tt>a</tt> and <tt>b</tt> such that
+* <tt>(!a.equals(b) && a.compareTo(b) == 0)</tt> to a sorted
+* set that does not use an explicit comparator, the second <tt>add</tt>
+* operation returns false (and the size of the sorted set does not increase)
+* because <tt>a</tt> and <tt>b</tt> are equivalent from the sorted set's
+* perspective.<p>
+*
+* Virtually all Java core classes that implement <tt>Comparable</tt> have natural
+* orderings that are consistent with equals.  One exception is
+* <tt>java.math.BigDecimal</tt>, whose natural ordering equates
+* <tt>BigDecimal</tt> objects with equal values and different precisions
+* (such as 4.0 and 4.00).<p>
+*
+* For the mathematically inclined, the <i>relation</i> that defines
+* the natural ordering on a given class C is:<pre>
+*       {(x, y) such that x.compareTo(y) &lt;= 0}.
+* </pre> The <i>quotient</i> for this total order is: <pre>
+*       {(x, y) such that x.compareTo(y) == 0}.
+* </pre>
+*
+* It follows immediately from the contract for <tt>compareTo</tt> that the
+* quotient is an <i>equivalence relation</i> on <tt>C</tt>, and that the
+* natural ordering is a <i>total order</i> on <tt>C</tt>.  When we say that a
+* class's natural ordering is <i>consistent with equals</i>, we mean that the
+* quotient for the natural ordering is the equivalence relation defined by
+* the class's {@link Object#equals(Object) equals(Object)} method:<pre>
+*     {(x, y) such that x.equals(y)}. </pre><p>
+*
+* This interface is a member of the
+* <a href="{@docRoot}/../technotes/guides/collections/index.html">
+* Java Collections Framework</a>.
+*
+* @param <T> the type of objects that this object may be compared to
+*
+* @author  Josh Bloch
+* @see java.util.Comparator
+* @since 1.2
+*/
+@:require(java2) extern interface Comparable<T>
+{
+	/**
+	* Compares this object with the specified object for order.  Returns a
+	* negative integer, zero, or a positive integer as this object is less
+	* than, equal to, or greater than the specified object.
+	*
+	* <p>The implementor must ensure <tt>sgn(x.compareTo(y)) ==
+	* -sgn(y.compareTo(x))</tt> for all <tt>x</tt> and <tt>y</tt>.  (This
+	* implies that <tt>x.compareTo(y)</tt> must throw an exception iff
+	* <tt>y.compareTo(x)</tt> throws an exception.)
+	*
+	* <p>The implementor must also ensure that the relation is transitive:
+	* <tt>(x.compareTo(y)&gt;0 &amp;&amp; y.compareTo(z)&gt;0)</tt> implies
+	* <tt>x.compareTo(z)&gt;0</tt>.
+	*
+	* <p>Finally, the implementor must ensure that <tt>x.compareTo(y)==0</tt>
+	* implies that <tt>sgn(x.compareTo(z)) == sgn(y.compareTo(z))</tt>, for
+	* all <tt>z</tt>.
+	*
+	* <p>It is strongly recommended, but <i>not</i> strictly required that
+	* <tt>(x.compareTo(y)==0) == (x.equals(y))</tt>.  Generally speaking, any
+	* class that implements the <tt>Comparable</tt> interface and violates
+	* this condition should clearly indicate this fact.  The recommended
+	* language is "Note: this class has a natural ordering that is
+	* inconsistent with equals."
+	*
+	* <p>In the foregoing description, the notation
+	* <tt>sgn(</tt><i>expression</i><tt>)</tt> designates the mathematical
+	* <i>signum</i> function, which is defined to return one of <tt>-1</tt>,
+	* <tt>0</tt>, or <tt>1</tt> according to whether the value of
+	* <i>expression</i> is negative, zero or positive.
+	*
+	* @param   o the object to be compared.
+	* @return  a negative integer, zero, or a positive integer as this object
+	*          is less than, equal to, or greater than the specified object.
+	*
+	* @throws NullPointerException if the specified object is null
+	* @throws ClassCastException if the specified object's type prevents it
+	*         from being compared to this object.
+	*/
+	@:overload public function compareTo(o : T) : Int;
+	
+	
+}

+ 853 - 0
std/java/lang/Double.hx

@@ -0,0 +1,853 @@
+package java.lang;
+/*
+* Copyright (c) 1994, 2010, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* The {@code Double} class wraps a value of the primitive type
+* {@code double} in an object. An object of type
+* {@code Double} contains a single field whose type is
+* {@code double}.
+*
+* <p>In addition, this class provides several methods for converting a
+* {@code double} to a {@code String} and a
+* {@code String} to a {@code double}, as well as other
+* constants and methods useful when dealing with a
+* {@code double}.
+*
+* @author  Lee Boynton
+* @author  Arthur van Hoff
+* @author  Joseph D. Darcy
+* @since JDK1.0
+*/
+@:require(java0) extern class Double extends java.lang.Number implements java.lang.Comparable<Double>
+{
+	/**
+	* A constant holding the positive infinity of type
+	* {@code double}. It is equal to the value returned by
+	* {@code Double.longBitsToDouble(0x7ff0000000000000L)}.
+	*/
+	public static var POSITIVE_INFINITY(default, null) : Float;
+
+	/**
+	* A constant holding the negative infinity of type
+	* {@code double}. It is equal to the value returned by
+	* {@code Double.longBitsToDouble(0xfff0000000000000L)}.
+	*/
+	public static var NEGATIVE_INFINITY(default, null) : Float;
+
+	/**
+	* A constant holding a Not-a-Number (NaN) value of type
+	* {@code double}. It is equivalent to the value returned by
+	* {@code Double.longBitsToDouble(0x7ff8000000000000L)}.
+	*/
+	public static var NaN(default, null) : Float;
+
+	/**
+	* A constant holding the largest positive finite value of type
+	* {@code double},
+	* (2-2<sup>-52</sup>)&middot;2<sup>1023</sup>.  It is equal to
+	* the hexadecimal floating-point literal
+	* {@code 0x1.fffffffffffffP+1023} and also equal to
+	* {@code Double.longBitsToDouble(0x7fefffffffffffffL)}.
+	*/
+	public static var MAX_VALUE(default, null) : Float;
+
+	/**
+	* A constant holding the smallest positive normal value of type
+	* {@code double}, 2<sup>-1022</sup>.  It is equal to the
+	* hexadecimal floating-point literal {@code 0x1.0p-1022} and also
+	* equal to {@code Double.longBitsToDouble(0x0010000000000000L)}.
+	*
+	* @since 1.6
+	*/
+	@:require(java6) public static var MIN_NORMAL(default, null) : Float;
+
+	/**
+	* A constant holding the smallest positive nonzero value of type
+	* {@code double}, 2<sup>-1074</sup>. It is equal to the
+	* hexadecimal floating-point literal
+	* {@code 0x0.0000000000001P-1022} and also equal to
+	* {@code Double.longBitsToDouble(0x1L)}.
+	*/
+	public static var MIN_VALUE(default, null) : Float;
+
+	/**
+	* Maximum exponent a finite {@code double} variable may have.
+	* It is equal to the value returned by
+	* {@code Math.getExponent(Double.MAX_VALUE)}.
+	*
+	* @since 1.6
+	*/
+	@:require(java6) public static var MAX_EXPONENT(default, null) : Int;
+
+	/**
+	* Minimum exponent a normalized {@code double} variable may
+	* have.  It is equal to the value returned by
+	* {@code Math.getExponent(Double.MIN_NORMAL)}.
+	*
+	* @since 1.6
+	*/
+	@:require(java6) public static var MIN_EXPONENT(default, null) : Int;
+
+	/**
+	* The number of bits used to represent a {@code double} value.
+	*
+	* @since 1.5
+	*/
+	@:require(java5) public static var SIZE(default, null) : Int;
+
+	/**
+	* The {@code Class} instance representing the primitive type
+	* {@code double}.
+	*
+	* @since JDK1.1
+	*/
+	@:require(java1) public static var TYPE(default, null) : Class<Double>;
+
+	/**
+	* Returns a string representation of the {@code double}
+	* argument. All characters mentioned below are ASCII characters.
+	* <ul>
+	* <li>If the argument is NaN, the result is the string
+	*     "{@code NaN}".
+	* <li>Otherwise, the result is a string that represents the sign and
+	* magnitude (absolute value) of the argument. If the sign is negative,
+	* the first character of the result is '{@code -}'
+	* (<code>'&#92;u002D'</code>); if the sign is positive, no sign character
+	* appears in the result. As for the magnitude <i>m</i>:
+	* <ul>
+	* <li>If <i>m</i> is infinity, it is represented by the characters
+	* {@code "Infinity"}; thus, positive infinity produces the result
+	* {@code "Infinity"} and negative infinity produces the result
+	* {@code "-Infinity"}.
+	*
+	* <li>If <i>m</i> is zero, it is represented by the characters
+	* {@code "0.0"}; thus, negative zero produces the result
+	* {@code "-0.0"} and positive zero produces the result
+	* {@code "0.0"}.
+	*
+	* <li>If <i>m</i> is greater than or equal to 10<sup>-3</sup> but less
+	* than 10<sup>7</sup>, then it is represented as the integer part of
+	* <i>m</i>, in decimal form with no leading zeroes, followed by
+	* '{@code .}' (<code>'&#92;u002E'</code>), followed by one or
+	* more decimal digits representing the fractional part of <i>m</i>.
+	*
+	* <li>If <i>m</i> is less than 10<sup>-3</sup> or greater than or
+	* equal to 10<sup>7</sup>, then it is represented in so-called
+	* "computerized scientific notation." Let <i>n</i> be the unique
+	* integer such that 10<sup><i>n</i></sup> &le; <i>m</i> {@literal <}
+	* 10<sup><i>n</i>+1</sup>; then let <i>a</i> be the
+	* mathematically exact quotient of <i>m</i> and
+	* 10<sup><i>n</i></sup> so that 1 &le; <i>a</i> {@literal <} 10. The
+	* magnitude is then represented as the integer part of <i>a</i>,
+	* as a single decimal digit, followed by '{@code .}'
+	* (<code>'&#92;u002E'</code>), followed by decimal digits
+	* representing the fractional part of <i>a</i>, followed by the
+	* letter '{@code E}' (<code>'&#92;u0045'</code>), followed
+	* by a representation of <i>n</i> as a decimal integer, as
+	* produced by the method {@link Integer#toString(int)}.
+	* </ul>
+	* </ul>
+	* How many digits must be printed for the fractional part of
+	* <i>m</i> or <i>a</i>? There must be at least one digit to represent
+	* the fractional part, and beyond that as many, but only as many, more
+	* digits as are needed to uniquely distinguish the argument value from
+	* adjacent values of type {@code double}. That is, suppose that
+	* <i>x</i> is the exact mathematical value represented by the decimal
+	* representation produced by this method for a finite nonzero argument
+	* <i>d</i>. Then <i>d</i> must be the {@code double} value nearest
+	* to <i>x</i>; or if two {@code double} values are equally close
+	* to <i>x</i>, then <i>d</i> must be one of them and the least
+	* significant bit of the significand of <i>d</i> must be {@code 0}.
+	*
+	* <p>To create localized string representations of a floating-point
+	* value, use subclasses of {@link java.text.NumberFormat}.
+	*
+	* @param   d   the {@code double} to be converted.
+	* @return a string representation of the argument.
+	*/
+	@:native('toString') @:overload public static function _toString(d : Float) : String;
+
+	/**
+	* Returns a hexadecimal string representation of the
+	* {@code double} argument. All characters mentioned below
+	* are ASCII characters.
+	*
+	* <ul>
+	* <li>If the argument is NaN, the result is the string
+	*     "{@code NaN}".
+	* <li>Otherwise, the result is a string that represents the sign
+	* and magnitude of the argument. If the sign is negative, the
+	* first character of the result is '{@code -}'
+	* (<code>'&#92;u002D'</code>); if the sign is positive, no sign
+	* character appears in the result. As for the magnitude <i>m</i>:
+	*
+	* <ul>
+	* <li>If <i>m</i> is infinity, it is represented by the string
+	* {@code "Infinity"}; thus, positive infinity produces the
+	* result {@code "Infinity"} and negative infinity produces
+	* the result {@code "-Infinity"}.
+	*
+	* <li>If <i>m</i> is zero, it is represented by the string
+	* {@code "0x0.0p0"}; thus, negative zero produces the result
+	* {@code "-0x0.0p0"} and positive zero produces the result
+	* {@code "0x0.0p0"}.
+	*
+	* <li>If <i>m</i> is a {@code double} value with a
+	* normalized representation, substrings are used to represent the
+	* significand and exponent fields.  The significand is
+	* represented by the characters {@code "0x1."}
+	* followed by a lowercase hexadecimal representation of the rest
+	* of the significand as a fraction.  Trailing zeros in the
+	* hexadecimal representation are removed unless all the digits
+	* are zero, in which case a single zero is used. Next, the
+	* exponent is represented by {@code "p"} followed
+	* by a decimal string of the unbiased exponent as if produced by
+	* a call to {@link Integer#toString(int) Integer.toString} on the
+	* exponent value.
+	*
+	* <li>If <i>m</i> is a {@code double} value with a subnormal
+	* representation, the significand is represented by the
+	* characters {@code "0x0."} followed by a
+	* hexadecimal representation of the rest of the significand as a
+	* fraction.  Trailing zeros in the hexadecimal representation are
+	* removed. Next, the exponent is represented by
+	* {@code "p-1022"}.  Note that there must be at
+	* least one nonzero digit in a subnormal significand.
+	*
+	* </ul>
+	*
+	* </ul>
+	*
+	* <table border>
+	* <caption><h3>Examples</h3></caption>
+	* <tr><th>Floating-point Value</th><th>Hexadecimal String</th>
+	* <tr><td>{@code 1.0}</td> <td>{@code 0x1.0p0}</td>
+	* <tr><td>{@code -1.0}</td>        <td>{@code -0x1.0p0}</td>
+	* <tr><td>{@code 2.0}</td> <td>{@code 0x1.0p1}</td>
+	* <tr><td>{@code 3.0}</td> <td>{@code 0x1.8p1}</td>
+	* <tr><td>{@code 0.5}</td> <td>{@code 0x1.0p-1}</td>
+	* <tr><td>{@code 0.25}</td>        <td>{@code 0x1.0p-2}</td>
+	* <tr><td>{@code Double.MAX_VALUE}</td>
+	*     <td>{@code 0x1.fffffffffffffp1023}</td>
+	* <tr><td>{@code Minimum Normal Value}</td>
+	*     <td>{@code 0x1.0p-1022}</td>
+	* <tr><td>{@code Maximum Subnormal Value}</td>
+	*     <td>{@code 0x0.fffffffffffffp-1022}</td>
+	* <tr><td>{@code Double.MIN_VALUE}</td>
+	*     <td>{@code 0x0.0000000000001p-1022}</td>
+	* </table>
+	* @param   d   the {@code double} to be converted.
+	* @return a hex string representation of the argument.
+	* @since 1.5
+	* @author Joseph D. Darcy
+	*/
+	@:require(java5) @:overload public static function toHexString(d : Float) : String;
+
+	/**
+	* Returns a {@code Double} object holding the
+	* {@code double} value represented by the argument string
+	* {@code s}.
+	*
+	* <p>If {@code s} is {@code null}, then a
+	* {@code NullPointerException} is thrown.
+	*
+	* <p>Leading and trailing whitespace characters in {@code s}
+	* are ignored.  Whitespace is removed as if by the {@link
+	* String#trim} method; that is, both ASCII space and control
+	* characters are removed. The rest of {@code s} should
+	* constitute a <i>FloatValue</i> as described by the lexical
+	* syntax rules:
+	*
+	* <blockquote>
+	* <dl>
+	* <dt><i>FloatValue:</i>
+	* <dd><i>Sign<sub>opt</sub></i> {@code NaN}
+	* <dd><i>Sign<sub>opt</sub></i> {@code Infinity}
+	* <dd><i>Sign<sub>opt</sub> FloatingPointLiteral</i>
+	* <dd><i>Sign<sub>opt</sub> HexFloatingPointLiteral</i>
+	* <dd><i>SignedInteger</i>
+	* </dl>
+	*
+	* <p>
+	*
+	* <dl>
+	* <dt><i>HexFloatingPointLiteral</i>:
+	* <dd> <i>HexSignificand BinaryExponent FloatTypeSuffix<sub>opt</sub></i>
+	* </dl>
+	*
+	* <p>
+	*
+	* <dl>
+	* <dt><i>HexSignificand:</i>
+	* <dd><i>HexNumeral</i>
+	* <dd><i>HexNumeral</i> {@code .}
+	* <dd>{@code 0x} <i>HexDigits<sub>opt</sub>
+	*     </i>{@code .}<i> HexDigits</i>
+	* <dd>{@code 0X}<i> HexDigits<sub>opt</sub>
+	*     </i>{@code .} <i>HexDigits</i>
+	* </dl>
+	*
+	* <p>
+	*
+	* <dl>
+	* <dt><i>BinaryExponent:</i>
+	* <dd><i>BinaryExponentIndicator SignedInteger</i>
+	* </dl>
+	*
+	* <p>
+	*
+	* <dl>
+	* <dt><i>BinaryExponentIndicator:</i>
+	* <dd>{@code p}
+	* <dd>{@code P}
+	* </dl>
+	*
+	* </blockquote>
+	*
+	* where <i>Sign</i>, <i>FloatingPointLiteral</i>,
+	* <i>HexNumeral</i>, <i>HexDigits</i>, <i>SignedInteger</i> and
+	* <i>FloatTypeSuffix</i> are as defined in the lexical structure
+	* sections of
+	* <cite>The Java&trade; Language Specification</cite>,
+	* except that underscores are not accepted between digits.
+	* If {@code s} does not have the form of
+	* a <i>FloatValue</i>, then a {@code NumberFormatException}
+	* is thrown. Otherwise, {@code s} is regarded as
+	* representing an exact decimal value in the usual
+	* "computerized scientific notation" or as an exact
+	* hexadecimal value; this exact numerical value is then
+	* conceptually converted to an "infinitely precise"
+	* binary value that is then rounded to type {@code double}
+	* by the usual round-to-nearest rule of IEEE 754 floating-point
+	* arithmetic, which includes preserving the sign of a zero
+	* value.
+	*
+	* Note that the round-to-nearest rule also implies overflow and
+	* underflow behaviour; if the exact value of {@code s} is large
+	* enough in magnitude (greater than or equal to ({@link
+	* #MAX_VALUE} + {@link Math#ulp(double) ulp(MAX_VALUE)}/2),
+	* rounding to {@code double} will result in an infinity and if the
+	* exact value of {@code s} is small enough in magnitude (less
+	* than or equal to {@link #MIN_VALUE}/2), rounding to float will
+	* result in a zero.
+	*
+	* Finally, after rounding a {@code Double} object representing
+	* this {@code double} value is returned.
+	*
+	* <p> To interpret localized string representations of a
+	* floating-point value, use subclasses of {@link
+	* java.text.NumberFormat}.
+	*
+	* <p>Note that trailing format specifiers, specifiers that
+	* determine the type of a floating-point literal
+	* ({@code 1.0f} is a {@code float} value;
+	* {@code 1.0d} is a {@code double} value), do
+	* <em>not</em> influence the results of this method.  In other
+	* words, the numerical value of the input string is converted
+	* directly to the target floating-point type.  The two-step
+	* sequence of conversions, string to {@code float} followed
+	* by {@code float} to {@code double}, is <em>not</em>
+	* equivalent to converting a string directly to
+	* {@code double}. For example, the {@code float}
+	* literal {@code 0.1f} is equal to the {@code double}
+	* value {@code 0.10000000149011612}; the {@code float}
+	* literal {@code 0.1f} represents a different numerical
+	* value than the {@code double} literal
+	* {@code 0.1}. (The numerical value 0.1 cannot be exactly
+	* represented in a binary floating-point number.)
+	*
+	* <p>To avoid calling this method on an invalid string and having
+	* a {@code NumberFormatException} be thrown, the regular
+	* expression below can be used to screen the input string:
+	*
+	* <code>
+	* <pre>
+	*  final String Digits     = "(\\p{Digit}+)";
+	*  final String HexDigits  = "(\\p{XDigit}+)";
+	*  // an exponent is 'e' or 'E' followed by an optionally
+	*  // signed decimal integer.
+	*  final String Exp        = "[eE][+-]?"+Digits;
+	*  final String fpRegex    =
+	*      ("[\\x00-\\x20]*"+  // Optional leading "whitespace"
+	*       "[+-]?(" + // Optional sign character
+	*       "NaN|" +           // "NaN" string
+	*       "Infinity|" +      // "Infinity" string
+	*
+	*       // A decimal floating-point string representing a finite positive
+	*       // number without a leading sign has at most five basic pieces:
+	*       // Digits . Digits ExponentPart FloatTypeSuffix
+	*       //
+	*       // Since this method allows integer-only strings as input
+	*       // in addition to strings of floating-point literals, the
+	*       // two sub-patterns below are simplifications of the grammar
+	*       // productions from section 3.10.2 of
+	*       // <cite>The Java&trade; Language Specification</cite>.
+	*
+	*       // Digits ._opt Digits_opt ExponentPart_opt FloatTypeSuffix_opt
+	*       "((("+Digits+"(\\.)?("+Digits+"?)("+Exp+")?)|"+
+	*
+	*       // . Digits ExponentPart_opt FloatTypeSuffix_opt
+	*       "(\\.("+Digits+")("+Exp+")?)|"+
+	*
+	*       // Hexadecimal strings
+	*       "((" +
+	*        // 0[xX] HexDigits ._opt BinaryExponent FloatTypeSuffix_opt
+	*        "(0[xX]" + HexDigits + "(\\.)?)|" +
+	*
+	*        // 0[xX] HexDigits_opt . HexDigits BinaryExponent FloatTypeSuffix_opt
+	*        "(0[xX]" + HexDigits + "?(\\.)" + HexDigits + ")" +
+	*
+	*        ")[pP][+-]?" + Digits + "))" +
+	*       "[fFdD]?))" +
+	*       "[\\x00-\\x20]*");// Optional trailing "whitespace"
+	*
+	*  if (Pattern.matches(fpRegex, myString))
+	*      Double.valueOf(myString); // Will not throw NumberFormatException
+	*  else {
+	*      // Perform suitable alternative action
+	*  }
+	* </pre>
+	* </code>
+	*
+	* @param      s   the string to be parsed.
+	* @return     a {@code Double} object holding the value
+	*             represented by the {@code String} argument.
+	* @throws     NumberFormatException  if the string does not contain a
+	*             parsable number.
+	*/
+	@:overload public static function valueOf(s : String) : Double;
+
+	/**
+	* Returns a {@code Double} instance representing the specified
+	* {@code double} value.
+	* If a new {@code Double} instance is not required, this method
+	* should generally be used in preference to the constructor
+	* {@link #Double(double)}, as this method is likely to yield
+	* significantly better space and time performance by caching
+	* frequently requested values.
+	*
+	* @param  d a double value.
+	* @return a {@code Double} instance representing {@code d}.
+	* @since  1.5
+	*/
+	@:require(java5) @:overload public static function valueOf(d : Float) : Double;
+
+	/**
+	* Returns a new {@code double} initialized to the value
+	* represented by the specified {@code String}, as performed
+	* by the {@code valueOf} method of class
+	* {@code Double}.
+	*
+	* @param  s   the string to be parsed.
+	* @return the {@code double} value represented by the string
+	*         argument.
+	* @throws NullPointerException  if the string is null
+	* @throws NumberFormatException if the string does not contain
+	*         a parsable {@code double}.
+	* @see    java.lang.Double#valueOf(String)
+	* @since 1.2
+	*/
+	@:require(java2) @:overload public static function parseDouble(s : String) : Float;
+
+	/**
+	* Returns {@code true} if the specified number is a
+	* Not-a-Number (NaN) value, {@code false} otherwise.
+	*
+	* @param   v   the value to be tested.
+	* @return  {@code true} if the value of the argument is NaN;
+	*          {@code false} otherwise.
+	*/
+	@:native('isNaN') @:overload public static function _isNaN(v : Float) : Bool;
+
+	/**
+	* Returns {@code true} if the specified number is infinitely
+	* large in magnitude, {@code false} otherwise.
+	*
+	* @param   v   the value to be tested.
+	* @return  {@code true} if the value of the argument is positive
+	*          infinity or negative infinity; {@code false} otherwise.
+	*/
+	@:native('isInfinite') @:overload public static function _isInfinite(v : Float) : Bool;
+
+	/**
+	* Constructs a newly allocated {@code Double} object that
+	* represents the primitive {@code double} argument.
+	*
+	* @param   value   the value to be represented by the {@code Double}.
+	*/
+	@:overload public function new(value : Float) : Void;
+
+	/**
+	* Constructs a newly allocated {@code Double} object that
+	* represents the floating-point value of type {@code double}
+	* represented by the string. The string is converted to a
+	* {@code double} value as if by the {@code valueOf} method.
+	*
+	* @param  s  a string to be converted to a {@code Double}.
+	* @throws    NumberFormatException  if the string does not contain a
+	*            parsable number.
+	* @see       java.lang.Double#valueOf(java.lang.String)
+	*/
+	@:overload public function new(s : String) : Void;
+
+	/**
+	* Returns {@code true} if this {@code Double} value is
+	* a Not-a-Number (NaN), {@code false} otherwise.
+	*
+	* @return  {@code true} if the value represented by this object is
+	*          NaN; {@code false} otherwise.
+	*/
+	@:overload public function isNaN() : Bool;
+
+	/**
+	* Returns {@code true} if this {@code Double} value is
+	* infinitely large in magnitude, {@code false} otherwise.
+	*
+	* @return  {@code true} if the value represented by this object is
+	*          positive infinity or negative infinity;
+	*          {@code false} otherwise.
+	*/
+	@:overload public function isInfinite() : Bool;
+
+	/**
+	* Returns a string representation of this {@code Double} object.
+	* The primitive {@code double} value represented by this
+	* object is converted to a string exactly as if by the method
+	* {@code toString} of one argument.
+	*
+	* @return  a {@code String} representation of this object.
+	* @see java.lang.Double#toString(double)
+	*/
+	@:overload public function toString() : String;
+
+	/**
+	* Returns the value of this {@code Double} as a {@code byte} (by
+	* casting to a {@code byte}).
+	*
+	* @return  the {@code double} value represented by this object
+	*          converted to type {@code byte}
+	* @since JDK1.1
+	*/
+	@:require(java1) @:overload override public function byteValue() : java.StdTypes.Int8;
+
+	/**
+	* Returns the value of this {@code Double} as a
+	* {@code short} (by casting to a {@code short}).
+	*
+	* @return  the {@code double} value represented by this object
+	*          converted to type {@code short}
+	* @since JDK1.1
+	*/
+	@:require(java1) @:overload override public function shortValue() : java.StdTypes.Int16;
+
+	/**
+	* Returns the value of this {@code Double} as an
+	* {@code int} (by casting to type {@code int}).
+	*
+	* @return  the {@code double} value represented by this object
+	*          converted to type {@code int}
+	*/
+	@:overload override public function intValue() : Int;
+
+	/**
+	* Returns the value of this {@code Double} as a
+	* {@code long} (by casting to type {@code long}).
+	*
+	* @return  the {@code double} value represented by this object
+	*          converted to type {@code long}
+	*/
+	@:overload override public function longValue() : haxe.Int64;
+
+	/**
+	* Returns the {@code float} value of this
+	* {@code Double} object.
+	*
+	* @return  the {@code double} value represented by this object
+	*          converted to type {@code float}
+	* @since JDK1.0
+	*/
+	@:require(java0) @:overload override public function floatValue() : Single;
+
+	/**
+	* Returns the {@code double} value of this
+	* {@code Double} object.
+	*
+	* @return the {@code double} value represented by this object
+	*/
+	@:overload override public function doubleValue() : Float;
+
+	/**
+	* Returns a hash code for this {@code Double} object. The
+	* result is the exclusive OR of the two halves of the
+	* {@code long} integer bit representation, exactly as
+	* produced by the method {@link #doubleToLongBits(double)}, of
+	* the primitive {@code double} value represented by this
+	* {@code Double} object. That is, the hash code is the value
+	* of the expression:
+	*
+	* <blockquote>
+	*  {@code (int)(v^(v>>>32))}
+	* </blockquote>
+	*
+	* where {@code v} is defined by:
+	*
+	* <blockquote>
+	*  {@code long v = Double.doubleToLongBits(this.doubleValue());}
+	* </blockquote>
+	*
+	* @return  a {@code hash code} value for this object.
+	*/
+	@:overload public function hashCode() : Int;
+
+	/**
+	* Compares this object against the specified object.  The result
+	* is {@code true} if and only if the argument is not
+	* {@code null} and is a {@code Double} object that
+	* represents a {@code double} that has the same value as the
+	* {@code double} represented by this object. For this
+	* purpose, two {@code double} values are considered to be
+	* the same if and only if the method {@link
+	* #doubleToLongBits(double)} returns the identical
+	* {@code long} value when applied to each.
+	*
+	* <p>Note that in most cases, for two instances of class
+	* {@code Double}, {@code d1} and {@code d2}, the
+	* value of {@code d1.equals(d2)} is {@code true} if and
+	* only if
+	*
+	* <blockquote>
+	*  {@code d1.doubleValue() == d2.doubleValue()}
+	* </blockquote>
+	*
+	* <p>also has the value {@code true}. However, there are two
+	* exceptions:
+	* <ul>
+	* <li>If {@code d1} and {@code d2} both represent
+	*     {@code Double.NaN}, then the {@code equals} method
+	*     returns {@code true}, even though
+	*     {@code Double.NaN==Double.NaN} has the value
+	*     {@code false}.
+	* <li>If {@code d1} represents {@code +0.0} while
+	*     {@code d2} represents {@code -0.0}, or vice versa,
+	*     the {@code equal} test has the value {@code false},
+	*     even though {@code +0.0==-0.0} has the value {@code true}.
+	* </ul>
+	* This definition allows hash tables to operate properly.
+	* @param   obj   the object to compare with.
+	* @return  {@code true} if the objects are the same;
+	*          {@code false} otherwise.
+	* @see java.lang.Double#doubleToLongBits(double)
+	*/
+	@:overload public function equals(obj : Dynamic) : Bool;
+
+	/**
+	* Returns a representation of the specified floating-point value
+	* according to the IEEE 754 floating-point "double
+	* format" bit layout.
+	*
+	* <p>Bit 63 (the bit that is selected by the mask
+	* {@code 0x8000000000000000L}) represents the sign of the
+	* floating-point number. Bits
+	* 62-52 (the bits that are selected by the mask
+	* {@code 0x7ff0000000000000L}) represent the exponent. Bits 51-0
+	* (the bits that are selected by the mask
+	* {@code 0x000fffffffffffffL}) represent the significand
+	* (sometimes called the mantissa) of the floating-point number.
+	*
+	* <p>If the argument is positive infinity, the result is
+	* {@code 0x7ff0000000000000L}.
+	*
+	* <p>If the argument is negative infinity, the result is
+	* {@code 0xfff0000000000000L}.
+	*
+	* <p>If the argument is NaN, the result is
+	* {@code 0x7ff8000000000000L}.
+	*
+	* <p>In all cases, the result is a {@code long} integer that, when
+	* given to the {@link #longBitsToDouble(long)} method, will produce a
+	* floating-point value the same as the argument to
+	* {@code doubleToLongBits} (except all NaN values are
+	* collapsed to a single "canonical" NaN value).
+	*
+	* @param   value   a {@code double} precision floating-point number.
+	* @return the bits that represent the floating-point number.
+	*/
+	@:overload public static function doubleToLongBits(value : Float) : haxe.Int64;
+
+	/**
+	* Returns a representation of the specified floating-point value
+	* according to the IEEE 754 floating-point "double
+	* format" bit layout, preserving Not-a-Number (NaN) values.
+	*
+	* <p>Bit 63 (the bit that is selected by the mask
+	* {@code 0x8000000000000000L}) represents the sign of the
+	* floating-point number. Bits
+	* 62-52 (the bits that are selected by the mask
+	* {@code 0x7ff0000000000000L}) represent the exponent. Bits 51-0
+	* (the bits that are selected by the mask
+	* {@code 0x000fffffffffffffL}) represent the significand
+	* (sometimes called the mantissa) of the floating-point number.
+	*
+	* <p>If the argument is positive infinity, the result is
+	* {@code 0x7ff0000000000000L}.
+	*
+	* <p>If the argument is negative infinity, the result is
+	* {@code 0xfff0000000000000L}.
+	*
+	* <p>If the argument is NaN, the result is the {@code long}
+	* integer representing the actual NaN value.  Unlike the
+	* {@code doubleToLongBits} method,
+	* {@code doubleToRawLongBits} does not collapse all the bit
+	* patterns encoding a NaN to a single "canonical" NaN
+	* value.
+	*
+	* <p>In all cases, the result is a {@code long} integer that,
+	* when given to the {@link #longBitsToDouble(long)} method, will
+	* produce a floating-point value the same as the argument to
+	* {@code doubleToRawLongBits}.
+	*
+	* @param   value   a {@code double} precision floating-point number.
+	* @return the bits that represent the floating-point number.
+	* @since 1.3
+	*/
+	@:require(java3) @:overload @:native public static function doubleToRawLongBits(value : Float) : haxe.Int64;
+
+	/**
+	* Returns the {@code double} value corresponding to a given
+	* bit representation.
+	* The argument is considered to be a representation of a
+	* floating-point value according to the IEEE 754 floating-point
+	* "double format" bit layout.
+	*
+	* <p>If the argument is {@code 0x7ff0000000000000L}, the result
+	* is positive infinity.
+	*
+	* <p>If the argument is {@code 0xfff0000000000000L}, the result
+	* is negative infinity.
+	*
+	* <p>If the argument is any value in the range
+	* {@code 0x7ff0000000000001L} through
+	* {@code 0x7fffffffffffffffL} or in the range
+	* {@code 0xfff0000000000001L} through
+	* {@code 0xffffffffffffffffL}, the result is a NaN.  No IEEE
+	* 754 floating-point operation provided by Java can distinguish
+	* between two NaN values of the same type with different bit
+	* patterns.  Distinct values of NaN are only distinguishable by
+	* use of the {@code Double.doubleToRawLongBits} method.
+	*
+	* <p>In all other cases, let <i>s</i>, <i>e</i>, and <i>m</i> be three
+	* values that can be computed from the argument:
+	*
+	* <blockquote><pre>
+	* int s = ((bits &gt;&gt; 63) == 0) ? 1 : -1;
+	* int e = (int)((bits &gt;&gt; 52) & 0x7ffL);
+	* long m = (e == 0) ?
+	*                 (bits & 0xfffffffffffffL) &lt;&lt; 1 :
+	*                 (bits & 0xfffffffffffffL) | 0x10000000000000L;
+	* </pre></blockquote>
+	*
+	* Then the floating-point result equals the value of the mathematical
+	* expression <i>s</i>&middot;<i>m</i>&middot;2<sup><i>e</i>-1075</sup>.
+	*
+	* <p>Note that this method may not be able to return a
+	* {@code double} NaN with exactly same bit pattern as the
+	* {@code long} argument.  IEEE 754 distinguishes between two
+	* kinds of NaNs, quiet NaNs and <i>signaling NaNs</i>.  The
+	* differences between the two kinds of NaN are generally not
+	* visible in Java.  Arithmetic operations on signaling NaNs turn
+	* them into quiet NaNs with a different, but often similar, bit
+	* pattern.  However, on some processors merely copying a
+	* signaling NaN also performs that conversion.  In particular,
+	* copying a signaling NaN to return it to the calling method
+	* may perform this conversion.  So {@code longBitsToDouble}
+	* may not be able to return a {@code double} with a
+	* signaling NaN bit pattern.  Consequently, for some
+	* {@code long} values,
+	* {@code doubleToRawLongBits(longBitsToDouble(start))} may
+	* <i>not</i> equal {@code start}.  Moreover, which
+	* particular bit patterns represent signaling NaNs is platform
+	* dependent; although all NaN bit patterns, quiet or signaling,
+	* must be in the NaN range identified above.
+	*
+	* @param   bits   any {@code long} integer.
+	* @return  the {@code double} floating-point value with the same
+	*          bit pattern.
+	*/
+	@:overload @:native public static function longBitsToDouble(bits : haxe.Int64) : Float;
+
+	/**
+	* Compares two {@code Double} objects numerically.  There
+	* are two ways in which comparisons performed by this method
+	* differ from those performed by the Java language numerical
+	* comparison operators ({@code <, <=, ==, >=, >})
+	* when applied to primitive {@code double} values:
+	* <ul><li>
+	*          {@code Double.NaN} is considered by this method
+	*          to be equal to itself and greater than all other
+	*          {@code double} values (including
+	*          {@code Double.POSITIVE_INFINITY}).
+	* <li>
+	*          {@code 0.0d} is considered by this method to be greater
+	*          than {@code -0.0d}.
+	* </ul>
+	* This ensures that the <i>natural ordering</i> of
+	* {@code Double} objects imposed by this method is <i>consistent
+	* with equals</i>.
+	*
+	* @param   anotherDouble   the {@code Double} to be compared.
+	* @return  the value {@code 0} if {@code anotherDouble} is
+	*          numerically equal to this {@code Double}; a value
+	*          less than {@code 0} if this {@code Double}
+	*          is numerically less than {@code anotherDouble};
+	*          and a value greater than {@code 0} if this
+	*          {@code Double} is numerically greater than
+	*          {@code anotherDouble}.
+	*
+	* @since   1.2
+	*/
+	@:require(java2) @:overload public function compareTo(anotherDouble : Double) : Int;
+
+	/**
+	* Compares the two specified {@code double} values. The sign
+	* of the integer value returned is the same as that of the
+	* integer that would be returned by the call:
+	* <pre>
+	*    new Double(d1).compareTo(new Double(d2))
+	* </pre>
+	*
+	* @param   d1        the first {@code double} to compare
+	* @param   d2        the second {@code double} to compare
+	* @return  the value {@code 0} if {@code d1} is
+	*          numerically equal to {@code d2}; a value less than
+	*          {@code 0} if {@code d1} is numerically less than
+	*          {@code d2}; and a value greater than {@code 0}
+	*          if {@code d1} is numerically greater than
+	*          {@code d2}.
+	* @since 1.4
+	*/
+	@:require(java4) @:overload public static function compare(d1 : Float, d2 : Float) : Int;
+
+
+}

+ 185 - 0
std/java/lang/Enum.hx

@@ -0,0 +1,185 @@
+package java.lang;
+/*
+* Copyright (c) 2003, 2009, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* This is the common base class of all Java language enumeration types.
+*
+* More information about enums, including descriptions of the
+* implicitly declared methods synthesized by the compiler, can be
+* found in section 8.9 of
+* <cite>The Java&trade; Language Specification</cite>.
+*
+* <p> Note that when using an enumeration type as the type of a set
+* or as the type of the keys in a map, specialized and efficient
+* {@linkplain java.util.EnumSet set} and {@linkplain
+* java.util.EnumMap map} implementations are available.
+*
+* @param <E> The enum type subclass
+* @author  Josh Bloch
+* @author  Neal Gafter
+* @see     Class#getEnumConstants()
+* @see     java.util.EnumSet
+* @see     java.util.EnumMap
+* @since   1.5
+*/
+@:require(java5) extern class Enum<E> implements java.lang.Comparable<E> implements java.io.Serializable
+{
+	/**
+	* Returns the name of this enum constant, exactly as declared in its
+	* enum declaration.
+	*
+	* <b>Most programmers should use the {@link #toString} method in
+	* preference to this one, as the toString method may return
+	* a more user-friendly name.</b>  This method is designed primarily for
+	* use in specialized situations where correctness depends on getting the
+	* exact name, which will not vary from release to release.
+	*
+	* @return the name of this enum constant
+	*/
+	@:overload @:final public function name() : String;
+	
+	/**
+	* Returns the ordinal of this enumeration constant (its position
+	* in its enum declaration, where the initial constant is assigned
+	* an ordinal of zero).
+	*
+	* Most programmers will have no use for this method.  It is
+	* designed for use by sophisticated enum-based data structures, such
+	* as {@link java.util.EnumSet} and {@link java.util.EnumMap}.
+	*
+	* @return the ordinal of this enumeration constant
+	*/
+	@:overload @:final public function ordinal() : Int;
+	
+	/**
+	* Sole constructor.  Programmers cannot invoke this constructor.
+	* It is for use by code emitted by the compiler in response to
+	* enum type declarations.
+	*
+	* @param name - The name of this enum constant, which is the identifier
+	*               used to declare it.
+	* @param ordinal - The ordinal of this enumeration constant (its position
+	*         in the enum declaration, where the initial constant is assigned
+	*         an ordinal of zero).
+	*/
+	@:overload private function new(name : String, ordinal : Int) : Void;
+	
+	/**
+	* Returns the name of this enum constant, as contained in the
+	* declaration.  This method may be overridden, though it typically
+	* isn't necessary or desirable.  An enum type should override this
+	* method when a more "programmer-friendly" string form exists.
+	*
+	* @return the name of this enum constant
+	*/
+	@:overload public function toString() : String;
+	
+	/**
+	* Returns true if the specified object is equal to this
+	* enum constant.
+	*
+	* @param other the object to be compared for equality with this object.
+	* @return  true if the specified object is equal to this
+	*          enum constant.
+	*/
+	@:overload @:final public function equals(other : Dynamic) : Bool;
+	
+	/**
+	* Returns a hash code for this enum constant.
+	*
+	* @return a hash code for this enum constant.
+	*/
+	@:overload @:final public function hashCode() : Int;
+	
+	/**
+	* Throws CloneNotSupportedException.  This guarantees that enums
+	* are never cloned, which is necessary to preserve their "singleton"
+	* status.
+	*
+	* @return (never returns)
+	*/
+	@:overload @:final private function clone() : Dynamic;
+	
+	/**
+	* Compares this enum with the specified object for order.  Returns a
+	* negative integer, zero, or a positive integer as this object is less
+	* than, equal to, or greater than the specified object.
+	*
+	* Enum constants are only comparable to other enum constants of the
+	* same enum type.  The natural order implemented by this
+	* method is the order in which the constants are declared.
+	*/
+	@:overload @:final public function compareTo(o : E) : Int;
+	
+	/**
+	* Returns the Class object corresponding to this enum constant's
+	* enum type.  Two enum constants e1 and  e2 are of the
+	* same enum type if and only if
+	*   e1.getDeclaringClass() == e2.getDeclaringClass().
+	* (The value returned by this method may differ from the one returned
+	* by the {@link Object#getClass} method for enum constants with
+	* constant-specific class bodies.)
+	*
+	* @return the Class object corresponding to this enum constant's
+	*     enum type
+	*/
+	@:overload @:final public function getDeclaringClass() : Class<E>;
+	
+	/**
+	* Returns the enum constant of the specified enum type with the
+	* specified name.  The name must match exactly an identifier used
+	* to declare an enum constant in this type.  (Extraneous whitespace
+	* characters are not permitted.)
+	*
+	* <p>Note that for a particular enum type {@code T}, the
+	* implicitly declared {@code public static T valueOf(String)}
+	* method on that enum may be used instead of this method to map
+	* from a name to the corresponding enum constant.  All the
+	* constants of an enum type can be obtained by calling the
+	* implicit {@code public static T[] values()} method of that
+	* type.
+	*
+	* @param <T> The enum type whose constant is to be returned
+	* @param enumType the {@code Class} object of the enum type from which
+	*      to return a constant
+	* @param name the name of the constant to return
+	* @return the enum constant of the specified enum type with the
+	*      specified name
+	* @throws IllegalArgumentException if the specified enum type has
+	*         no constant with the specified name, or the specified
+	*         class object does not represent an enum type
+	* @throws NullPointerException if {@code enumType} or {@code name}
+	*         is null
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function valueOf<T : Enum<T>>(enumType : Class<T>, name : String) : T;
+	
+	/**
+	* enum classes cannot have finalize methods.
+	*/
+	@:overload @:final private function finalize() : Void;
+	
+	
+}

+ 111 - 0
std/java/lang/Exception.hx

@@ -0,0 +1,111 @@
+package java.lang;
+/*
+* Copyright (c) 1994, 2011, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* The class {@code Exception} and its subclasses are a form of
+* {@code Throwable} that indicates conditions that a reasonable
+* application might want to catch.
+*
+* <p>The class {@code Exception} and any subclasses that are not also
+* subclasses of {@link RuntimeException} are <em>checked
+* exceptions</em>.  Checked exceptions need to be declared in a
+* method or constructor's {@code throws} clause if they can be thrown
+* by the execution of the method or constructor and propagate outside
+* the method or constructor boundary.
+*
+* @author  Frank Yellin
+* @see     java.lang.Error
+* @jls 11.2 Compile-Time Checking of Exceptions
+* @since   JDK1.0
+*/
+@:require(java0) extern class Exception extends java.lang.Throwable
+{
+	/**
+	* Constructs a new exception with {@code null} as its detail message.
+	* The cause is not initialized, and may subsequently be initialized by a
+	* call to {@link #initCause}.
+	*/
+	@:overload public function new() : Void;
+	
+	/**
+	* Constructs a new exception with the specified detail message.  The
+	* cause is not initialized, and may subsequently be initialized by
+	* a call to {@link #initCause}.
+	*
+	* @param   message   the detail message. The detail message is saved for
+	*          later retrieval by the {@link #getMessage()} method.
+	*/
+	@:overload public function new(message : String) : Void;
+	
+	/**
+	* Constructs a new exception with the specified detail message and
+	* cause.  <p>Note that the detail message associated with
+	* {@code cause} is <i>not</i> automatically incorporated in
+	* this exception's detail message.
+	*
+	* @param  message the detail message (which is saved for later retrieval
+	*         by the {@link #getMessage()} method).
+	* @param  cause the cause (which is saved for later retrieval by the
+	*         {@link #getCause()} method).  (A <tt>null</tt> value is
+	*         permitted, and indicates that the cause is nonexistent or
+	*         unknown.)
+	* @since  1.4
+	*/
+	@:require(java4) @:overload public function new(message : String, cause : java.lang.Throwable) : Void;
+	
+	/**
+	* Constructs a new exception with the specified cause and a detail
+	* message of <tt>(cause==null ? null : cause.toString())</tt> (which
+	* typically contains the class and detail message of <tt>cause</tt>).
+	* This constructor is useful for exceptions that are little more than
+	* wrappers for other throwables (for example, {@link
+	* java.security.PrivilegedActionException}).
+	*
+	* @param  cause the cause (which is saved for later retrieval by the
+	*         {@link #getCause()} method).  (A <tt>null</tt> value is
+	*         permitted, and indicates that the cause is nonexistent or
+	*         unknown.)
+	* @since  1.4
+	*/
+	@:require(java4) @:overload public function new(cause : java.lang.Throwable) : Void;
+	
+	/**
+	* Constructs a new exception with the specified detail message,
+	* cause, suppression enabled or disabled, and writable stack
+	* trace enabled or disabled.
+	*
+	* @param  message the detail message.
+	* @param cause the cause.  (A {@code null} value is permitted,
+	* and indicates that the cause is nonexistent or unknown.)
+	* @param enableSuppression whether or not suppression is enabled
+	*                          or disabled
+	* @param writableStackTrace whether or not the stack trace should
+	*                           be writable
+	* @since 1.7
+	*/
+	@:require(java7) @:overload private function new(message : String, cause : java.lang.Throwable, enableSuppression : Bool, writableStackTrace : Bool) : Void;
+	
+	
+}

+ 798 - 0
std/java/lang/Float.hx

@@ -0,0 +1,798 @@
+package java.lang;
+/*
+* Copyright (c) 1994, 2010, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* The {@code Float} class wraps a value of primitive type
+* {@code float} in an object. An object of type
+* {@code Float} contains a single field whose type is
+* {@code float}.
+*
+* <p>In addition, this class provides several methods for converting a
+* {@code float} to a {@code String} and a
+* {@code String} to a {@code float}, as well as other
+* constants and methods useful when dealing with a
+* {@code float}.
+*
+* @author  Lee Boynton
+* @author  Arthur van Hoff
+* @author  Joseph D. Darcy
+* @since JDK1.0
+*/
+@:require(java0) extern class Float extends java.lang.Number implements java.lang.Comparable<Float>
+{
+	/**
+	* A constant holding the positive infinity of type
+	* {@code float}. It is equal to the value returned by
+	* {@code Float.intBitsToFloat(0x7f800000)}.
+	*/
+	public static var POSITIVE_INFINITY(default, null) : Single;
+	
+	/**
+	* A constant holding the negative infinity of type
+	* {@code float}. It is equal to the value returned by
+	* {@code Float.intBitsToFloat(0xff800000)}.
+	*/
+	public static var NEGATIVE_INFINITY(default, null) : Single;
+	
+	/**
+	* A constant holding a Not-a-Number (NaN) value of type
+	* {@code float}.  It is equivalent to the value returned by
+	* {@code Float.intBitsToFloat(0x7fc00000)}.
+	*/
+	public static var NaN(default, null) : Single;
+	
+	/**
+	* A constant holding the largest positive finite value of type
+	* {@code float}, (2-2<sup>-23</sup>)&middot;2<sup>127</sup>.
+	* It is equal to the hexadecimal floating-point literal
+	* {@code 0x1.fffffeP+127f} and also equal to
+	* {@code Float.intBitsToFloat(0x7f7fffff)}.
+	*/
+	public static var MAX_VALUE(default, null) : Single;
+	
+	/**
+	* A constant holding the smallest positive normal value of type
+	* {@code float}, 2<sup>-126</sup>.  It is equal to the
+	* hexadecimal floating-point literal {@code 0x1.0p-126f} and also
+	* equal to {@code Float.intBitsToFloat(0x00800000)}.
+	*
+	* @since 1.6
+	*/
+	@:require(java6) public static var MIN_NORMAL(default, null) : Single;
+	
+	/**
+	* A constant holding the smallest positive nonzero value of type
+	* {@code float}, 2<sup>-149</sup>. It is equal to the
+	* hexadecimal floating-point literal {@code 0x0.000002P-126f}
+	* and also equal to {@code Float.intBitsToFloat(0x1)}.
+	*/
+	public static var MIN_VALUE(default, null) : Single;
+	
+	/**
+	* Maximum exponent a finite {@code float} variable may have.  It
+	* is equal to the value returned by {@code
+	* Math.getExponent(Float.MAX_VALUE)}.
+	*
+	* @since 1.6
+	*/
+	@:require(java6) public static var MAX_EXPONENT(default, null) : Int;
+	
+	/**
+	* Minimum exponent a normalized {@code float} variable may have.
+	* It is equal to the value returned by {@code
+	* Math.getExponent(Float.MIN_NORMAL)}.
+	*
+	* @since 1.6
+	*/
+	@:require(java6) public static var MIN_EXPONENT(default, null) : Int;
+	
+	/**
+	* The number of bits used to represent a {@code float} value.
+	*
+	* @since 1.5
+	*/
+	@:require(java5) public static var SIZE(default, null) : Int;
+	
+	/**
+	* The {@code Class} instance representing the primitive type
+	* {@code float}.
+	*
+	* @since JDK1.1
+	*/
+	@:require(java1) public static var TYPE(default, null) : Class<Float>;
+	
+	/**
+	* Returns a string representation of the {@code float}
+	* argument. All characters mentioned below are ASCII characters.
+	* <ul>
+	* <li>If the argument is NaN, the result is the string
+	* "{@code NaN}".
+	* <li>Otherwise, the result is a string that represents the sign and
+	*     magnitude (absolute value) of the argument. If the sign is
+	*     negative, the first character of the result is
+	*     '{@code -}' (<code>'&#92;u002D'</code>); if the sign is
+	*     positive, no sign character appears in the result. As for
+	*     the magnitude <i>m</i>:
+	* <ul>
+	* <li>If <i>m</i> is infinity, it is represented by the characters
+	*     {@code "Infinity"}; thus, positive infinity produces
+	*     the result {@code "Infinity"} and negative infinity
+	*     produces the result {@code "-Infinity"}.
+	* <li>If <i>m</i> is zero, it is represented by the characters
+	*     {@code "0.0"}; thus, negative zero produces the result
+	*     {@code "-0.0"} and positive zero produces the result
+	*     {@code "0.0"}.
+	* <li> If <i>m</i> is greater than or equal to 10<sup>-3</sup> but
+	*      less than 10<sup>7</sup>, then it is represented as the
+	*      integer part of <i>m</i>, in decimal form with no leading
+	*      zeroes, followed by '{@code .}'
+	*      (<code>'&#92;u002E'</code>), followed by one or more
+	*      decimal digits representing the fractional part of
+	*      <i>m</i>.
+	* <li> If <i>m</i> is less than 10<sup>-3</sup> or greater than or
+	*      equal to 10<sup>7</sup>, then it is represented in
+	*      so-called "computerized scientific notation." Let <i>n</i>
+	*      be the unique integer such that 10<sup><i>n</i> </sup>&le;
+	*      <i>m</i> {@literal <} 10<sup><i>n</i>+1</sup>; then let <i>a</i>
+	*      be the mathematically exact quotient of <i>m</i> and
+	*      10<sup><i>n</i></sup> so that 1 &le; <i>a</i> {@literal <} 10.
+	*      The magnitude is then represented as the integer part of
+	*      <i>a</i>, as a single decimal digit, followed by
+	*      '{@code .}' (<code>'&#92;u002E'</code>), followed by
+	*      decimal digits representing the fractional part of
+	*      <i>a</i>, followed by the letter '{@code E}'
+	*      (<code>'&#92;u0045'</code>), followed by a representation
+	*      of <i>n</i> as a decimal integer, as produced by the
+	*      method {@link java.lang.Integer#toString(int)}.
+	*
+	* </ul>
+	* </ul>
+	* How many digits must be printed for the fractional part of
+	* <i>m</i> or <i>a</i>? There must be at least one digit
+	* to represent the fractional part, and beyond that as many, but
+	* only as many, more digits as are needed to uniquely distinguish
+	* the argument value from adjacent values of type
+	* {@code float}. That is, suppose that <i>x</i> is the
+	* exact mathematical value represented by the decimal
+	* representation produced by this method for a finite nonzero
+	* argument <i>f</i>. Then <i>f</i> must be the {@code float}
+	* value nearest to <i>x</i>; or, if two {@code float} values are
+	* equally close to <i>x</i>, then <i>f</i> must be one of
+	* them and the least significant bit of the significand of
+	* <i>f</i> must be {@code 0}.
+	*
+	* <p>To create localized string representations of a floating-point
+	* value, use subclasses of {@link java.text.NumberFormat}.
+	*
+	* @param   f   the float to be converted.
+	* @return a string representation of the argument.
+	*/
+	@:native('toString') @:overload public static function _toString(f : Single) : String;
+	
+	/**
+	* Returns a hexadecimal string representation of the
+	* {@code float} argument. All characters mentioned below are
+	* ASCII characters.
+	*
+	* <ul>
+	* <li>If the argument is NaN, the result is the string
+	*     "{@code NaN}".
+	* <li>Otherwise, the result is a string that represents the sign and
+	* magnitude (absolute value) of the argument. If the sign is negative,
+	* the first character of the result is '{@code -}'
+	* (<code>'&#92;u002D'</code>); if the sign is positive, no sign character
+	* appears in the result. As for the magnitude <i>m</i>:
+	*
+	* <ul>
+	* <li>If <i>m</i> is infinity, it is represented by the string
+	* {@code "Infinity"}; thus, positive infinity produces the
+	* result {@code "Infinity"} and negative infinity produces
+	* the result {@code "-Infinity"}.
+	*
+	* <li>If <i>m</i> is zero, it is represented by the string
+	* {@code "0x0.0p0"}; thus, negative zero produces the result
+	* {@code "-0x0.0p0"} and positive zero produces the result
+	* {@code "0x0.0p0"}.
+	*
+	* <li>If <i>m</i> is a {@code float} value with a
+	* normalized representation, substrings are used to represent the
+	* significand and exponent fields.  The significand is
+	* represented by the characters {@code "0x1."}
+	* followed by a lowercase hexadecimal representation of the rest
+	* of the significand as a fraction.  Trailing zeros in the
+	* hexadecimal representation are removed unless all the digits
+	* are zero, in which case a single zero is used. Next, the
+	* exponent is represented by {@code "p"} followed
+	* by a decimal string of the unbiased exponent as if produced by
+	* a call to {@link Integer#toString(int) Integer.toString} on the
+	* exponent value.
+	*
+	* <li>If <i>m</i> is a {@code float} value with a subnormal
+	* representation, the significand is represented by the
+	* characters {@code "0x0."} followed by a
+	* hexadecimal representation of the rest of the significand as a
+	* fraction.  Trailing zeros in the hexadecimal representation are
+	* removed. Next, the exponent is represented by
+	* {@code "p-126"}.  Note that there must be at
+	* least one nonzero digit in a subnormal significand.
+	*
+	* </ul>
+	*
+	* </ul>
+	*
+	* <table border>
+	* <caption><h3>Examples</h3></caption>
+	* <tr><th>Floating-point Value</th><th>Hexadecimal String</th>
+	* <tr><td>{@code 1.0}</td> <td>{@code 0x1.0p0}</td>
+	* <tr><td>{@code -1.0}</td>        <td>{@code -0x1.0p0}</td>
+	* <tr><td>{@code 2.0}</td> <td>{@code 0x1.0p1}</td>
+	* <tr><td>{@code 3.0}</td> <td>{@code 0x1.8p1}</td>
+	* <tr><td>{@code 0.5}</td> <td>{@code 0x1.0p-1}</td>
+	* <tr><td>{@code 0.25}</td>        <td>{@code 0x1.0p-2}</td>
+	* <tr><td>{@code Float.MAX_VALUE}</td>
+	*     <td>{@code 0x1.fffffep127}</td>
+	* <tr><td>{@code Minimum Normal Value}</td>
+	*     <td>{@code 0x1.0p-126}</td>
+	* <tr><td>{@code Maximum Subnormal Value}</td>
+	*     <td>{@code 0x0.fffffep-126}</td>
+	* <tr><td>{@code Float.MIN_VALUE}</td>
+	*     <td>{@code 0x0.000002p-126}</td>
+	* </table>
+	* @param   f   the {@code float} to be converted.
+	* @return a hex string representation of the argument.
+	* @since 1.5
+	* @author Joseph D. Darcy
+	*/
+	@:require(java5) @:overload public static function toHexString(f : Single) : String;
+	
+	/**
+	* Returns a {@code Float} object holding the
+	* {@code float} value represented by the argument string
+	* {@code s}.
+	*
+	* <p>If {@code s} is {@code null}, then a
+	* {@code NullPointerException} is thrown.
+	*
+	* <p>Leading and trailing whitespace characters in {@code s}
+	* are ignored.  Whitespace is removed as if by the {@link
+	* String#trim} method; that is, both ASCII space and control
+	* characters are removed. The rest of {@code s} should
+	* constitute a <i>FloatValue</i> as described by the lexical
+	* syntax rules:
+	*
+	* <blockquote>
+	* <dl>
+	* <dt><i>FloatValue:</i>
+	* <dd><i>Sign<sub>opt</sub></i> {@code NaN}
+	* <dd><i>Sign<sub>opt</sub></i> {@code Infinity}
+	* <dd><i>Sign<sub>opt</sub> FloatingPointLiteral</i>
+	* <dd><i>Sign<sub>opt</sub> HexFloatingPointLiteral</i>
+	* <dd><i>SignedInteger</i>
+	* </dl>
+	*
+	* <p>
+	*
+	* <dl>
+	* <dt><i>HexFloatingPointLiteral</i>:
+	* <dd> <i>HexSignificand BinaryExponent FloatTypeSuffix<sub>opt</sub></i>
+	* </dl>
+	*
+	* <p>
+	*
+	* <dl>
+	* <dt><i>HexSignificand:</i>
+	* <dd><i>HexNumeral</i>
+	* <dd><i>HexNumeral</i> {@code .}
+	* <dd>{@code 0x} <i>HexDigits<sub>opt</sub>
+	*     </i>{@code .}<i> HexDigits</i>
+	* <dd>{@code 0X}<i> HexDigits<sub>opt</sub>
+	*     </i>{@code .} <i>HexDigits</i>
+	* </dl>
+	*
+	* <p>
+	*
+	* <dl>
+	* <dt><i>BinaryExponent:</i>
+	* <dd><i>BinaryExponentIndicator SignedInteger</i>
+	* </dl>
+	*
+	* <p>
+	*
+	* <dl>
+	* <dt><i>BinaryExponentIndicator:</i>
+	* <dd>{@code p}
+	* <dd>{@code P}
+	* </dl>
+	*
+	* </blockquote>
+	*
+	* where <i>Sign</i>, <i>FloatingPointLiteral</i>,
+	* <i>HexNumeral</i>, <i>HexDigits</i>, <i>SignedInteger</i> and
+	* <i>FloatTypeSuffix</i> are as defined in the lexical structure
+	* sections of
+	* <cite>The Java&trade; Language Specification</cite>,
+	* except that underscores are not accepted between digits.
+	* If {@code s} does not have the form of
+	* a <i>FloatValue</i>, then a {@code NumberFormatException}
+	* is thrown. Otherwise, {@code s} is regarded as
+	* representing an exact decimal value in the usual
+	* "computerized scientific notation" or as an exact
+	* hexadecimal value; this exact numerical value is then
+	* conceptually converted to an "infinitely precise"
+	* binary value that is then rounded to type {@code float}
+	* by the usual round-to-nearest rule of IEEE 754 floating-point
+	* arithmetic, which includes preserving the sign of a zero
+	* value.
+	*
+	* Note that the round-to-nearest rule also implies overflow and
+	* underflow behaviour; if the exact value of {@code s} is large
+	* enough in magnitude (greater than or equal to ({@link
+	* #MAX_VALUE} + {@link Math#ulp(float) ulp(MAX_VALUE)}/2),
+	* rounding to {@code float} will result in an infinity and if the
+	* exact value of {@code s} is small enough in magnitude (less
+	* than or equal to {@link #MIN_VALUE}/2), rounding to float will
+	* result in a zero.
+	*
+	* Finally, after rounding a {@code Float} object representing
+	* this {@code float} value is returned.
+	*
+	* <p>To interpret localized string representations of a
+	* floating-point value, use subclasses of {@link
+	* java.text.NumberFormat}.
+	*
+	* <p>Note that trailing format specifiers, specifiers that
+	* determine the type of a floating-point literal
+	* ({@code 1.0f} is a {@code float} value;
+	* {@code 1.0d} is a {@code double} value), do
+	* <em>not</em> influence the results of this method.  In other
+	* words, the numerical value of the input string is converted
+	* directly to the target floating-point type.  In general, the
+	* two-step sequence of conversions, string to {@code double}
+	* followed by {@code double} to {@code float}, is
+	* <em>not</em> equivalent to converting a string directly to
+	* {@code float}.  For example, if first converted to an
+	* intermediate {@code double} and then to
+	* {@code float}, the string<br>
+	* {@code "1.00000017881393421514957253748434595763683319091796875001d"}<br>
+	* results in the {@code float} value
+	* {@code 1.0000002f}; if the string is converted directly to
+	* {@code float}, <code>1.000000<b>1</b>f</code> results.
+	*
+	* <p>To avoid calling this method on an invalid string and having
+	* a {@code NumberFormatException} be thrown, the documentation
+	* for {@link Double#valueOf Double.valueOf} lists a regular
+	* expression which can be used to screen the input.
+	*
+	* @param   s   the string to be parsed.
+	* @return  a {@code Float} object holding the value
+	*          represented by the {@code String} argument.
+	* @throws  NumberFormatException  if the string does not contain a
+	*          parsable number.
+	*/
+	@:overload public static function valueOf(s : String) : Float;
+	
+	/**
+	* Returns a {@code Float} instance representing the specified
+	* {@code float} value.
+	* If a new {@code Float} instance is not required, this method
+	* should generally be used in preference to the constructor
+	* {@link #Float(float)}, as this method is likely to yield
+	* significantly better space and time performance by caching
+	* frequently requested values.
+	*
+	* @param  f a float value.
+	* @return a {@code Float} instance representing {@code f}.
+	* @since  1.5
+	*/
+	@:require(java5) @:overload public static function valueOf(f : Single) : Float;
+	
+	/**
+	* Returns a new {@code float} initialized to the value
+	* represented by the specified {@code String}, as performed
+	* by the {@code valueOf} method of class {@code Float}.
+	*
+	* @param  s the string to be parsed.
+	* @return the {@code float} value represented by the string
+	*         argument.
+	* @throws NullPointerException  if the string is null
+	* @throws NumberFormatException if the string does not contain a
+	*               parsable {@code float}.
+	* @see    java.lang.Float#valueOf(String)
+	* @since 1.2
+	*/
+	@:require(java2) @:overload public static function parseFloat(s : String) : Single;
+	
+	/**
+	* Returns {@code true} if the specified number is a
+	* Not-a-Number (NaN) value, {@code false} otherwise.
+	*
+	* @param   v   the value to be tested.
+	* @return  {@code true} if the argument is NaN;
+	*          {@code false} otherwise.
+	*/
+	@:native('isNaN') @:overload public static function _isNaN(v : Single) : Bool;
+	
+	/**
+	* Returns {@code true} if the specified number is infinitely
+	* large in magnitude, {@code false} otherwise.
+	*
+	* @param   v   the value to be tested.
+	* @return  {@code true} if the argument is positive infinity or
+	*          negative infinity; {@code false} otherwise.
+	*/
+	@:native('isInfinite') @:overload public static function _isInfinite(v : Single) : Bool;
+	
+	/**
+	* Constructs a newly allocated {@code Float} object that
+	* represents the primitive {@code float} argument.
+	*
+	* @param   value   the value to be represented by the {@code Float}.
+	*/
+	@:overload public function new(value : Single) : Void;
+	
+	/**
+	* Constructs a newly allocated {@code Float} object that
+	* represents the argument converted to type {@code float}.
+	*
+	* @param   value   the value to be represented by the {@code Float}.
+	*/
+	@:overload public function new(value : Float) : Void;
+	
+	/**
+	* Constructs a newly allocated {@code Float} object that
+	* represents the floating-point value of type {@code float}
+	* represented by the string. The string is converted to a
+	* {@code float} value as if by the {@code valueOf} method.
+	*
+	* @param      s   a string to be converted to a {@code Float}.
+	* @throws  NumberFormatException  if the string does not contain a
+	*               parsable number.
+	* @see        java.lang.Float#valueOf(java.lang.String)
+	*/
+	@:overload public function new(s : String) : Void;
+	
+	/**
+	* Returns {@code true} if this {@code Float} value is a
+	* Not-a-Number (NaN), {@code false} otherwise.
+	*
+	* @return  {@code true} if the value represented by this object is
+	*          NaN; {@code false} otherwise.
+	*/
+	@:overload public function isNaN() : Bool;
+	
+	/**
+	* Returns {@code true} if this {@code Float} value is
+	* infinitely large in magnitude, {@code false} otherwise.
+	*
+	* @return  {@code true} if the value represented by this object is
+	*          positive infinity or negative infinity;
+	*          {@code false} otherwise.
+	*/
+	@:overload public function isInfinite() : Bool;
+	
+	/**
+	* Returns a string representation of this {@code Float} object.
+	* The primitive {@code float} value represented by this object
+	* is converted to a {@code String} exactly as if by the method
+	* {@code toString} of one argument.
+	*
+	* @return  a {@code String} representation of this object.
+	* @see java.lang.Float#toString(float)
+	*/
+	@:overload public function toString() : String;
+	
+	/**
+	* Returns the value of this {@code Float} as a {@code byte} (by
+	* casting to a {@code byte}).
+	*
+	* @return  the {@code float} value represented by this object
+	*          converted to type {@code byte}
+	*/
+	@:overload override public function byteValue() : java.StdTypes.Int8;
+	
+	/**
+	* Returns the value of this {@code Float} as a {@code short} (by
+	* casting to a {@code short}).
+	*
+	* @return  the {@code float} value represented by this object
+	*          converted to type {@code short}
+	* @since JDK1.1
+	*/
+	@:require(java1) @:overload override public function shortValue() : java.StdTypes.Int16;
+	
+	/**
+	* Returns the value of this {@code Float} as an {@code int} (by
+	* casting to type {@code int}).
+	*
+	* @return  the {@code float} value represented by this object
+	*          converted to type {@code int}
+	*/
+	@:overload override public function intValue() : Int;
+	
+	/**
+	* Returns value of this {@code Float} as a {@code long} (by
+	* casting to type {@code long}).
+	*
+	* @return  the {@code float} value represented by this object
+	*          converted to type {@code long}
+	*/
+	@:overload override public function longValue() : haxe.Int64;
+	
+	/**
+	* Returns the {@code float} value of this {@code Float} object.
+	*
+	* @return the {@code float} value represented by this object
+	*/
+	@:overload override public function floatValue() : Single;
+	
+	/**
+	* Returns the {@code double} value of this {@code Float} object.
+	*
+	* @return the {@code float} value represented by this
+	*         object is converted to type {@code double} and the
+	*         result of the conversion is returned.
+	*/
+	@:overload override public function doubleValue() : Float;
+	
+	/**
+	* Returns a hash code for this {@code Float} object. The
+	* result is the integer bit representation, exactly as produced
+	* by the method {@link #floatToIntBits(float)}, of the primitive
+	* {@code float} value represented by this {@code Float}
+	* object.
+	*
+	* @return a hash code value for this object.
+	*/
+	@:overload public function hashCode() : Int;
+	
+	/**
+
+	* Compares this object against the specified object.  The result
+	* is {@code true} if and only if the argument is not
+	* {@code null} and is a {@code Float} object that
+	* represents a {@code float} with the same value as the
+	* {@code float} represented by this object. For this
+	* purpose, two {@code float} values are considered to be the
+	* same if and only if the method {@link #floatToIntBits(float)}
+	* returns the identical {@code int} value when applied to
+	* each.
+	*
+	* <p>Note that in most cases, for two instances of class
+	* {@code Float}, {@code f1} and {@code f2}, the value
+	* of {@code f1.equals(f2)} is {@code true} if and only if
+	*
+	* <blockquote><pre>
+	*   f1.floatValue() == f2.floatValue()
+	* </pre></blockquote>
+	*
+	* <p>also has the value {@code true}. However, there are two exceptions:
+	* <ul>
+	* <li>If {@code f1} and {@code f2} both represent
+	*     {@code Float.NaN}, then the {@code equals} method returns
+	*     {@code true}, even though {@code Float.NaN==Float.NaN}
+	*     has the value {@code false}.
+	* <li>If {@code f1} represents {@code +0.0f} while
+	*     {@code f2} represents {@code -0.0f}, or vice
+	*     versa, the {@code equal} test has the value
+	*     {@code false}, even though {@code 0.0f==-0.0f}
+	*     has the value {@code true}.
+	* </ul>
+	*
+	* This definition allows hash tables to operate properly.
+	*
+	* @param obj the object to be compared
+	* @return  {@code true} if the objects are the same;
+	*          {@code false} otherwise.
+	* @see java.lang.Float#floatToIntBits(float)
+	*/
+	@:overload public function equals(obj : Dynamic) : Bool;
+	
+	/**
+	* Returns a representation of the specified floating-point value
+	* according to the IEEE 754 floating-point "single format" bit
+	* layout.
+	*
+	* <p>Bit 31 (the bit that is selected by the mask
+	* {@code 0x80000000}) represents the sign of the floating-point
+	* number.
+	* Bits 30-23 (the bits that are selected by the mask
+	* {@code 0x7f800000}) represent the exponent.
+	* Bits 22-0 (the bits that are selected by the mask
+	* {@code 0x007fffff}) represent the significand (sometimes called
+	* the mantissa) of the floating-point number.
+	*
+	* <p>If the argument is positive infinity, the result is
+	* {@code 0x7f800000}.
+	*
+	* <p>If the argument is negative infinity, the result is
+	* {@code 0xff800000}.
+	*
+	* <p>If the argument is NaN, the result is {@code 0x7fc00000}.
+	*
+	* <p>In all cases, the result is an integer that, when given to the
+	* {@link #intBitsToFloat(int)} method, will produce a floating-point
+	* value the same as the argument to {@code floatToIntBits}
+	* (except all NaN values are collapsed to a single
+	* "canonical" NaN value).
+	*
+	* @param   value   a floating-point number.
+	* @return the bits that represent the floating-point number.
+	*/
+	@:overload public static function floatToIntBits(value : Single) : Int;
+	
+	/**
+	* Returns a representation of the specified floating-point value
+	* according to the IEEE 754 floating-point "single format" bit
+	* layout, preserving Not-a-Number (NaN) values.
+	*
+	* <p>Bit 31 (the bit that is selected by the mask
+	* {@code 0x80000000}) represents the sign of the floating-point
+	* number.
+	* Bits 30-23 (the bits that are selected by the mask
+	* {@code 0x7f800000}) represent the exponent.
+	* Bits 22-0 (the bits that are selected by the mask
+	* {@code 0x007fffff}) represent the significand (sometimes called
+	* the mantissa) of the floating-point number.
+	*
+	* <p>If the argument is positive infinity, the result is
+	* {@code 0x7f800000}.
+	*
+	* <p>If the argument is negative infinity, the result is
+	* {@code 0xff800000}.
+	*
+	* <p>If the argument is NaN, the result is the integer representing
+	* the actual NaN value.  Unlike the {@code floatToIntBits}
+	* method, {@code floatToRawIntBits} does not collapse all the
+	* bit patterns encoding a NaN to a single "canonical"
+	* NaN value.
+	*
+	* <p>In all cases, the result is an integer that, when given to the
+	* {@link #intBitsToFloat(int)} method, will produce a
+	* floating-point value the same as the argument to
+	* {@code floatToRawIntBits}.
+	*
+	* @param   value   a floating-point number.
+	* @return the bits that represent the floating-point number.
+	* @since 1.3
+	*/
+	@:require(java3) @:overload @:native public static function floatToRawIntBits(value : Single) : Int;
+	
+	/**
+	* Returns the {@code float} value corresponding to a given
+	* bit representation.
+	* The argument is considered to be a representation of a
+	* floating-point value according to the IEEE 754 floating-point
+	* "single format" bit layout.
+	*
+	* <p>If the argument is {@code 0x7f800000}, the result is positive
+	* infinity.
+	*
+	* <p>If the argument is {@code 0xff800000}, the result is negative
+	* infinity.
+	*
+	* <p>If the argument is any value in the range
+	* {@code 0x7f800001} through {@code 0x7fffffff} or in
+	* the range {@code 0xff800001} through
+	* {@code 0xffffffff}, the result is a NaN.  No IEEE 754
+	* floating-point operation provided by Java can distinguish
+	* between two NaN values of the same type with different bit
+	* patterns.  Distinct values of NaN are only distinguishable by
+	* use of the {@code Float.floatToRawIntBits} method.
+	*
+	* <p>In all other cases, let <i>s</i>, <i>e</i>, and <i>m</i> be three
+	* values that can be computed from the argument:
+	*
+	* <blockquote><pre>
+	* int s = ((bits &gt;&gt; 31) == 0) ? 1 : -1;
+	* int e = ((bits &gt;&gt; 23) & 0xff);
+	* int m = (e == 0) ?
+	*                 (bits & 0x7fffff) &lt;&lt; 1 :
+	*                 (bits & 0x7fffff) | 0x800000;
+	* </pre></blockquote>
+	*
+	* Then the floating-point result equals the value of the mathematical
+	* expression <i>s</i>&middot;<i>m</i>&middot;2<sup><i>e</i>-150</sup>.
+	*
+	* <p>Note that this method may not be able to return a
+	* {@code float} NaN with exactly same bit pattern as the
+	* {@code int} argument.  IEEE 754 distinguishes between two
+	* kinds of NaNs, quiet NaNs and <i>signaling NaNs</i>.  The
+	* differences between the two kinds of NaN are generally not
+	* visible in Java.  Arithmetic operations on signaling NaNs turn
+	* them into quiet NaNs with a different, but often similar, bit
+	* pattern.  However, on some processors merely copying a
+	* signaling NaN also performs that conversion.  In particular,
+	* copying a signaling NaN to return it to the calling method may
+	* perform this conversion.  So {@code intBitsToFloat} may
+	* not be able to return a {@code float} with a signaling NaN
+	* bit pattern.  Consequently, for some {@code int} values,
+	* {@code floatToRawIntBits(intBitsToFloat(start))} may
+	* <i>not</i> equal {@code start}.  Moreover, which
+	* particular bit patterns represent signaling NaNs is platform
+	* dependent; although all NaN bit patterns, quiet or signaling,
+	* must be in the NaN range identified above.
+	*
+	* @param   bits   an integer.
+	* @return  the {@code float} floating-point value with the same bit
+	*          pattern.
+	*/
+	@:overload @:native public static function intBitsToFloat(bits : Int) : Single;
+	
+	/**
+	* Compares two {@code Float} objects numerically.  There are
+	* two ways in which comparisons performed by this method differ
+	* from those performed by the Java language numerical comparison
+	* operators ({@code <, <=, ==, >=, >}) when
+	* applied to primitive {@code float} values:
+	*
+	* <ul><li>
+	*          {@code Float.NaN} is considered by this method to
+	*          be equal to itself and greater than all other
+	*          {@code float} values
+	*          (including {@code Float.POSITIVE_INFINITY}).
+	* <li>
+	*          {@code 0.0f} is considered by this method to be greater
+	*          than {@code -0.0f}.
+	* </ul>
+	*
+	* This ensures that the <i>natural ordering</i> of {@code Float}
+	* objects imposed by this method is <i>consistent with equals</i>.
+	*
+	* @param   anotherFloat   the {@code Float} to be compared.
+	* @return  the value {@code 0} if {@code anotherFloat} is
+	*          numerically equal to this {@code Float}; a value
+	*          less than {@code 0} if this {@code Float}
+	*          is numerically less than {@code anotherFloat};
+	*          and a value greater than {@code 0} if this
+	*          {@code Float} is numerically greater than
+	*          {@code anotherFloat}.
+	*
+	* @since   1.2
+	* @see Comparable#compareTo(Object)
+	*/
+	@:require(java2) @:overload public function compareTo(anotherFloat : Float) : Int;
+	
+	/**
+	* Compares the two specified {@code float} values. The sign
+	* of the integer value returned is the same as that of the
+	* integer that would be returned by the call:
+	* <pre>
+	*    new Float(f1).compareTo(new Float(f2))
+	* </pre>
+	*
+	* @param   f1        the first {@code float} to compare.
+	* @param   f2        the second {@code float} to compare.
+	* @return  the value {@code 0} if {@code f1} is
+	*          numerically equal to {@code f2}; a value less than
+	*          {@code 0} if {@code f1} is numerically less than
+	*          {@code f2}; and a value greater than {@code 0}
+	*          if {@code f1} is numerically greater than
+	*          {@code f2}.
+	* @since 1.4
+	*/
+	@:require(java4) @:overload public static function compare(f1 : Single, f2 : Single) : Int;
+	
+	
+}

+ 796 - 0
std/java/lang/Integer.hx

@@ -0,0 +1,796 @@
+package java.lang;
+/*
+* Copyright (c) 1994, 2010, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* The {@code Integer} class wraps a value of the primitive type
+* {@code int} in an object. An object of type {@code Integer}
+* contains a single field whose type is {@code int}.
+*
+* <p>In addition, this class provides several methods for converting
+* an {@code int} to a {@code String} and a {@code String} to an
+* {@code int}, as well as other constants and methods useful when
+* dealing with an {@code int}.
+*
+* <p>Implementation note: The implementations of the "bit twiddling"
+* methods (such as {@link #highestOneBit(int) highestOneBit} and
+* {@link #numberOfTrailingZeros(int) numberOfTrailingZeros}) are
+* based on material from Henry S. Warren, Jr.'s <i>Hacker's
+* Delight</i>, (Addison Wesley, 2002).
+*
+* @author  Lee Boynton
+* @author  Arthur van Hoff
+* @author  Josh Bloch
+* @author  Joseph D. Darcy
+* @since JDK1.0
+*/
+@:require(java0) extern class Integer extends java.lang.Number implements java.lang.Comparable<Integer>
+{
+	/**
+	* A constant holding the minimum value an {@code int} can
+	* have, -2<sup>31</sup>.
+	*/
+	public static var MIN_VALUE(default, null) : Int;
+	
+	/**
+	* A constant holding the maximum value an {@code int} can
+	* have, 2<sup>31</sup>-1.
+	*/
+	public static var MAX_VALUE(default, null) : Int;
+	
+	/**
+	* The {@code Class} instance representing the primitive type
+	* {@code int}.
+	*
+	* @since   JDK1.1
+	*/
+	@:require(java1) public static var TYPE(default, null) : Class<Integer>;
+	
+	/**
+	* Returns a string representation of the first argument in the
+	* radix specified by the second argument.
+	*
+	* <p>If the radix is smaller than {@code Character.MIN_RADIX}
+	* or larger than {@code Character.MAX_RADIX}, then the radix
+	* {@code 10} is used instead.
+	*
+	* <p>If the first argument is negative, the first element of the
+	* result is the ASCII minus character {@code '-'}
+	* (<code>'&#92;u002D'</code>). If the first argument is not
+	* negative, no sign character appears in the result.
+	*
+	* <p>The remaining characters of the result represent the magnitude
+	* of the first argument. If the magnitude is zero, it is
+	* represented by a single zero character {@code '0'}
+	* (<code>'&#92;u0030'</code>); otherwise, the first character of
+	* the representation of the magnitude will not be the zero
+	* character.  The following ASCII characters are used as digits:
+	*
+	* <blockquote>
+	*   {@code 0123456789abcdefghijklmnopqrstuvwxyz}
+	* </blockquote>
+	*
+	* These are <code>'&#92;u0030'</code> through
+	* <code>'&#92;u0039'</code> and <code>'&#92;u0061'</code> through
+	* <code>'&#92;u007A'</code>. If {@code radix} is
+	* <var>N</var>, then the first <var>N</var> of these characters
+	* are used as radix-<var>N</var> digits in the order shown. Thus,
+	* the digits for hexadecimal (radix 16) are
+	* {@code 0123456789abcdef}. If uppercase letters are
+	* desired, the {@link java.lang.String#toUpperCase()} method may
+	* be called on the result:
+	*
+	* <blockquote>
+	*  {@code Integer.toString(n, 16).toUpperCase()}
+	* </blockquote>
+	*
+	* @param   i       an integer to be converted to a string.
+	* @param   radix   the radix to use in the string representation.
+	* @return  a string representation of the argument in the specified radix.
+	* @see     java.lang.Character#MAX_RADIX
+	* @see     java.lang.Character#MIN_RADIX
+	*/
+	@:native('toString') @:overload public static function _toString(i : Int, radix : Int) : String;
+	
+	/**
+	* Returns a string representation of the integer argument as an
+	* unsigned integer in base&nbsp;16.
+	*
+	* <p>The unsigned integer value is the argument plus 2<sup>32</sup>
+	* if the argument is negative; otherwise, it is equal to the
+	* argument.  This value is converted to a string of ASCII digits
+	* in hexadecimal (base&nbsp;16) with no extra leading
+	* {@code 0}s. If the unsigned magnitude is zero, it is
+	* represented by a single zero character {@code '0'}
+	* (<code>'&#92;u0030'</code>); otherwise, the first character of
+	* the representation of the unsigned magnitude will not be the
+	* zero character. The following characters are used as
+	* hexadecimal digits:
+	*
+	* <blockquote>
+	*  {@code 0123456789abcdef}
+	* </blockquote>
+	*
+	* These are the characters <code>'&#92;u0030'</code> through
+	* <code>'&#92;u0039'</code> and <code>'&#92;u0061'</code> through
+	* <code>'&#92;u0066'</code>. If uppercase letters are
+	* desired, the {@link java.lang.String#toUpperCase()} method may
+	* be called on the result:
+	*
+	* <blockquote>
+	*  {@code Integer.toHexString(n).toUpperCase()}
+	* </blockquote>
+	*
+	* @param   i   an integer to be converted to a string.
+	* @return  the string representation of the unsigned integer value
+	*          represented by the argument in hexadecimal (base&nbsp;16).
+	* @since   JDK1.0.2
+	*/
+	@:require(java0) @:overload public static function toHexString(i : Int) : String;
+	
+	/**
+	* Returns a string representation of the integer argument as an
+	* unsigned integer in base&nbsp;8.
+	*
+	* <p>The unsigned integer value is the argument plus 2<sup>32</sup>
+	* if the argument is negative; otherwise, it is equal to the
+	* argument.  This value is converted to a string of ASCII digits
+	* in octal (base&nbsp;8) with no extra leading {@code 0}s.
+	*
+	* <p>If the unsigned magnitude is zero, it is represented by a
+	* single zero character {@code '0'}
+	* (<code>'&#92;u0030'</code>); otherwise, the first character of
+	* the representation of the unsigned magnitude will not be the
+	* zero character. The following characters are used as octal
+	* digits:
+	*
+	* <blockquote>
+	* {@code 01234567}
+	* </blockquote>
+	*
+	* These are the characters <code>'&#92;u0030'</code> through
+	* <code>'&#92;u0037'</code>.
+	*
+	* @param   i   an integer to be converted to a string.
+	* @return  the string representation of the unsigned integer value
+	*          represented by the argument in octal (base&nbsp;8).
+	* @since   JDK1.0.2
+	*/
+	@:require(java0) @:overload public static function toOctalString(i : Int) : String;
+	
+	/**
+	* Returns a string representation of the integer argument as an
+	* unsigned integer in base&nbsp;2.
+	*
+	* <p>The unsigned integer value is the argument plus 2<sup>32</sup>
+	* if the argument is negative; otherwise it is equal to the
+	* argument.  This value is converted to a string of ASCII digits
+	* in binary (base&nbsp;2) with no extra leading {@code 0}s.
+	* If the unsigned magnitude is zero, it is represented by a
+	* single zero character {@code '0'}
+	* (<code>'&#92;u0030'</code>); otherwise, the first character of
+	* the representation of the unsigned magnitude will not be the
+	* zero character. The characters {@code '0'}
+	* (<code>'&#92;u0030'</code>) and {@code '1'}
+	* (<code>'&#92;u0031'</code>) are used as binary digits.
+	*
+	* @param   i   an integer to be converted to a string.
+	* @return  the string representation of the unsigned integer value
+	*          represented by the argument in binary (base&nbsp;2).
+	* @since   JDK1.0.2
+	*/
+	@:require(java0) @:overload public static function toBinaryString(i : Int) : String;
+	
+	/**
+	* Returns a {@code String} object representing the
+	* specified integer. The argument is converted to signed decimal
+	* representation and returned as a string, exactly as if the
+	* argument and radix 10 were given as arguments to the {@link
+	* #toString(int, int)} method.
+	*
+	* @param   i   an integer to be converted.
+	* @return  a string representation of the argument in base&nbsp;10.
+	*/
+	@:native('toString') @:overload public static function _toString(i : Int) : String;
+	
+	/**
+	* Parses the string argument as a signed integer in the radix
+	* specified by the second argument. The characters in the string
+	* must all be digits of the specified radix (as determined by
+	* whether {@link java.lang.Character#digit(char, int)} returns a
+	* nonnegative value), except that the first character may be an
+	* ASCII minus sign {@code '-'} (<code>'&#92;u002D'</code>) to
+	* indicate a negative value or an ASCII plus sign {@code '+'}
+	* (<code>'&#92;u002B'</code>) to indicate a positive value. The
+	* resulting integer value is returned.
+	*
+	* <p>An exception of type {@code NumberFormatException} is
+	* thrown if any of the following situations occurs:
+	* <ul>
+	* <li>The first argument is {@code null} or is a string of
+	* length zero.
+	*
+	* <li>The radix is either smaller than
+	* {@link java.lang.Character#MIN_RADIX} or
+	* larger than {@link java.lang.Character#MAX_RADIX}.
+	*
+	* <li>Any character of the string is not a digit of the specified
+	* radix, except that the first character may be a minus sign
+	* {@code '-'} (<code>'&#92;u002D'</code>) or plus sign
+	* {@code '+'} (<code>'&#92;u002B'</code>) provided that the
+	* string is longer than length 1.
+	*
+	* <li>The value represented by the string is not a value of type
+	* {@code int}.
+	* </ul>
+	*
+	* <p>Examples:
+	* <blockquote><pre>
+	* parseInt("0", 10) returns 0
+	* parseInt("473", 10) returns 473
+	* parseInt("+42", 10) returns 42
+	* parseInt("-0", 10) returns 0
+	* parseInt("-FF", 16) returns -255
+	* parseInt("1100110", 2) returns 102
+	* parseInt("2147483647", 10) returns 2147483647
+	* parseInt("-2147483648", 10) returns -2147483648
+	* parseInt("2147483648", 10) throws a NumberFormatException
+	* parseInt("99", 8) throws a NumberFormatException
+	* parseInt("Kona", 10) throws a NumberFormatException
+	* parseInt("Kona", 27) returns 411787
+	* </pre></blockquote>
+	*
+	* @param      s   the {@code String} containing the integer
+	*                  representation to be parsed
+	* @param      radix   the radix to be used while parsing {@code s}.
+	* @return     the integer represented by the string argument in the
+	*             specified radix.
+	* @exception  NumberFormatException if the {@code String}
+	*             does not contain a parsable {@code int}.
+	*/
+	@:overload public static function parseInt(s : String, radix : Int) : Int;
+	
+	/**
+	* Parses the string argument as a signed decimal integer. The
+	* characters in the string must all be decimal digits, except
+	* that the first character may be an ASCII minus sign {@code '-'}
+	* (<code>'&#92;u002D'</code>) to indicate a negative value or an
+	* ASCII plus sign {@code '+'} (<code>'&#92;u002B'</code>) to
+	* indicate a positive value. The resulting integer value is
+	* returned, exactly as if the argument and the radix 10 were
+	* given as arguments to the {@link #parseInt(java.lang.String,
+	* int)} method.
+	*
+	* @param s    a {@code String} containing the {@code int}
+	*             representation to be parsed
+	* @return     the integer value represented by the argument in decimal.
+	* @exception  NumberFormatException  if the string does not contain a
+	*               parsable integer.
+	*/
+	@:overload public static function parseInt(s : String) : Int;
+	
+	/**
+	* Returns an {@code Integer} object holding the value
+	* extracted from the specified {@code String} when parsed
+	* with the radix given by the second argument. The first argument
+	* is interpreted as representing a signed integer in the radix
+	* specified by the second argument, exactly as if the arguments
+	* were given to the {@link #parseInt(java.lang.String, int)}
+	* method. The result is an {@code Integer} object that
+	* represents the integer value specified by the string.
+	*
+	* <p>In other words, this method returns an {@code Integer}
+	* object equal to the value of:
+	*
+	* <blockquote>
+	*  {@code new Integer(Integer.parseInt(s, radix))}
+	* </blockquote>
+	*
+	* @param      s   the string to be parsed.
+	* @param      radix the radix to be used in interpreting {@code s}
+	* @return     an {@code Integer} object holding the value
+	*             represented by the string argument in the specified
+	*             radix.
+	* @exception NumberFormatException if the {@code String}
+	*            does not contain a parsable {@code int}.
+	*/
+	@:overload public static function valueOf(s : String, radix : Int) : Integer;
+	
+	/**
+	* Returns an {@code Integer} object holding the
+	* value of the specified {@code String}. The argument is
+	* interpreted as representing a signed decimal integer, exactly
+	* as if the argument were given to the {@link
+	* #parseInt(java.lang.String)} method. The result is an
+	* {@code Integer} object that represents the integer value
+	* specified by the string.
+	*
+	* <p>In other words, this method returns an {@code Integer}
+	* object equal to the value of:
+	*
+	* <blockquote>
+	*  {@code new Integer(Integer.parseInt(s))}
+	* </blockquote>
+	*
+	* @param      s   the string to be parsed.
+	* @return     an {@code Integer} object holding the value
+	*             represented by the string argument.
+	* @exception  NumberFormatException  if the string cannot be parsed
+	*             as an integer.
+	*/
+	@:overload public static function valueOf(s : String) : Integer;
+	
+	/**
+	* Returns an {@code Integer} instance representing the specified
+	* {@code int} value.  If a new {@code Integer} instance is not
+	* required, this method should generally be used in preference to
+	* the constructor {@link #Integer(int)}, as this method is likely
+	* to yield significantly better space and time performance by
+	* caching frequently requested values.
+	*
+	* This method will always cache values in the range -128 to 127,
+	* inclusive, and may cache other values outside of this range.
+	*
+	* @param  i an {@code int} value.
+	* @return an {@code Integer} instance representing {@code i}.
+	* @since  1.5
+	*/
+	@:require(java5) @:overload public static function valueOf(i : Int) : Integer;
+	
+	/**
+	* Constructs a newly allocated {@code Integer} object that
+	* represents the specified {@code int} value.
+	*
+	* @param   value   the value to be represented by the
+	*                  {@code Integer} object.
+	*/
+	@:overload public function new(value : Int) : Void;
+	
+	/**
+	* Constructs a newly allocated {@code Integer} object that
+	* represents the {@code int} value indicated by the
+	* {@code String} parameter. The string is converted to an
+	* {@code int} value in exactly the manner used by the
+	* {@code parseInt} method for radix 10.
+	*
+	* @param      s   the {@code String} to be converted to an
+	*                 {@code Integer}.
+	* @exception  NumberFormatException  if the {@code String} does not
+	*               contain a parsable integer.
+	* @see        java.lang.Integer#parseInt(java.lang.String, int)
+	*/
+	@:overload public function new(s : String) : Void;
+	
+	/**
+	* Returns the value of this {@code Integer} as a
+	* {@code byte}.
+	*/
+	@:overload override public function byteValue() : java.StdTypes.Int8;
+	
+	/**
+	* Returns the value of this {@code Integer} as a
+	* {@code short}.
+	*/
+	@:overload override public function shortValue() : java.StdTypes.Int16;
+	
+	/**
+	* Returns the value of this {@code Integer} as an
+	* {@code int}.
+	*/
+	@:overload override public function intValue() : Int;
+	
+	/**
+	* Returns the value of this {@code Integer} as a
+	* {@code long}.
+	*/
+	@:overload override public function longValue() : haxe.Int64;
+	
+	/**
+	* Returns the value of this {@code Integer} as a
+	* {@code float}.
+	*/
+	@:overload override public function floatValue() : Single;
+	
+	/**
+	* Returns the value of this {@code Integer} as a
+	* {@code double}.
+	*/
+	@:overload override public function doubleValue() : Float;
+	
+	/**
+	* Returns a {@code String} object representing this
+	* {@code Integer}'s value. The value is converted to signed
+	* decimal representation and returned as a string, exactly as if
+	* the integer value were given as an argument to the {@link
+	* java.lang.Integer#toString(int)} method.
+	*
+	* @return  a string representation of the value of this object in
+	*          base&nbsp;10.
+	*/
+	@:overload public function toString() : String;
+	
+	/**
+	* Returns a hash code for this {@code Integer}.
+	*
+	* @return  a hash code value for this object, equal to the
+	*          primitive {@code int} value represented by this
+	*          {@code Integer} object.
+	*/
+	@:overload public function hashCode() : Int;
+	
+	/**
+	* Compares this object to the specified object.  The result is
+	* {@code true} if and only if the argument is not
+	* {@code null} and is an {@code Integer} object that
+	* contains the same {@code int} value as this object.
+	*
+	* @param   obj   the object to compare with.
+	* @return  {@code true} if the objects are the same;
+	*          {@code false} otherwise.
+	*/
+	@:overload public function equals(obj : Dynamic) : Bool;
+	
+	/**
+	* Determines the integer value of the system property with the
+	* specified name.
+	*
+	* <p>The first argument is treated as the name of a system property.
+	* System properties are accessible through the
+	* {@link java.lang.System#getProperty(java.lang.String)} method. The
+	* string value of this property is then interpreted as an integer
+	* value and an {@code Integer} object representing this value is
+	* returned. Details of possible numeric formats can be found with
+	* the definition of {@code getProperty}.
+	*
+	* <p>If there is no property with the specified name, if the specified name
+	* is empty or {@code null}, or if the property does not have
+	* the correct numeric format, then {@code null} is returned.
+	*
+	* <p>In other words, this method returns an {@code Integer}
+	* object equal to the value of:
+	*
+	* <blockquote>
+	*  {@code getInteger(nm, null)}
+	* </blockquote>
+	*
+	* @param   nm   property name.
+	* @return  the {@code Integer} value of the property.
+	* @see     java.lang.System#getProperty(java.lang.String)
+	* @see     java.lang.System#getProperty(java.lang.String, java.lang.String)
+	*/
+	@:overload public static function getInteger(nm : String) : Integer;
+	
+	/**
+	* Determines the integer value of the system property with the
+	* specified name.
+	*
+	* <p>The first argument is treated as the name of a system property.
+	* System properties are accessible through the {@link
+	* java.lang.System#getProperty(java.lang.String)} method. The
+	* string value of this property is then interpreted as an integer
+	* value and an {@code Integer} object representing this value is
+	* returned. Details of possible numeric formats can be found with
+	* the definition of {@code getProperty}.
+	*
+	* <p>The second argument is the default value. An {@code Integer} object
+	* that represents the value of the second argument is returned if there
+	* is no property of the specified name, if the property does not have
+	* the correct numeric format, or if the specified name is empty or
+	* {@code null}.
+	*
+	* <p>In other words, this method returns an {@code Integer} object
+	* equal to the value of:
+	*
+	* <blockquote>
+	*  {@code getInteger(nm, new Integer(val))}
+	* </blockquote>
+	*
+	* but in practice it may be implemented in a manner such as:
+	*
+	* <blockquote><pre>
+	* Integer result = getInteger(nm, null);
+	* return (result == null) ? new Integer(val) : result;
+	* </pre></blockquote>
+	*
+	* to avoid the unnecessary allocation of an {@code Integer}
+	* object when the default value is not needed.
+	*
+	* @param   nm   property name.
+	* @param   val   default value.
+	* @return  the {@code Integer} value of the property.
+	* @see     java.lang.System#getProperty(java.lang.String)
+	* @see     java.lang.System#getProperty(java.lang.String, java.lang.String)
+	*/
+	@:overload public static function getInteger(nm : String, val : Int) : Integer;
+	
+	/**
+	* Returns the integer value of the system property with the
+	* specified name.  The first argument is treated as the name of a
+	* system property.  System properties are accessible through the
+	* {@link java.lang.System#getProperty(java.lang.String)} method.
+	* The string value of this property is then interpreted as an
+	* integer value, as per the {@code Integer.decode} method,
+	* and an {@code Integer} object representing this value is
+	* returned.
+	*
+	* <ul><li>If the property value begins with the two ASCII characters
+	*         {@code 0x} or the ASCII character {@code #}, not
+	*      followed by a minus sign, then the rest of it is parsed as a
+	*      hexadecimal integer exactly as by the method
+	*      {@link #valueOf(java.lang.String, int)} with radix 16.
+	* <li>If the property value begins with the ASCII character
+	*     {@code 0} followed by another character, it is parsed as an
+	*     octal integer exactly as by the method
+	*     {@link #valueOf(java.lang.String, int)} with radix 8.
+	* <li>Otherwise, the property value is parsed as a decimal integer
+	* exactly as by the method {@link #valueOf(java.lang.String, int)}
+	* with radix 10.
+	* </ul>
+	*
+	* <p>The second argument is the default value. The default value is
+	* returned if there is no property of the specified name, if the
+	* property does not have the correct numeric format, or if the
+	* specified name is empty or {@code null}.
+	*
+	* @param   nm   property name.
+	* @param   val   default value.
+	* @return  the {@code Integer} value of the property.
+	* @see     java.lang.System#getProperty(java.lang.String)
+	* @see java.lang.System#getProperty(java.lang.String, java.lang.String)
+	* @see java.lang.Integer#decode
+	*/
+	@:overload public static function getInteger(nm : String, val : Integer) : Integer;
+	
+	/**
+	* Decodes a {@code String} into an {@code Integer}.
+	* Accepts decimal, hexadecimal, and octal numbers given
+	* by the following grammar:
+	*
+	* <blockquote>
+	* <dl>
+	* <dt><i>DecodableString:</i>
+	* <dd><i>Sign<sub>opt</sub> DecimalNumeral</i>
+	* <dd><i>Sign<sub>opt</sub></i> {@code 0x} <i>HexDigits</i>
+	* <dd><i>Sign<sub>opt</sub></i> {@code 0X} <i>HexDigits</i>
+	* <dd><i>Sign<sub>opt</sub></i> {@code #} <i>HexDigits</i>
+	* <dd><i>Sign<sub>opt</sub></i> {@code 0} <i>OctalDigits</i>
+	* <p>
+	* <dt><i>Sign:</i>
+	* <dd>{@code -}
+	* <dd>{@code +}
+	* </dl>
+	* </blockquote>
+	*
+	* <i>DecimalNumeral</i>, <i>HexDigits</i>, and <i>OctalDigits</i>
+	* are as defined in section 3.10.1 of
+	* <cite>The Java&trade; Language Specification</cite>,
+	* except that underscores are not accepted between digits.
+	*
+	* <p>The sequence of characters following an optional
+	* sign and/or radix specifier ("{@code 0x}", "{@code 0X}",
+	* "{@code #}", or leading zero) is parsed as by the {@code
+	* Integer.parseInt} method with the indicated radix (10, 16, or
+	* 8).  This sequence of characters must represent a positive
+	* value or a {@link NumberFormatException} will be thrown.  The
+	* result is negated if first character of the specified {@code
+	* String} is the minus sign.  No whitespace characters are
+	* permitted in the {@code String}.
+	*
+	* @param     nm the {@code String} to decode.
+	* @return    an {@code Integer} object holding the {@code int}
+	*             value represented by {@code nm}
+	* @exception NumberFormatException  if the {@code String} does not
+	*            contain a parsable integer.
+	* @see java.lang.Integer#parseInt(java.lang.String, int)
+	*/
+	@:overload public static function decode(nm : String) : Integer;
+	
+	/**
+	* Compares two {@code Integer} objects numerically.
+	*
+	* @param   anotherInteger   the {@code Integer} to be compared.
+	* @return  the value {@code 0} if this {@code Integer} is
+	*          equal to the argument {@code Integer}; a value less than
+	*          {@code 0} if this {@code Integer} is numerically less
+	*          than the argument {@code Integer}; and a value greater
+	*          than {@code 0} if this {@code Integer} is numerically
+	*           greater than the argument {@code Integer} (signed
+	*           comparison).
+	* @since   1.2
+	*/
+	@:require(java2) @:overload public function compareTo(anotherInteger : Integer) : Int;
+	
+	/**
+	* Compares two {@code int} values numerically.
+	* The value returned is identical to what would be returned by:
+	* <pre>
+	*    Integer.valueOf(x).compareTo(Integer.valueOf(y))
+	* </pre>
+	*
+	* @param  x the first {@code int} to compare
+	* @param  y the second {@code int} to compare
+	* @return the value {@code 0} if {@code x == y};
+	*         a value less than {@code 0} if {@code x < y}; and
+	*         a value greater than {@code 0} if {@code x > y}
+	* @since 1.7
+	*/
+	@:require(java7) @:overload public static function compare(x : Int, y : Int) : Int;
+	
+	/**
+	* The number of bits used to represent an {@code int} value in two's
+	* complement binary form.
+	*
+	* @since 1.5
+	*/
+	@:require(java5) public static var SIZE(default, null) : Int;
+	
+	/**
+	* Returns an {@code int} value with at most a single one-bit, in the
+	* position of the highest-order ("leftmost") one-bit in the specified
+	* {@code int} value.  Returns zero if the specified value has no
+	* one-bits in its two's complement binary representation, that is, if it
+	* is equal to zero.
+	*
+	* @return an {@code int} value with a single one-bit, in the position
+	*     of the highest-order one-bit in the specified value, or zero if
+	*     the specified value is itself equal to zero.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function highestOneBit(i : Int) : Int;
+	
+	/**
+	* Returns an {@code int} value with at most a single one-bit, in the
+	* position of the lowest-order ("rightmost") one-bit in the specified
+	* {@code int} value.  Returns zero if the specified value has no
+	* one-bits in its two's complement binary representation, that is, if it
+	* is equal to zero.
+	*
+	* @return an {@code int} value with a single one-bit, in the position
+	*     of the lowest-order one-bit in the specified value, or zero if
+	*     the specified value is itself equal to zero.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function lowestOneBit(i : Int) : Int;
+	
+	/**
+	* Returns the number of zero bits preceding the highest-order
+	* ("leftmost") one-bit in the two's complement binary representation
+	* of the specified {@code int} value.  Returns 32 if the
+	* specified value has no one-bits in its two's complement representation,
+	* in other words if it is equal to zero.
+	*
+	* <p>Note that this method is closely related to the logarithm base 2.
+	* For all positive {@code int} values x:
+	* <ul>
+	* <li>floor(log<sub>2</sub>(x)) = {@code 31 - numberOfLeadingZeros(x)}
+	* <li>ceil(log<sub>2</sub>(x)) = {@code 32 - numberOfLeadingZeros(x - 1)}
+	* </ul>
+	*
+	* @return the number of zero bits preceding the highest-order
+	*     ("leftmost") one-bit in the two's complement binary representation
+	*     of the specified {@code int} value, or 32 if the value
+	*     is equal to zero.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function numberOfLeadingZeros(i : Int) : Int;
+	
+	/**
+	* Returns the number of zero bits following the lowest-order ("rightmost")
+	* one-bit in the two's complement binary representation of the specified
+	* {@code int} value.  Returns 32 if the specified value has no
+	* one-bits in its two's complement representation, in other words if it is
+	* equal to zero.
+	*
+	* @return the number of zero bits following the lowest-order ("rightmost")
+	*     one-bit in the two's complement binary representation of the
+	*     specified {@code int} value, or 32 if the value is equal
+	*     to zero.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function numberOfTrailingZeros(i : Int) : Int;
+	
+	/**
+	* Returns the number of one-bits in the two's complement binary
+	* representation of the specified {@code int} value.  This function is
+	* sometimes referred to as the <i>population count</i>.
+	*
+	* @return the number of one-bits in the two's complement binary
+	*     representation of the specified {@code int} value.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function bitCount(i : Int) : Int;
+	
+	/**
+	* Returns the value obtained by rotating the two's complement binary
+	* representation of the specified {@code int} value left by the
+	* specified number of bits.  (Bits shifted out of the left hand, or
+	* high-order, side reenter on the right, or low-order.)
+	*
+	* <p>Note that left rotation with a negative distance is equivalent to
+	* right rotation: {@code rotateLeft(val, -distance) == rotateRight(val,
+	* distance)}.  Note also that rotation by any multiple of 32 is a
+	* no-op, so all but the last five bits of the rotation distance can be
+	* ignored, even if the distance is negative: {@code rotateLeft(val,
+	* distance) == rotateLeft(val, distance & 0x1F)}.
+	*
+	* @return the value obtained by rotating the two's complement binary
+	*     representation of the specified {@code int} value left by the
+	*     specified number of bits.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function rotateLeft(i : Int, distance : Int) : Int;
+	
+	/**
+	* Returns the value obtained by rotating the two's complement binary
+	* representation of the specified {@code int} value right by the
+	* specified number of bits.  (Bits shifted out of the right hand, or
+	* low-order, side reenter on the left, or high-order.)
+	*
+	* <p>Note that right rotation with a negative distance is equivalent to
+	* left rotation: {@code rotateRight(val, -distance) == rotateLeft(val,
+	* distance)}.  Note also that rotation by any multiple of 32 is a
+	* no-op, so all but the last five bits of the rotation distance can be
+	* ignored, even if the distance is negative: {@code rotateRight(val,
+	* distance) == rotateRight(val, distance & 0x1F)}.
+	*
+	* @return the value obtained by rotating the two's complement binary
+	*     representation of the specified {@code int} value right by the
+	*     specified number of bits.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function rotateRight(i : Int, distance : Int) : Int;
+	
+	/**
+	* Returns the value obtained by reversing the order of the bits in the
+	* two's complement binary representation of the specified {@code int}
+	* value.
+	*
+	* @return the value obtained by reversing order of the bits in the
+	*     specified {@code int} value.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function reverse(i : Int) : Int;
+	
+	/**
+	* Returns the signum function of the specified {@code int} value.  (The
+	* return value is -1 if the specified value is negative; 0 if the
+	* specified value is zero; and 1 if the specified value is positive.)
+	*
+	* @return the signum function of the specified {@code int} value.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function signum(i : Int) : Int;
+	
+	/**
+	* Returns the value obtained by reversing the order of the bytes in the
+	* two's complement representation of the specified {@code int} value.
+	*
+	* @return the value obtained by reversing the bytes in the specified
+	*     {@code int} value.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function reverseBytes(i : Int) : Int;
+	
+	
+}

+ 44 - 0
std/java/lang/Iterable.hx

@@ -0,0 +1,44 @@
+package java.lang;
+/*
+* Copyright (c) 2003, 2010, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* Implementing this interface allows an object to be the target of
+* the "foreach" statement.
+*
+* @param <T> the type of elements returned by the iterator
+*
+* @since 1.5
+*/
+@:require(java5) extern interface Iterable<T>
+{
+	/**
+	* Returns an iterator over a set of elements of type T.
+	*
+	* @return an Iterator.
+	*/
+	@:overload public function iterator() : java.util.Iterator<T>;
+	
+	
+}

+ 830 - 0
std/java/lang/Long.hx

@@ -0,0 +1,830 @@
+package java.lang;
+/*
+* Copyright (c) 1994, 2009, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* The {@code Long} class wraps a value of the primitive type {@code
+* long} in an object. An object of type {@code Long} contains a
+* single field whose type is {@code long}.
+*
+* <p> In addition, this class provides several methods for converting
+* a {@code long} to a {@code String} and a {@code String} to a {@code
+* long}, as well as other constants and methods useful when dealing
+* with a {@code long}.
+*
+* <p>Implementation note: The implementations of the "bit twiddling"
+* methods (such as {@link #highestOneBit(long) highestOneBit} and
+* {@link #numberOfTrailingZeros(long) numberOfTrailingZeros}) are
+* based on material from Henry S. Warren, Jr.'s <i>Hacker's
+* Delight</i>, (Addison Wesley, 2002).
+*
+* @author  Lee Boynton
+* @author  Arthur van Hoff
+* @author  Josh Bloch
+* @author  Joseph D. Darcy
+* @since   JDK1.0
+*/
+@:require(java0) extern class Long extends java.lang.Number implements java.lang.Comparable<Long>
+{
+	/**
+	* A constant holding the minimum value a {@code long} can
+	* have, -2<sup>63</sup>.
+	*/
+	public static var MIN_VALUE(default, null) : haxe.Int64;
+	
+	/**
+	* A constant holding the maximum value a {@code long} can
+	* have, 2<sup>63</sup>-1.
+	*/
+	public static var MAX_VALUE(default, null) : haxe.Int64;
+	
+	/**
+	* The {@code Class} instance representing the primitive type
+	* {@code long}.
+	*
+	* @since   JDK1.1
+	*/
+	@:require(java1) public static var TYPE(default, null) : Class<Long>;
+	
+	/**
+	* Returns a string representation of the first argument in the
+	* radix specified by the second argument.
+	*
+	* <p>If the radix is smaller than {@code Character.MIN_RADIX}
+	* or larger than {@code Character.MAX_RADIX}, then the radix
+	* {@code 10} is used instead.
+	*
+	* <p>If the first argument is negative, the first element of the
+	* result is the ASCII minus sign {@code '-'}
+	* (<code>'&#92;u002d'</code>). If the first argument is not
+	* negative, no sign character appears in the result.
+	*
+	* <p>The remaining characters of the result represent the magnitude
+	* of the first argument. If the magnitude is zero, it is
+	* represented by a single zero character {@code '0'}
+	* (<code>'&#92;u0030'</code>); otherwise, the first character of
+	* the representation of the magnitude will not be the zero
+	* character.  The following ASCII characters are used as digits:
+	*
+	* <blockquote>
+	*   {@code 0123456789abcdefghijklmnopqrstuvwxyz}
+	* </blockquote>
+	*
+	* These are <code>'&#92;u0030'</code> through
+	* <code>'&#92;u0039'</code> and <code>'&#92;u0061'</code> through
+	* <code>'&#92;u007a'</code>. If {@code radix} is
+	* <var>N</var>, then the first <var>N</var> of these characters
+	* are used as radix-<var>N</var> digits in the order shown. Thus,
+	* the digits for hexadecimal (radix 16) are
+	* {@code 0123456789abcdef}. If uppercase letters are
+	* desired, the {@link java.lang.String#toUpperCase()} method may
+	* be called on the result:
+	*
+	* <blockquote>
+	*  {@code Long.toString(n, 16).toUpperCase()}
+	* </blockquote>
+	*
+	* @param   i       a {@code long} to be converted to a string.
+	* @param   radix   the radix to use in the string representation.
+	* @return  a string representation of the argument in the specified radix.
+	* @see     java.lang.Character#MAX_RADIX
+	* @see     java.lang.Character#MIN_RADIX
+	*/
+	@:native('toString') @:overload public static function _toString(i : haxe.Int64, radix : Int) : String;
+	
+	/**
+	* Returns a string representation of the {@code long}
+	* argument as an unsigned integer in base&nbsp;16.
+	*
+	* <p>The unsigned {@code long} value is the argument plus
+	* 2<sup>64</sup> if the argument is negative; otherwise, it is
+	* equal to the argument.  This value is converted to a string of
+	* ASCII digits in hexadecimal (base&nbsp;16) with no extra
+	* leading {@code 0}s.  If the unsigned magnitude is zero, it
+	* is represented by a single zero character {@code '0'}
+	* (<code>'&#92;u0030'</code>); otherwise, the first character of
+	* the representation of the unsigned magnitude will not be the
+	* zero character. The following characters are used as
+	* hexadecimal digits:
+	*
+	* <blockquote>
+	*  {@code 0123456789abcdef}
+	* </blockquote>
+	*
+	* These are the characters <code>'&#92;u0030'</code> through
+	* <code>'&#92;u0039'</code> and  <code>'&#92;u0061'</code> through
+	* <code>'&#92;u0066'</code>.  If uppercase letters are desired,
+	* the {@link java.lang.String#toUpperCase()} method may be called
+	* on the result:
+	*
+	* <blockquote>
+	*  {@code Long.toHexString(n).toUpperCase()}
+	* </blockquote>
+	*
+	* @param   i   a {@code long} to be converted to a string.
+	* @return  the string representation of the unsigned {@code long}
+	*          value represented by the argument in hexadecimal
+	*          (base&nbsp;16).
+	* @since   JDK 1.0.2
+	*/
+	@:require(java0) @:overload public static function toHexString(i : haxe.Int64) : String;
+	
+	/**
+	* Returns a string representation of the {@code long}
+	* argument as an unsigned integer in base&nbsp;8.
+	*
+	* <p>The unsigned {@code long} value is the argument plus
+	* 2<sup>64</sup> if the argument is negative; otherwise, it is
+	* equal to the argument.  This value is converted to a string of
+	* ASCII digits in octal (base&nbsp;8) with no extra leading
+	* {@code 0}s.
+	*
+	* <p>If the unsigned magnitude is zero, it is represented by a
+	* single zero character {@code '0'}
+	* (<code>'&#92;u0030'</code>); otherwise, the first character of
+	* the representation of the unsigned magnitude will not be the
+	* zero character. The following characters are used as octal
+	* digits:
+	*
+	* <blockquote>
+	*  {@code 01234567}
+	* </blockquote>
+	*
+	* These are the characters <code>'&#92;u0030'</code> through
+	* <code>'&#92;u0037'</code>.
+	*
+	* @param   i   a {@code long} to be converted to a string.
+	* @return  the string representation of the unsigned {@code long}
+	*          value represented by the argument in octal (base&nbsp;8).
+	* @since   JDK 1.0.2
+	*/
+	@:require(java0) @:overload public static function toOctalString(i : haxe.Int64) : String;
+	
+	/**
+	* Returns a string representation of the {@code long}
+	* argument as an unsigned integer in base&nbsp;2.
+	*
+	* <p>The unsigned {@code long} value is the argument plus
+	* 2<sup>64</sup> if the argument is negative; otherwise, it is
+	* equal to the argument.  This value is converted to a string of
+	* ASCII digits in binary (base&nbsp;2) with no extra leading
+	* {@code 0}s.  If the unsigned magnitude is zero, it is
+	* represented by a single zero character {@code '0'}
+	* (<code>'&#92;u0030'</code>); otherwise, the first character of
+	* the representation of the unsigned magnitude will not be the
+	* zero character. The characters {@code '0'}
+	* (<code>'&#92;u0030'</code>) and {@code '1'}
+	* (<code>'&#92;u0031'</code>) are used as binary digits.
+	*
+	* @param   i   a {@code long} to be converted to a string.
+	* @return  the string representation of the unsigned {@code long}
+	*          value represented by the argument in binary (base&nbsp;2).
+	* @since   JDK 1.0.2
+	*/
+	@:require(java0) @:overload public static function toBinaryString(i : haxe.Int64) : String;
+	
+	/**
+	* Returns a {@code String} object representing the specified
+	* {@code long}.  The argument is converted to signed decimal
+	* representation and returned as a string, exactly as if the
+	* argument and the radix 10 were given as arguments to the {@link
+	* #toString(long, int)} method.
+	*
+	* @param   i   a {@code long} to be converted.
+	* @return  a string representation of the argument in base&nbsp;10.
+	*/
+	@:native('toString') @:overload public static function _toString(i : haxe.Int64) : String;
+	
+	/**
+	* Parses the string argument as a signed {@code long} in the
+	* radix specified by the second argument. The characters in the
+	* string must all be digits of the specified radix (as determined
+	* by whether {@link java.lang.Character#digit(char, int)} returns
+	* a nonnegative value), except that the first character may be an
+	* ASCII minus sign {@code '-'} (<code>'&#92;u002D'</code>) to
+	* indicate a negative value or an ASCII plus sign {@code '+'}
+	* (<code>'&#92;u002B'</code>) to indicate a positive value. The
+	* resulting {@code long} value is returned.
+	*
+	* <p>Note that neither the character {@code L}
+	* (<code>'&#92;u004C'</code>) nor {@code l}
+	* (<code>'&#92;u006C'</code>) is permitted to appear at the end
+	* of the string as a type indicator, as would be permitted in
+	* Java programming language source code - except that either
+	* {@code L} or {@code l} may appear as a digit for a
+	* radix greater than 22.
+	*
+	* <p>An exception of type {@code NumberFormatException} is
+	* thrown if any of the following situations occurs:
+	* <ul>
+	*
+	* <li>The first argument is {@code null} or is a string of
+	* length zero.
+	*
+	* <li>The {@code radix} is either smaller than {@link
+	* java.lang.Character#MIN_RADIX} or larger than {@link
+	* java.lang.Character#MAX_RADIX}.
+	*
+	* <li>Any character of the string is not a digit of the specified
+	* radix, except that the first character may be a minus sign
+	* {@code '-'} (<code>'&#92;u002d'</code>) or plus sign {@code
+	* '+'} (<code>'&#92;u002B'</code>) provided that the string is
+	* longer than length 1.
+	*
+	* <li>The value represented by the string is not a value of type
+	*      {@code long}.
+	* </ul>
+	*
+	* <p>Examples:
+	* <blockquote><pre>
+	* parseLong("0", 10) returns 0L
+	* parseLong("473", 10) returns 473L
+	* parseLong("+42", 10) returns 42L
+	* parseLong("-0", 10) returns 0L
+	* parseLong("-FF", 16) returns -255L
+	* parseLong("1100110", 2) returns 102L
+	* parseLong("99", 8) throws a NumberFormatException
+	* parseLong("Hazelnut", 10) throws a NumberFormatException
+	* parseLong("Hazelnut", 36) returns 1356099454469L
+	* </pre></blockquote>
+	*
+	* @param      s       the {@code String} containing the
+	*                     {@code long} representation to be parsed.
+	* @param      radix   the radix to be used while parsing {@code s}.
+	* @return     the {@code long} represented by the string argument in
+	*             the specified radix.
+	* @throws     NumberFormatException  if the string does not contain a
+	*             parsable {@code long}.
+	*/
+	@:overload public static function parseLong(s : String, radix : Int) : haxe.Int64;
+	
+	/**
+	* Parses the string argument as a signed decimal {@code long}.
+	* The characters in the string must all be decimal digits, except
+	* that the first character may be an ASCII minus sign {@code '-'}
+	* (<code>&#92;u002D'</code>) to indicate a negative value or an
+	* ASCII plus sign {@code '+'} (<code>'&#92;u002B'</code>) to
+	* indicate a positive value. The resulting {@code long} value is
+	* returned, exactly as if the argument and the radix {@code 10}
+	* were given as arguments to the {@link
+	* #parseLong(java.lang.String, int)} method.
+	*
+	* <p>Note that neither the character {@code L}
+	* (<code>'&#92;u004C'</code>) nor {@code l}
+	* (<code>'&#92;u006C'</code>) is permitted to appear at the end
+	* of the string as a type indicator, as would be permitted in
+	* Java programming language source code.
+	*
+	* @param      s   a {@code String} containing the {@code long}
+	*             representation to be parsed
+	* @return     the {@code long} represented by the argument in
+	*             decimal.
+	* @throws     NumberFormatException  if the string does not contain a
+	*             parsable {@code long}.
+	*/
+	@:overload public static function parseLong(s : String) : haxe.Int64;
+	
+	/**
+	* Returns a {@code Long} object holding the value
+	* extracted from the specified {@code String} when parsed
+	* with the radix given by the second argument.  The first
+	* argument is interpreted as representing a signed
+	* {@code long} in the radix specified by the second
+	* argument, exactly as if the arguments were given to the {@link
+	* #parseLong(java.lang.String, int)} method. The result is a
+	* {@code Long} object that represents the {@code long}
+	* value specified by the string.
+	*
+	* <p>In other words, this method returns a {@code Long} object equal
+	* to the value of:
+	*
+	* <blockquote>
+	*  {@code new Long(Long.parseLong(s, radix))}
+	* </blockquote>
+	*
+	* @param      s       the string to be parsed
+	* @param      radix   the radix to be used in interpreting {@code s}
+	* @return     a {@code Long} object holding the value
+	*             represented by the string argument in the specified
+	*             radix.
+	* @throws     NumberFormatException  If the {@code String} does not
+	*             contain a parsable {@code long}.
+	*/
+	@:overload public static function valueOf(s : String, radix : Int) : Long;
+	
+	/**
+	* Returns a {@code Long} object holding the value
+	* of the specified {@code String}. The argument is
+	* interpreted as representing a signed decimal {@code long},
+	* exactly as if the argument were given to the {@link
+	* #parseLong(java.lang.String)} method. The result is a
+	* {@code Long} object that represents the integer value
+	* specified by the string.
+	*
+	* <p>In other words, this method returns a {@code Long} object
+	* equal to the value of:
+	*
+	* <blockquote>
+	*  {@code new Long(Long.parseLong(s))}
+	* </blockquote>
+	*
+	* @param      s   the string to be parsed.
+	* @return     a {@code Long} object holding the value
+	*             represented by the string argument.
+	* @throws     NumberFormatException  If the string cannot be parsed
+	*             as a {@code long}.
+	*/
+	@:overload public static function valueOf(s : String) : Long;
+	
+	/**
+	* Returns a {@code Long} instance representing the specified
+	* {@code long} value.
+	* If a new {@code Long} instance is not required, this method
+	* should generally be used in preference to the constructor
+	* {@link #Long(long)}, as this method is likely to yield
+	* significantly better space and time performance by caching
+	* frequently requested values.
+	*
+	* Note that unlike the {@linkplain Integer#valueOf(int)
+	* corresponding method} in the {@code Integer} class, this method
+	* is <em>not</em> required to cache values within a particular
+	* range.
+	*
+	* @param  l a long value.
+	* @return a {@code Long} instance representing {@code l}.
+	* @since  1.5
+	*/
+	@:require(java5) @:overload public static function valueOf(l : haxe.Int64) : Long;
+	
+	/**
+	* Decodes a {@code String} into a {@code Long}.
+	* Accepts decimal, hexadecimal, and octal numbers given by the
+	* following grammar:
+	*
+	* <blockquote>
+	* <dl>
+	* <dt><i>DecodableString:</i>
+	* <dd><i>Sign<sub>opt</sub> DecimalNumeral</i>
+	* <dd><i>Sign<sub>opt</sub></i> {@code 0x} <i>HexDigits</i>
+	* <dd><i>Sign<sub>opt</sub></i> {@code 0X} <i>HexDigits</i>
+	* <dd><i>Sign<sub>opt</sub></i> {@code #} <i>HexDigits</i>
+	* <dd><i>Sign<sub>opt</sub></i> {@code 0} <i>OctalDigits</i>
+	* <p>
+	* <dt><i>Sign:</i>
+	* <dd>{@code -}
+	* <dd>{@code +}
+	* </dl>
+	* </blockquote>
+	*
+	* <i>DecimalNumeral</i>, <i>HexDigits</i>, and <i>OctalDigits</i>
+	* are as defined in section 3.10.1 of
+	* <cite>The Java&trade; Language Specification</cite>,
+	* except that underscores are not accepted between digits.
+	*
+	* <p>The sequence of characters following an optional
+	* sign and/or radix specifier ("{@code 0x}", "{@code 0X}",
+	* "{@code #}", or leading zero) is parsed as by the {@code
+	* Long.parseLong} method with the indicated radix (10, 16, or 8).
+	* This sequence of characters must represent a positive value or
+	* a {@link NumberFormatException} will be thrown.  The result is
+	* negated if first character of the specified {@code String} is
+	* the minus sign.  No whitespace characters are permitted in the
+	* {@code String}.
+	*
+	* @param     nm the {@code String} to decode.
+	* @return    a {@code Long} object holding the {@code long}
+	*            value represented by {@code nm}
+	* @throws    NumberFormatException  if the {@code String} does not
+	*            contain a parsable {@code long}.
+	* @see java.lang.Long#parseLong(String, int)
+	* @since 1.2
+	*/
+	@:require(java2) @:overload public static function decode(nm : String) : Long;
+	
+	/**
+	* Constructs a newly allocated {@code Long} object that
+	* represents the specified {@code long} argument.
+	*
+	* @param   value   the value to be represented by the
+	*          {@code Long} object.
+	*/
+	@:overload public function new(value : haxe.Int64) : Void;
+	
+	/**
+	* Constructs a newly allocated {@code Long} object that
+	* represents the {@code long} value indicated by the
+	* {@code String} parameter. The string is converted to a
+	* {@code long} value in exactly the manner used by the
+	* {@code parseLong} method for radix 10.
+	*
+	* @param      s   the {@code String} to be converted to a
+	*             {@code Long}.
+	* @throws     NumberFormatException  if the {@code String} does not
+	*             contain a parsable {@code long}.
+	* @see        java.lang.Long#parseLong(java.lang.String, int)
+	*/
+	@:overload public function new(s : String) : Void;
+	
+	/**
+	* Returns the value of this {@code Long} as a
+	* {@code byte}.
+	*/
+	@:overload override public function byteValue() : java.StdTypes.Int8;
+	
+	/**
+	* Returns the value of this {@code Long} as a
+	* {@code short}.
+	*/
+	@:overload override public function shortValue() : java.StdTypes.Int16;
+	
+	/**
+	* Returns the value of this {@code Long} as an
+	* {@code int}.
+	*/
+	@:overload override public function intValue() : Int;
+	
+	/**
+	* Returns the value of this {@code Long} as a
+	* {@code long} value.
+	*/
+	@:overload override public function longValue() : haxe.Int64;
+	
+	/**
+	* Returns the value of this {@code Long} as a
+	* {@code float}.
+	*/
+	@:overload override public function floatValue() : Single;
+	
+	/**
+	* Returns the value of this {@code Long} as a
+	* {@code double}.
+	*/
+	@:overload override public function doubleValue() : Float;
+	
+	/**
+	* Returns a {@code String} object representing this
+	* {@code Long}'s value.  The value is converted to signed
+	* decimal representation and returned as a string, exactly as if
+	* the {@code long} value were given as an argument to the
+	* {@link java.lang.Long#toString(long)} method.
+	*
+	* @return  a string representation of the value of this object in
+	*          base&nbsp;10.
+	*/
+	@:overload public function toString() : String;
+	
+	/**
+	* Returns a hash code for this {@code Long}. The result is
+	* the exclusive OR of the two halves of the primitive
+	* {@code long} value held by this {@code Long}
+	* object. That is, the hashcode is the value of the expression:
+	*
+	* <blockquote>
+	*  {@code (int)(this.longValue()^(this.longValue()>>>32))}
+	* </blockquote>
+	*
+	* @return  a hash code value for this object.
+	*/
+	@:overload public function hashCode() : Int;
+	
+	/**
+	* Compares this object to the specified object.  The result is
+	* {@code true} if and only if the argument is not
+	* {@code null} and is a {@code Long} object that
+	* contains the same {@code long} value as this object.
+	*
+	* @param   obj   the object to compare with.
+	* @return  {@code true} if the objects are the same;
+	*          {@code false} otherwise.
+	*/
+	@:overload public function equals(obj : Dynamic) : Bool;
+	
+	/**
+	* Determines the {@code long} value of the system property
+	* with the specified name.
+	*
+	* <p>The first argument is treated as the name of a system property.
+	* System properties are accessible through the {@link
+	* java.lang.System#getProperty(java.lang.String)} method. The
+	* string value of this property is then interpreted as a
+	* {@code long} value and a {@code Long} object
+	* representing this value is returned.  Details of possible
+	* numeric formats can be found with the definition of
+	* {@code getProperty}.
+	*
+	* <p>If there is no property with the specified name, if the
+	* specified name is empty or {@code null}, or if the
+	* property does not have the correct numeric format, then
+	* {@code null} is returned.
+	*
+	* <p>In other words, this method returns a {@code Long} object equal to
+	* the value of:
+	*
+	* <blockquote>
+	*  {@code getLong(nm, null)}
+	* </blockquote>
+	*
+	* @param   nm   property name.
+	* @return  the {@code Long} value of the property.
+	* @see     java.lang.System#getProperty(java.lang.String)
+	* @see     java.lang.System#getProperty(java.lang.String, java.lang.String)
+	*/
+	@:overload public static function getLong(nm : String) : Long;
+	
+	/**
+	* Determines the {@code long} value of the system property
+	* with the specified name.
+	*
+	* <p>The first argument is treated as the name of a system property.
+	* System properties are accessible through the {@link
+	* java.lang.System#getProperty(java.lang.String)} method. The
+	* string value of this property is then interpreted as a
+	* {@code long} value and a {@code Long} object
+	* representing this value is returned.  Details of possible
+	* numeric formats can be found with the definition of
+	* {@code getProperty}.
+	*
+	* <p>The second argument is the default value. A {@code Long} object
+	* that represents the value of the second argument is returned if there
+	* is no property of the specified name, if the property does not have
+	* the correct numeric format, or if the specified name is empty or null.
+	*
+	* <p>In other words, this method returns a {@code Long} object equal
+	* to the value of:
+	*
+	* <blockquote>
+	*  {@code getLong(nm, new Long(val))}
+	* </blockquote>
+	*
+	* but in practice it may be implemented in a manner such as:
+	*
+	* <blockquote><pre>
+	* Long result = getLong(nm, null);
+	* return (result == null) ? new Long(val) : result;
+	* </pre></blockquote>
+	*
+	* to avoid the unnecessary allocation of a {@code Long} object when
+	* the default value is not needed.
+	*
+	* @param   nm    property name.
+	* @param   val   default value.
+	* @return  the {@code Long} value of the property.
+	* @see     java.lang.System#getProperty(java.lang.String)
+	* @see     java.lang.System#getProperty(java.lang.String, java.lang.String)
+	*/
+	@:overload public static function getLong(nm : String, val : haxe.Int64) : Long;
+	
+	/**
+	* Returns the {@code long} value of the system property with
+	* the specified name.  The first argument is treated as the name
+	* of a system property.  System properties are accessible through
+	* the {@link java.lang.System#getProperty(java.lang.String)}
+	* method. The string value of this property is then interpreted
+	* as a {@code long} value, as per the
+	* {@code Long.decode} method, and a {@code Long} object
+	* representing this value is returned.
+	*
+	* <ul>
+	* <li>If the property value begins with the two ASCII characters
+	* {@code 0x} or the ASCII character {@code #}, not followed by
+	* a minus sign, then the rest of it is parsed as a hexadecimal integer
+	* exactly as for the method {@link #valueOf(java.lang.String, int)}
+	* with radix 16.
+	* <li>If the property value begins with the ASCII character
+	* {@code 0} followed by another character, it is parsed as
+	* an octal integer exactly as by the method {@link
+	* #valueOf(java.lang.String, int)} with radix 8.
+	* <li>Otherwise the property value is parsed as a decimal
+	* integer exactly as by the method
+	* {@link #valueOf(java.lang.String, int)} with radix 10.
+	* </ul>
+	*
+	* <p>Note that, in every case, neither {@code L}
+	* (<code>'&#92;u004C'</code>) nor {@code l}
+	* (<code>'&#92;u006C'</code>) is permitted to appear at the end
+	* of the property value as a type indicator, as would be
+	* permitted in Java programming language source code.
+	*
+	* <p>The second argument is the default value. The default value is
+	* returned if there is no property of the specified name, if the
+	* property does not have the correct numeric format, or if the
+	* specified name is empty or {@code null}.
+	*
+	* @param   nm   property name.
+	* @param   val   default value.
+	* @return  the {@code Long} value of the property.
+	* @see     java.lang.System#getProperty(java.lang.String)
+	* @see java.lang.System#getProperty(java.lang.String, java.lang.String)
+	* @see java.lang.Long#decode
+	*/
+	@:overload public static function getLong(nm : String, val : Long) : Long;
+	
+	/**
+	* Compares two {@code Long} objects numerically.
+	*
+	* @param   anotherLong   the {@code Long} to be compared.
+	* @return  the value {@code 0} if this {@code Long} is
+	*          equal to the argument {@code Long}; a value less than
+	*          {@code 0} if this {@code Long} is numerically less
+	*          than the argument {@code Long}; and a value greater
+	*          than {@code 0} if this {@code Long} is numerically
+	*           greater than the argument {@code Long} (signed
+	*           comparison).
+	* @since   1.2
+	*/
+	@:require(java2) @:overload public function compareTo(anotherLong : Long) : Int;
+	
+	/**
+	* Compares two {@code long} values numerically.
+	* The value returned is identical to what would be returned by:
+	* <pre>
+	*    Long.valueOf(x).compareTo(Long.valueOf(y))
+	* </pre>
+	*
+	* @param  x the first {@code long} to compare
+	* @param  y the second {@code long} to compare
+	* @return the value {@code 0} if {@code x == y};
+	*         a value less than {@code 0} if {@code x < y}; and
+	*         a value greater than {@code 0} if {@code x > y}
+	* @since 1.7
+	*/
+	@:require(java7) @:overload public static function compare(x : haxe.Int64, y : haxe.Int64) : Int;
+	
+	/**
+	* The number of bits used to represent a {@code long} value in two's
+	* complement binary form.
+	*
+	* @since 1.5
+	*/
+	@:require(java5) public static var SIZE(default, null) : Int;
+	
+	/**
+	* Returns a {@code long} value with at most a single one-bit, in the
+	* position of the highest-order ("leftmost") one-bit in the specified
+	* {@code long} value.  Returns zero if the specified value has no
+	* one-bits in its two's complement binary representation, that is, if it
+	* is equal to zero.
+	*
+	* @return a {@code long} value with a single one-bit, in the position
+	*     of the highest-order one-bit in the specified value, or zero if
+	*     the specified value is itself equal to zero.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function highestOneBit(i : haxe.Int64) : haxe.Int64;
+	
+	/**
+	* Returns a {@code long} value with at most a single one-bit, in the
+	* position of the lowest-order ("rightmost") one-bit in the specified
+	* {@code long} value.  Returns zero if the specified value has no
+	* one-bits in its two's complement binary representation, that is, if it
+	* is equal to zero.
+	*
+	* @return a {@code long} value with a single one-bit, in the position
+	*     of the lowest-order one-bit in the specified value, or zero if
+	*     the specified value is itself equal to zero.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function lowestOneBit(i : haxe.Int64) : haxe.Int64;
+	
+	/**
+	* Returns the number of zero bits preceding the highest-order
+	* ("leftmost") one-bit in the two's complement binary representation
+	* of the specified {@code long} value.  Returns 64 if the
+	* specified value has no one-bits in its two's complement representation,
+	* in other words if it is equal to zero.
+	*
+	* <p>Note that this method is closely related to the logarithm base 2.
+	* For all positive {@code long} values x:
+	* <ul>
+	* <li>floor(log<sub>2</sub>(x)) = {@code 63 - numberOfLeadingZeros(x)}
+	* <li>ceil(log<sub>2</sub>(x)) = {@code 64 - numberOfLeadingZeros(x - 1)}
+	* </ul>
+	*
+	* @return the number of zero bits preceding the highest-order
+	*     ("leftmost") one-bit in the two's complement binary representation
+	*     of the specified {@code long} value, or 64 if the value
+	*     is equal to zero.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function numberOfLeadingZeros(i : haxe.Int64) : Int;
+	
+	/**
+	* Returns the number of zero bits following the lowest-order ("rightmost")
+	* one-bit in the two's complement binary representation of the specified
+	* {@code long} value.  Returns 64 if the specified value has no
+	* one-bits in its two's complement representation, in other words if it is
+	* equal to zero.
+	*
+	* @return the number of zero bits following the lowest-order ("rightmost")
+	*     one-bit in the two's complement binary representation of the
+	*     specified {@code long} value, or 64 if the value is equal
+	*     to zero.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function numberOfTrailingZeros(i : haxe.Int64) : Int;
+	
+	/**
+	* Returns the number of one-bits in the two's complement binary
+	* representation of the specified {@code long} value.  This function is
+	* sometimes referred to as the <i>population count</i>.
+	*
+	* @return the number of one-bits in the two's complement binary
+	*     representation of the specified {@code long} value.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function bitCount(i : haxe.Int64) : Int;
+	
+	/**
+	* Returns the value obtained by rotating the two's complement binary
+	* representation of the specified {@code long} value left by the
+	* specified number of bits.  (Bits shifted out of the left hand, or
+	* high-order, side reenter on the right, or low-order.)
+	*
+	* <p>Note that left rotation with a negative distance is equivalent to
+	* right rotation: {@code rotateLeft(val, -distance) == rotateRight(val,
+	* distance)}.  Note also that rotation by any multiple of 64 is a
+	* no-op, so all but the last six bits of the rotation distance can be
+	* ignored, even if the distance is negative: {@code rotateLeft(val,
+	* distance) == rotateLeft(val, distance & 0x3F)}.
+	*
+	* @return the value obtained by rotating the two's complement binary
+	*     representation of the specified {@code long} value left by the
+	*     specified number of bits.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function rotateLeft(i : haxe.Int64, distance : Int) : haxe.Int64;
+	
+	/**
+	* Returns the value obtained by rotating the two's complement binary
+	* representation of the specified {@code long} value right by the
+	* specified number of bits.  (Bits shifted out of the right hand, or
+	* low-order, side reenter on the left, or high-order.)
+	*
+	* <p>Note that right rotation with a negative distance is equivalent to
+	* left rotation: {@code rotateRight(val, -distance) == rotateLeft(val,
+	* distance)}.  Note also that rotation by any multiple of 64 is a
+	* no-op, so all but the last six bits of the rotation distance can be
+	* ignored, even if the distance is negative: {@code rotateRight(val,
+	* distance) == rotateRight(val, distance & 0x3F)}.
+	*
+	* @return the value obtained by rotating the two's complement binary
+	*     representation of the specified {@code long} value right by the
+	*     specified number of bits.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function rotateRight(i : haxe.Int64, distance : Int) : haxe.Int64;
+	
+	/**
+	* Returns the value obtained by reversing the order of the bits in the
+	* two's complement binary representation of the specified {@code long}
+	* value.
+	*
+	* @return the value obtained by reversing order of the bits in the
+	*     specified {@code long} value.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function reverse(i : haxe.Int64) : haxe.Int64;
+	
+	/**
+	* Returns the signum function of the specified {@code long} value.  (The
+	* return value is -1 if the specified value is negative; 0 if the
+	* specified value is zero; and 1 if the specified value is positive.)
+	*
+	* @return the signum function of the specified {@code long} value.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function signum(i : haxe.Int64) : Int;
+	
+	/**
+	* Returns the value obtained by reversing the order of the bytes in the
+	* two's complement representation of the specified {@code long} value.
+	*
+	* @return the value obtained by reversing the bytes in the specified
+	*     {@code long} value.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function reverseBytes(i : haxe.Int64) : haxe.Int64;
+	
+	
+}

+ 1366 - 0
std/java/lang/Math.hx

@@ -0,0 +1,1366 @@
+package java.lang;
+/*
+* Copyright (c) 1994, 2011, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* The class {@code Math} contains methods for performing basic
+* numeric operations such as the elementary exponential, logarithm,
+* square root, and trigonometric functions.
+*
+* <p>Unlike some of the numeric methods of class
+* {@code StrictMath}, all implementations of the equivalent
+* functions of class {@code Math} are not defined to return the
+* bit-for-bit same results.  This relaxation permits
+* better-performing implementations where strict reproducibility is
+* not required.
+*
+* <p>By default many of the {@code Math} methods simply call
+* the equivalent method in {@code StrictMath} for their
+* implementation.  Code generators are encouraged to use
+* platform-specific native libraries or microprocessor instructions,
+* where available, to provide higher-performance implementations of
+* {@code Math} methods.  Such higher-performance
+* implementations still must conform to the specification for
+* {@code Math}.
+*
+* <p>The quality of implementation specifications concern two
+* properties, accuracy of the returned result and monotonicity of the
+* method.  Accuracy of the floating-point {@code Math} methods
+* is measured in terms of <i>ulps</i>, units in the last place.  For
+* a given floating-point format, an ulp of a specific real number
+* value is the distance between the two floating-point values
+* bracketing that numerical value.  When discussing the accuracy of a
+* method as a whole rather than at a specific argument, the number of
+* ulps cited is for the worst-case error at any argument.  If a
+* method always has an error less than 0.5 ulps, the method always
+* returns the floating-point number nearest the exact result; such a
+* method is <i>correctly rounded</i>.  A correctly rounded method is
+* generally the best a floating-point approximation can be; however,
+* it is impractical for many floating-point methods to be correctly
+* rounded.  Instead, for the {@code Math} class, a larger error
+* bound of 1 or 2 ulps is allowed for certain methods.  Informally,
+* with a 1 ulp error bound, when the exact result is a representable
+* number, the exact result should be returned as the computed result;
+* otherwise, either of the two floating-point values which bracket
+* the exact result may be returned.  For exact results large in
+* magnitude, one of the endpoints of the bracket may be infinite.
+* Besides accuracy at individual arguments, maintaining proper
+* relations between the method at different arguments is also
+* important.  Therefore, most methods with more than 0.5 ulp errors
+* are required to be <i>semi-monotonic</i>: whenever the mathematical
+* function is non-decreasing, so is the floating-point approximation,
+* likewise, whenever the mathematical function is non-increasing, so
+* is the floating-point approximation.  Not all approximations that
+* have 1 ulp accuracy will automatically meet the monotonicity
+* requirements.
+*
+* @author  unascribed
+* @author  Joseph D. Darcy
+* @since   JDK1.0
+*/
+@:require(java0) extern class Math
+{
+	/**
+	* The {@code double} value that is closer than any other to
+	* <i>e</i>, the base of the natural logarithms.
+	*/
+	public static var E(default, null) : Float;
+	
+	/**
+	* The {@code double} value that is closer than any other to
+	* <i>pi</i>, the ratio of the circumference of a circle to its
+	* diameter.
+	*/
+	public static var PI(default, null) : Float;
+	
+	/**
+	* Returns the trigonometric sine of an angle.  Special cases:
+	* <ul><li>If the argument is NaN or an infinity, then the
+	* result is NaN.
+	* <li>If the argument is zero, then the result is a zero with the
+	* same sign as the argument.</ul>
+	*
+	* <p>The computed result must be within 1 ulp of the exact result.
+	* Results must be semi-monotonic.
+	*
+	* @param   a   an angle, in radians.
+	* @return  the sine of the argument.
+	*/
+	@:overload public static function sin(a : Float) : Float;
+	
+	/**
+	* Returns the trigonometric cosine of an angle. Special cases:
+	* <ul><li>If the argument is NaN or an infinity, then the
+	* result is NaN.</ul>
+	*
+	* <p>The computed result must be within 1 ulp of the exact result.
+	* Results must be semi-monotonic.
+	*
+	* @param   a   an angle, in radians.
+	* @return  the cosine of the argument.
+	*/
+	@:overload public static function cos(a : Float) : Float;
+	
+	/**
+	* Returns the trigonometric tangent of an angle.  Special cases:
+	* <ul><li>If the argument is NaN or an infinity, then the result
+	* is NaN.
+	* <li>If the argument is zero, then the result is a zero with the
+	* same sign as the argument.</ul>
+	*
+	* <p>The computed result must be within 1 ulp of the exact result.
+	* Results must be semi-monotonic.
+	*
+	* @param   a   an angle, in radians.
+	* @return  the tangent of the argument.
+	*/
+	@:overload public static function tan(a : Float) : Float;
+	
+	/**
+	* Returns the arc sine of a value; the returned angle is in the
+	* range -<i>pi</i>/2 through <i>pi</i>/2.  Special cases:
+	* <ul><li>If the argument is NaN or its absolute value is greater
+	* than 1, then the result is NaN.
+	* <li>If the argument is zero, then the result is a zero with the
+	* same sign as the argument.</ul>
+	*
+	* <p>The computed result must be within 1 ulp of the exact result.
+	* Results must be semi-monotonic.
+	*
+	* @param   a   the value whose arc sine is to be returned.
+	* @return  the arc sine of the argument.
+	*/
+	@:overload public static function asin(a : Float) : Float;
+	
+	/**
+	* Returns the arc cosine of a value; the returned angle is in the
+	* range 0.0 through <i>pi</i>.  Special case:
+	* <ul><li>If the argument is NaN or its absolute value is greater
+	* than 1, then the result is NaN.</ul>
+	*
+	* <p>The computed result must be within 1 ulp of the exact result.
+	* Results must be semi-monotonic.
+	*
+	* @param   a   the value whose arc cosine is to be returned.
+	* @return  the arc cosine of the argument.
+	*/
+	@:overload public static function acos(a : Float) : Float;
+	
+	/**
+	* Returns the arc tangent of a value; the returned angle is in the
+	* range -<i>pi</i>/2 through <i>pi</i>/2.  Special cases:
+	* <ul><li>If the argument is NaN, then the result is NaN.
+	* <li>If the argument is zero, then the result is a zero with the
+	* same sign as the argument.</ul>
+	*
+	* <p>The computed result must be within 1 ulp of the exact result.
+	* Results must be semi-monotonic.
+	*
+	* @param   a   the value whose arc tangent is to be returned.
+	* @return  the arc tangent of the argument.
+	*/
+	@:overload public static function atan(a : Float) : Float;
+	
+	/**
+	* Converts an angle measured in degrees to an approximately
+	* equivalent angle measured in radians.  The conversion from
+	* degrees to radians is generally inexact.
+	*
+	* @param   angdeg   an angle, in degrees
+	* @return  the measurement of the angle {@code angdeg}
+	*          in radians.
+	* @since   1.2
+	*/
+	@:require(java2) @:overload public static function toRadians(angdeg : Float) : Float;
+	
+	/**
+	* Converts an angle measured in radians to an approximately
+	* equivalent angle measured in degrees.  The conversion from
+	* radians to degrees is generally inexact; users should
+	* <i>not</i> expect {@code cos(toRadians(90.0))} to exactly
+	* equal {@code 0.0}.
+	*
+	* @param   angrad   an angle, in radians
+	* @return  the measurement of the angle {@code angrad}
+	*          in degrees.
+	* @since   1.2
+	*/
+	@:require(java2) @:overload public static function toDegrees(angrad : Float) : Float;
+	
+	/**
+	* Returns Euler's number <i>e</i> raised to the power of a
+	* {@code double} value.  Special cases:
+	* <ul><li>If the argument is NaN, the result is NaN.
+	* <li>If the argument is positive infinity, then the result is
+	* positive infinity.
+	* <li>If the argument is negative infinity, then the result is
+	* positive zero.</ul>
+	*
+	* <p>The computed result must be within 1 ulp of the exact result.
+	* Results must be semi-monotonic.
+	*
+	* @param   a   the exponent to raise <i>e</i> to.
+	* @return  the value <i>e</i><sup>{@code a}</sup>,
+	*          where <i>e</i> is the base of the natural logarithms.
+	*/
+	@:overload public static function exp(a : Float) : Float;
+	
+	/**
+	* Returns the natural logarithm (base <i>e</i>) of a {@code double}
+	* value.  Special cases:
+	* <ul><li>If the argument is NaN or less than zero, then the result
+	* is NaN.
+	* <li>If the argument is positive infinity, then the result is
+	* positive infinity.
+	* <li>If the argument is positive zero or negative zero, then the
+	* result is negative infinity.</ul>
+	*
+	* <p>The computed result must be within 1 ulp of the exact result.
+	* Results must be semi-monotonic.
+	*
+	* @param   a   a value
+	* @return  the value ln&nbsp;{@code a}, the natural logarithm of
+	*          {@code a}.
+	*/
+	@:overload public static function log(a : Float) : Float;
+	
+	/**
+	* Returns the base 10 logarithm of a {@code double} value.
+	* Special cases:
+	*
+	* <ul><li>If the argument is NaN or less than zero, then the result
+	* is NaN.
+	* <li>If the argument is positive infinity, then the result is
+	* positive infinity.
+	* <li>If the argument is positive zero or negative zero, then the
+	* result is negative infinity.
+	* <li> If the argument is equal to 10<sup><i>n</i></sup> for
+	* integer <i>n</i>, then the result is <i>n</i>.
+	* </ul>
+	*
+	* <p>The computed result must be within 1 ulp of the exact result.
+	* Results must be semi-monotonic.
+	*
+	* @param   a   a value
+	* @return  the base 10 logarithm of  {@code a}.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function log10(a : Float) : Float;
+	
+	/**
+	* Returns the correctly rounded positive square root of a
+	* {@code double} value.
+	* Special cases:
+	* <ul><li>If the argument is NaN or less than zero, then the result
+	* is NaN.
+	* <li>If the argument is positive infinity, then the result is positive
+	* infinity.
+	* <li>If the argument is positive zero or negative zero, then the
+	* result is the same as the argument.</ul>
+	* Otherwise, the result is the {@code double} value closest to
+	* the true mathematical square root of the argument value.
+	*
+	* @param   a   a value.
+	* @return  the positive square root of {@code a}.
+	*          If the argument is NaN or less than zero, the result is NaN.
+	*/
+	@:overload public static function sqrt(a : Float) : Float;
+	
+	/**
+	* Returns the cube root of a {@code double} value.  For
+	* positive finite {@code x}, {@code cbrt(-x) ==
+	* -cbrt(x)}; that is, the cube root of a negative value is
+	* the negative of the cube root of that value's magnitude.
+	*
+	* Special cases:
+	*
+	* <ul>
+	*
+	* <li>If the argument is NaN, then the result is NaN.
+	*
+	* <li>If the argument is infinite, then the result is an infinity
+	* with the same sign as the argument.
+	*
+	* <li>If the argument is zero, then the result is a zero with the
+	* same sign as the argument.
+	*
+	* </ul>
+	*
+	* <p>The computed result must be within 1 ulp of the exact result.
+	*
+	* @param   a   a value.
+	* @return  the cube root of {@code a}.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function cbrt(a : Float) : Float;
+	
+	/**
+	* Computes the remainder operation on two arguments as prescribed
+	* by the IEEE 754 standard.
+	* The remainder value is mathematically equal to
+	* <code>f1&nbsp;-&nbsp;f2</code>&nbsp;&times;&nbsp;<i>n</i>,
+	* where <i>n</i> is the mathematical integer closest to the exact
+	* mathematical value of the quotient {@code f1/f2}, and if two
+	* mathematical integers are equally close to {@code f1/f2},
+	* then <i>n</i> is the integer that is even. If the remainder is
+	* zero, its sign is the same as the sign of the first argument.
+	* Special cases:
+	* <ul><li>If either argument is NaN, or the first argument is infinite,
+	* or the second argument is positive zero or negative zero, then the
+	* result is NaN.
+	* <li>If the first argument is finite and the second argument is
+	* infinite, then the result is the same as the first argument.</ul>
+	*
+	* @param   f1   the dividend.
+	* @param   f2   the divisor.
+	* @return  the remainder when {@code f1} is divided by
+	*          {@code f2}.
+	*/
+	@:overload public static function IEEEremainder(f1 : Float, f2 : Float) : Float;
+	
+	/**
+	* Returns the smallest (closest to negative infinity)
+	* {@code double} value that is greater than or equal to the
+	* argument and is equal to a mathematical integer. Special cases:
+	* <ul><li>If the argument value is already equal to a
+	* mathematical integer, then the result is the same as the
+	* argument.  <li>If the argument is NaN or an infinity or
+	* positive zero or negative zero, then the result is the same as
+	* the argument.  <li>If the argument value is less than zero but
+	* greater than -1.0, then the result is negative zero.</ul> Note
+	* that the value of {@code Math.ceil(x)} is exactly the
+	* value of {@code -Math.floor(-x)}.
+	*
+	*
+	* @param   a   a value.
+	* @return  the smallest (closest to negative infinity)
+	*          floating-point value that is greater than or equal to
+	*          the argument and is equal to a mathematical integer.
+	*/
+	@:overload public static function ceil(a : Float) : Float;
+	
+	/**
+	* Returns the largest (closest to positive infinity)
+	* {@code double} value that is less than or equal to the
+	* argument and is equal to a mathematical integer. Special cases:
+	* <ul><li>If the argument value is already equal to a
+	* mathematical integer, then the result is the same as the
+	* argument.  <li>If the argument is NaN or an infinity or
+	* positive zero or negative zero, then the result is the same as
+	* the argument.</ul>
+	*
+	* @param   a   a value.
+	* @return  the largest (closest to positive infinity)
+	*          floating-point value that less than or equal to the argument
+	*          and is equal to a mathematical integer.
+	*/
+	@:overload public static function floor(a : Float) : Float;
+	
+	/**
+	* Returns the {@code double} value that is closest in value
+	* to the argument and is equal to a mathematical integer. If two
+	* {@code double} values that are mathematical integers are
+	* equally close, the result is the integer value that is
+	* even. Special cases:
+	* <ul><li>If the argument value is already equal to a mathematical
+	* integer, then the result is the same as the argument.
+	* <li>If the argument is NaN or an infinity or positive zero or negative
+	* zero, then the result is the same as the argument.</ul>
+	*
+	* @param   a   a {@code double} value.
+	* @return  the closest floating-point value to {@code a} that is
+	*          equal to a mathematical integer.
+	*/
+	@:overload public static function rint(a : Float) : Float;
+	
+	/**
+	* Returns the angle <i>theta</i> from the conversion of rectangular
+	* coordinates ({@code x},&nbsp;{@code y}) to polar
+	* coordinates (r,&nbsp;<i>theta</i>).
+	* This method computes the phase <i>theta</i> by computing an arc tangent
+	* of {@code y/x} in the range of -<i>pi</i> to <i>pi</i>. Special
+	* cases:
+	* <ul><li>If either argument is NaN, then the result is NaN.
+	* <li>If the first argument is positive zero and the second argument
+	* is positive, or the first argument is positive and finite and the
+	* second argument is positive infinity, then the result is positive
+	* zero.
+	* <li>If the first argument is negative zero and the second argument
+	* is positive, or the first argument is negative and finite and the
+	* second argument is positive infinity, then the result is negative zero.
+	* <li>If the first argument is positive zero and the second argument
+	* is negative, or the first argument is positive and finite and the
+	* second argument is negative infinity, then the result is the
+	* {@code double} value closest to <i>pi</i>.
+	* <li>If the first argument is negative zero and the second argument
+	* is negative, or the first argument is negative and finite and the
+	* second argument is negative infinity, then the result is the
+	* {@code double} value closest to -<i>pi</i>.
+	* <li>If the first argument is positive and the second argument is
+	* positive zero or negative zero, or the first argument is positive
+	* infinity and the second argument is finite, then the result is the
+	* {@code double} value closest to <i>pi</i>/2.
+	* <li>If the first argument is negative and the second argument is
+	* positive zero or negative zero, or the first argument is negative
+	* infinity and the second argument is finite, then the result is the
+	* {@code double} value closest to -<i>pi</i>/2.
+	* <li>If both arguments are positive infinity, then the result is the
+	* {@code double} value closest to <i>pi</i>/4.
+	* <li>If the first argument is positive infinity and the second argument
+	* is negative infinity, then the result is the {@code double}
+	* value closest to 3*<i>pi</i>/4.
+	* <li>If the first argument is negative infinity and the second argument
+	* is positive infinity, then the result is the {@code double} value
+	* closest to -<i>pi</i>/4.
+	* <li>If both arguments are negative infinity, then the result is the
+	* {@code double} value closest to -3*<i>pi</i>/4.</ul>
+	*
+	* <p>The computed result must be within 2 ulps of the exact result.
+	* Results must be semi-monotonic.
+	*
+	* @param   y   the ordinate coordinate
+	* @param   x   the abscissa coordinate
+	* @return  the <i>theta</i> component of the point
+	*          (<i>r</i>,&nbsp;<i>theta</i>)
+	*          in polar coordinates that corresponds to the point
+	*          (<i>x</i>,&nbsp;<i>y</i>) in Cartesian coordinates.
+	*/
+	@:overload public static function atan2(y : Float, x : Float) : Float;
+	
+	/**
+	* Returns the value of the first argument raised to the power of the
+	* second argument. Special cases:
+	*
+	* <ul><li>If the second argument is positive or negative zero, then the
+	* result is 1.0.
+	* <li>If the second argument is 1.0, then the result is the same as the
+	* first argument.
+	* <li>If the second argument is NaN, then the result is NaN.
+	* <li>If the first argument is NaN and the second argument is nonzero,
+	* then the result is NaN.
+	*
+	* <li>If
+	* <ul>
+	* <li>the absolute value of the first argument is greater than 1
+	* and the second argument is positive infinity, or
+	* <li>the absolute value of the first argument is less than 1 and
+	* the second argument is negative infinity,
+	* </ul>
+	* then the result is positive infinity.
+	*
+	* <li>If
+	* <ul>
+	* <li>the absolute value of the first argument is greater than 1 and
+	* the second argument is negative infinity, or
+	* <li>the absolute value of the
+	* first argument is less than 1 and the second argument is positive
+	* infinity,
+	* </ul>
+	* then the result is positive zero.
+	*
+	* <li>If the absolute value of the first argument equals 1 and the
+	* second argument is infinite, then the result is NaN.
+	*
+	* <li>If
+	* <ul>
+	* <li>the first argument is positive zero and the second argument
+	* is greater than zero, or
+	* <li>the first argument is positive infinity and the second
+	* argument is less than zero,
+	* </ul>
+	* then the result is positive zero.
+	*
+	* <li>If
+	* <ul>
+	* <li>the first argument is positive zero and the second argument
+	* is less than zero, or
+	* <li>the first argument is positive infinity and the second
+	* argument is greater than zero,
+	* </ul>
+	* then the result is positive infinity.
+	*
+	* <li>If
+	* <ul>
+	* <li>the first argument is negative zero and the second argument
+	* is greater than zero but not a finite odd integer, or
+	* <li>the first argument is negative infinity and the second
+	* argument is less than zero but not a finite odd integer,
+	* </ul>
+	* then the result is positive zero.
+	*
+	* <li>If
+	* <ul>
+	* <li>the first argument is negative zero and the second argument
+	* is a positive finite odd integer, or
+	* <li>the first argument is negative infinity and the second
+	* argument is a negative finite odd integer,
+	* </ul>
+	* then the result is negative zero.
+	*
+	* <li>If
+	* <ul>
+	* <li>the first argument is negative zero and the second argument
+	* is less than zero but not a finite odd integer, or
+	* <li>the first argument is negative infinity and the second
+	* argument is greater than zero but not a finite odd integer,
+	* </ul>
+	* then the result is positive infinity.
+	*
+	* <li>If
+	* <ul>
+	* <li>the first argument is negative zero and the second argument
+	* is a negative finite odd integer, or
+	* <li>the first argument is negative infinity and the second
+	* argument is a positive finite odd integer,
+	* </ul>
+	* then the result is negative infinity.
+	*
+	* <li>If the first argument is finite and less than zero
+	* <ul>
+	* <li> if the second argument is a finite even integer, the
+	* result is equal to the result of raising the absolute value of
+	* the first argument to the power of the second argument
+	*
+	* <li>if the second argument is a finite odd integer, the result
+	* is equal to the negative of the result of raising the absolute
+	* value of the first argument to the power of the second
+	* argument
+	*
+	* <li>if the second argument is finite and not an integer, then
+	* the result is NaN.
+	* </ul>
+	*
+	* <li>If both arguments are integers, then the result is exactly equal
+	* to the mathematical result of raising the first argument to the power
+	* of the second argument if that result can in fact be represented
+	* exactly as a {@code double} value.</ul>
+	*
+	* <p>(In the foregoing descriptions, a floating-point value is
+	* considered to be an integer if and only if it is finite and a
+	* fixed point of the method {@link #ceil ceil} or,
+	* equivalently, a fixed point of the method {@link #floor
+	* floor}. A value is a fixed point of a one-argument
+	* method if and only if the result of applying the method to the
+	* value is equal to the value.)
+	*
+	* <p>The computed result must be within 1 ulp of the exact result.
+	* Results must be semi-monotonic.
+	*
+	* @param   a   the base.
+	* @param   b   the exponent.
+	* @return  the value {@code a}<sup>{@code b}</sup>.
+	*/
+	@:overload public static function pow(a : Float, b : Float) : Float;
+	
+	/**
+	* Returns the closest {@code int} to the argument, with ties
+	* rounding up.
+	*
+	* <p>
+	* Special cases:
+	* <ul><li>If the argument is NaN, the result is 0.
+	* <li>If the argument is negative infinity or any value less than or
+	* equal to the value of {@code Integer.MIN_VALUE}, the result is
+	* equal to the value of {@code Integer.MIN_VALUE}.
+	* <li>If the argument is positive infinity or any value greater than or
+	* equal to the value of {@code Integer.MAX_VALUE}, the result is
+	* equal to the value of {@code Integer.MAX_VALUE}.</ul>
+	*
+	* @param   a   a floating-point value to be rounded to an integer.
+	* @return  the value of the argument rounded to the nearest
+	*          {@code int} value.
+	* @see     java.lang.Integer#MAX_VALUE
+	* @see     java.lang.Integer#MIN_VALUE
+	*/
+	@:overload public static function round(a : Single) : Int;
+	
+	/**
+	* Returns the closest {@code long} to the argument, with ties
+	* rounding up.
+	*
+	* <p>Special cases:
+	* <ul><li>If the argument is NaN, the result is 0.
+	* <li>If the argument is negative infinity or any value less than or
+	* equal to the value of {@code Long.MIN_VALUE}, the result is
+	* equal to the value of {@code Long.MIN_VALUE}.
+	* <li>If the argument is positive infinity or any value greater than or
+	* equal to the value of {@code Long.MAX_VALUE}, the result is
+	* equal to the value of {@code Long.MAX_VALUE}.</ul>
+	*
+	* @param   a   a floating-point value to be rounded to a
+	*          {@code long}.
+	* @return  the value of the argument rounded to the nearest
+	*          {@code long} value.
+	* @see     java.lang.Long#MAX_VALUE
+	* @see     java.lang.Long#MIN_VALUE
+	*/
+	@:overload public static function round(a : Float) : haxe.Int64;
+	
+	/**
+	* Returns a {@code double} value with a positive sign, greater
+	* than or equal to {@code 0.0} and less than {@code 1.0}.
+	* Returned values are chosen pseudorandomly with (approximately)
+	* uniform distribution from that range.
+	*
+	* <p>When this method is first called, it creates a single new
+	* pseudorandom-number generator, exactly as if by the expression
+	*
+	* <blockquote>{@code new java.util.Random()}</blockquote>
+	*
+	* This new pseudorandom-number generator is used thereafter for
+	* all calls to this method and is used nowhere else.
+	*
+	* <p>This method is properly synchronized to allow correct use by
+	* more than one thread. However, if many threads need to generate
+	* pseudorandom numbers at a great rate, it may reduce contention
+	* for each thread to have its own pseudorandom-number generator.
+	*
+	* @return  a pseudorandom {@code double} greater than or equal
+	* to {@code 0.0} and less than {@code 1.0}.
+	* @see Random#nextDouble()
+	*/
+	@:overload public static function random() : Float;
+	
+	/**
+	* Returns the absolute value of an {@code int} value.
+	* If the argument is not negative, the argument is returned.
+	* If the argument is negative, the negation of the argument is returned.
+	*
+	* <p>Note that if the argument is equal to the value of
+	* {@link Integer#MIN_VALUE}, the most negative representable
+	* {@code int} value, the result is that same value, which is
+	* negative.
+	*
+	* @param   a   the argument whose absolute value is to be determined
+	* @return  the absolute value of the argument.
+	*/
+	@:overload public static function abs(a : Int) : Int;
+	
+	/**
+	* Returns the absolute value of a {@code long} value.
+	* If the argument is not negative, the argument is returned.
+	* If the argument is negative, the negation of the argument is returned.
+	*
+	* <p>Note that if the argument is equal to the value of
+	* {@link Long#MIN_VALUE}, the most negative representable
+	* {@code long} value, the result is that same value, which
+	* is negative.
+	*
+	* @param   a   the argument whose absolute value is to be determined
+	* @return  the absolute value of the argument.
+	*/
+	@:overload public static function abs(a : haxe.Int64) : haxe.Int64;
+	
+	/**
+	* Returns the absolute value of a {@code float} value.
+	* If the argument is not negative, the argument is returned.
+	* If the argument is negative, the negation of the argument is returned.
+	* Special cases:
+	* <ul><li>If the argument is positive zero or negative zero, the
+	* result is positive zero.
+	* <li>If the argument is infinite, the result is positive infinity.
+	* <li>If the argument is NaN, the result is NaN.</ul>
+	* In other words, the result is the same as the value of the expression:
+	* <p>{@code Float.intBitsToFloat(0x7fffffff & Float.floatToIntBits(a))}
+	*
+	* @param   a   the argument whose absolute value is to be determined
+	* @return  the absolute value of the argument.
+	*/
+	@:overload public static function abs(a : Single) : Single;
+	
+	/**
+	* Returns the absolute value of a {@code double} value.
+	* If the argument is not negative, the argument is returned.
+	* If the argument is negative, the negation of the argument is returned.
+	* Special cases:
+	* <ul><li>If the argument is positive zero or negative zero, the result
+	* is positive zero.
+	* <li>If the argument is infinite, the result is positive infinity.
+	* <li>If the argument is NaN, the result is NaN.</ul>
+	* In other words, the result is the same as the value of the expression:
+	* <p>{@code Double.longBitsToDouble((Double.doubleToLongBits(a)<<1)>>>1)}
+	*
+	* @param   a   the argument whose absolute value is to be determined
+	* @return  the absolute value of the argument.
+	*/
+	@:overload public static function abs(a : Float) : Float;
+	
+	/**
+	* Returns the greater of two {@code int} values. That is, the
+	* result is the argument closer to the value of
+	* {@link Integer#MAX_VALUE}. If the arguments have the same value,
+	* the result is that same value.
+	*
+	* @param   a   an argument.
+	* @param   b   another argument.
+	* @return  the larger of {@code a} and {@code b}.
+	*/
+	@:overload public static function max(a : Int, b : Int) : Int;
+	
+	/**
+	* Returns the greater of two {@code long} values. That is, the
+	* result is the argument closer to the value of
+	* {@link Long#MAX_VALUE}. If the arguments have the same value,
+	* the result is that same value.
+	*
+	* @param   a   an argument.
+	* @param   b   another argument.
+	* @return  the larger of {@code a} and {@code b}.
+	*/
+	@:overload public static function max(a : haxe.Int64, b : haxe.Int64) : haxe.Int64;
+	
+	/**
+	* Returns the greater of two {@code float} values.  That is,
+	* the result is the argument closer to positive infinity. If the
+	* arguments have the same value, the result is that same
+	* value. If either value is NaN, then the result is NaN.  Unlike
+	* the numerical comparison operators, this method considers
+	* negative zero to be strictly smaller than positive zero. If one
+	* argument is positive zero and the other negative zero, the
+	* result is positive zero.
+	*
+	* @param   a   an argument.
+	* @param   b   another argument.
+	* @return  the larger of {@code a} and {@code b}.
+	*/
+	@:overload public static function max(a : Single, b : Single) : Single;
+	
+	/**
+	* Returns the greater of two {@code double} values.  That
+	* is, the result is the argument closer to positive infinity. If
+	* the arguments have the same value, the result is that same
+	* value. If either value is NaN, then the result is NaN.  Unlike
+	* the numerical comparison operators, this method considers
+	* negative zero to be strictly smaller than positive zero. If one
+	* argument is positive zero and the other negative zero, the
+	* result is positive zero.
+	*
+	* @param   a   an argument.
+	* @param   b   another argument.
+	* @return  the larger of {@code a} and {@code b}.
+	*/
+	@:overload public static function max(a : Float, b : Float) : Float;
+	
+	/**
+	* Returns the smaller of two {@code int} values. That is,
+	* the result the argument closer to the value of
+	* {@link Integer#MIN_VALUE}.  If the arguments have the same
+	* value, the result is that same value.
+	*
+	* @param   a   an argument.
+	* @param   b   another argument.
+	* @return  the smaller of {@code a} and {@code b}.
+	*/
+	@:overload public static function min(a : Int, b : Int) : Int;
+	
+	/**
+	* Returns the smaller of two {@code long} values. That is,
+	* the result is the argument closer to the value of
+	* {@link Long#MIN_VALUE}. If the arguments have the same
+	* value, the result is that same value.
+	*
+	* @param   a   an argument.
+	* @param   b   another argument.
+	* @return  the smaller of {@code a} and {@code b}.
+	*/
+	@:overload public static function min(a : haxe.Int64, b : haxe.Int64) : haxe.Int64;
+	
+	/**
+	* Returns the smaller of two {@code float} values.  That is,
+	* the result is the value closer to negative infinity. If the
+	* arguments have the same value, the result is that same
+	* value. If either value is NaN, then the result is NaN.  Unlike
+	* the numerical comparison operators, this method considers
+	* negative zero to be strictly smaller than positive zero.  If
+	* one argument is positive zero and the other is negative zero,
+	* the result is negative zero.
+	*
+	* @param   a   an argument.
+	* @param   b   another argument.
+	* @return  the smaller of {@code a} and {@code b}.
+	*/
+	@:overload public static function min(a : Single, b : Single) : Single;
+	
+	/**
+	* Returns the smaller of two {@code double} values.  That
+	* is, the result is the value closer to negative infinity. If the
+	* arguments have the same value, the result is that same
+	* value. If either value is NaN, then the result is NaN.  Unlike
+	* the numerical comparison operators, this method considers
+	* negative zero to be strictly smaller than positive zero. If one
+	* argument is positive zero and the other is negative zero, the
+	* result is negative zero.
+	*
+	* @param   a   an argument.
+	* @param   b   another argument.
+	* @return  the smaller of {@code a} and {@code b}.
+	*/
+	@:overload public static function min(a : Float, b : Float) : Float;
+	
+	/**
+	* Returns the size of an ulp of the argument.  An ulp of a
+	* {@code double} value is the positive distance between this
+	* floating-point value and the {@code double} value next
+	* larger in magnitude.  Note that for non-NaN <i>x</i>,
+	* <code>ulp(-<i>x</i>) == ulp(<i>x</i>)</code>.
+	*
+	* <p>Special Cases:
+	* <ul>
+	* <li> If the argument is NaN, then the result is NaN.
+	* <li> If the argument is positive or negative infinity, then the
+	* result is positive infinity.
+	* <li> If the argument is positive or negative zero, then the result is
+	* {@code Double.MIN_VALUE}.
+	* <li> If the argument is &plusmn;{@code Double.MAX_VALUE}, then
+	* the result is equal to 2<sup>971</sup>.
+	* </ul>
+	*
+	* @param d the floating-point value whose ulp is to be returned
+	* @return the size of an ulp of the argument
+	* @author Joseph D. Darcy
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function ulp(d : Float) : Float;
+	
+	/**
+	* Returns the size of an ulp of the argument.  An ulp of a
+	* {@code float} value is the positive distance between this
+	* floating-point value and the {@code float} value next
+	* larger in magnitude.  Note that for non-NaN <i>x</i>,
+	* <code>ulp(-<i>x</i>) == ulp(<i>x</i>)</code>.
+	*
+	* <p>Special Cases:
+	* <ul>
+	* <li> If the argument is NaN, then the result is NaN.
+	* <li> If the argument is positive or negative infinity, then the
+	* result is positive infinity.
+	* <li> If the argument is positive or negative zero, then the result is
+	* {@code Float.MIN_VALUE}.
+	* <li> If the argument is &plusmn;{@code Float.MAX_VALUE}, then
+	* the result is equal to 2<sup>104</sup>.
+	* </ul>
+	*
+	* @param f the floating-point value whose ulp is to be returned
+	* @return the size of an ulp of the argument
+	* @author Joseph D. Darcy
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function ulp(f : Single) : Single;
+	
+	/**
+	* Returns the signum function of the argument; zero if the argument
+	* is zero, 1.0 if the argument is greater than zero, -1.0 if the
+	* argument is less than zero.
+	*
+	* <p>Special Cases:
+	* <ul>
+	* <li> If the argument is NaN, then the result is NaN.
+	* <li> If the argument is positive zero or negative zero, then the
+	*      result is the same as the argument.
+	* </ul>
+	*
+	* @param d the floating-point value whose signum is to be returned
+	* @return the signum function of the argument
+	* @author Joseph D. Darcy
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function signum(d : Float) : Float;
+	
+	/**
+	* Returns the signum function of the argument; zero if the argument
+	* is zero, 1.0f if the argument is greater than zero, -1.0f if the
+	* argument is less than zero.
+	*
+	* <p>Special Cases:
+	* <ul>
+	* <li> If the argument is NaN, then the result is NaN.
+	* <li> If the argument is positive zero or negative zero, then the
+	*      result is the same as the argument.
+	* </ul>
+	*
+	* @param f the floating-point value whose signum is to be returned
+	* @return the signum function of the argument
+	* @author Joseph D. Darcy
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function signum(f : Single) : Single;
+	
+	/**
+	* Returns the hyperbolic sine of a {@code double} value.
+	* The hyperbolic sine of <i>x</i> is defined to be
+	* (<i>e<sup>x</sup>&nbsp;-&nbsp;e<sup>-x</sup></i>)/2
+	* where <i>e</i> is {@linkplain Math#E Euler's number}.
+	*
+	* <p>Special cases:
+	* <ul>
+	*
+	* <li>If the argument is NaN, then the result is NaN.
+	*
+	* <li>If the argument is infinite, then the result is an infinity
+	* with the same sign as the argument.
+	*
+	* <li>If the argument is zero, then the result is a zero with the
+	* same sign as the argument.
+	*
+	* </ul>
+	*
+	* <p>The computed result must be within 2.5 ulps of the exact result.
+	*
+	* @param   x The number whose hyperbolic sine is to be returned.
+	* @return  The hyperbolic sine of {@code x}.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function sinh(x : Float) : Float;
+	
+	/**
+	* Returns the hyperbolic cosine of a {@code double} value.
+	* The hyperbolic cosine of <i>x</i> is defined to be
+	* (<i>e<sup>x</sup>&nbsp;+&nbsp;e<sup>-x</sup></i>)/2
+	* where <i>e</i> is {@linkplain Math#E Euler's number}.
+	*
+	* <p>Special cases:
+	* <ul>
+	*
+	* <li>If the argument is NaN, then the result is NaN.
+	*
+	* <li>If the argument is infinite, then the result is positive
+	* infinity.
+	*
+	* <li>If the argument is zero, then the result is {@code 1.0}.
+	*
+	* </ul>
+	*
+	* <p>The computed result must be within 2.5 ulps of the exact result.
+	*
+	* @param   x The number whose hyperbolic cosine is to be returned.
+	* @return  The hyperbolic cosine of {@code x}.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function cosh(x : Float) : Float;
+	
+	/**
+	* Returns the hyperbolic tangent of a {@code double} value.
+	* The hyperbolic tangent of <i>x</i> is defined to be
+	* (<i>e<sup>x</sup>&nbsp;-&nbsp;e<sup>-x</sup></i>)/(<i>e<sup>x</sup>&nbsp;+&nbsp;e<sup>-x</sup></i>),
+	* in other words, {@linkplain Math#sinh
+	* sinh(<i>x</i>)}/{@linkplain Math#cosh cosh(<i>x</i>)}.  Note
+	* that the absolute value of the exact tanh is always less than
+	* 1.
+	*
+	* <p>Special cases:
+	* <ul>
+	*
+	* <li>If the argument is NaN, then the result is NaN.
+	*
+	* <li>If the argument is zero, then the result is a zero with the
+	* same sign as the argument.
+	*
+	* <li>If the argument is positive infinity, then the result is
+	* {@code +1.0}.
+	*
+	* <li>If the argument is negative infinity, then the result is
+	* {@code -1.0}.
+	*
+	* </ul>
+	*
+	* <p>The computed result must be within 2.5 ulps of the exact result.
+	* The result of {@code tanh} for any finite input must have
+	* an absolute value less than or equal to 1.  Note that once the
+	* exact result of tanh is within 1/2 of an ulp of the limit value
+	* of &plusmn;1, correctly signed &plusmn;{@code 1.0} should
+	* be returned.
+	*
+	* @param   x The number whose hyperbolic tangent is to be returned.
+	* @return  The hyperbolic tangent of {@code x}.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function tanh(x : Float) : Float;
+	
+	/**
+	* Returns sqrt(<i>x</i><sup>2</sup>&nbsp;+<i>y</i><sup>2</sup>)
+	* without intermediate overflow or underflow.
+	*
+	* <p>Special cases:
+	* <ul>
+	*
+	* <li> If either argument is infinite, then the result
+	* is positive infinity.
+	*
+	* <li> If either argument is NaN and neither argument is infinite,
+	* then the result is NaN.
+	*
+	* </ul>
+	*
+	* <p>The computed result must be within 1 ulp of the exact
+	* result.  If one parameter is held constant, the results must be
+	* semi-monotonic in the other parameter.
+	*
+	* @param x a value
+	* @param y a value
+	* @return sqrt(<i>x</i><sup>2</sup>&nbsp;+<i>y</i><sup>2</sup>)
+	* without intermediate overflow or underflow
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function hypot(x : Float, y : Float) : Float;
+	
+	/**
+	* Returns <i>e</i><sup>x</sup>&nbsp;-1.  Note that for values of
+	* <i>x</i> near 0, the exact sum of
+	* {@code expm1(x)}&nbsp;+&nbsp;1 is much closer to the true
+	* result of <i>e</i><sup>x</sup> than {@code exp(x)}.
+	*
+	* <p>Special cases:
+	* <ul>
+	* <li>If the argument is NaN, the result is NaN.
+	*
+	* <li>If the argument is positive infinity, then the result is
+	* positive infinity.
+	*
+	* <li>If the argument is negative infinity, then the result is
+	* -1.0.
+	*
+	* <li>If the argument is zero, then the result is a zero with the
+	* same sign as the argument.
+	*
+	* </ul>
+	*
+	* <p>The computed result must be within 1 ulp of the exact result.
+	* Results must be semi-monotonic.  The result of
+	* {@code expm1} for any finite input must be greater than or
+	* equal to {@code -1.0}.  Note that once the exact result of
+	* <i>e</i><sup>{@code x}</sup>&nbsp;-&nbsp;1 is within 1/2
+	* ulp of the limit value -1, {@code -1.0} should be
+	* returned.
+	*
+	* @param   x   the exponent to raise <i>e</i> to in the computation of
+	*              <i>e</i><sup>{@code x}</sup>&nbsp;-1.
+	* @return  the value <i>e</i><sup>{@code x}</sup>&nbsp;-&nbsp;1.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function expm1(x : Float) : Float;
+	
+	/**
+	* Returns the natural logarithm of the sum of the argument and 1.
+	* Note that for small values {@code x}, the result of
+	* {@code log1p(x)} is much closer to the true result of ln(1
+	* + {@code x}) than the floating-point evaluation of
+	* {@code log(1.0+x)}.
+	*
+	* <p>Special cases:
+	*
+	* <ul>
+	*
+	* <li>If the argument is NaN or less than -1, then the result is
+	* NaN.
+	*
+	* <li>If the argument is positive infinity, then the result is
+	* positive infinity.
+	*
+	* <li>If the argument is negative one, then the result is
+	* negative infinity.
+	*
+	* <li>If the argument is zero, then the result is a zero with the
+	* same sign as the argument.
+	*
+	* </ul>
+	*
+	* <p>The computed result must be within 1 ulp of the exact result.
+	* Results must be semi-monotonic.
+	*
+	* @param   x   a value
+	* @return the value ln({@code x}&nbsp;+&nbsp;1), the natural
+	* log of {@code x}&nbsp;+&nbsp;1
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function log1p(x : Float) : Float;
+	
+	/**
+	* Returns the first floating-point argument with the sign of the
+	* second floating-point argument.  Note that unlike the {@link
+	* StrictMath#copySign(double, double) StrictMath.copySign}
+	* method, this method does not require NaN {@code sign}
+	* arguments to be treated as positive values; implementations are
+	* permitted to treat some NaN arguments as positive and other NaN
+	* arguments as negative to allow greater performance.
+	*
+	* @param magnitude  the parameter providing the magnitude of the result
+	* @param sign   the parameter providing the sign of the result
+	* @return a value with the magnitude of {@code magnitude}
+	* and the sign of {@code sign}.
+	* @since 1.6
+	*/
+	@:require(java6) @:overload public static function copySign(magnitude : Float, sign : Float) : Float;
+	
+	/**
+	* Returns the first floating-point argument with the sign of the
+	* second floating-point argument.  Note that unlike the {@link
+	* StrictMath#copySign(float, float) StrictMath.copySign}
+	* method, this method does not require NaN {@code sign}
+	* arguments to be treated as positive values; implementations are
+	* permitted to treat some NaN arguments as positive and other NaN
+	* arguments as negative to allow greater performance.
+	*
+	* @param magnitude  the parameter providing the magnitude of the result
+	* @param sign   the parameter providing the sign of the result
+	* @return a value with the magnitude of {@code magnitude}
+	* and the sign of {@code sign}.
+	* @since 1.6
+	*/
+	@:require(java6) @:overload public static function copySign(magnitude : Single, sign : Single) : Single;
+	
+	/**
+	* Returns the unbiased exponent used in the representation of a
+	* {@code float}.  Special cases:
+	*
+	* <ul>
+	* <li>If the argument is NaN or infinite, then the result is
+	* {@link Float#MAX_EXPONENT} + 1.
+	* <li>If the argument is zero or subnormal, then the result is
+	* {@link Float#MIN_EXPONENT} -1.
+	* </ul>
+	* @param f a {@code float} value
+	* @return the unbiased exponent of the argument
+	* @since 1.6
+	*/
+	@:require(java6) @:overload public static function getExponent(f : Single) : Int;
+	
+	/**
+	* Returns the unbiased exponent used in the representation of a
+	* {@code double}.  Special cases:
+	*
+	* <ul>
+	* <li>If the argument is NaN or infinite, then the result is
+	* {@link Double#MAX_EXPONENT} + 1.
+	* <li>If the argument is zero or subnormal, then the result is
+	* {@link Double#MIN_EXPONENT} -1.
+	* </ul>
+	* @param d a {@code double} value
+	* @return the unbiased exponent of the argument
+	* @since 1.6
+	*/
+	@:require(java6) @:overload public static function getExponent(d : Float) : Int;
+	
+	/**
+	* Returns the floating-point number adjacent to the first
+	* argument in the direction of the second argument.  If both
+	* arguments compare as equal the second argument is returned.
+	*
+	* <p>
+	* Special cases:
+	* <ul>
+	* <li> If either argument is a NaN, then NaN is returned.
+	*
+	* <li> If both arguments are signed zeros, {@code direction}
+	* is returned unchanged (as implied by the requirement of
+	* returning the second argument if the arguments compare as
+	* equal).
+	*
+	* <li> If {@code start} is
+	* &plusmn;{@link Double#MIN_VALUE} and {@code direction}
+	* has a value such that the result should have a smaller
+	* magnitude, then a zero with the same sign as {@code start}
+	* is returned.
+	*
+	* <li> If {@code start} is infinite and
+	* {@code direction} has a value such that the result should
+	* have a smaller magnitude, {@link Double#MAX_VALUE} with the
+	* same sign as {@code start} is returned.
+	*
+	* <li> If {@code start} is equal to &plusmn;
+	* {@link Double#MAX_VALUE} and {@code direction} has a
+	* value such that the result should have a larger magnitude, an
+	* infinity with same sign as {@code start} is returned.
+	* </ul>
+	*
+	* @param start  starting floating-point value
+	* @param direction value indicating which of
+	* {@code start}'s neighbors or {@code start} should
+	* be returned
+	* @return The floating-point number adjacent to {@code start} in the
+	* direction of {@code direction}.
+	* @since 1.6
+	*/
+	@:require(java6) @:overload public static function nextAfter(start : Float, direction : Float) : Float;
+	
+	/**
+	* Returns the floating-point number adjacent to the first
+	* argument in the direction of the second argument.  If both
+	* arguments compare as equal a value equivalent to the second argument
+	* is returned.
+	*
+	* <p>
+	* Special cases:
+	* <ul>
+	* <li> If either argument is a NaN, then NaN is returned.
+	*
+	* <li> If both arguments are signed zeros, a value equivalent
+	* to {@code direction} is returned.
+	*
+	* <li> If {@code start} is
+	* &plusmn;{@link Float#MIN_VALUE} and {@code direction}
+	* has a value such that the result should have a smaller
+	* magnitude, then a zero with the same sign as {@code start}
+	* is returned.
+	*
+	* <li> If {@code start} is infinite and
+	* {@code direction} has a value such that the result should
+	* have a smaller magnitude, {@link Float#MAX_VALUE} with the
+	* same sign as {@code start} is returned.
+	*
+	* <li> If {@code start} is equal to &plusmn;
+	* {@link Float#MAX_VALUE} and {@code direction} has a
+	* value such that the result should have a larger magnitude, an
+	* infinity with same sign as {@code start} is returned.
+	* </ul>
+	*
+	* @param start  starting floating-point value
+	* @param direction value indicating which of
+	* {@code start}'s neighbors or {@code start} should
+	* be returned
+	* @return The floating-point number adjacent to {@code start} in the
+	* direction of {@code direction}.
+	* @since 1.6
+	*/
+	@:require(java6) @:overload public static function nextAfter(start : Single, direction : Float) : Single;
+	
+	/**
+	* Returns the floating-point value adjacent to {@code d} in
+	* the direction of positive infinity.  This method is
+	* semantically equivalent to {@code nextAfter(d,
+	* Double.POSITIVE_INFINITY)}; however, a {@code nextUp}
+	* implementation may run faster than its equivalent
+	* {@code nextAfter} call.
+	*
+	* <p>Special Cases:
+	* <ul>
+	* <li> If the argument is NaN, the result is NaN.
+	*
+	* <li> If the argument is positive infinity, the result is
+	* positive infinity.
+	*
+	* <li> If the argument is zero, the result is
+	* {@link Double#MIN_VALUE}
+	*
+	* </ul>
+	*
+	* @param d starting floating-point value
+	* @return The adjacent floating-point value closer to positive
+	* infinity.
+	* @since 1.6
+	*/
+	@:require(java6) @:overload public static function nextUp(d : Float) : Float;
+	
+	/**
+	* Returns the floating-point value adjacent to {@code f} in
+	* the direction of positive infinity.  This method is
+	* semantically equivalent to {@code nextAfter(f,
+	* Float.POSITIVE_INFINITY)}; however, a {@code nextUp}
+	* implementation may run faster than its equivalent
+	* {@code nextAfter} call.
+	*
+	* <p>Special Cases:
+	* <ul>
+	* <li> If the argument is NaN, the result is NaN.
+	*
+	* <li> If the argument is positive infinity, the result is
+	* positive infinity.
+	*
+	* <li> If the argument is zero, the result is
+	* {@link Float#MIN_VALUE}
+	*
+	* </ul>
+	*
+	* @param f starting floating-point value
+	* @return The adjacent floating-point value closer to positive
+	* infinity.
+	* @since 1.6
+	*/
+	@:require(java6) @:overload public static function nextUp(f : Single) : Single;
+	
+	/**
+	* Return {@code d} &times;
+	* 2<sup>{@code scaleFactor}</sup> rounded as if performed
+	* by a single correctly rounded floating-point multiply to a
+	* member of the double value set.  See the Java
+	* Language Specification for a discussion of floating-point
+	* value sets.  If the exponent of the result is between {@link
+	* Double#MIN_EXPONENT} and {@link Double#MAX_EXPONENT}, the
+	* answer is calculated exactly.  If the exponent of the result
+	* would be larger than {@code Double.MAX_EXPONENT}, an
+	* infinity is returned.  Note that if the result is subnormal,
+	* precision may be lost; that is, when {@code scalb(x, n)}
+	* is subnormal, {@code scalb(scalb(x, n), -n)} may not equal
+	* <i>x</i>.  When the result is non-NaN, the result has the same
+	* sign as {@code d}.
+	*
+	* <p>Special cases:
+	* <ul>
+	* <li> If the first argument is NaN, NaN is returned.
+	* <li> If the first argument is infinite, then an infinity of the
+	* same sign is returned.
+	* <li> If the first argument is zero, then a zero of the same
+	* sign is returned.
+	* </ul>
+	*
+	* @param d number to be scaled by a power of two.
+	* @param scaleFactor power of 2 used to scale {@code d}
+	* @return {@code d} &times; 2<sup>{@code scaleFactor}</sup>
+	* @since 1.6
+	*/
+	@:require(java6) @:overload public static function scalb(d : Float, scaleFactor : Int) : Float;
+	
+	/**
+	* Return {@code f} &times;
+	* 2<sup>{@code scaleFactor}</sup> rounded as if performed
+	* by a single correctly rounded floating-point multiply to a
+	* member of the float value set.  See the Java
+	* Language Specification for a discussion of floating-point
+	* value sets.  If the exponent of the result is between {@link
+	* Float#MIN_EXPONENT} and {@link Float#MAX_EXPONENT}, the
+	* answer is calculated exactly.  If the exponent of the result
+	* would be larger than {@code Float.MAX_EXPONENT}, an
+	* infinity is returned.  Note that if the result is subnormal,
+	* precision may be lost; that is, when {@code scalb(x, n)}
+	* is subnormal, {@code scalb(scalb(x, n), -n)} may not equal
+	* <i>x</i>.  When the result is non-NaN, the result has the same
+	* sign as {@code f}.
+	*
+	* <p>Special cases:
+	* <ul>
+	* <li> If the first argument is NaN, NaN is returned.
+	* <li> If the first argument is infinite, then an infinity of the
+	* same sign is returned.
+	* <li> If the first argument is zero, then a zero of the same
+	* sign is returned.
+	* </ul>
+	*
+	* @param f number to be scaled by a power of two.
+	* @param scaleFactor power of 2 used to scale {@code f}
+	* @return {@code f} &times; 2<sup>{@code scaleFactor}</sup>
+	* @since 1.6
+	*/
+	@:require(java6) @:overload public static function scalb(f : Single, scaleFactor : Int) : Single;
+	
+	
+}

+ 106 - 114
std/java/lang/Number.hx

@@ -1,114 +1,106 @@
-/*
- * Copyright (C)2005-2012 Haxe Foundation
- *
- * Permission is hereby granted, free of charge, to any person obtaining a
- * copy of this software and associated documentation files (the "Software"),
- * to deal in the Software without restriction, including without limitation
- * the rights to use, copy, modify, merge, publish, distribute, sublicense,
- * and/or sell copies of the Software, and to permit persons to whom the
- * Software is furnished to do so, subject to the following conditions:
- *
- * The above copyright notice and this permission notice shall be included in
- * all copies or substantial portions of the Software.
- *
- * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
- * IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
- * FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
- * AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
- * LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
- * FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER
- * DEALINGS IN THE SOFTWARE.
- */
-package java.lang;
-import haxe.Int64;
-import java.StdTypes;
-
-private typedef StdFloat = Float;
-
-@:abstract extern class Number
-{
-
-	public function byteValue():Int8;
-	public function doubleValue():StdFloat;
-	public function floatValue():Single;
-	public function intValue():Int;
-	public function longValue():Int64;
-	public function shortValue():Int16;
-
-}
-
-@:final extern class Byte extends Number/*, implements Int */
-{
-	static var MAX_VALUE(default, null):Int8;
-	static var MIN_VALUE(default, null):Int8;
-
-	@:overload(function(s:String):Void {})
-	function new(value:Int8):Void;
-
-	static function parseByte(s:String, radix:Int):Int8;
-}
-
-@:hack @:final extern class Double extends Number/* , implements StdFloat */
-{
-	static var MAX_VALUE(default, null):StdFloat;
-	static var MIN_VALUE(default, null):StdFloat;
-	static var NaN(default, null):StdFloat;
-	static var NEGATIVE_INFINITY(default, null):StdFloat;
-	static var POSITIVE_INFINITY(default, null):StdFloat;
-
-	@:overload(function(s:String):Void {})
-	function new(value:StdFloat):Void;
-
-	public static function isInfinite(f:Float):Bool;
-	public static function isNaN(f:Float):Bool;
-}
-
-@:final extern class Float extends Number /*, implements StdFloat*/
-{
-	static var MAX_VALUE(default, null):Single;
-	static var MIN_VALUE(default, null):Single;
-	static var NaN(default, null):Single;
-	static var NEGATIVE_INFINITY(default, null):Single;
-	static var POSITIVE_INFINITY(default, null):Single;
-
-	static function isNaN(f:Float):Bool;
-
-	@:overload(function(s:String):Void {})
-	function new(value:Single):Void;
-}
-
-@:final extern class Integer extends Number/*, implements Int */
-{
-	static var MAX_VALUE(default, null):Int;
-	static var MIN_VALUE(default, null):Int;
-
-	@:overload(function(s:String):Void {})
-	function new(value:Int):Void;
-
-	static function toString(i:Int):String;
-	static function parseInt(s:String, radix:Int):Int;
-}
-
-@:final extern class Long extends Number
-{
-	static var MAX_VALUE(default, null):Int64;
-	static var MIN_VALUE(default, null):Int64;
-
-	@:overload(function(s:String):Void {})
-	function new(value:Int64):Void;
-
-	static function toString(i:Int64):String;
-	static function parseLong(s:String, radix:Int):Int64;
-}
-
-@:final extern class Short extends Number/*, implements Int */
-{
-	static var MAX_VALUE(default, null):Int16;
-	static var MIN_VALUE(default, null):Int16;
-
-	@:overload(function(s:String):Void {})
-	function new(value:Int16):Void;
-
-	static function parseShort(s:String, radix:Int):Int16;
-}
-
+package java.lang;
+/*
+* Copyright (c) 1994, 2001, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* The abstract class <code>Number</code> is the superclass of classes
+* <code>BigDecimal</code>, <code>BigInteger</code>,
+* <code>Byte</code>, <code>Double</code>, <code>Float</code>,
+* <code>Integer</code>, <code>Long</code>, and <code>Short</code>.
+* <p>
+* Subclasses of <code>Number</code> must provide methods to convert
+* the represented numeric value to <code>byte</code>, <code>double</code>,
+* <code>float</code>, <code>int</code>, <code>long</code>, and
+* <code>short</code>.
+*
+* @author      Lee Boynton
+* @author      Arthur van Hoff
+* @see     java.lang.Byte
+* @see     java.lang.Double
+* @see     java.lang.Float
+* @see     java.lang.Integer
+* @see     java.lang.Long
+* @see     java.lang.Short
+* @since   JDK1.0
+*/
+@:require(java0) extern class Number implements java.io.Serializable
+{
+	/**
+	* Returns the value of the specified number as an <code>int</code>.
+	* This may involve rounding or truncation.
+	*
+	* @return  the numeric value represented by this object after conversion
+	*          to type <code>int</code>.
+	*/
+	@:overload @:abstract public function intValue() : Int;
+	
+	/**
+	* Returns the value of the specified number as a <code>long</code>.
+	* This may involve rounding or truncation.
+	*
+	* @return  the numeric value represented by this object after conversion
+	*          to type <code>long</code>.
+	*/
+	@:overload @:abstract public function longValue() : haxe.Int64;
+	
+	/**
+	* Returns the value of the specified number as a <code>float</code>.
+	* This may involve rounding.
+	*
+	* @return  the numeric value represented by this object after conversion
+	*          to type <code>float</code>.
+	*/
+	@:overload @:abstract public function floatValue() : Single;
+	
+	/**
+	* Returns the value of the specified number as a <code>double</code>.
+	* This may involve rounding.
+	*
+	* @return  the numeric value represented by this object after conversion
+	*          to type <code>double</code>.
+	*/
+	@:overload @:abstract public function doubleValue() : Float;
+	
+	/**
+	* Returns the value of the specified number as a <code>byte</code>.
+	* This may involve rounding or truncation.
+	*
+	* @return  the numeric value represented by this object after conversion
+	*          to type <code>byte</code>.
+	* @since   JDK1.1
+	*/
+	@:require(java1) @:overload public function byteValue() : java.StdTypes.Int8;
+	
+	/**
+	* Returns the value of the specified number as a <code>short</code>.
+	* This may involve rounding or truncation.
+	*
+	* @return  the numeric value represented by this object after conversion
+	*          to type <code>short</code>.
+	* @since   JDK1.1
+	*/
+	@:require(java1) @:overload public function shortValue() : java.StdTypes.Int16;
+	
+	
+}

+ 106 - 0
std/java/lang/RuntimeException.hx

@@ -0,0 +1,106 @@
+package java.lang;
+/*
+* Copyright (c) 1995, 2011, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* {@code RuntimeException} is the superclass of those
+* exceptions that can be thrown during the normal operation of the
+* Java Virtual Machine.
+*
+* <p>{@code RuntimeException} and its subclasses are <em>unchecked
+* exceptions</em>.  Unchecked exceptions do <em>not</em> need to be
+* declared in a method or constructor's {@code throws} clause if they
+* can be thrown by the execution of the method or constructor and
+* propagate outside the method or constructor boundary.
+*
+* @author  Frank Yellin
+* @jls 11.2 Compile-Time Checking of Exceptions
+* @since   JDK1.0
+*/
+@:require(java0) extern class RuntimeException extends java.lang.Exception
+{
+	/** Constructs a new runtime exception with {@code null} as its
+	* detail message.  The cause is not initialized, and may subsequently be
+	* initialized by a call to {@link #initCause}.
+	*/
+	@:overload public function new() : Void;
+	
+	/** Constructs a new runtime exception with the specified detail message.
+	* The cause is not initialized, and may subsequently be initialized by a
+	* call to {@link #initCause}.
+	*
+	* @param   message   the detail message. The detail message is saved for
+	*          later retrieval by the {@link #getMessage()} method.
+	*/
+	@:overload public function new(message : String) : Void;
+	
+	/**
+	* Constructs a new runtime exception with the specified detail message and
+	* cause.  <p>Note that the detail message associated with
+	* {@code cause} is <i>not</i> automatically incorporated in
+	* this runtime exception's detail message.
+	*
+	* @param  message the detail message (which is saved for later retrieval
+	*         by the {@link #getMessage()} method).
+	* @param  cause the cause (which is saved for later retrieval by the
+	*         {@link #getCause()} method).  (A <tt>null</tt> value is
+	*         permitted, and indicates that the cause is nonexistent or
+	*         unknown.)
+	* @since  1.4
+	*/
+	@:require(java4) @:overload public function new(message : String, cause : java.lang.Throwable) : Void;
+	
+	/** Constructs a new runtime exception with the specified cause and a
+	* detail message of <tt>(cause==null ? null : cause.toString())</tt>
+	* (which typically contains the class and detail message of
+	* <tt>cause</tt>).  This constructor is useful for runtime exceptions
+	* that are little more than wrappers for other throwables.
+	*
+	* @param  cause the cause (which is saved for later retrieval by the
+	*         {@link #getCause()} method).  (A <tt>null</tt> value is
+	*         permitted, and indicates that the cause is nonexistent or
+	*         unknown.)
+	* @since  1.4
+	*/
+	@:require(java4) @:overload public function new(cause : java.lang.Throwable) : Void;
+	
+	/**
+	* Constructs a new runtime exception with the specified detail
+	* message, cause, suppression enabled or disabled, and writable
+	* stack trace enabled or disabled.
+	*
+	* @param  message the detail message.
+	* @param cause the cause.  (A {@code null} value is permitted,
+	* and indicates that the cause is nonexistent or unknown.)
+	* @param enableSuppression whether or not suppression is enabled
+	*                          or disabled
+	* @param writableStackTrace whether or not the stack trace should
+	*                           be writable
+	*
+	* @since 1.7
+	*/
+	@:require(java7) @:overload private function new(message : String, cause : java.lang.Throwable, enableSuppression : Bool, writableStackTrace : Bool) : Void;
+	
+	
+}

+ 387 - 0
std/java/lang/Short.hx

@@ -0,0 +1,387 @@
+package java.lang;
+/*
+* Copyright (c) 1996, 2009, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* The {@code Short} class wraps a value of primitive type {@code
+* short} in an object.  An object of type {@code Short} contains a
+* single field whose type is {@code short}.
+*
+* <p>In addition, this class provides several methods for converting
+* a {@code short} to a {@code String} and a {@code String} to a
+* {@code short}, as well as other constants and methods useful when
+* dealing with a {@code short}.
+*
+* @author  Nakul Saraiya
+* @author  Joseph D. Darcy
+* @see     java.lang.Number
+* @since   JDK1.1
+*/
+@:require(java1) extern class Short extends java.lang.Number implements java.lang.Comparable<Short>
+{
+	/**
+	* A constant holding the minimum value a {@code short} can
+	* have, -2<sup>15</sup>.
+	*/
+	public static var MIN_VALUE(default, null) : java.StdTypes.Int16;
+	
+	/**
+	* A constant holding the maximum value a {@code short} can
+	* have, 2<sup>15</sup>-1.
+	*/
+	public static var MAX_VALUE(default, null) : java.StdTypes.Int16;
+	
+	/**
+	* The {@code Class} instance representing the primitive type
+	* {@code short}.
+	*/
+	public static var TYPE(default, null) : Class<Short>;
+	
+	/**
+	* Returns a new {@code String} object representing the
+	* specified {@code short}. The radix is assumed to be 10.
+	*
+	* @param s the {@code short} to be converted
+	* @return the string representation of the specified {@code short}
+	* @see java.lang.Integer#toString(int)
+	*/
+	@:native('toString') @:overload public static function _toString(s : java.StdTypes.Int16) : String;
+	
+	/**
+	* Parses the string argument as a signed {@code short} in the
+	* radix specified by the second argument. The characters in the
+	* string must all be digits, of the specified radix (as
+	* determined by whether {@link java.lang.Character#digit(char,
+	* int)} returns a nonnegative value) except that the first
+	* character may be an ASCII minus sign {@code '-'}
+	* (<code>'&#92;u002D'</code>) to indicate a negative value or an
+	* ASCII plus sign {@code '+'} (<code>'&#92;u002B'</code>) to
+	* indicate a positive value.  The resulting {@code short} value
+	* is returned.
+	*
+	* <p>An exception of type {@code NumberFormatException} is
+	* thrown if any of the following situations occurs:
+	* <ul>
+	* <li> The first argument is {@code null} or is a string of
+	* length zero.
+	*
+	* <li> The radix is either smaller than {@link
+	* java.lang.Character#MIN_RADIX} or larger than {@link
+	* java.lang.Character#MAX_RADIX}.
+	*
+	* <li> Any character of the string is not a digit of the
+	* specified radix, except that the first character may be a minus
+	* sign {@code '-'} (<code>'&#92;u002D'</code>) or plus sign
+	* {@code '+'} (<code>'&#92;u002B'</code>) provided that the
+	* string is longer than length 1.
+	*
+	* <li> The value represented by the string is not a value of type
+	* {@code short}.
+	* </ul>
+	*
+	* @param s         the {@code String} containing the
+	*                  {@code short} representation to be parsed
+	* @param radix     the radix to be used while parsing {@code s}
+	* @return          the {@code short} represented by the string
+	*                  argument in the specified radix.
+	* @throws          NumberFormatException If the {@code String}
+	*                  does not contain a parsable {@code short}.
+	*/
+	@:overload public static function parseShort(s : String, radix : Int) : java.StdTypes.Int16;
+	
+	/**
+	* Parses the string argument as a signed decimal {@code
+	* short}. The characters in the string must all be decimal
+	* digits, except that the first character may be an ASCII minus
+	* sign {@code '-'} (<code>'&#92;u002D'</code>) to indicate a
+	* negative value or an ASCII plus sign {@code '+'}
+	* (<code>'&#92;u002B'</code>) to indicate a positive value.  The
+	* resulting {@code short} value is returned, exactly as if the
+	* argument and the radix 10 were given as arguments to the {@link
+	* #parseShort(java.lang.String, int)} method.
+	*
+	* @param s a {@code String} containing the {@code short}
+	*          representation to be parsed
+	* @return  the {@code short} value represented by the
+	*          argument in decimal.
+	* @throws  NumberFormatException If the string does not
+	*          contain a parsable {@code short}.
+	*/
+	@:overload public static function parseShort(s : String) : java.StdTypes.Int16;
+	
+	/**
+	* Returns a {@code Short} object holding the value
+	* extracted from the specified {@code String} when parsed
+	* with the radix given by the second argument. The first argument
+	* is interpreted as representing a signed {@code short} in
+	* the radix specified by the second argument, exactly as if the
+	* argument were given to the {@link #parseShort(java.lang.String,
+	* int)} method. The result is a {@code Short} object that
+	* represents the {@code short} value specified by the string.
+	*
+	* <p>In other words, this method returns a {@code Short} object
+	* equal to the value of:
+	*
+	* <blockquote>
+	*  {@code new Short(Short.parseShort(s, radix))}
+	* </blockquote>
+	*
+	* @param s         the string to be parsed
+	* @param radix     the radix to be used in interpreting {@code s}
+	* @return          a {@code Short} object holding the value
+	*                  represented by the string argument in the
+	*                  specified radix.
+	* @throws          NumberFormatException If the {@code String} does
+	*                  not contain a parsable {@code short}.
+	*/
+	@:overload public static function valueOf(s : String, radix : Int) : Short;
+	
+	/**
+	* Returns a {@code Short} object holding the
+	* value given by the specified {@code String}. The argument
+	* is interpreted as representing a signed decimal
+	* {@code short}, exactly as if the argument were given to
+	* the {@link #parseShort(java.lang.String)} method. The result is
+	* a {@code Short} object that represents the
+	* {@code short} value specified by the string.
+	*
+	* <p>In other words, this method returns a {@code Short} object
+	* equal to the value of:
+	*
+	* <blockquote>
+	*  {@code new Short(Short.parseShort(s))}
+	* </blockquote>
+	*
+	* @param s the string to be parsed
+	* @return  a {@code Short} object holding the value
+	*          represented by the string argument
+	* @throws  NumberFormatException If the {@code String} does
+	*          not contain a parsable {@code short}.
+	*/
+	@:overload public static function valueOf(s : String) : Short;
+	
+	/**
+	* Returns a {@code Short} instance representing the specified
+	* {@code short} value.
+	* If a new {@code Short} instance is not required, this method
+	* should generally be used in preference to the constructor
+	* {@link #Short(short)}, as this method is likely to yield
+	* significantly better space and time performance by caching
+	* frequently requested values.
+	*
+	* This method will always cache values in the range -128 to 127,
+	* inclusive, and may cache other values outside of this range.
+	*
+	* @param  s a short value.
+	* @return a {@code Short} instance representing {@code s}.
+	* @since  1.5
+	*/
+	@:require(java5) @:overload public static function valueOf(s : java.StdTypes.Int16) : Short;
+	
+	/**
+	* Decodes a {@code String} into a {@code Short}.
+	* Accepts decimal, hexadecimal, and octal numbers given by
+	* the following grammar:
+	*
+	* <blockquote>
+	* <dl>
+	* <dt><i>DecodableString:</i>
+	* <dd><i>Sign<sub>opt</sub> DecimalNumeral</i>
+	* <dd><i>Sign<sub>opt</sub></i> {@code 0x} <i>HexDigits</i>
+	* <dd><i>Sign<sub>opt</sub></i> {@code 0X} <i>HexDigits</i>
+	* <dd><i>Sign<sub>opt</sub></i> {@code #} <i>HexDigits</i>
+	* <dd><i>Sign<sub>opt</sub></i> {@code 0} <i>OctalDigits</i>
+	* <p>
+	* <dt><i>Sign:</i>
+	* <dd>{@code -}
+	* <dd>{@code +}
+	* </dl>
+	* </blockquote>
+	*
+	* <i>DecimalNumeral</i>, <i>HexDigits</i>, and <i>OctalDigits</i>
+	* are as defined in section 3.10.1 of
+	* <cite>The Java&trade; Language Specification</cite>,
+	* except that underscores are not accepted between digits.
+	*
+	* <p>The sequence of characters following an optional
+	* sign and/or radix specifier ("{@code 0x}", "{@code 0X}",
+	* "{@code #}", or leading zero) is parsed as by the {@code
+	* Short.parseShort} method with the indicated radix (10, 16, or
+	* 8).  This sequence of characters must represent a positive
+	* value or a {@link NumberFormatException} will be thrown.  The
+	* result is negated if first character of the specified {@code
+	* String} is the minus sign.  No whitespace characters are
+	* permitted in the {@code String}.
+	*
+	* @param     nm the {@code String} to decode.
+	* @return    a {@code Short} object holding the {@code short}
+	*            value represented by {@code nm}
+	* @throws    NumberFormatException  if the {@code String} does not
+	*            contain a parsable {@code short}.
+	* @see java.lang.Short#parseShort(java.lang.String, int)
+	*/
+	@:overload public static function decode(nm : String) : Short;
+	
+	/**
+	* Constructs a newly allocated {@code Short} object that
+	* represents the specified {@code short} value.
+	*
+	* @param value     the value to be represented by the
+	*                  {@code Short}.
+	*/
+	@:overload public function new(value : java.StdTypes.Int16) : Void;
+	
+	/**
+	* Constructs a newly allocated {@code Short} object that
+	* represents the {@code short} value indicated by the
+	* {@code String} parameter. The string is converted to a
+	* {@code short} value in exactly the manner used by the
+	* {@code parseShort} method for radix 10.
+	*
+	* @param s the {@code String} to be converted to a
+	*          {@code Short}
+	* @throws  NumberFormatException If the {@code String}
+	*          does not contain a parsable {@code short}.
+	* @see     java.lang.Short#parseShort(java.lang.String, int)
+	*/
+	@:overload public function new(s : String) : Void;
+	
+	/**
+	* Returns the value of this {@code Short} as a
+	* {@code byte}.
+	*/
+	@:overload override public function byteValue() : java.StdTypes.Int8;
+	
+	/**
+	* Returns the value of this {@code Short} as a
+	* {@code short}.
+	*/
+	@:overload override public function shortValue() : java.StdTypes.Int16;
+	
+	/**
+	* Returns the value of this {@code Short} as an
+	* {@code int}.
+	*/
+	@:overload override public function intValue() : Int;
+	
+	/**
+	* Returns the value of this {@code Short} as a
+	* {@code long}.
+	*/
+	@:overload override public function longValue() : haxe.Int64;
+	
+	/**
+	* Returns the value of this {@code Short} as a
+	* {@code float}.
+	*/
+	@:overload override public function floatValue() : Single;
+	
+	/**
+	* Returns the value of this {@code Short} as a
+	* {@code double}.
+	*/
+	@:overload override public function doubleValue() : Float;
+	
+	/**
+	* Returns a {@code String} object representing this
+	* {@code Short}'s value.  The value is converted to signed
+	* decimal representation and returned as a string, exactly as if
+	* the {@code short} value were given as an argument to the
+	* {@link java.lang.Short#toString(short)} method.
+	*
+	* @return  a string representation of the value of this object in
+	*          base&nbsp;10.
+	*/
+	@:overload public function toString() : String;
+	
+	/**
+	* Returns a hash code for this {@code Short}; equal to the result
+	* of invoking {@code intValue()}.
+	*
+	* @return a hash code value for this {@code Short}
+	*/
+	@:overload public function hashCode() : Int;
+	
+	/**
+	* Compares this object to the specified object.  The result is
+	* {@code true} if and only if the argument is not
+	* {@code null} and is a {@code Short} object that
+	* contains the same {@code short} value as this object.
+	*
+	* @param obj       the object to compare with
+	* @return          {@code true} if the objects are the same;
+	*                  {@code false} otherwise.
+	*/
+	@:overload public function equals(obj : Dynamic) : Bool;
+	
+	/**
+	* Compares two {@code Short} objects numerically.
+	*
+	* @param   anotherShort   the {@code Short} to be compared.
+	* @return  the value {@code 0} if this {@code Short} is
+	*          equal to the argument {@code Short}; a value less than
+	*          {@code 0} if this {@code Short} is numerically less
+	*          than the argument {@code Short}; and a value greater than
+	*           {@code 0} if this {@code Short} is numerically
+	*           greater than the argument {@code Short} (signed
+	*           comparison).
+	* @since   1.2
+	*/
+	@:require(java2) @:overload public function compareTo(anotherShort : Short) : Int;
+	
+	/**
+	* Compares two {@code short} values numerically.
+	* The value returned is identical to what would be returned by:
+	* <pre>
+	*    Short.valueOf(x).compareTo(Short.valueOf(y))
+	* </pre>
+	*
+	* @param  x the first {@code short} to compare
+	* @param  y the second {@code short} to compare
+	* @return the value {@code 0} if {@code x == y};
+	*         a value less than {@code 0} if {@code x < y}; and
+	*         a value greater than {@code 0} if {@code x > y}
+	* @since 1.7
+	*/
+	@:require(java7) @:overload public static function compare(x : java.StdTypes.Int16, y : java.StdTypes.Int16) : Int;
+	
+	/**
+	* The number of bits used to represent a {@code short} value in two's
+	* complement binary form.
+	* @since 1.5
+	*/
+	@:require(java5) public static var SIZE(default, null) : Int;
+	
+	/**
+	* Returns the value obtained by reversing the order of the bytes in the
+	* two's complement representation of the specified {@code short} value.
+	*
+	* @return the value obtained by reversing (or, equivalently, swapping)
+	*     the bytes in the specified {@code short} value.
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public static function reverseBytes(i : java.StdTypes.Int16) : java.StdTypes.Int16;
+	
+	
+}

+ 175 - 0
std/java/lang/StackTraceElement.hx

@@ -0,0 +1,175 @@
+package java.lang;
+/*
+* Copyright (c) 2000, 2011, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* An element in a stack trace, as returned by {@link
+* Throwable#getStackTrace()}.  Each element represents a single stack frame.
+* All stack frames except for the one at the top of the stack represent
+* a method invocation.  The frame at the top of the stack represents the
+* execution point at which the stack trace was generated.  Typically,
+* this is the point at which the throwable corresponding to the stack trace
+* was created.
+*
+* @since  1.4
+* @author Josh Bloch
+*/
+@:require(java4) extern class StackTraceElement implements java.io.Serializable
+{
+	/**
+	* Creates a stack trace element representing the specified execution
+	* point.
+	*
+	* @param declaringClass the fully qualified name of the class containing
+	*        the execution point represented by the stack trace element
+	* @param methodName the name of the method containing the execution point
+	*        represented by the stack trace element
+	* @param fileName the name of the file containing the execution point
+	*         represented by the stack trace element, or {@code null} if
+	*         this information is unavailable
+	* @param lineNumber the line number of the source line containing the
+	*         execution point represented by this stack trace element, or
+	*         a negative number if this information is unavailable. A value
+	*         of -2 indicates that the method containing the execution point
+	*         is a native method
+	* @throws NullPointerException if {@code declaringClass} or
+	*         {@code methodName} is null
+	* @since 1.5
+	*/
+	@:require(java5) @:overload public function new(declaringClass : String, methodName : String, fileName : String, lineNumber : Int) : Void;
+	
+	/**
+	* Returns the name of the source file containing the execution point
+	* represented by this stack trace element.  Generally, this corresponds
+	* to the {@code SourceFile} attribute of the relevant {@code class}
+	* file (as per <i>The Java Virtual Machine Specification</i>, Section
+	* 4.7.7).  In some systems, the name may refer to some source code unit
+	* other than a file, such as an entry in source repository.
+	*
+	* @return the name of the file containing the execution point
+	*         represented by this stack trace element, or {@code null} if
+	*         this information is unavailable.
+	*/
+	@:overload public function getFileName() : String;
+	
+	/**
+	* Returns the line number of the source line containing the execution
+	* point represented by this stack trace element.  Generally, this is
+	* derived from the {@code LineNumberTable} attribute of the relevant
+	* {@code class} file (as per <i>The Java Virtual Machine
+	* Specification</i>, Section 4.7.8).
+	*
+	* @return the line number of the source line containing the execution
+	*         point represented by this stack trace element, or a negative
+	*         number if this information is unavailable.
+	*/
+	@:overload public function getLineNumber() : Int;
+	
+	/**
+	* Returns the fully qualified name of the class containing the
+	* execution point represented by this stack trace element.
+	*
+	* @return the fully qualified name of the {@code Class} containing
+	*         the execution point represented by this stack trace element.
+	*/
+	@:overload public function getClassName() : String;
+	
+	/**
+	* Returns the name of the method containing the execution point
+	* represented by this stack trace element.  If the execution point is
+	* contained in an instance or class initializer, this method will return
+	* the appropriate <i>special method name</i>, {@code <init>} or
+	* {@code <clinit>}, as per Section 3.9 of <i>The Java Virtual
+	* Machine Specification</i>.
+	*
+	* @return the name of the method containing the execution point
+	*         represented by this stack trace element.
+	*/
+	@:overload public function getMethodName() : String;
+	
+	/**
+	* Returns true if the method containing the execution point
+	* represented by this stack trace element is a native method.
+	*
+	* @return {@code true} if the method containing the execution point
+	*         represented by this stack trace element is a native method.
+	*/
+	@:overload public function isNativeMethod() : Bool;
+	
+	/**
+	* Returns a string representation of this stack trace element.  The
+	* format of this string depends on the implementation, but the following
+	* examples may be regarded as typical:
+	* <ul>
+	* <li>
+	*   {@code "MyClass.mash(MyClass.java:9)"} - Here, {@code "MyClass"}
+	*   is the <i>fully-qualified name</i> of the class containing the
+	*   execution point represented by this stack trace element,
+	*   {@code "mash"} is the name of the method containing the execution
+	*   point, {@code "MyClass.java"} is the source file containing the
+	*   execution point, and {@code "9"} is the line number of the source
+	*   line containing the execution point.
+	* <li>
+	*   {@code "MyClass.mash(MyClass.java)"} - As above, but the line
+	*   number is unavailable.
+	* <li>
+	*   {@code "MyClass.mash(Unknown Source)"} - As above, but neither
+	*   the file name nor the line  number are available.
+	* <li>
+	*   {@code "MyClass.mash(Native Method)"} - As above, but neither
+	*   the file name nor the line  number are available, and the method
+	*   containing the execution point is known to be a native method.
+	* </ul>
+	* @see    Throwable#printStackTrace()
+	*/
+	@:overload public function toString() : String;
+	
+	/**
+	* Returns true if the specified object is another
+	* {@code StackTraceElement} instance representing the same execution
+	* point as this instance.  Two stack trace elements {@code a} and
+	* {@code b} are equal if and only if:
+	* <pre>
+	*     equals(a.getFileName(), b.getFileName()) &&
+	*     a.getLineNumber() == b.getLineNumber()) &&
+	*     equals(a.getClassName(), b.getClassName()) &&
+	*     equals(a.getMethodName(), b.getMethodName())
+	* </pre>
+	* where {@code equals} has the semantics of {@link
+	* java.util.Objects#equals(Object, Object) Objects.equals}.
+	*
+	* @param  obj the object to be compared with this stack trace element.
+	* @return true if the specified object is another
+	*         {@code StackTraceElement} instance representing the same
+	*         execution point as this instance.
+	*/
+	@:overload public function equals(obj : Dynamic) : Bool;
+	
+	/**
+	* Returns a hash code value for this stack trace element.
+	*/
+	@:overload public function hashCode() : Int;
+	
+	
+}

+ 619 - 55
std/java/lang/Throwable.hx

@@ -1,55 +1,619 @@
-/*
- * Copyright (C)2005-2012 Haxe Foundation
- *
- * Permission is hereby granted, free of charge, to any person obtaining a
- * copy of this software and associated documentation files (the "Software"),
- * to deal in the Software without restriction, including without limitation
- * the rights to use, copy, modify, merge, publish, distribute, sublicense,
- * and/or sell copies of the Software, and to permit persons to whom the
- * Software is furnished to do so, subject to the following conditions:
- *
- * The above copyright notice and this permission notice shall be included in
- * all copies or substantial portions of the Software.
- *
- * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
- * IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
- * FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
- * AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
- * LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
- * FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER
- * DEALINGS IN THE SOFTWARE.
- */
-package java.lang;
-import java.NativeArray;
-
-extern class Throwable 
-{
-	
-	function new(message:String, cause:Throwable):Void;
-	function fillInStackTrace():Throwable;
-	function getCause():Throwable;
-	function getLocalizedMessage():String;
-	function getMessage():String;
-	function getStackTrace():NativeArray<StackTraceElement>;
-	function setStackTrace(stackTrace:NativeArray<StackTraceElement>):Void;
-	function initCause(cause:Throwable):Throwable;
-	function printStackTrace():Void;
-	
-}
-
-extern class Exception extends Throwable { }
-
-extern class RuntimeException extends Exception { }
-
-extern class Error extends Throwable { }
-
-extern class StackTraceElement
-{
-	function new(declaringClass:String, methodName:String, fileName:String, lineNumber:Int):Void;
-	
-	function getClassName():String;
-	function getFileName():String;
-	function getLineNumber():Int;
-	function getMethodName():String;
-	function isNativeMethod():Bool;
-}
+package java.lang;
+/*
+* Copyright (c) 1994, 2011, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/**
+* The {@code Throwable} class is the superclass of all errors and
+* exceptions in the Java language. Only objects that are instances of this
+* class (or one of its subclasses) are thrown by the Java Virtual Machine or
+* can be thrown by the Java {@code throw} statement. Similarly, only
+* this class or one of its subclasses can be the argument type in a
+* {@code catch} clause.
+*
+* For the purposes of compile-time checking of exceptions, {@code
+* Throwable} and any subclass of {@code Throwable} that is not also a
+* subclass of either {@link RuntimeException} or {@link Error} are
+* regarded as checked exceptions.
+*
+* <p>Instances of two subclasses, {@link java.lang.Error} and
+* {@link java.lang.Exception}, are conventionally used to indicate
+* that exceptional situations have occurred. Typically, these instances
+* are freshly created in the context of the exceptional situation so
+* as to include relevant information (such as stack trace data).
+*
+* <p>A throwable contains a snapshot of the execution stack of its
+* thread at the time it was created. It can also contain a message
+* string that gives more information about the error. Over time, a
+* throwable can {@linkplain Throwable#addSuppressed suppress} other
+* throwables from being propagated.  Finally, the throwable can also
+* contain a <i>cause</i>: another throwable that caused this
+* throwable to be constructed.  The recording of this causal information
+* is referred to as the <i>chained exception</i> facility, as the
+* cause can, itself, have a cause, and so on, leading to a "chain" of
+* exceptions, each caused by another.
+*
+* <p>One reason that a throwable may have a cause is that the class that
+* throws it is built atop a lower layered abstraction, and an operation on
+* the upper layer fails due to a failure in the lower layer.  It would be bad
+* design to let the throwable thrown by the lower layer propagate outward, as
+* it is generally unrelated to the abstraction provided by the upper layer.
+* Further, doing so would tie the API of the upper layer to the details of
+* its implementation, assuming the lower layer's exception was a checked
+* exception.  Throwing a "wrapped exception" (i.e., an exception containing a
+* cause) allows the upper layer to communicate the details of the failure to
+* its caller without incurring either of these shortcomings.  It preserves
+* the flexibility to change the implementation of the upper layer without
+* changing its API (in particular, the set of exceptions thrown by its
+* methods).
+*
+* <p>A second reason that a throwable may have a cause is that the method
+* that throws it must conform to a general-purpose interface that does not
+* permit the method to throw the cause directly.  For example, suppose
+* a persistent collection conforms to the {@link java.util.Collection
+* Collection} interface, and that its persistence is implemented atop
+* {@code java.io}.  Suppose the internals of the {@code add} method
+* can throw an {@link java.io.IOException IOException}.  The implementation
+* can communicate the details of the {@code IOException} to its caller
+* while conforming to the {@code Collection} interface by wrapping the
+* {@code IOException} in an appropriate unchecked exception.  (The
+* specification for the persistent collection should indicate that it is
+* capable of throwing such exceptions.)
+*
+* <p>A cause can be associated with a throwable in two ways: via a
+* constructor that takes the cause as an argument, or via the
+* {@link #initCause(Throwable)} method.  New throwable classes that
+* wish to allow causes to be associated with them should provide constructors
+* that take a cause and delegate (perhaps indirectly) to one of the
+* {@code Throwable} constructors that takes a cause.
+*
+* Because the {@code initCause} method is public, it allows a cause to be
+* associated with any throwable, even a "legacy throwable" whose
+* implementation predates the addition of the exception chaining mechanism to
+* {@code Throwable}.
+*
+* <p>By convention, class {@code Throwable} and its subclasses have two
+* constructors, one that takes no arguments and one that takes a
+* {@code String} argument that can be used to produce a detail message.
+* Further, those subclasses that might likely have a cause associated with
+* them should have two more constructors, one that takes a
+* {@code Throwable} (the cause), and one that takes a
+* {@code String} (the detail message) and a {@code Throwable} (the
+* cause).
+*
+* @author  unascribed
+* @author  Josh Bloch (Added exception chaining and programmatic access to
+*          stack trace in 1.4.)
+* @jls 11.2 Compile-Time Checking of Exceptions
+* @since JDK1.0
+*/
+@:require(java0) extern class Throwable implements java.io.Serializable
+{
+	/**
+	* Constructs a new throwable with {@code null} as its detail message.
+	* The cause is not initialized, and may subsequently be initialized by a
+	* call to {@link #initCause}.
+	*
+	* <p>The {@link #fillInStackTrace()} method is called to initialize
+	* the stack trace data in the newly created throwable.
+	*/
+	@:overload public function new() : Void;
+	
+	/**
+	* Constructs a new throwable with the specified detail message.  The
+	* cause is not initialized, and may subsequently be initialized by
+	* a call to {@link #initCause}.
+	*
+	* <p>The {@link #fillInStackTrace()} method is called to initialize
+	* the stack trace data in the newly created throwable.
+	*
+	* @param   message   the detail message. The detail message is saved for
+	*          later retrieval by the {@link #getMessage()} method.
+	*/
+	@:overload public function new(message : String) : Void;
+	
+	/**
+	* Constructs a new throwable with the specified detail message and
+	* cause.  <p>Note that the detail message associated with
+	* {@code cause} is <i>not</i> automatically incorporated in
+	* this throwable's detail message.
+	*
+	* <p>The {@link #fillInStackTrace()} method is called to initialize
+	* the stack trace data in the newly created throwable.
+	*
+	* @param  message the detail message (which is saved for later retrieval
+	*         by the {@link #getMessage()} method).
+	* @param  cause the cause (which is saved for later retrieval by the
+	*         {@link #getCause()} method).  (A {@code null} value is
+	*         permitted, and indicates that the cause is nonexistent or
+	*         unknown.)
+	* @since  1.4
+	*/
+	@:require(java4) @:overload public function new(message : String, cause : Throwable) : Void;
+	
+	/**
+	* Constructs a new throwable with the specified cause and a detail
+	* message of {@code (cause==null ? null : cause.toString())} (which
+	* typically contains the class and detail message of {@code cause}).
+	* This constructor is useful for throwables that are little more than
+	* wrappers for other throwables (for example, {@link
+	* java.security.PrivilegedActionException}).
+	*
+	* <p>The {@link #fillInStackTrace()} method is called to initialize
+	* the stack trace data in the newly created throwable.
+	*
+	* @param  cause the cause (which is saved for later retrieval by the
+	*         {@link #getCause()} method).  (A {@code null} value is
+	*         permitted, and indicates that the cause is nonexistent or
+	*         unknown.)
+	* @since  1.4
+	*/
+	@:require(java4) @:overload public function new(cause : Throwable) : Void;
+	
+	/**
+	* Constructs a new throwable with the specified detail message,
+	* cause, {@linkplain #addSuppressed suppression} enabled or
+	* disabled, and writable stack trace enabled or disabled.  If
+	* suppression is disabled, {@link #getSuppressed} for this object
+	* will return a zero-length array and calls to {@link
+	* #addSuppressed} that would otherwise append an exception to the
+	* suppressed list will have no effect.  If the writable stack
+	* trace is false, this constructor will not call {@link
+	* #fillInStackTrace()}, a {@code null} will be written to the
+	* {@code stackTrace} field, and subsequent calls to {@code
+	* fillInStackTrace} and {@link
+	* #setStackTrace(StackTraceElement[])} will not set the stack
+	* trace.  If the writable stack trace is false, {@link
+	* #getStackTrace} will return a zero length array.
+	*
+	* <p>Note that the other constructors of {@code Throwable} treat
+	* suppression as being enabled and the stack trace as being
+	* writable.  Subclasses of {@code Throwable} should document any
+	* conditions under which suppression is disabled and document
+	* conditions under which the stack trace is not writable.
+	* Disabling of suppression should only occur in exceptional
+	* circumstances where special requirements exist, such as a
+	* virtual machine reusing exception objects under low-memory
+	* situations.  Circumstances where a given exception object is
+	* repeatedly caught and rethrown, such as to implement control
+	* flow between two sub-systems, is another situation where
+	* immutable throwable objects would be appropriate.
+	*
+	* @param  message the detail message.
+	* @param cause the cause.  (A {@code null} value is permitted,
+	* and indicates that the cause is nonexistent or unknown.)
+	* @param enableSuppression whether or not suppression is enabled or disabled
+	* @param writableStackTrace whether or not the stack trace should be
+	*                           writable
+	*
+	* @see OutOfMemoryError
+	* @see NullPointerException
+	* @see ArithmeticException
+	* @since 1.7
+	*/
+	@:require(java7) @:overload private function new(message : String, cause : Throwable, enableSuppression : Bool, writableStackTrace : Bool) : Void;
+	
+	/**
+	* Returns the detail message string of this throwable.
+	*
+	* @return  the detail message string of this {@code Throwable} instance
+	*          (which may be {@code null}).
+	*/
+	@:overload public function getMessage() : String;
+	
+	/**
+	* Creates a localized description of this throwable.
+	* Subclasses may override this method in order to produce a
+	* locale-specific message.  For subclasses that do not override this
+	* method, the default implementation returns the same result as
+	* {@code getMessage()}.
+	*
+	* @return  The localized description of this throwable.
+	* @since   JDK1.1
+	*/
+	@:require(java1) @:overload public function getLocalizedMessage() : String;
+	
+	/**
+	* Returns the cause of this throwable or {@code null} if the
+	* cause is nonexistent or unknown.  (The cause is the throwable that
+	* caused this throwable to get thrown.)
+	*
+	* <p>This implementation returns the cause that was supplied via one of
+	* the constructors requiring a {@code Throwable}, or that was set after
+	* creation with the {@link #initCause(Throwable)} method.  While it is
+	* typically unnecessary to override this method, a subclass can override
+	* it to return a cause set by some other means.  This is appropriate for
+	* a "legacy chained throwable" that predates the addition of chained
+	* exceptions to {@code Throwable}.  Note that it is <i>not</i>
+	* necessary to override any of the {@code PrintStackTrace} methods,
+	* all of which invoke the {@code getCause} method to determine the
+	* cause of a throwable.
+	*
+	* @return  the cause of this throwable or {@code null} if the
+	*          cause is nonexistent or unknown.
+	* @since 1.4
+	*/
+	@:require(java4) @:overload @:synchronized public function getCause() : Throwable;
+	
+	/**
+	* Initializes the <i>cause</i> of this throwable to the specified value.
+	* (The cause is the throwable that caused this throwable to get thrown.)
+	*
+	* <p>This method can be called at most once.  It is generally called from
+	* within the constructor, or immediately after creating the
+	* throwable.  If this throwable was created
+	* with {@link #Throwable(Throwable)} or
+	* {@link #Throwable(String,Throwable)}, this method cannot be called
+	* even once.
+	*
+	* <p>An example of using this method on a legacy throwable type
+	* without other support for setting the cause is:
+	*
+	* <pre>
+	* try {
+	*     lowLevelOp();
+	* } catch (LowLevelException le) {
+	*     throw (HighLevelException)
+	*           new HighLevelException().initCause(le); // Legacy constructor
+	* }
+	* </pre>
+	*
+	* @param  cause the cause (which is saved for later retrieval by the
+	*         {@link #getCause()} method).  (A {@code null} value is
+	*         permitted, and indicates that the cause is nonexistent or
+	*         unknown.)
+	* @return  a reference to this {@code Throwable} instance.
+	* @throws IllegalArgumentException if {@code cause} is this
+	*         throwable.  (A throwable cannot be its own cause.)
+	* @throws IllegalStateException if this throwable was
+	*         created with {@link #Throwable(Throwable)} or
+	*         {@link #Throwable(String,Throwable)}, or this method has already
+	*         been called on this throwable.
+	* @since  1.4
+	*/
+	@:require(java4) @:overload @:synchronized public function initCause(cause : Throwable) : Throwable;
+	
+	/**
+	* Returns a short description of this throwable.
+	* The result is the concatenation of:
+	* <ul>
+	* <li> the {@linkplain Class#getName() name} of the class of this object
+	* <li> ": " (a colon and a space)
+	* <li> the result of invoking this object's {@link #getLocalizedMessage}
+	*      method
+	* </ul>
+	* If {@code getLocalizedMessage} returns {@code null}, then just
+	* the class name is returned.
+	*
+	* @return a string representation of this throwable.
+	*/
+	@:overload public function toString() : String;
+	
+	/**
+	* Prints this throwable and its backtrace to the
+	* standard error stream. This method prints a stack trace for this
+	* {@code Throwable} object on the error output stream that is
+	* the value of the field {@code System.err}. The first line of
+	* output contains the result of the {@link #toString()} method for
+	* this object.  Remaining lines represent data previously recorded by
+	* the method {@link #fillInStackTrace()}. The format of this
+	* information depends on the implementation, but the following
+	* example may be regarded as typical:
+	* <blockquote><pre>
+	* java.lang.NullPointerException
+	*         at MyClass.mash(MyClass.java:9)
+	*         at MyClass.crunch(MyClass.java:6)
+	*         at MyClass.main(MyClass.java:3)
+	* </pre></blockquote>
+	* This example was produced by running the program:
+	* <pre>
+	* class MyClass {
+	*     public static void main(String[] args) {
+	*         crunch(null);
+	*     }
+	*     static void crunch(int[] a) {
+	*         mash(a);
+	*     }
+	*     static void mash(int[] b) {
+	*         System.out.println(b[0]);
+	*     }
+	* }
+	* </pre>
+	* The backtrace for a throwable with an initialized, non-null cause
+	* should generally include the backtrace for the cause.  The format
+	* of this information depends on the implementation, but the following
+	* example may be regarded as typical:
+	* <pre>
+	* HighLevelException: MidLevelException: LowLevelException
+	*         at Junk.a(Junk.java:13)
+	*         at Junk.main(Junk.java:4)
+	* Caused by: MidLevelException: LowLevelException
+	*         at Junk.c(Junk.java:23)
+	*         at Junk.b(Junk.java:17)
+	*         at Junk.a(Junk.java:11)
+	*         ... 1 more
+	* Caused by: LowLevelException
+	*         at Junk.e(Junk.java:30)
+	*         at Junk.d(Junk.java:27)
+	*         at Junk.c(Junk.java:21)
+	*         ... 3 more
+	* </pre>
+	* Note the presence of lines containing the characters {@code "..."}.
+	* These lines indicate that the remainder of the stack trace for this
+	* exception matches the indicated number of frames from the bottom of the
+	* stack trace of the exception that was caused by this exception (the
+	* "enclosing" exception).  This shorthand can greatly reduce the length
+	* of the output in the common case where a wrapped exception is thrown
+	* from same method as the "causative exception" is caught.  The above
+	* example was produced by running the program:
+	* <pre>
+	* public class Junk {
+	*     public static void main(String args[]) {
+	*         try {
+	*             a();
+	*         } catch(HighLevelException e) {
+	*             e.printStackTrace();
+	*         }
+	*     }
+	*     static void a() throws HighLevelException {
+	*         try {
+	*             b();
+	*         } catch(MidLevelException e) {
+	*             throw new HighLevelException(e);
+	*         }
+	*     }
+	*     static void b() throws MidLevelException {
+	*         c();
+	*     }
+	*     static void c() throws MidLevelException {
+	*         try {
+	*             d();
+	*         } catch(LowLevelException e) {
+	*             throw new MidLevelException(e);
+	*         }
+	*     }
+	*     static void d() throws LowLevelException {
+	*        e();
+	*     }
+	*     static void e() throws LowLevelException {
+	*         throw new LowLevelException();
+	*     }
+	* }
+	*
+	* class HighLevelException extends Exception {
+	*     HighLevelException(Throwable cause) { super(cause); }
+	* }
+	*
+	* class MidLevelException extends Exception {
+	*     MidLevelException(Throwable cause)  { super(cause); }
+	* }
+	*
+	* class LowLevelException extends Exception {
+	* }
+	* </pre>
+	* As of release 7, the platform supports the notion of
+	* <i>suppressed exceptions</i> (in conjunction with the {@code
+	* try}-with-resources statement). Any exceptions that were
+	* suppressed in order to deliver an exception are printed out
+	* beneath the stack trace.  The format of this information
+	* depends on the implementation, but the following example may be
+	* regarded as typical:
+	*
+	* <pre>
+	* Exception in thread "main" java.lang.Exception: Something happened
+	*  at Foo.bar(Foo.java:10)
+	*  at Foo.main(Foo.java:5)
+	*  Suppressed: Resource$CloseFailException: Resource ID = 0
+	*          at Resource.close(Resource.java:26)
+	*          at Foo.bar(Foo.java:9)
+	*          ... 1 more
+	* </pre>
+	* Note that the "... n more" notation is used on suppressed exceptions
+	* just at it is used on causes. Unlike causes, suppressed exceptions are
+	* indented beyond their "containing exceptions."
+	*
+	* <p>An exception can have both a cause and one or more suppressed
+	* exceptions:
+	* <pre>
+	* Exception in thread "main" java.lang.Exception: Main block
+	*  at Foo3.main(Foo3.java:7)
+	*  Suppressed: Resource$CloseFailException: Resource ID = 2
+	*          at Resource.close(Resource.java:26)
+	*          at Foo3.main(Foo3.java:5)
+	*  Suppressed: Resource$CloseFailException: Resource ID = 1
+	*          at Resource.close(Resource.java:26)
+	*          at Foo3.main(Foo3.java:5)
+	* Caused by: java.lang.Exception: I did it
+	*  at Foo3.main(Foo3.java:8)
+	* </pre>
+	* Likewise, a suppressed exception can have a cause:
+	* <pre>
+	* Exception in thread "main" java.lang.Exception: Main block
+	*  at Foo4.main(Foo4.java:6)
+	*  Suppressed: Resource2$CloseFailException: Resource ID = 1
+	*          at Resource2.close(Resource2.java:20)
+	*          at Foo4.main(Foo4.java:5)
+	*  Caused by: java.lang.Exception: Rats, you caught me
+	*          at Resource2$CloseFailException.<init>(Resource2.java:45)
+	*          ... 2 more
+	* </pre>
+	*/
+	@:overload public function printStackTrace() : Void;
+	
+	/**
+	* Prints this throwable and its backtrace to the specified print stream.
+	*
+	* @param s {@code PrintStream} to use for output
+	*/
+	@:overload public function printStackTrace(s : java.io.PrintStream) : Void;
+	
+	/**
+	* Prints this throwable and its backtrace to the specified
+	* print writer.
+	*
+	* @param s {@code PrintWriter} to use for output
+	* @since   JDK1.1
+	*/
+	@:require(java1) @:overload public function printStackTrace(s : java.io.PrintWriter) : Void;
+	
+	/**
+	* Fills in the execution stack trace. This method records within this
+	* {@code Throwable} object information about the current state of
+	* the stack frames for the current thread.
+	*
+	* <p>If the stack trace of this {@code Throwable} {@linkplain
+	* Throwable#Throwable(String, Throwable, boolean, boolean) is not
+	* writable}, calling this method has no effect.
+	*
+	* @return  a reference to this {@code Throwable} instance.
+	* @see     java.lang.Throwable#printStackTrace()
+	*/
+	@:overload @:synchronized public function fillInStackTrace() : Throwable;
+	
+	/**
+	* Provides programmatic access to the stack trace information printed by
+	* {@link #printStackTrace()}.  Returns an array of stack trace elements,
+	* each representing one stack frame.  The zeroth element of the array
+	* (assuming the array's length is non-zero) represents the top of the
+	* stack, which is the last method invocation in the sequence.  Typically,
+	* this is the point at which this throwable was created and thrown.
+	* The last element of the array (assuming the array's length is non-zero)
+	* represents the bottom of the stack, which is the first method invocation
+	* in the sequence.
+	*
+	* <p>Some virtual machines may, under some circumstances, omit one
+	* or more stack frames from the stack trace.  In the extreme case,
+	* a virtual machine that has no stack trace information concerning
+	* this throwable is permitted to return a zero-length array from this
+	* method.  Generally speaking, the array returned by this method will
+	* contain one element for every frame that would be printed by
+	* {@code printStackTrace}.  Writes to the returned array do not
+	* affect future calls to this method.
+	*
+	* @return an array of stack trace elements representing the stack trace
+	*         pertaining to this throwable.
+	* @since  1.4
+	*/
+	@:require(java4) @:overload public function getStackTrace() : java.NativeArray<java.lang.StackTraceElement>;
+	
+	/**
+	* Sets the stack trace elements that will be returned by
+	* {@link #getStackTrace()} and printed by {@link #printStackTrace()}
+	* and related methods.
+	*
+	* This method, which is designed for use by RPC frameworks and other
+	* advanced systems, allows the client to override the default
+	* stack trace that is either generated by {@link #fillInStackTrace()}
+	* when a throwable is constructed or deserialized when a throwable is
+	* read from a serialization stream.
+	*
+	* <p>If the stack trace of this {@code Throwable} {@linkplain
+	* Throwable#Throwable(String, Throwable, boolean, boolean) is not
+	* writable}, calling this method has no effect other than
+	* validating its argument.
+	*
+	* @param   stackTrace the stack trace elements to be associated with
+	* this {@code Throwable}.  The specified array is copied by this
+	* call; changes in the specified array after the method invocation
+	* returns will have no affect on this {@code Throwable}'s stack
+	* trace.
+	*
+	* @throws NullPointerException if {@code stackTrace} is
+	*         {@code null} or if any of the elements of
+	*         {@code stackTrace} are {@code null}
+	*
+	* @since  1.4
+	*/
+	@:require(java4) @:overload public function setStackTrace(stackTrace : java.NativeArray<java.lang.StackTraceElement>) : Void;
+	
+	/**
+	* Appends the specified exception to the exceptions that were
+	* suppressed in order to deliver this exception. This method is
+	* thread-safe and typically called (automatically and implicitly)
+	* by the {@code try}-with-resources statement.
+	*
+	* <p>The suppression behavior is enabled <em>unless</em> disabled
+	* {@linkplain #Throwable(String, Throwable, boolean, boolean) via
+	* a constructor}.  When suppression is disabled, this method does
+	* nothing other than to validate its argument.
+	*
+	* <p>Note that when one exception {@linkplain
+	* #initCause(Throwable) causes} another exception, the first
+	* exception is usually caught and then the second exception is
+	* thrown in response.  In other words, there is a causal
+	* connection between the two exceptions.
+	*
+	* In contrast, there are situations where two independent
+	* exceptions can be thrown in sibling code blocks, in particular
+	* in the {@code try} block of a {@code try}-with-resources
+	* statement and the compiler-generated {@code finally} block
+	* which closes the resource.
+	*
+	* In these situations, only one of the thrown exceptions can be
+	* propagated.  In the {@code try}-with-resources statement, when
+	* there are two such exceptions, the exception originating from
+	* the {@code try} block is propagated and the exception from the
+	* {@code finally} block is added to the list of exceptions
+	* suppressed by the exception from the {@code try} block.  As an
+	* exception unwinds the stack, it can accumulate multiple
+	* suppressed exceptions.
+	*
+	* <p>An exception may have suppressed exceptions while also being
+	* caused by another exception.  Whether or not an exception has a
+	* cause is semantically known at the time of its creation, unlike
+	* whether or not an exception will suppress other exceptions
+	* which is typically only determined after an exception is
+	* thrown.
+	*
+	* <p>Note that programmer written code is also able to take
+	* advantage of calling this method in situations where there are
+	* multiple sibling exceptions and only one can be propagated.
+	*
+	* @param exception the exception to be added to the list of
+	*        suppressed exceptions
+	* @throws IllegalArgumentException if {@code exception} is this
+	*         throwable; a throwable cannot suppress itself.
+	* @throws NullPointerException if {@code exception} is {@code null}
+	* @since 1.7
+	*/
+	@:require(java7) @:overload @:final @:synchronized public function addSuppressed(exception : Throwable) : Void;
+	
+	/**
+	* Returns an array containing all of the exceptions that were
+	* suppressed, typically by the {@code try}-with-resources
+	* statement, in order to deliver this exception.
+	*
+	* If no exceptions were suppressed or {@linkplain
+	* #Throwable(String, Throwable, boolean, boolean) suppression is
+	* disabled}, an empty array is returned.  This method is
+	* thread-safe.  Writes to the returned array do not affect future
+	* calls to this method.
+	*
+	* @return an array containing all of the exceptions that were
+	*         suppressed to deliver this exception.
+	* @since 1.7
+	*/
+	@:require(java7) @:overload @:final @:synchronized public function getSuppressed() : java.NativeArray<Throwable>;
+	
+	
+}

+ 1528 - 0
std/java/util/Locale.hx

@@ -0,0 +1,1528 @@
+package java.util;
+/*
+* Copyright (c) 1996, 2011, Oracle and/or its affiliates. All rights reserved.
+* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
+*
+* This code is free software; you can redistribute it and/or modify it
+* under the terms of the GNU General Public License version 2 only, as
+* published by the Free Software Foundation.  Oracle designates this
+* particular file as subject to the "Classpath" exception as provided
+* by Oracle in the LICENSE file that accompanied this code.
+*
+* This code is distributed in the hope that it will be useful, but WITHOUT
+* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
+* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+* version 2 for more details (a copy is included in the LICENSE file that
+* accompanied this code).
+*
+* You should have received a copy of the GNU General Public License version
+* 2 along with this work; if not, write to the Free Software Foundation,
+* Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
+*
+* Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
+* or visit www.oracle.com if you need additional information or have any
+* questions.
+*/
+/*
+* (C) Copyright Taligent, Inc. 1996, 1997 - All Rights Reserved
+* (C) Copyright IBM Corp. 1996 - 1998 - All Rights Reserved
+*
+* The original version of this source code and documentation
+* is copyrighted and owned by Taligent, Inc., a wholly-owned
+* subsidiary of IBM. These materials are provided under terms
+* of a License Agreement between Taligent and Sun. This technology
+* is protected by multiple US and International patents.
+*
+* This notice and attribution to Taligent may not be removed.
+* Taligent is a registered trademark of Taligent, Inc.
+*
+*/
+/**
+* A <code>Locale</code> object represents a specific geographical, political,
+* or cultural region. An operation that requires a <code>Locale</code> to perform
+* its task is called <em>locale-sensitive</em> and uses the <code>Locale</code>
+* to tailor information for the user. For example, displaying a number
+* is a locale-sensitive operation&mdash; the number should be formatted
+* according to the customs and conventions of the user's native country,
+* region, or culture.
+*
+* <p> The <code>Locale</code> class implements identifiers
+* interchangeable with BCP 47 (IETF BCP 47, "Tags for Identifying
+* Languages"), with support for the LDML (UTS#35, "Unicode Locale
+* Data Markup Language") BCP 47-compatible extensions for locale data
+* exchange.
+*
+* <p> A <code>Locale</code> object logically consists of the fields
+* described below.
+*
+* <dl>
+*   <dt><a name="def_language"/><b>language</b></dt>
+*
+*   <dd>ISO 639 alpha-2 or alpha-3 language code, or registered
+*   language subtags up to 8 alpha letters (for future enhancements).
+*   When a language has both an alpha-2 code and an alpha-3 code, the
+*   alpha-2 code must be used.  You can find a full list of valid
+*   language codes in the IANA Language Subtag Registry (search for
+*   "Type: language").  The language field is case insensitive, but
+*   <code>Locale</code> always canonicalizes to lower case.</dd><br>
+*
+*   <dd>Well-formed language values have the form
+*   <code>[a-zA-Z]{2,8}</code>.  Note that this is not the the full
+*   BCP47 language production, since it excludes extlang.  They are
+*   not needed since modern three-letter language codes replace
+*   them.</dd><br>
+*
+*   <dd>Example: "en" (English), "ja" (Japanese), "kok" (Konkani)</dd><br>
+*
+*   <dt><a name="def_script"/><b>script</b></dt>
+*
+*   <dd>ISO 15924 alpha-4 script code.  You can find a full list of
+*   valid script codes in the IANA Language Subtag Registry (search
+*   for "Type: script").  The script field is case insensitive, but
+*   <code>Locale</code> always canonicalizes to title case (the first
+*   letter is upper case and the rest of the letters are lower
+*   case).</dd><br>
+*
+*   <dd>Well-formed script values have the form
+*   <code>[a-zA-Z]{4}</code></dd><br>
+*
+*   <dd>Example: "Latn" (Latin), "Cyrl" (Cyrillic)</dd><br>
+*
+*   <dt><a name="def_region"/><b>country (region)</b></dt>
+*
+*   <dd>ISO 3166 alpha-2 country code or UN M.49 numeric-3 area code.
+*   You can find a full list of valid country and region codes in the
+*   IANA Language Subtag Registry (search for "Type: region").  The
+*   country (region) field is case insensitive, but
+*   <code>Locale</code> always canonicalizes to upper case.</dd><br>
+*
+*   <dd>Well-formed country/region values have
+*   the form <code>[a-zA-Z]{2} | [0-9]{3}</code></dd><br>
+*
+*   <dd>Example: "US" (United States), "FR" (France), "029"
+*   (Caribbean)</dd><br>
+*
+*   <dt><a name="def_variant"/><b>variant</b></dt>
+*
+*   <dd>Any arbitrary value used to indicate a variation of a
+*   <code>Locale</code>.  Where there are two or more variant values
+*   each indicating its own semantics, these values should be ordered
+*   by importance, with most important first, separated by
+*   underscore('_').  The variant field is case sensitive.</dd><br>
+*
+*   <dd>Note: IETF BCP 47 places syntactic restrictions on variant
+*   subtags.  Also BCP 47 subtags are strictly used to indicate
+*   additional variations that define a language or its dialects that
+*   are not covered by any combinations of language, script and
+*   region subtags.  You can find a full list of valid variant codes
+*   in the IANA Language Subtag Registry (search for "Type: variant").
+*
+*   <p>However, the variant field in <code>Locale</code> has
+*   historically been used for any kind of variation, not just
+*   language variations.  For example, some supported variants
+*   available in Java SE Runtime Environments indicate alternative
+*   cultural behaviors such as calendar type or number script.  In
+*   BCP 47 this kind of information, which does not identify the
+*   language, is supported by extension subtags or private use
+*   subtags.</dd><br>
+*
+*   <dd>Well-formed variant values have the form <code>SUBTAG
+*   (('_'|'-') SUBTAG)*</code> where <code>SUBTAG =
+*   [0-9][0-9a-zA-Z]{3} | [0-9a-zA-Z]{5,8}</code>. (Note: BCP 47 only
+*   uses hyphen ('-') as a delimiter, this is more lenient).</dd><br>
+*
+*   <dd>Example: "polyton" (Polytonic Greek), "POSIX"</dd><br>
+*
+*   <dt><a name="def_extensions"/><b>extensions</b></dt>
+*
+*   <dd>A map from single character keys to string values, indicating
+*   extensions apart from language identification.  The extensions in
+*   <code>Locale</code> implement the semantics and syntax of BCP 47
+*   extension subtags and private use subtags. The extensions are
+*   case insensitive, but <code>Locale</code> canonicalizes all
+*   extension keys and values to lower case. Note that extensions
+*   cannot have empty values.</dd><br>
+*
+*   <dd>Well-formed keys are single characters from the set
+*   <code>[0-9a-zA-Z]</code>.  Well-formed values have the form
+*   <code>SUBTAG ('-' SUBTAG)*</code> where for the key 'x'
+*   <code>SUBTAG = [0-9a-zA-Z]{1,8}</code> and for other keys
+*   <code>SUBTAG = [0-9a-zA-Z]{2,8}</code> (that is, 'x' allows
+*   single-character subtags).</dd><br>
+*
+*   <dd>Example: key="u"/value="ca-japanese" (Japanese Calendar),
+*   key="x"/value="java-1-7"</dd>
+* </dl>
+*
+* <b>Note:</b> Although BCP 47 requires field values to be registered
+* in the IANA Language Subtag Registry, the <code>Locale</code> class
+* does not provide any validation features.  The <code>Builder</code>
+* only checks if an individual field satisfies the syntactic
+* requirement (is well-formed), but does not validate the value
+* itself.  See {@link Builder} for details.
+*
+* <h4><a name="def_locale_extension">Unicode locale/language extension</h4>
+*
+* <p>UTS#35, "Unicode Locale Data Markup Language" defines optional
+* attributes and keywords to override or refine the default behavior
+* associated with a locale.  A keyword is represented by a pair of
+* key and type.  For example, "nu-thai" indicates that Thai local
+* digits (value:"thai") should be used for formatting numbers
+* (key:"nu").
+*
+* <p>The keywords are mapped to a BCP 47 extension value using the
+* extension key 'u' ({@link #UNICODE_LOCALE_EXTENSION}).  The above
+* example, "nu-thai", becomes the extension "u-nu-thai".code
+*
+* <p>Thus, when a <code>Locale</code> object contains Unicode locale
+* attributes and keywords,
+* <code>getExtension(UNICODE_LOCALE_EXTENSION)</code> will return a
+* String representing this information, for example, "nu-thai".  The
+* <code>Locale</code> class also provides {@link
+* #getUnicodeLocaleAttributes}, {@link #getUnicodeLocaleKeys}, and
+* {@link #getUnicodeLocaleType} which allow you to access Unicode
+* locale attributes and key/type pairs directly.  When represented as
+* a string, the Unicode Locale Extension lists attributes
+* alphabetically, followed by key/type sequences with keys listed
+* alphabetically (the order of subtags comprising a key's type is
+* fixed when the type is defined)
+*
+* <p>A well-formed locale key has the form
+* <code>[0-9a-zA-Z]{2}</code>.  A well-formed locale type has the
+* form <code>"" | [0-9a-zA-Z]{3,8} ('-' [0-9a-zA-Z]{3,8})*</code> (it
+* can be empty, or a series of subtags 3-8 alphanums in length).  A
+* well-formed locale attribute has the form
+* <code>[0-9a-zA-Z]{3,8}</code> (it is a single subtag with the same
+* form as a locale type subtag).
+*
+* <p>The Unicode locale extension specifies optional behavior in
+* locale-sensitive services.  Although the LDML specification defines
+* various keys and values, actual locale-sensitive service
+* implementations in a Java Runtime Environment might not support any
+* particular Unicode locale attributes or key/type pairs.
+*
+* <h4>Creating a Locale</h4>
+*
+* <p>There are several different ways to create a <code>Locale</code>
+* object.
+*
+* <h5>Builder</h5>
+*
+* <p>Using {@link Builder} you can construct a <code>Locale</code> object
+* that conforms to BCP 47 syntax.
+*
+* <h5>Constructors</h5>
+*
+* <p>The <code>Locale</code> class provides three constructors:
+* <blockquote>
+* <pre>
+*     {@link #Locale(String language)}
+*     {@link #Locale(String language, String country)}
+*     {@link #Locale(String language, String country, String variant)}
+* </pre>
+* </blockquote>
+* These constructors allow you to create a <code>Locale</code> object
+* with language, country and variant, but you cannot specify
+* script or extensions.
+*
+* <h5>Factory Methods</h5>
+*
+* <p>The method {@link #forLanguageTag} creates a <code>Locale</code>
+* object for a well-formed BCP 47 language tag.
+*
+* <h5>Locale Constants</h5>
+*
+* <p>The <code>Locale</code> class provides a number of convenient constants
+* that you can use to create <code>Locale</code> objects for commonly used
+* locales. For example, the following creates a <code>Locale</code> object
+* for the United States:
+* <blockquote>
+* <pre>
+*     Locale.US
+* </pre>
+* </blockquote>
+*
+* <h4>Use of Locale</h4>
+*
+* <p>Once you've created a <code>Locale</code> you can query it for information
+* about itself. Use <code>getCountry</code> to get the country (or region)
+* code and <code>getLanguage</code> to get the language code.
+* You can use <code>getDisplayCountry</code> to get the
+* name of the country suitable for displaying to the user. Similarly,
+* you can use <code>getDisplayLanguage</code> to get the name of
+* the language suitable for displaying to the user. Interestingly,
+* the <code>getDisplayXXX</code> methods are themselves locale-sensitive
+* and have two versions: one that uses the default locale and one
+* that uses the locale specified as an argument.
+*
+* <p>The Java Platform provides a number of classes that perform locale-sensitive
+* operations. For example, the <code>NumberFormat</code> class formats
+* numbers, currency, and percentages in a locale-sensitive manner. Classes
+* such as <code>NumberFormat</code> have several convenience methods
+* for creating a default object of that type. For example, the
+* <code>NumberFormat</code> class provides these three convenience methods
+* for creating a default <code>NumberFormat</code> object:
+* <blockquote>
+* <pre>
+*     NumberFormat.getInstance()
+*     NumberFormat.getCurrencyInstance()
+*     NumberFormat.getPercentInstance()
+* </pre>
+* </blockquote>
+* Each of these methods has two variants; one with an explicit locale
+* and one without; the latter uses the default locale:
+* <blockquote>
+* <pre>
+*     NumberFormat.getInstance(myLocale)
+*     NumberFormat.getCurrencyInstance(myLocale)
+*     NumberFormat.getPercentInstance(myLocale)
+* </pre>
+* </blockquote>
+* A <code>Locale</code> is the mechanism for identifying the kind of object
+* (<code>NumberFormat</code>) that you would like to get. The locale is
+* <STRONG>just</STRONG> a mechanism for identifying objects,
+* <STRONG>not</STRONG> a container for the objects themselves.
+*
+* <h4>Compatibility</h4>
+*
+* <p>In order to maintain compatibility with existing usage, Locale's
+* constructors retain their behavior prior to the Java Runtime
+* Environment version 1.7.  The same is largely true for the
+* <code>toString</code> method. Thus Locale objects can continue to
+* be used as they were. In particular, clients who parse the output
+* of toString into language, country, and variant fields can continue
+* to do so (although this is strongly discouraged), although the
+* variant field will have additional information in it if script or
+* extensions are present.
+*
+* <p>In addition, BCP 47 imposes syntax restrictions that are not
+* imposed by Locale's constructors. This means that conversions
+* between some Locales and BCP 47 language tags cannot be made without
+* losing information. Thus <code>toLanguageTag</code> cannot
+* represent the state of locales whose language, country, or variant
+* do not conform to BCP 47.
+*
+* <p>Because of these issues, it is recommended that clients migrate
+* away from constructing non-conforming locales and use the
+* <code>forLanguageTag</code> and <code>Locale.Builder</code> APIs instead.
+* Clients desiring a string representation of the complete locale can
+* then always rely on <code>toLanguageTag</code> for this purpose.
+*
+* <h5><a name="special_cases_constructor"/>Special cases</h5>
+*
+* <p>For compatibility reasons, two
+* non-conforming locales are treated as special cases.  These are
+* <b><tt>ja_JP_JP</tt></b> and <b><tt>th_TH_TH</tt></b>. These are ill-formed
+* in BCP 47 since the variants are too short. To ease migration to BCP 47,
+* these are treated specially during construction.  These two cases (and only
+* these) cause a constructor to generate an extension, all other values behave
+* exactly as they did prior to Java 7.
+*
+* <p>Java has used <tt>ja_JP_JP</tt> to represent Japanese as used in
+* Japan together with the Japanese Imperial calendar. This is now
+* representable using a Unicode locale extension, by specifying the
+* Unicode locale key <tt>ca</tt> (for "calendar") and type
+* <tt>japanese</tt>. When the Locale constructor is called with the
+* arguments "ja", "JP", "JP", the extension "u-ca-japanese" is
+* automatically added.
+*
+* <p>Java has used <tt>th_TH_TH</tt> to represent Thai as used in
+* Thailand together with Thai digits. This is also now representable using
+* a Unicode locale extension, by specifying the Unicode locale key
+* <tt>nu</tt> (for "number") and value <tt>thai</tt>. When the Locale
+* constructor is called with the arguments "th", "TH", "TH", the
+* extension "u-nu-thai" is automatically added.
+*
+* <h5>Serialization</h5>
+*
+* <p>During serialization, writeObject writes all fields to the output
+* stream, including extensions.
+*
+* <p>During deserialization, readResolve adds extensions as described
+* in <a href="#special_cases_constructor">Special Cases</a>, only
+* for the two cases th_TH_TH and ja_JP_JP.
+*
+* <h5>Legacy language codes</h5>
+*
+* <p>Locale's constructor has always converted three language codes to
+* their earlier, obsoleted forms: <tt>he</tt> maps to <tt>iw</tt>,
+* <tt>yi</tt> maps to <tt>ji</tt>, and <tt>id</tt> maps to
+* <tt>in</tt>.  This continues to be the case, in order to not break
+* backwards compatibility.
+*
+* <p>The APIs added in 1.7 map between the old and new language codes,
+* maintaining the old codes internal to Locale (so that
+* <code>getLanguage</code> and <code>toString</code> reflect the old
+* code), but using the new codes in the BCP 47 language tag APIs (so
+* that <code>toLanguageTag</code> reflects the new one). This
+* preserves the equivalence between Locales no matter which code or
+* API is used to construct them. Java's default resource bundle
+* lookup mechanism also implements this mapping, so that resources
+* can be named using either convention, see {@link ResourceBundle.Control}.
+*
+* <h5>Three-letter language/country(region) codes</h5>
+*
+* <p>The Locale constructors have always specified that the language
+* and the country param be two characters in length, although in
+* practice they have accepted any length.  The specification has now
+* been relaxed to allow language codes of two to eight characters and
+* country (region) codes of two to three characters, and in
+* particular, three-letter language codes and three-digit region
+* codes as specified in the IANA Language Subtag Registry.  For
+* compatibility, the implementation still does not impose a length
+* constraint.
+*
+* @see Builder
+* @see ResourceBundle
+* @see java.text.Format
+* @see java.text.NumberFormat
+* @see java.text.Collator
+* @author Mark Davis
+* @since 1.1
+*/
+@:require(java1) extern class Locale implements java.lang.Cloneable implements java.io.Serializable
+{
+	/** Useful constant for language.
+	*/
+	public static var ENGLISH(default, null) : Locale;
+	
+	/** Useful constant for language.
+	*/
+	public static var FRENCH(default, null) : Locale;
+	
+	/** Useful constant for language.
+	*/
+	public static var GERMAN(default, null) : Locale;
+	
+	/** Useful constant for language.
+	*/
+	public static var ITALIAN(default, null) : Locale;
+	
+	/** Useful constant for language.
+	*/
+	public static var JAPANESE(default, null) : Locale;
+	
+	/** Useful constant for language.
+	*/
+	public static var KOREAN(default, null) : Locale;
+	
+	/** Useful constant for language.
+	*/
+	public static var CHINESE(default, null) : Locale;
+	
+	/** Useful constant for language.
+	*/
+	public static var SIMPLIFIED_CHINESE(default, null) : Locale;
+	
+	/** Useful constant for language.
+	*/
+	public static var TRADITIONAL_CHINESE(default, null) : Locale;
+	
+	/** Useful constant for country.
+	*/
+	public static var FRANCE(default, null) : Locale;
+	
+	/** Useful constant for country.
+	*/
+	public static var GERMANY(default, null) : Locale;
+	
+	/** Useful constant for country.
+	*/
+	public static var ITALY(default, null) : Locale;
+	
+	/** Useful constant for country.
+	*/
+	public static var JAPAN(default, null) : Locale;
+	
+	/** Useful constant for country.
+	*/
+	public static var KOREA(default, null) : Locale;
+	
+	/** Useful constant for country.
+	*/
+	public static var CHINA(default, null) : Locale;
+	
+	/** Useful constant for country.
+	*/
+	public static var PRC(default, null) : Locale;
+	
+	/** Useful constant for country.
+	*/
+	public static var TAIWAN(default, null) : Locale;
+	
+	/** Useful constant for country.
+	*/
+	public static var UK(default, null) : Locale;
+	
+	/** Useful constant for country.
+	*/
+	public static var US(default, null) : Locale;
+	
+	/** Useful constant for country.
+	*/
+	public static var CANADA(default, null) : Locale;
+	
+	/** Useful constant for country.
+	*/
+	public static var CANADA_FRENCH(default, null) : Locale;
+	
+	/**
+	* Useful constant for the root locale.  The root locale is the locale whose
+	* language, country, and variant are empty ("") strings.  This is regarded
+	* as the base locale of all locales, and is used as the language/country
+	* neutral locale for the locale sensitive operations.
+	*
+	* @since 1.6
+	*/
+	@:require(java6) public static var ROOT(default, null) : Locale;
+	
+	/**
+	* The key for the private use extension ('x').
+	*
+	* @see #getExtension(char)
+	* @see Builder#setExtension(char, String)
+	* @since 1.7
+	*/
+	@:require(java7) public static var PRIVATE_USE_EXTENSION(default, null) : java.StdTypes.Char16;
+	
+	/**
+	* The key for Unicode locale extension ('u').
+	*
+	* @see #getExtension(char)
+	* @see Builder#setExtension(char, String)
+	* @since 1.7
+	*/
+	@:require(java7) public static var UNICODE_LOCALE_EXTENSION(default, null) : java.StdTypes.Char16;
+	
+	/**
+	* Construct a locale from language, country and variant.
+	* This constructor normalizes the language value to lowercase and
+	* the country value to uppercase.
+	* <p>
+	* <b>Note:</b>
+	* <ul>
+	* <li>ISO 639 is not a stable standard; some of the language codes it defines
+	* (specifically "iw", "ji", and "in") have changed.  This constructor accepts both the
+	* old codes ("iw", "ji", and "in") and the new codes ("he", "yi", and "id"), but all other
+	* API on Locale will return only the OLD codes.
+	* <li>For backward compatibility reasons, this constructor does not make
+	* any syntactic checks on the input.
+	* <li>The two cases ("ja", "JP", "JP") and ("th", "TH", "TH") are handled specially,
+	* see <a href="#special_cases_constructor">Special Cases</a> for more information.
+	* </ul>
+	*
+	* @param language An ISO 639 alpha-2 or alpha-3 language code, or a language subtag
+	* up to 8 characters in length.  See the <code>Locale</code> class description about
+	* valid language values.
+	* @param country An ISO 3166 alpha-2 country code or a UN M.49 numeric-3 area code.
+	* See the <code>Locale</code> class description about valid country values.
+	* @param variant Any arbitrary value used to indicate a variation of a <code>Locale</code>.
+	* See the <code>Locale</code> class description for the details.
+	* @exception NullPointerException thrown if any argument is null.
+	*/
+	@:overload public function new(language : String, country : String, variant : String) : Void;
+	
+	/**
+	* Construct a locale from language and country.
+	* This constructor normalizes the language value to lowercase and
+	* the country value to uppercase.
+	* <p>
+	* <b>Note:</b>
+	* <ul>
+	* <li>ISO 639 is not a stable standard; some of the language codes it defines
+	* (specifically "iw", "ji", and "in") have changed.  This constructor accepts both the
+	* old codes ("iw", "ji", and "in") and the new codes ("he", "yi", and "id"), but all other
+	* API on Locale will return only the OLD codes.
+	* <li>For backward compatibility reasons, this constructor does not make
+	* any syntactic checks on the input.
+	* </ul>
+	*
+	* @param language An ISO 639 alpha-2 or alpha-3 language code, or a language subtag
+	* up to 8 characters in length.  See the <code>Locale</code> class description about
+	* valid language values.
+	* @param country An ISO 3166 alpha-2 country code or a UN M.49 numeric-3 area code.
+	* See the <code>Locale</code> class description about valid country values.
+	* @exception NullPointerException thrown if either argument is null.
+	*/
+	@:overload public function new(language : String, country : String) : Void;
+	
+	/**
+	* Construct a locale from a language code.
+	* This constructor normalizes the language value to lowercase.
+	* <p>
+	* <b>Note:</b>
+	* <ul>
+	* <li>ISO 639 is not a stable standard; some of the language codes it defines
+	* (specifically "iw", "ji", and "in") have changed.  This constructor accepts both the
+	* old codes ("iw", "ji", and "in") and the new codes ("he", "yi", and "id"), but all other
+	* API on Locale will return only the OLD codes.
+	* <li>For backward compatibility reasons, this constructor does not make
+	* any syntactic checks on the input.
+	* </ul>
+	*
+	* @param language An ISO 639 alpha-2 or alpha-3 language code, or a language subtag
+	* up to 8 characters in length.  See the <code>Locale</code> class description about
+	* valid language values.
+	* @exception NullPointerException thrown if argument is null.
+	* @since 1.4
+	*/
+	@:require(java4) @:overload public function new(language : String) : Void;
+	
+	/**
+	* Gets the current value of the default locale for this instance
+	* of the Java Virtual Machine.
+	* <p>
+	* The Java Virtual Machine sets the default locale during startup
+	* based on the host environment. It is used by many locale-sensitive
+	* methods if no locale is explicitly specified.
+	* It can be changed using the
+	* {@link #setDefault(java.util.Locale) setDefault} method.
+	*
+	* @return the default locale for this instance of the Java Virtual Machine
+	*/
+	@:overload public static function getDefault() : Locale;
+	
+	/**
+	* Gets the current value of the default locale for the specified Category
+	* for this instance of the Java Virtual Machine.
+	* <p>
+	* The Java Virtual Machine sets the default locale during startup based
+	* on the host environment. It is used by many locale-sensitive methods
+	* if no locale is explicitly specified. It can be changed using the
+	* setDefault(Locale.Category, Locale) method.
+	*
+	* @param category - the specified category to get the default locale
+	* @throws NullPointerException - if category is null
+	* @return the default locale for the specified Category for this instance
+	*     of the Java Virtual Machine
+	* @see #setDefault(Locale.Category, Locale)
+	* @since 1.7
+	*/
+	@:require(java7) @:overload public static function getDefault(category : Locale_Category) : Locale;
+	
+	/**
+	* Sets the default locale for this instance of the Java Virtual Machine.
+	* This does not affect the host locale.
+	* <p>
+	* If there is a security manager, its <code>checkPermission</code>
+	* method is called with a <code>PropertyPermission("user.language", "write")</code>
+	* permission before the default locale is changed.
+	* <p>
+	* The Java Virtual Machine sets the default locale during startup
+	* based on the host environment. It is used by many locale-sensitive
+	* methods if no locale is explicitly specified.
+	* <p>
+	* Since changing the default locale may affect many different areas
+	* of functionality, this method should only be used if the caller
+	* is prepared to reinitialize locale-sensitive code running
+	* within the same Java Virtual Machine.
+	* <p>
+	* By setting the default locale with this method, all of the default
+	* locales for each Category are also set to the specified default locale.
+	*
+	* @throws SecurityException
+	*        if a security manager exists and its
+	*        <code>checkPermission</code> method doesn't allow the operation.
+	* @throws NullPointerException if <code>newLocale</code> is null
+	* @param newLocale the new default locale
+	* @see SecurityManager#checkPermission
+	* @see java.util.PropertyPermission
+	*/
+	@:overload @:synchronized public static function setDefault(newLocale : Locale) : Void;
+	
+	/**
+	* Sets the default locale for the specified Category for this instance
+	* of the Java Virtual Machine. This does not affect the host locale.
+	* <p>
+	* If there is a security manager, its checkPermission method is called
+	* with a PropertyPermission("user.language", "write") permission before
+	* the default locale is changed.
+	* <p>
+	* The Java Virtual Machine sets the default locale during startup based
+	* on the host environment. It is used by many locale-sensitive methods
+	* if no locale is explicitly specified.
+	* <p>
+	* Since changing the default locale may affect many different areas of
+	* functionality, this method should only be used if the caller is
+	* prepared to reinitialize locale-sensitive code running within the
+	* same Java Virtual Machine.
+	* <p>
+	*
+	* @param category - the specified category to set the default locale
+	* @param newLocale - the new default locale
+	* @throws SecurityException - if a security manager exists and its
+	*     checkPermission method doesn't allow the operation.
+	* @throws NullPointerException - if category and/or newLocale is null
+	* @see SecurityManager#checkPermission(java.security.Permission)
+	* @see PropertyPermission
+	* @see #getDefault(Locale.Category)
+	* @since 1.7
+	*/
+	@:require(java7) @:overload @:synchronized public static function setDefault(category : Locale_Category, newLocale : Locale) : Void;
+	
+	/**
+	* Returns an array of all installed locales.
+	* The returned array represents the union of locales supported
+	* by the Java runtime environment and by installed
+	* {@link java.util.spi.LocaleServiceProvider LocaleServiceProvider}
+	* implementations.  It must contain at least a <code>Locale</code>
+	* instance equal to {@link java.util.Locale#US Locale.US}.
+	*
+	* @return An array of installed locales.
+	*/
+	@:overload public static function getAvailableLocales() : java.NativeArray<Locale>;
+	
+	/**
+	* Returns a list of all 2-letter country codes defined in ISO 3166.
+	* Can be used to create Locales.
+	* <p>
+	* <b>Note:</b> The <code>Locale</code> class also supports other codes for
+	* country (region), such as 3-letter numeric UN M.49 area codes.
+	* Therefore, the list returned by this method does not contain ALL valid
+	* codes that can be used to create Locales.
+	*/
+	@:overload public static function getISOCountries() : java.NativeArray<String>;
+	
+	/**
+	* Returns a list of all 2-letter language codes defined in ISO 639.
+	* Can be used to create Locales.
+	* <p>
+	* <b>Note:</b>
+	* <ul>
+	* <li>ISO 639 is not a stable standard&mdash; some languages' codes have changed.
+	* The list this function returns includes both the new and the old codes for the
+	* languages whose codes have changed.
+	* <li>The <code>Locale</code> class also supports language codes up to
+	* 8 characters in length.  Therefore, the list returned by this method does
+	* not contain ALL valid codes that can be used to create Locales.
+	* </ul>
+	*/
+	@:overload public static function getISOLanguages() : java.NativeArray<String>;
+	
+	/**
+	* Returns the language code of this Locale.
+	*
+	* <p><b>Note:</b> ISO 639 is not a stable standard&mdash; some languages' codes have changed.
+	* Locale's constructor recognizes both the new and the old codes for the languages
+	* whose codes have changed, but this function always returns the old code.  If you
+	* want to check for a specific language whose code has changed, don't do
+	* <pre>
+	* if (locale.getLanguage().equals("he")) // BAD!
+	*    ...
+	* </pre>
+	* Instead, do
+	* <pre>
+	* if (locale.getLanguage().equals(new Locale("he").getLanguage()))
+	*    ...
+	* </pre>
+	* @return The language code, or the empty string if none is defined.
+	* @see #getDisplayLanguage
+	*/
+	@:overload public function getLanguage() : String;
+	
+	/**
+	* Returns the script for this locale, which should
+	* either be the empty string or an ISO 15924 4-letter script
+	* code. The first letter is uppercase and the rest are
+	* lowercase, for example, 'Latn', 'Cyrl'.
+	*
+	* @return The script code, or the empty string if none is defined.
+	* @see #getDisplayScript
+	* @since 1.7
+	*/
+	@:require(java7) @:overload public function getScript() : String;
+	
+	/**
+	* Returns the country/region code for this locale, which should
+	* either be the empty string, an uppercase ISO 3166 2-letter code,
+	* or a UN M.49 3-digit code.
+	*
+	* @return The country/region code, or the empty string if none is defined.
+	* @see #getDisplayCountry
+	*/
+	@:overload public function getCountry() : String;
+	
+	/**
+	* Returns the variant code for this locale.
+	*
+	* @return The variant code, or the empty string if none is defined.
+	* @see #getDisplayVariant
+	*/
+	@:overload public function getVariant() : String;
+	
+	/**
+	* Returns the extension (or private use) value associated with
+	* the specified key, or null if there is no extension
+	* associated with the key. To be well-formed, the key must be one
+	* of <code>[0-9A-Za-z]</code>. Keys are case-insensitive, so
+	* for example 'z' and 'Z' represent the same extension.
+	*
+	* @param key the extension key
+	* @return The extension, or null if this locale defines no
+	* extension for the specified key.
+	* @throws IllegalArgumentException if key is not well-formed
+	* @see #PRIVATE_USE_EXTENSION
+	* @see #UNICODE_LOCALE_EXTENSION
+	* @since 1.7
+	*/
+	@:require(java7) @:overload public function getExtension(key : java.StdTypes.Char16) : String;
+	
+	/**
+	* Returns the set of extension keys associated with this locale, or the
+	* empty set if it has no extensions. The returned set is unmodifiable.
+	* The keys will all be lower-case.
+	*
+	* @return The set of extension keys, or the empty set if this locale has
+	* no extensions.
+	* @since 1.7
+	*/
+	@:require(java7) @:overload public function getExtensionKeys() : java.util.Set<Null<java.StdTypes.Char16>>;
+	
+	/**
+	* Returns the set of unicode locale attributes associated with
+	* this locale, or the empty set if it has no attributes. The
+	* returned set is unmodifiable.
+	*
+	* @return The set of attributes.
+	* @since 1.7
+	*/
+	@:require(java7) @:overload public function getUnicodeLocaleAttributes() : java.util.Set<String>;
+	
+	/**
+	* Returns the Unicode locale type associated with the specified Unicode locale key
+	* for this locale. Returns the empty string for keys that are defined with no type.
+	* Returns null if the key is not defined. Keys are case-insensitive. The key must
+	* be two alphanumeric characters ([0-9a-zA-Z]), or an IllegalArgumentException is
+	* thrown.
+	*
+	* @param key the Unicode locale key
+	* @return The Unicode locale type associated with the key, or null if the
+	* locale does not define the key.
+	* @throws IllegalArgumentException if the key is not well-formed
+	* @throws NullPointerException if <code>key</code> is null
+	* @since 1.7
+	*/
+	@:require(java7) @:overload public function getUnicodeLocaleType(key : String) : String;
+	
+	/**
+	* Returns the set of Unicode locale keys defined by this locale, or the empty set if
+	* this locale has none.  The returned set is immutable.  Keys are all lower case.
+	*
+	* @return The set of Unicode locale keys, or the empty set if this locale has
+	* no Unicode locale keywords.
+	* @since 1.7
+	*/
+	@:require(java7) @:overload public function getUnicodeLocaleKeys() : java.util.Set<String>;
+	
+	/**
+	* Returns a string representation of this <code>Locale</code>
+	* object, consisting of language, country, variant, script,
+	* and extensions as below:
+	* <p><blockquote>
+	* language + "_" + country + "_" + (variant + "_#" | "#") + script + "-" + extensions
+	* </blockquote>
+	*
+	* Language is always lower case, country is always upper case, script is always title
+	* case, and extensions are always lower case.  Extensions and private use subtags
+	* will be in canonical order as explained in {@link #toLanguageTag}.
+	*
+	* <p>When the locale has neither script nor extensions, the result is the same as in
+	* Java 6 and prior.
+	*
+	* <p>If both the language and country fields are missing, this function will return
+	* the empty string, even if the variant, script, or extensions field is present (you
+	* can't have a locale with just a variant, the variant must accompany a well-formed
+	* language or country code).
+	*
+	* <p>If script or extensions are present and variant is missing, no underscore is
+	* added before the "#".
+	*
+	* <p>This behavior is designed to support debugging and to be compatible with
+	* previous uses of <code>toString</code> that expected language, country, and variant
+	* fields only.  To represent a Locale as a String for interchange purposes, use
+	* {@link #toLanguageTag}.
+	*
+	* <p>Examples: <ul><tt>
+	* <li>en
+	* <li>de_DE
+	* <li>_GB
+	* <li>en_US_WIN
+	* <li>de__POSIX
+	* <li>zh_CN_#Hans
+	* <li>zh_TW_#Hant-x-java
+	* <li>th_TH_TH_#u-nu-thai</tt></ul>
+	*
+	* @return A string representation of the Locale, for debugging.
+	* @see #getDisplayName
+	* @see #toLanguageTag
+	*/
+	@:overload @:final public function toString() : String;
+	
+	/**
+	* Returns a well-formed IETF BCP 47 language tag representing
+	* this locale.
+	*
+	* <p>If this <code>Locale</code> has a language, country, or
+	* variant that does not satisfy the IETF BCP 47 language tag
+	* syntax requirements, this method handles these fields as
+	* described below:
+	*
+	* <p><b>Language:</b> If language is empty, or not <a
+	* href="#def_language" >well-formed</a> (for example "a" or
+	* "e2"), it will be emitted as "und" (Undetermined).
+	*
+	* <p><b>Country:</b> If country is not <a
+	* href="#def_region">well-formed</a> (for example "12" or "USA"),
+	* it will be omitted.
+	*
+	* <p><b>Variant:</b> If variant <b>is</b> <a
+	* href="#def_variant">well-formed</a>, each sub-segment
+	* (delimited by '-' or '_') is emitted as a subtag.  Otherwise:
+	* <ul>
+	*
+	* <li>if all sub-segments match <code>[0-9a-zA-Z]{1,8}</code>
+	* (for example "WIN" or "Oracle_JDK_Standard_Edition"), the first
+	* ill-formed sub-segment and all following will be appended to
+	* the private use subtag.  The first appended subtag will be
+	* "lvariant", followed by the sub-segments in order, separated by
+	* hyphen. For example, "x-lvariant-WIN",
+	* "Oracle-x-lvariant-JDK-Standard-Edition".
+	*
+	* <li>if any sub-segment does not match
+	* <code>[0-9a-zA-Z]{1,8}</code>, the variant will be truncated
+	* and the problematic sub-segment and all following sub-segments
+	* will be omitted.  If the remainder is non-empty, it will be
+	* emitted as a private use subtag as above (even if the remainder
+	* turns out to be well-formed).  For example,
+	* "Solaris_isjustthecoolestthing" is emitted as
+	* "x-lvariant-Solaris", not as "solaris".</li></ul>
+	*
+	* <p><b>Special Conversions:</b> Java supports some old locale
+	* representations, including deprecated ISO language codes,
+	* for compatibility. This method performs the following
+	* conversions:
+	* <ul>
+	*
+	* <li>Deprecated ISO language codes "iw", "ji", and "in" are
+	* converted to "he", "yi", and "id", respectively.
+	*
+	* <li>A locale with language "no", country "NO", and variant
+	* "NY", representing Norwegian Nynorsk (Norway), is converted
+	* to a language tag "nn-NO".</li></ul>
+	*
+	* <p><b>Note:</b> Although the language tag created by this
+	* method is well-formed (satisfies the syntax requirements
+	* defined by the IETF BCP 47 specification), it is not
+	* necessarily a valid BCP 47 language tag.  For example,
+	* <pre>
+	*   new Locale("xx", "YY").toLanguageTag();</pre>
+	*
+	* will return "xx-YY", but the language subtag "xx" and the
+	* region subtag "YY" are invalid because they are not registered
+	* in the IANA Language Subtag Registry.
+	*
+	* @return a BCP47 language tag representing the locale
+	* @see #forLanguageTag(String)
+	* @since 1.7
+	*/
+	@:require(java7) @:overload public function toLanguageTag() : String;
+	
+	/**
+	* Returns a locale for the specified IETF BCP 47 language tag string.
+	*
+	* <p>If the specified language tag contains any ill-formed subtags,
+	* the first such subtag and all following subtags are ignored.  Compare
+	* to {@link Locale.Builder#setLanguageTag} which throws an exception
+	* in this case.
+	*
+	* <p>The following <b>conversions</b> are performed:<ul>
+	*
+	* <li>The language code "und" is mapped to language "".
+	*
+	* <li>The language codes "he", "yi", and "id" are mapped to "iw",
+	* "ji", and "in" respectively. (This is the same canonicalization
+	* that's done in Locale's constructors.)
+	*
+	* <li>The portion of a private use subtag prefixed by "lvariant",
+	* if any, is removed and appended to the variant field in the
+	* result locale (without case normalization).  If it is then
+	* empty, the private use subtag is discarded:
+	*
+	* <pre>
+	*     Locale loc;
+	*     loc = Locale.forLanguageTag("en-US-x-lvariant-POSIX");
+	*     loc.getVariant(); // returns "POSIX"
+	*     loc.getExtension('x'); // returns null
+	*
+	*     loc = Locale.forLanguageTag("de-POSIX-x-URP-lvariant-Abc-Def");
+	*     loc.getVariant(); // returns "POSIX_Abc_Def"
+	*     loc.getExtension('x'); // returns "urp"
+	* </pre>
+	*
+	* <li>When the languageTag argument contains an extlang subtag,
+	* the first such subtag is used as the language, and the primary
+	* language subtag and other extlang subtags are ignored:
+	*
+	* <pre>
+	*     Locale.forLanguageTag("ar-aao").getLanguage(); // returns "aao"
+	*     Locale.forLanguageTag("en-abc-def-us").toString(); // returns "abc_US"
+	* </pre>
+	*
+	* <li>Case is normalized except for variant tags, which are left
+	* unchanged.  Language is normalized to lower case, script to
+	* title case, country to upper case, and extensions to lower
+	* case.
+	*
+	* <li>If, after processing, the locale would exactly match either
+	* ja_JP_JP or th_TH_TH with no extensions, the appropriate
+	* extensions are added as though the constructor had been called:
+	*
+	* <pre>
+	*    Locale.forLanguageTag("ja-JP-x-lvariant-JP").toLanguageTag();
+	*    // returns "ja-JP-u-ca-japanese-x-lvariant-JP"
+	*    Locale.forLanguageTag("th-TH-x-lvariant-TH").toLanguageTag();
+	*    // returns "th-TH-u-nu-thai-x-lvariant-TH"
+	* <pre></ul>
+	*
+	* <p>This implements the 'Language-Tag' production of BCP47, and
+	* so supports grandfathered (regular and irregular) as well as
+	* private use language tags.  Stand alone private use tags are
+	* represented as empty language and extension 'x-whatever',
+	* and grandfathered tags are converted to their canonical replacements
+	* where they exist.
+	*
+	* <p>Grandfathered tags with canonical replacements are as follows:
+	*
+	* <table>
+	* <tbody align="center">
+	* <tr><th>grandfathered tag</th><th>&nbsp;</th><th>modern replacement</th></tr>
+	* <tr><td>art-lojban</td><td>&nbsp;</td><td>jbo</td></tr>
+	* <tr><td>i-ami</td><td>&nbsp;</td><td>ami</td></tr>
+	* <tr><td>i-bnn</td><td>&nbsp;</td><td>bnn</td></tr>
+	* <tr><td>i-hak</td><td>&nbsp;</td><td>hak</td></tr>
+	* <tr><td>i-klingon</td><td>&nbsp;</td><td>tlh</td></tr>
+	* <tr><td>i-lux</td><td>&nbsp;</td><td>lb</td></tr>
+	* <tr><td>i-navajo</td><td>&nbsp;</td><td>nv</td></tr>
+	* <tr><td>i-pwn</td><td>&nbsp;</td><td>pwn</td></tr>
+	* <tr><td>i-tao</td><td>&nbsp;</td><td>tao</td></tr>
+	* <tr><td>i-tay</td><td>&nbsp;</td><td>tay</td></tr>
+	* <tr><td>i-tsu</td><td>&nbsp;</td><td>tsu</td></tr>
+	* <tr><td>no-bok</td><td>&nbsp;</td><td>nb</td></tr>
+	* <tr><td>no-nyn</td><td>&nbsp;</td><td>nn</td></tr>
+	* <tr><td>sgn-BE-FR</td><td>&nbsp;</td><td>sfb</td></tr>
+	* <tr><td>sgn-BE-NL</td><td>&nbsp;</td><td>vgt</td></tr>
+	* <tr><td>sgn-CH-DE</td><td>&nbsp;</td><td>sgg</td></tr>
+	* <tr><td>zh-guoyu</td><td>&nbsp;</td><td>cmn</td></tr>
+	* <tr><td>zh-hakka</td><td>&nbsp;</td><td>hak</td></tr>
+	* <tr><td>zh-min-nan</td><td>&nbsp;</td><td>nan</td></tr>
+	* <tr><td>zh-xiang</td><td>&nbsp;</td><td>hsn</td></tr>
+	* </tbody>
+	* </table>
+	*
+	* <p>Grandfathered tags with no modern replacement will be
+	* converted as follows:
+	*
+	* <table>
+	* <tbody align="center">
+	* <tr><th>grandfathered tag</th><th>&nbsp;</th><th>converts to</th></tr>
+	* <tr><td>cel-gaulish</td><td>&nbsp;</td><td>xtg-x-cel-gaulish</td></tr>
+	* <tr><td>en-GB-oed</td><td>&nbsp;</td><td>en-GB-x-oed</td></tr>
+	* <tr><td>i-default</td><td>&nbsp;</td><td>en-x-i-default</td></tr>
+	* <tr><td>i-enochian</td><td>&nbsp;</td><td>und-x-i-enochian</td></tr>
+	* <tr><td>i-mingo</td><td>&nbsp;</td><td>see-x-i-mingo</td></tr>
+	* <tr><td>zh-min</td><td>&nbsp;</td><td>nan-x-zh-min</td></tr>
+	* </tbody>
+	* </table>
+	*
+	* <p>For a list of all grandfathered tags, see the
+	* IANA Language Subtag Registry (search for "Type: grandfathered").
+	*
+	* <p><b>Note</b>: there is no guarantee that <code>toLanguageTag</code>
+	* and <code>forLanguageTag</code> will round-trip.
+	*
+	* @param languageTag the language tag
+	* @return The locale that best represents the language tag.
+	* @throws NullPointerException if <code>languageTag</code> is <code>null</code>
+	* @see #toLanguageTag()
+	* @see java.util.Locale.Builder#setLanguageTag(String)
+	* @since 1.7
+	*/
+	@:require(java7) @:overload public static function forLanguageTag(languageTag : String) : Locale;
+	
+	/**
+	* Returns a three-letter abbreviation of this locale's language.
+	* If the language matches an ISO 639-1 two-letter code, the
+	* corresponding ISO 639-2/T three-letter lowercase code is
+	* returned.  The ISO 639-2 language codes can be found on-line,
+	* see "Codes for the Representation of Names of Languages Part 2:
+	* Alpha-3 Code".  If the locale specifies a three-letter
+	* language, the language is returned as is.  If the locale does
+	* not specify a language the empty string is returned.
+	*
+	* @return A three-letter abbreviation of this locale's language.
+	* @exception MissingResourceException Throws MissingResourceException if
+	* three-letter language abbreviation is not available for this locale.
+	*/
+	@:overload public function getISO3Language() : String;
+	
+	/**
+	* Returns a three-letter abbreviation for this locale's country.
+	* If the country matches an ISO 3166-1 alpha-2 code, the
+	* corresponding ISO 3166-1 alpha-3 uppercase code is returned.
+	* If the locale doesn't specify a country, this will be the empty
+	* string.
+	*
+	* <p>The ISO 3166-1 codes can be found on-line.
+	*
+	* @return A three-letter abbreviation of this locale's country.
+	* @exception MissingResourceException Throws MissingResourceException if the
+	* three-letter country abbreviation is not available for this locale.
+	*/
+	@:overload public function getISO3Country() : String;
+	
+	/**
+	* Returns a name for the locale's language that is appropriate for display to the
+	* user.
+	* If possible, the name returned will be localized for the default locale.
+	* For example, if the locale is fr_FR and the default locale
+	* is en_US, getDisplayLanguage() will return "French"; if the locale is en_US and
+	* the default locale is fr_FR, getDisplayLanguage() will return "anglais".
+	* If the name returned cannot be localized for the default locale,
+	* (say, we don't have a Japanese name for Croatian),
+	* this function falls back on the English name, and uses the ISO code as a last-resort
+	* value.  If the locale doesn't specify a language, this function returns the empty string.
+	*/
+	@:overload @:final public function getDisplayLanguage() : String;
+	
+	/**
+	* Returns a name for the locale's language that is appropriate for display to the
+	* user.
+	* If possible, the name returned will be localized according to inLocale.
+	* For example, if the locale is fr_FR and inLocale
+	* is en_US, getDisplayLanguage() will return "French"; if the locale is en_US and
+	* inLocale is fr_FR, getDisplayLanguage() will return "anglais".
+	* If the name returned cannot be localized according to inLocale,
+	* (say, we don't have a Japanese name for Croatian),
+	* this function falls back on the English name, and finally
+	* on the ISO code as a last-resort value.  If the locale doesn't specify a language,
+	* this function returns the empty string.
+	*
+	* @exception NullPointerException if <code>inLocale</code> is <code>null</code>
+	*/
+	@:overload public function getDisplayLanguage(inLocale : Locale) : String;
+	
+	/**
+	* Returns a name for the the locale's script that is appropriate for display to
+	* the user. If possible, the name will be localized for the default locale.  Returns
+	* the empty string if this locale doesn't specify a script code.
+	*
+	* @return the display name of the script code for the current default locale
+	* @since 1.7
+	*/
+	@:require(java7) @:overload public function getDisplayScript() : String;
+	
+	/**
+	* Returns a name for the locale's script that is appropriate
+	* for display to the user. If possible, the name will be
+	* localized for the given locale. Returns the empty string if
+	* this locale doesn't specify a script code.
+	*
+	* @return the display name of the script code for the current default locale
+	* @throws NullPointerException if <code>inLocale</code> is <code>null</code>
+	* @since 1.7
+	*/
+	@:require(java7) @:overload public function getDisplayScript(inLocale : Locale) : String;
+	
+	/**
+	* Returns a name for the locale's country that is appropriate for display to the
+	* user.
+	* If possible, the name returned will be localized for the default locale.
+	* For example, if the locale is fr_FR and the default locale
+	* is en_US, getDisplayCountry() will return "France"; if the locale is en_US and
+	* the default locale is fr_FR, getDisplayCountry() will return "Etats-Unis".
+	* If the name returned cannot be localized for the default locale,
+	* (say, we don't have a Japanese name for Croatia),
+	* this function falls back on the English name, and uses the ISO code as a last-resort
+	* value.  If the locale doesn't specify a country, this function returns the empty string.
+	*/
+	@:overload @:final public function getDisplayCountry() : String;
+	
+	/**
+	* Returns a name for the locale's country that is appropriate for display to the
+	* user.
+	* If possible, the name returned will be localized according to inLocale.
+	* For example, if the locale is fr_FR and inLocale
+	* is en_US, getDisplayCountry() will return "France"; if the locale is en_US and
+	* inLocale is fr_FR, getDisplayCountry() will return "Etats-Unis".
+	* If the name returned cannot be localized according to inLocale.
+	* (say, we don't have a Japanese name for Croatia),
+	* this function falls back on the English name, and finally
+	* on the ISO code as a last-resort value.  If the locale doesn't specify a country,
+	* this function returns the empty string.
+	*
+	* @exception NullPointerException if <code>inLocale</code> is <code>null</code>
+	*/
+	@:overload public function getDisplayCountry(inLocale : Locale) : String;
+	
+	/**
+	* Returns a name for the locale's variant code that is appropriate for display to the
+	* user.  If possible, the name will be localized for the default locale.  If the locale
+	* doesn't specify a variant code, this function returns the empty string.
+	*/
+	@:overload @:final public function getDisplayVariant() : String;
+	
+	/**
+	* Returns a name for the locale's variant code that is appropriate for display to the
+	* user.  If possible, the name will be localized for inLocale.  If the locale
+	* doesn't specify a variant code, this function returns the empty string.
+	*
+	* @exception NullPointerException if <code>inLocale</code> is <code>null</code>
+	*/
+	@:overload public function getDisplayVariant(inLocale : Locale) : String;
+	
+	/**
+	* Returns a name for the locale that is appropriate for display to the
+	* user. This will be the values returned by getDisplayLanguage(),
+	* getDisplayScript(), getDisplayCountry(), and getDisplayVariant() assembled
+	* into a single string. The the non-empty values are used in order,
+	* with the second and subsequent names in parentheses.  For example:
+	* <blockquote>
+	* language (script, country, variant)<br>
+	* language (country)<br>
+	* language (variant)<br>
+	* script (country)<br>
+	* country<br>
+	* </blockquote>
+	* depending on which fields are specified in the locale.  If the
+	* language, sacript, country, and variant fields are all empty,
+	* this function returns the empty string.
+	*/
+	@:overload @:final public function getDisplayName() : String;
+	
+	/**
+	* Returns a name for the locale that is appropriate for display
+	* to the user.  This will be the values returned by
+	* getDisplayLanguage(), getDisplayScript(),getDisplayCountry(),
+	* and getDisplayVariant() assembled into a single string.
+	* The non-empty values are used in order,
+	* with the second and subsequent names in parentheses.  For example:
+	* <blockquote>
+	* language (script, country, variant)<br>
+	* language (country)<br>
+	* language (variant)<br>
+	* script (country)<br>
+	* country<br>
+	* </blockquote>
+	* depending on which fields are specified in the locale.  If the
+	* language, script, country, and variant fields are all empty,
+	* this function returns the empty string.
+	*
+	* @throws NullPointerException if <code>inLocale</code> is <code>null</code>
+	*/
+	@:overload public function getDisplayName(inLocale : Locale) : String;
+	
+	/**
+	* Overrides Cloneable.
+	*/
+	@:overload public function clone() : Dynamic;
+	
+	/**
+	* Override hashCode.
+	* Since Locales are often used in hashtables, caches the value
+	* for speed.
+	*/
+	@:overload public function hashCode() : Int;
+	
+	/**
+	* Returns true if this Locale is equal to another object.  A Locale is
+	* deemed equal to another Locale with identical language, script, country,
+	* variant and extensions, and unequal to all other objects.
+	*
+	* @return true if this Locale is equal to the specified object.
+	*/
+	@:overload public function equals(obj : Dynamic) : Bool;
+	
+	
+}
+/**
+* Enum for locale categories.  These locale categories are used to get/set
+* the default locale for the specific functionality represented by the
+* category.
+*
+* @see #getDefault(Locale.Category)
+* @see #setDefault(Locale.Category, Locale)
+* @since 1.7
+*/
+@:require(java7) @:native('java.util.Locale.Category') extern enum Locale_Category
+{
+	/**
+	* Category used to represent the default locale for
+	* displaying user interfaces.
+	*/
+	DISPLAY;
+	/**
+	* Category used to represent the default locale for
+	* formatting dates, numbers, and/or currencies.
+	*/
+	FORMAT;
+	
+}
+
+/**
+* <code>Builder</code> is used to build instances of <code>Locale</code>
+* from values configured by the setters.  Unlike the <code>Locale</code>
+* constructors, the <code>Builder</code> checks if a value configured by a
+* setter satisfies the syntax requirements defined by the <code>Locale</code>
+* class.  A <code>Locale</code> object created by a <code>Builder</code> is
+* well-formed and can be transformed to a well-formed IETF BCP 47 language tag
+* without losing information.
+*
+* <p><b>Note:</b> The <code>Locale</code> class does not provide any
+* syntactic restrictions on variant, while BCP 47 requires each variant
+* subtag to be 5 to 8 alphanumerics or a single numeric followed by 3
+* alphanumerics.  The method <code>setVariant</code> throws
+* <code>IllformedLocaleException</code> for a variant that does not satisfy
+* this restriction. If it is necessary to support such a variant, use a
+* Locale constructor.  However, keep in mind that a <code>Locale</code>
+* object created this way might lose the variant information when
+* transformed to a BCP 47 language tag.
+*
+* <p>The following example shows how to create a <code>Locale</code> object
+* with the <code>Builder</code>.
+* <blockquote>
+* <pre>
+*     Locale aLocale = new Builder().setLanguage("sr").setScript("Latn").setRegion("RS").build();
+* </pre>
+* </blockquote>
+*
+* <p>Builders can be reused; <code>clear()</code> resets all
+* fields to their default values.
+*
+* @see Locale#forLanguageTag
+* @since 1.7
+*/
+@:require(java7) @:native('java.util.Locale.Builder') extern class Locale_Builder
+{
+	/**
+	* Constructs an empty Builder. The default value of all
+	* fields, extensions, and private use information is the
+	* empty string.
+	*/
+	@:overload public function new() : Void;
+	
+	/**
+	* Resets the <code>Builder</code> to match the provided
+	* <code>locale</code>.  Existing state is discarded.
+	*
+	* <p>All fields of the locale must be well-formed, see {@link Locale}.
+	*
+	* <p>Locales with any ill-formed fields cause
+	* <code>IllformedLocaleException</code> to be thrown, except for the
+	* following three cases which are accepted for compatibility
+	* reasons:<ul>
+	* <li>Locale("ja", "JP", "JP") is treated as "ja-JP-u-ca-japanese"
+	* <li>Locale("th", "TH", "TH") is treated as "th-TH-u-nu-thai"
+	* <li>Locale("no", "NO", "NY") is treated as "nn-NO"</ul>
+	*
+	* @param locale the locale
+	* @return This builder.
+	* @throws IllformedLocaleException if <code>locale</code> has
+	* any ill-formed fields.
+	* @throws NullPointerException if <code>locale</code> is null.
+	*/
+	@:overload public function setLocale(locale : Locale) : Locale_Builder;
+	
+	/**
+	* Resets the Builder to match the provided IETF BCP 47
+	* language tag.  Discards the existing state.  Null and the
+	* empty string cause the builder to be reset, like {@link
+	* #clear}.  Grandfathered tags (see {@link
+	* Locale#forLanguageTag}) are converted to their canonical
+	* form before being processed.  Otherwise, the language tag
+	* must be well-formed (see {@link Locale}) or an exception is
+	* thrown (unlike <code>Locale.forLanguageTag</code>, which
+	* just discards ill-formed and following portions of the
+	* tag).
+	*
+	* @param languageTag the language tag
+	* @return This builder.
+	* @throws IllformedLocaleException if <code>languageTag</code> is ill-formed
+	* @see Locale#forLanguageTag(String)
+	*/
+	@:overload public function setLanguageTag(languageTag : String) : Locale_Builder;
+	
+	/**
+	* Sets the language.  If <code>language</code> is the empty string or
+	* null, the language in this <code>Builder</code> is removed.  Otherwise,
+	* the language must be <a href="./Locale.html#def_language">well-formed</a>
+	* or an exception is thrown.
+	*
+	* <p>The typical language value is a two or three-letter language
+	* code as defined in ISO639.
+	*
+	* @param language the language
+	* @return This builder.
+	* @throws IllformedLocaleException if <code>language</code> is ill-formed
+	*/
+	@:overload public function setLanguage(language : String) : Locale_Builder;
+	
+	/**
+	* Sets the script. If <code>script</code> is null or the empty string,
+	* the script in this <code>Builder</code> is removed.
+	* Otherwise, the script must be <a href="./Locale.html#def_script">well-formed</a> or an
+	* exception is thrown.
+	*
+	* <p>The typical script value is a four-letter script code as defined by ISO 15924.
+	*
+	* @param script the script
+	* @return This builder.
+	* @throws IllformedLocaleException if <code>script</code> is ill-formed
+	*/
+	@:overload public function setScript(script : String) : Locale_Builder;
+	
+	/**
+	* Sets the region.  If region is null or the empty string, the region
+	* in this <code>Builder</code> is removed.  Otherwise,
+	* the region must be <a href="./Locale.html#def_region">well-formed</a> or an
+	* exception is thrown.
+	*
+	* <p>The typical region value is a two-letter ISO 3166 code or a
+	* three-digit UN M.49 area code.
+	*
+	* <p>The country value in the <code>Locale</code> created by the
+	* <code>Builder</code> is always normalized to upper case.
+	*
+	* @param region the region
+	* @return This builder.
+	* @throws IllformedLocaleException if <code>region</code> is ill-formed
+	*/
+	@:overload public function setRegion(region : String) : Locale_Builder;
+	
+	/**
+	* Sets the variant.  If variant is null or the empty string, the
+	* variant in this <code>Builder</code> is removed.  Otherwise, it
+	* must consist of one or more <a href="./Locale.html#def_variant">well-formed</a>
+	* subtags, or an exception is thrown.
+	*
+	* <p><b>Note:</b> This method checks if <code>variant</code>
+	* satisfies the IETF BCP 47 variant subtag's syntax requirements,
+	* and normalizes the value to lowercase letters.  However,
+	* the <code>Locale</code> class does not impose any syntactic
+	* restriction on variant, and the variant value in
+	* <code>Locale</code> is case sensitive.  To set such a variant,
+	* use a Locale constructor.
+	*
+	* @param variant the variant
+	* @return This builder.
+	* @throws IllformedLocaleException if <code>variant</code> is ill-formed
+	*/
+	@:overload public function setVariant(variant : String) : Locale_Builder;
+	
+	/**
+	* Sets the extension for the given key. If the value is null or the
+	* empty string, the extension is removed.  Otherwise, the extension
+	* must be <a href="./Locale.html#def_extensions">well-formed</a> or an exception
+	* is thrown.
+	*
+	* <p><b>Note:</b> The key {@link Locale#UNICODE_LOCALE_EXTENSION
+	* UNICODE_LOCALE_EXTENSION} ('u') is used for the Unicode locale extension.
+	* Setting a value for this key replaces any existing Unicode locale key/type
+	* pairs with those defined in the extension.
+	*
+	* <p><b>Note:</b> The key {@link Locale#PRIVATE_USE_EXTENSION
+	* PRIVATE_USE_EXTENSION} ('x') is used for the private use code. To be
+	* well-formed, the value for this key needs only to have subtags of one to
+	* eight alphanumeric characters, not two to eight as in the general case.
+	*
+	* @param key the extension key
+	* @param value the extension value
+	* @return This builder.
+	* @throws IllformedLocaleException if <code>key</code> is illegal
+	* or <code>value</code> is ill-formed
+	* @see #setUnicodeLocaleKeyword(String, String)
+	*/
+	@:overload public function setExtension(key : java.StdTypes.Char16, value : String) : Locale_Builder;
+	
+	/**
+	* Sets the Unicode locale keyword type for the given key.  If the type
+	* is null, the Unicode keyword is removed.  Otherwise, the key must be
+	* non-null and both key and type must be <a
+	* href="./Locale.html#def_locale_extension">well-formed</a> or an exception
+	* is thrown.
+	*
+	* <p>Keys and types are converted to lower case.
+	*
+	* <p><b>Note</b>:Setting the 'u' extension via {@link #setExtension}
+	* replaces all Unicode locale keywords with those defined in the
+	* extension.
+	*
+	* @param key the Unicode locale key
+	* @param type the Unicode locale type
+	* @return This builder.
+	* @throws IllformedLocaleException if <code>key</code> or <code>type</code>
+	* is ill-formed
+	* @throws NullPointerException if <code>key</code> is null
+	* @see #setExtension(char, String)
+	*/
+	@:overload public function setUnicodeLocaleKeyword(key : String, type : String) : Locale_Builder;
+	
+	/**
+	* Adds a unicode locale attribute, if not already present, otherwise
+	* has no effect.  The attribute must not be null and must be <a
+	* href="./Locale.html#def_locale_extension">well-formed</a> or an exception
+	* is thrown.
+	*
+	* @param attribute the attribute
+	* @return This builder.
+	* @throws NullPointerException if <code>attribute</code> is null
+	* @throws IllformedLocaleException if <code>attribute</code> is ill-formed
+	* @see #setExtension(char, String)
+	*/
+	@:overload public function addUnicodeLocaleAttribute(attribute : String) : Locale_Builder;
+	
+	/**
+	* Removes a unicode locale attribute, if present, otherwise has no
+	* effect.  The attribute must not be null and must be <a
+	* href="./Locale.html#def_locale_extension">well-formed</a> or an exception
+	* is thrown.
+	*
+	* <p>Attribute comparision for removal is case-insensitive.
+	*
+	* @param attribute the attribute
+	* @return This builder.
+	* @throws NullPointerException if <code>attribute</code> is null
+	* @throws IllformedLocaleException if <code>attribute</code> is ill-formed
+	* @see #setExtension(char, String)
+	*/
+	@:overload public function removeUnicodeLocaleAttribute(attribute : String) : Locale_Builder;
+	
+	/**
+	* Resets the builder to its initial, empty state.
+	*
+	* @return This builder.
+	*/
+	@:overload public function clear() : Locale_Builder;
+	
+	/**
+	* Resets the extensions to their initial, empty state.
+	* Language, script, region and variant are unchanged.
+	*
+	* @return This builder.
+	* @see #setExtension(char, String)
+	*/
+	@:overload public function clearExtensions() : Locale_Builder;
+	
+	/**
+	* Returns an instance of <code>Locale</code> created from the fields set
+	* on this builder.
+	*
+	* <p>This applies the conversions listed in {@link Locale#forLanguageTag}
+	* when constructing a Locale. (Grandfathered tags are handled in
+	* {@link #setLanguageTag}.)
+	*
+	* @return A Locale.
+	*/
+	@:overload public function build() : Locale;
+	
+	
+}

+ 21 - 1
tests/unit/TestJava.hx

@@ -181,12 +181,23 @@ class TestJava extends Test
 		eq(child.someField(true, 10), 52);
 		eq(child.someField(true, 10), 52);
 	}
 	}
 
 
+	function testHaxeKeywords()
+	{
+		eq(Base._inline, 42);
+		eq(Base._callback, 43);
+		eq(Base._cast, 44);
+		eq(Base._untyped, 45);
+		eq(Base._in, 46);
+		Base._in = 40;
+		eq(Base._in, 40);
+	}
+
 
 
 	function testInnerClass()
 	function testInnerClass()
 	{
 	{
 		//-java-lib should be able to detect inner classes on import
 		//-java-lib should be able to detect inner classes on import
 		var i = new Base_InnerClass();
 		var i = new Base_InnerClass();
-		t(true);
+		eq(i.nameClash(), 10);
 
 
 		var i2 = new Base_InnerClass_InnerInnerClass();
 		var i2 = new Base_InnerClass_InnerInnerClass();
 		t(true);
 		t(true);
@@ -208,6 +219,15 @@ class TestJava extends Test
 		t(true);
 		t(true);
 	}
 	}
 
 
+	function testNameClash()
+	{
+		eq(Base._nameClash(null), -1);
+		eq(new Base().nameClash(), 2);
+		eq(new Base().varNameClash(1), 1);
+		eq(Base._varNameClash(10.4), 10.4);
+
+	}
+
 	function testOverloadOverride()
 	function testOverloadOverride()
 	{
 	{
 		var c = new TestMyClass();
 		var c = new TestMyClass();

+ 32 - 1
tests/unit/native_java/src/haxe/test/Base.java

@@ -9,6 +9,9 @@ public class Base
 	public static final int cast = 44;
 	public static final int cast = 44;
 	public static final int untyped = 45;
 	public static final int untyped = 45;
 
 
+	//test haxe keyword
+	public static int in = 46;
+
 	//final + static variable = inline var in Haxe
 	//final + static variable = inline var in Haxe
 	public static final int inlineNumber = 42;
 	public static final int inlineNumber = 42;
 
 
@@ -19,11 +22,34 @@ public class Base
 	private String privateField;
 	private String privateField;
 	protected int protectedField;
 	protected int protectedField;
 
 
+	//static + nonstatic clash
+	public static int nameClash(Base t)
+	{
+		return -1;
+	}
+
+	public int nameClash()
+	{
+		return 1;
+	}
+
 	protected int protectedFunction()
 	protected int protectedFunction()
 	{
 	{
 		return protectedField;
 		return protectedField;
 	}
 	}
 
 
+	public int varNameClash(int b)
+	{
+		return b;
+	}
+
+	public static double varNameClash(double d)
+	{
+		return d;
+	}
+
+	public int varNameClash;
+
 	public static class InnerClass extends Base
 	public static class InnerClass extends Base
 	{
 	{
 		private int privateField = 42;
 		private int privateField = 42;
@@ -34,6 +60,11 @@ public class Base
 			return privateField;
 			return privateField;
 		}
 		}
 
 
+		public int nameClash()
+		{
+			return 10;
+		}
+
 		public static int getValue(OverloadInterface2 oiface)
 		public static int getValue(OverloadInterface2 oiface)
 		{
 		{
 			return oiface.someOverloadedMethod(42);
 			return oiface.someOverloadedMethod(42);
@@ -46,7 +77,7 @@ public class Base
 			//protected override without explicit override tag
 			//protected override without explicit override tag
 			protected int protectedFunction()
 			protected int protectedFunction()
 			{
 			{
-				return protectedField;
+				return 10;
 			}
 			}
 		}
 		}
 	}
 	}

+ 14 - 5
typeload.ml

@@ -654,6 +654,15 @@ let rec get_overloads c i =
 	| Some (c,tl) ->
 	| Some (c,tl) ->
 			ret @ ( List.map (fun (t,f) -> apply_params c.cl_types tl t, f) (get_overloads c i) )
 			ret @ ( List.map (fun (t,f) -> apply_params c.cl_types tl t, f) (get_overloads c i) )
 
 
+let same_overload_args t1 t2 =
+  match follow t1, follow t2 with
+  | TFun(a1,_), TFun(a2,_) ->
+    (try
+      List.for_all2 (fun (_,_,t1) (_,_,t2) -> type_iseq t1 t2) a1 a2
+    with | Invalid_argument("List.for_all2") ->
+      false)
+  | _ -> assert false
+
 let check_overriding ctx c =
 let check_overriding ctx c =
 	let p = c.cl_pos in
 	let p = c.cl_pos in
 	match c.cl_super with
 	match c.cl_super with
@@ -708,7 +717,7 @@ let check_overriding ctx c =
 				(* check if field with same signature was declared more than once *)
 				(* check if field with same signature was declared more than once *)
 				List.iter (fun f2 ->
 				List.iter (fun f2 ->
 					try
 					try
-						ignore (List.find (fun f3 -> f3 != f2 && type_iseq f2.cf_type f3.cf_type) (f :: f.cf_overloads));
+						ignore (List.find (fun f3 -> f3 != f2 && same_overload_args f2.cf_type f3.cf_type) (f :: f.cf_overloads));
 						display_error ctx ("Another overloaded field of same signature was already declared : " ^ f2.cf_name) f2.cf_pos
 						display_error ctx ("Another overloaded field of same signature was already declared : " ^ f2.cf_name) f2.cf_pos
 					with | Not_found -> ()
 					with | Not_found -> ()
 				) (f :: f.cf_overloads);
 				) (f :: f.cf_overloads);
@@ -717,7 +726,7 @@ let check_overriding ctx c =
 					(* find the exact field being overridden *)
 					(* find the exact field being overridden *)
 					check_field f (fun csup i ->
 					check_field f (fun csup i ->
 						List.find (fun (t,f2) ->
 						List.find (fun (t,f2) ->
-							type_iseq f.cf_type (apply_params csup.cl_types params t)
+							same_overload_args f.cf_type (apply_params csup.cl_types params t)
 						) overloads
 						) overloads
 					) true
 					) true
 				) f.cf_overloads
 				) f.cf_overloads
@@ -756,7 +765,7 @@ let rec check_interface ctx c intf params =
 					let overloads = get_overloads c i in
 					let overloads = get_overloads c i in
 					is_overload := true;
 					is_overload := true;
 					let t = (apply_params intf.cl_types params f.cf_type) in
 					let t = (apply_params intf.cl_types params f.cf_type) in
-					List.find (fun (t1,f1) -> type_iseq t t1) overloads
+					List.find (fun (t1,f1) -> same_overload_args t t1) overloads
 				else
 				else
 					t2, f2
 					t2, f2
 			in
 			in
@@ -1732,7 +1741,7 @@ let init_class ctx c p context_init herits fields =
 		List.iter (fun f ->
 		List.iter (fun f ->
 			try
 			try
 				(* TODO: consider making a broader check, and treat some types, like TAnon and type parameters as Dynamic *)
 				(* TODO: consider making a broader check, and treat some types, like TAnon and type parameters as Dynamic *)
-				ignore(List.find (fun f2 -> f != f2 && type_iseq f.cf_type f2.cf_type) (ctor :: ctor.cf_overloads));
+				ignore(List.find (fun f2 -> f != f2 && same_overload_args f.cf_type f2.cf_type) (ctor :: ctor.cf_overloads));
 				display_error ctx ("Another overloaded field of same signature was already declared : " ^ f.cf_name) f.cf_pos;
 				display_error ctx ("Another overloaded field of same signature was already declared : " ^ f.cf_name) f.cf_pos;
 			with Not_found -> ()
 			with Not_found -> ()
 		) (ctor :: ctor.cf_overloads)
 		) (ctor :: ctor.cf_overloads)
@@ -2243,4 +2252,4 @@ let load_module ctx m p =
 	m2
 	m2
 
 
 ;;
 ;;
-type_function_params_rec := type_function_params
+type_function_params_rec := type_function_params