瀏覽代碼

Merge branch 'development'

Simon Krajewski 8 年之前
父節點
當前提交
5c4454808a

+ 9 - 1
extra/CHANGES.txt

@@ -1,15 +1,23 @@
-2017-03-14: 3.4.1
+2017-03-17: 3.4.1
 
 	New features:
 
 	php7 : added source maps generation with `-D source_map` flag.
 
+	General improvements and optimizations:
+
+	cpp : added cpp.Star and cpp.Struct to help with extern typing
+	lua : cleaned up various parts of the standard library
+
 	Bugfixes:
 
 	all : fixed compilation server issue with two identical @:native paths on extern abstracts (#5993)
 	all : fixed invalid inling in a specific case (#6067)
 	all : fixed various display related issues
+	all : fixed inline super() calls missing field initializations (#6097)
+	all : consider UNC paths to be absolute in haxe.io.Path.isAbsolute (#6061)
 	cpp : improved typing of some Function/Callable-related types
+	cpp : fixed problem with line numbers when debugging
 	hl : various fixes and improvements
 	php : fixed FileSystem.stat() for directories on Windows (#6057)
 	php/php7 : fixed invalid result of Web.getPostData() (#6033)

+ 10 - 6
extra/release-checklist.txt

@@ -19,13 +19,17 @@
 
 # Making the release
 
-- Copy relevant changelog part to downloads/$version/CHANGES.md.
-- Write announcement post.
-- Copy announcement post to downloads/$version/RELEASE.md.
-- Update downloads/versions.json
-- Push the generated binaries and installers to haxe.org, requires git-lfs
+- Regenerate API documentation (check --title and -D version values).
+- Make a GitHub release in https://github.com/HaxeFoundation/haxe/releases with
+  - the generated binaries and installers
+  - the API documentation
+- Update haxe.org
+  - Copy relevant changelog part to downloads/$version/CHANGES.md.
+  - Write announcement post in downloads/$version/RELEASE.md.
+  - Update downloads/versions.json.
+  - Push to staging, check https://staging.haxe.org/.
+  - Merge staging to master, check https://haxe.org/.
 
 # Announcing the release
 
-- Regenerate and upload API documentation (check --title and -D version values).
 - Post announcement post to haxelang.

+ 190 - 38
src/generators/gencpp.ml

@@ -1290,13 +1290,6 @@ let default_value_string = function
 
 
 
-let get_return_type field =
-   match follow field.cf_type with
-      | TFun (_,return_type) -> return_type
-      | _ -> raise Not_found
-;;
-
-
 let get_nth_type field index =
    match follow field.ef_type with
       | TFun (args,_) ->
@@ -1385,7 +1378,8 @@ type tcpp =
    | TCppObjCBlock of tcpp list * tcpp
    | TCppRest of tcpp
    | TCppReference of tcpp
-   | TCppStar of tcpp
+   | TCppStruct of tcpp
+   | TCppStar of tcpp * bool
    | TCppVoidStar
    | TCppVarArg
    | TCppAutoCast
@@ -1501,6 +1495,7 @@ and tcpp_expr_expr =
    | CppCall of tcppfuncloc * tcppexpr list
    | CppFunctionAddress of tclass * tclass_field
    | CppAddressOf of tcppexpr
+   | CppDereference of tcppexpr
    | CppArray of tcpparrayloc
    | CppCrement of  tcppcrementop * Ast.unop_flag * tcpplvalue
    | CppSet of tcpplvalue * tcppexpr
@@ -1579,6 +1574,7 @@ let rec s_tcpp = function
    | CppCall (FuncGlobal _,_) -> "CppCallGlobal"
    | CppCall (FuncFromStaticFunction,_) -> "CppCallFromStaticFunction"
    | CppAddressOf _  -> "CppAddressOf"
+   | CppDereference _  -> "CppDereference"
    | CppFunctionAddress  _ -> "CppFunctionAddress"
    | CppArray  _ -> "CppArray"
    | CppCrement  _ -> "CppCrement"
@@ -1622,7 +1618,8 @@ and tcpp_to_string_suffix suffix tcpp = match tcpp with
    | TCppObject -> " ::Dynamic"
    | TCppObjectPtr -> " ::hx::Object *"
    | TCppReference t -> (tcpp_to_string t) ^" &"
-   | TCppStar t -> (tcpp_to_string t) ^" *"
+   | TCppStruct t -> "cpp::Struct< " ^ (tcpp_to_string t) ^" >"
+   | TCppStar(t,const) -> (if const then "const " else "" ) ^ (tcpp_to_string t) ^" *"
    | TCppVoid -> "void"
    | TCppVoidStar -> "void *"
    | TCppRest _ -> "vaarg_list"
@@ -1750,6 +1747,7 @@ let rec const_string_of expr =
 let rec cpp_is_struct_access t =
    match t with
    | TCppFunction _ -> true
+   | TCppStruct _-> false
    | TCppInst (class_def) -> (has_meta_key class_def.cl_meta Meta.StructAccess)
    | TCppReference (r) -> cpp_is_struct_access r
    | _ -> false
@@ -1858,8 +1856,12 @@ let rec cpp_type_of ctx haxe_type =
             )
       | (["cpp"],"Reference"), [param] ->
             TCppReference(cpp_type_of ctx param)
+      | (["cpp"],"Struct"), [param] ->
+            TCppStruct(cpp_type_of ctx param)
       | (["cpp"],"Star"), [param] ->
-            TCppStar(cpp_type_of ctx param)
+            TCppStar(cpp_type_of ctx param,false)
+      | (["cpp"],"ConstStar"), [param] ->
+            TCppStar(cpp_type_of ctx param,true)
 
       | ([],"Array"), [p] ->
          let arrayOf = cpp_type_of ctx p in
@@ -1871,6 +1873,7 @@ let rec cpp_type_of ctx haxe_type =
             | TCppObject
             | TCppObjectPtr
             | TCppReference _
+            | TCppStruct _
             | TCppStar _
             | TCppEnum _
             | TCppInst _
@@ -2023,6 +2026,7 @@ let cpp_variant_type_of t = match t with
    | TCppObject
    | TCppObjectPtr
    | TCppReference _
+   | TCppStruct _
    | TCppStar _
    | TCppVoid
    | TCppFastIterator _
@@ -2230,7 +2234,7 @@ let is_array_splice_call obj member =
 
 let cpp_can_static_cast funcType inferredType =
    match funcType with
-   | TCppReference(_) | TCppStar(_) -> false
+   | TCppReference(_) | TCppStar(_) | TCppStruct(_) -> false
    | _ ->
       (match inferredType with
       | TCppInst _
@@ -2968,7 +2972,7 @@ let retype_expression ctx request_type function_args expression_tree forInjectio
             CppTry(cppBlock, cppCatches), TCppVoid
 
          | TReturn eo ->
-            CppReturn(match eo with None -> None | Some e -> Some (retype (cpp_type_of expr.etype) e)), TCppVoid
+            CppReturn(match eo with None -> None | Some e -> Some (retype (cpp_type_of e.etype) e)), TCppVoid
 
          | TCast (base,None) -> (* Use auto-cast rules *)
             let return_type = cpp_type_of expr.etype in
@@ -2994,6 +2998,7 @@ let retype_expression ctx request_type function_args expression_tree forInjectio
          | TCast (base,Some t) ->
             let baseCpp = retype (cpp_type_of base.etype) base in
             let baseStr = (tcpp_to_string baseCpp.cpptype) in
+            let return_type = if return_type=TCppUnchanged then cpp_type_of expr.etype else return_type in
             let returnStr = (tcpp_to_string return_type) in
 
             if baseStr=returnStr then
@@ -3024,6 +3029,7 @@ let retype_expression ctx request_type function_args expression_tree forInjectio
                 mk_cppexpr (CppCastNative(toDynamic)) TCppVoidStar
       end else if (cppExpr.cpptype=TCppVariant || cppExpr.cpptype=TCppDynamic) then begin
          match return_type with
+         | TCppUnchanged -> cppExpr
          | TCppObjectArray _
          | TCppScalarArray _
          | TCppNativePointer _
@@ -3054,24 +3060,77 @@ let retype_expression ctx request_type function_args expression_tree forInjectio
          | _ -> cppExpr
       end else match cppExpr.cpptype, return_type with
          | _, TCppUnchanged -> cppExpr
+         (*
+            Using the 'typedef hack', where we use typedef X<T> = T, allows the
+            haxe compiler to use these types interchangeably. We then work
+            out the correct way to convert between them when one is expected, but another provided.
+ 
+            TCppFunction: these do not really interact with the haxe function type, T
+            Since they are implemented with cpp::Function, conversion to/from Dynamic should happen automatically
+               CallableData<T> = T;
+               FunctionData<T,ABI> = T;
+
+            TCppObjCBlock can move in and out of Dyanmic
+               ObjcBlock<T> = T;
+
+             TCppProtocol can move in and out of Dyanmic, via delegate creation
+               Protocol<T /*:interface*/ > = T;
+
+            Explicitly wrapped type - already interacts well with Dynamic and T
+              Struct<T> = T;
+
+            TCppStar, TCppStruct, TCppReference - for interacting with native code
+              Star<T> = T;
+              ConstStar<T> = T;
+              Reference<T> = T;
+              T may be an extern class, with @:structAccess - in which case
+                 Dynamic interaction must be handled explicitly
+            These types, plus Dynamic can be used interchangeably by haxe
+            Derived/inherited types may also be mixed in
+         *)
          | TCppAutoCast, _
          | TCppObjC(_), TCppDynamic
          | TCppObjCBlock(_), TCppDynamic
               -> mk_cppexpr (CppCast(cppExpr,return_type)) return_type
+
+         (* Infer type from right-hand-side for pointer or reference to Dynamic *)
          | TCppReference(TCppDynamic), TCppReference(_) -> cppExpr
          | TCppReference(TCppDynamic),  t ->
              mk_cppexpr retypedExpr (TCppReference(t))
-         | TCppStar(TCppDynamic), TCppStar(_) -> cppExpr
-         | TCppStar(TCppDynamic),  t ->
-             mk_cppexpr retypedExpr (TCppStar(t))
+         | TCppStar(TCppDynamic,_), TCppStar(_,_) -> cppExpr
+         | TCppStar(TCppDynamic,const),  t ->
+             mk_cppexpr retypedExpr (TCppStar(t,const))
+
+         | TCppStar(t,const),  TCppDynamic ->
+             let ptrType = TCppPointer((if const then "ConstPointer" else "Pointer"),t) in
+             let ptrCast =  mk_cppexpr (CppCast(cppExpr,ptrType)) ptrType in
+             mk_cppexpr (CppCast(ptrCast,TCppDynamic)) TCppDynamic
+         | TCppDynamic, TCppStar(t,const) ->
+             let ptrType = TCppPointer((if const then "ConstPointer" else "Pointer"),t) in
+             let ptrCast =  mk_cppexpr (CppCast(cppExpr,ptrType)) ptrType in
+             mk_cppexpr (CppCast(ptrCast,TCppStar(t,const))) (TCppStar(t,const))
+
+         | TCppStar(t,const), TCppInst _
+         | TCppStar(t,const), TCppStruct _ ->
+             mk_cppexpr (CppDereference(cppExpr)) return_type
+
+         | TCppInst _, TCppStar(p,const)
+         | TCppStruct _, TCppStar(p,const) ->
+             mk_cppexpr (CppAddressOf(cppExpr)) return_type
+
          | TCppObjectPtr, TCppObjectPtr -> cppExpr
          | TCppObjectPtr, _ ->
-             mk_cppexpr (CppCast(cppExpr,TCppDynamic)) TCppDynamic
+                mk_cppexpr (CppCast(cppExpr,TCppDynamic)) TCppDynamic
 
          | TCppProtocol _, TCppProtocol _ -> cppExpr
          | t, TCppProtocol protocol ->
               mk_cppexpr (CppCastProtocol(cppExpr,protocol)) return_type
 
+         | TCppInst(t), TCppDynamic when (has_meta_key t.cl_meta Meta.StructAccess) ->
+             let structType = TCppStruct( TCppInst(t) ) in
+             let structCast =  mk_cppexpr (CppCast(cppExpr,structType)) structType in
+             mk_cppexpr (CppCast(structCast,TCppDynamic)) TCppDynamic
+
          | _, TCppObjectPtr ->
              mk_cppexpr (CppCast(cppExpr,TCppObjectPtr)) TCppObjectPtr
          | _ -> cppExpr
@@ -3394,6 +3453,8 @@ let gen_cpp_ast_expression_tree ctx class_name func_name function_args injection
          out (")" ^ !closeCall);
       | CppAddressOf(e) ->
          out ("&("); gen e; out ")";
+      | CppDereference(e) ->
+         out ("(*("); gen e; out "))";
       | CppFunctionAddress(klass, member) ->
          let signature = ctx_function_signature ctx false member.cf_type "" in
          let name = cpp_member_name_of member in
@@ -3938,6 +3999,10 @@ let gen_cpp_ast_expression_tree ctx class_name func_name function_args injection
                 output_i ("HX_STACK_THIS(__this.mPtr)\n");
              List.iter (fun (v,_) -> output_i ("HX_STACK_ARG(" ^ (cpp_var_name_of v) ^ ",\"" ^ (cpp_debug_name_of v) ^"\")\n") )
                 (List.filter (cpp_debug_var_visible ctx) closure.close_args);
+
+             let line = Lexer.get_error_line closure.close_expr.cpppos in
+             let lineName = Printf.sprintf "%4d" line in
+             out ("HXLINE(" ^ lineName ^ ")\n" );
           end
       in
 
@@ -3972,6 +4037,10 @@ let gen_cpp_function_body ctx clazz is_static func_name function_def head_code t
             then output_i ("HX_STACK_THIS(" ^ (if ctx.ctx_real_this_ptr then "this" else "__this") ^")\n");
          List.iter (fun (v,_) -> if not (cpp_no_debug_synbol ctx v) then
               output_i ("HX_STACK_ARG(" ^ (cpp_var_name_of v) ^ ",\"" ^ v.v_name ^"\")\n") ) function_def.tf_args;
+
+         let line = Lexer.get_error_line function_def.tf_expr.epos in
+         let lineName = Printf.sprintf "%4d" line in
+         output ("HXLINE(" ^ lineName ^ ")\n" );
       end;
       if (head_code<>"") then
          output_i (head_code ^ "\n");
@@ -4095,10 +4164,17 @@ let gen_field ctx class_def class_name ptr_name dot_name is_static is_interface
    end else (match  field.cf_expr with
    (* Function field *)
    | Some { eexpr = TFunction function_def } ->
-      let return_type = (ctx_type_string ctx function_def.tf_type) in
+      let return_type_str = (ctx_type_string ctx function_def.tf_type) in
       let nargs = string_of_int (List.length function_def.tf_args) in
-      let is_void = (cpp_type_of ctx function_def.tf_type ) = TCppVoid in
+      let return_type = (cpp_type_of ctx function_def.tf_type ) in
+      let is_void = return_type = TCppVoid in
       let ret = if is_void  then "(void)" else "return " in
+
+      let needsWrapper t = match t with
+         | TCppStar _ -> true
+         | TCppInst(t) -> has_meta_key t.cl_meta Meta.StructAccess
+         | _ -> false
+      in
       let orig_debug = ctx.ctx_debug_level in
       let no_debug = has_meta_key field.cf_meta Meta.NoDebug in
 
@@ -4106,7 +4182,7 @@ let gen_field ctx class_def class_name ptr_name dot_name is_static is_interface
          (* The actual function definition *)
          let nativeImpl = get_meta_string field.cf_meta Meta.Native in
          let remap_name = native_field_name_remap is_static field in
-         output (if is_void then "void" else return_type );
+         output (if is_void then "void" else return_type_str );
          output (" " ^ class_name ^ "::" ^ remap_name ^ "(" );
          output (ctx_arg_list ctx function_def.tf_args "__o_");
          output ")";
@@ -4126,16 +4202,66 @@ let gen_field ctx class_def class_name ptr_name dot_name is_static is_interface
          let doDynamic =  (nonVirtual || not (is_override class_def field.cf_name ) ) && (reflective class_def field ) in
          (* generate dynamic version too ... *)
          if ( doDynamic ) then begin
-            if (is_static) then output "STATIC_";
-            output ("HX_DEFINE_DYNAMIC_FUNC" ^ nargs ^ "(" ^ class_name ^ "," ^
-                     remap_name ^ "," ^ ret ^ ")\n\n");
+            let tcpp_args = List.map (fun (v,_) -> cpp_type_of ctx v.v_type  ) function_def.tf_args in
+            let wrap = (needsWrapper return_type) || (List.exists needsWrapper tcpp_args) in
+            if wrap then begin
+               let wrapName = "_hx_wrap" ^ class_name ^ "_" ^ remap_name in
+               output ("static ::Dynamic " ^ wrapName ^ "( "  );
+               let sep = ref " " in
+               if not is_static then begin
+                  output "hx::Object *obj";
+                  sep := ",";
+               end;
+               ExtList.List.iteri (fun i _ -> output (!sep ^ "const Dynamic &a" ^ (string_of_int i)) ; sep:=",")  tcpp_args;
+               output ( ") {\n\t");
+               if not is_void then begin
+                  match return_type with
+                    | TCppStar _ ->
+                       output "return (cpp::Pointer<const void *>) "
+                    | TCppInst(t) when has_meta_key t.cl_meta Meta.StructAccess ->
+                       output ("return (cpp::Struct< " ^ (tcpp_to_string return_type) ^ " >) ");
+                    | _ -> output "return ";
+               end;
+
+               if is_static then
+                  output (class_name ^ "::" ^ remap_name ^ "(")
+               else
+                  output ("reinterpret_cast< " ^ class_name ^ " *>(obj)->" ^ remap_name ^ "(");
+
+               sep := "";
+               ExtList.List.iteri (fun i arg ->
+                     output !sep; sep := ",";
+                     (match arg with
+                       | TCppStar (t,const) ->
+                          output ("(cpp::" ^ (if const then "Const" else "") ^"Pointer<" ^ (tcpp_to_string t)^" >) ")
+                       | TCppInst(t) when has_meta_key t.cl_meta Meta.StructAccess ->
+                          output ("(cpp::Struct< " ^ (tcpp_to_string return_type) ^ " >) ");
+                       | _ -> () );
+                     output ("a" ^ (string_of_int i));
+                  )  tcpp_args;
+
+               output ");\n";
+
+               if is_void then output "\treturn null();\n";
+               output "}\n";
+               let nName = string_of_int (List.length tcpp_args) in
+               output ("::Dynamic " ^ class_name ^ "::" ^ remap_name ^ "_dyn() {\n\treturn ");
+               if is_static then
+                  output ("hx::CreateStaticFunction" ^ nName ^ "(\"" ^ remap_name ^ "\"," ^ wrapName ^ ");")
+               else
+                  output ("hx::CreateMemberFunction" ^ nName ^ "(\"" ^ remap_name ^ "\",this," ^ wrapName ^ ");");
+               output "}\n";
+            end else begin
+               if (is_static) then output "STATIC_";
+               output ("HX_DEFINE_DYNAMIC_FUNC" ^ nargs ^ "(" ^ class_name ^ "," ^ remap_name ^ "," ^ ret ^ ")\n\n");
+            end
          end;
 
       end else begin
          ctx.ctx_real_this_ptr <- false;
          let func_name = "__default_" ^ (remap_name) in
          output ("HX_BEGIN_DEFAULT_FUNC(" ^ func_name ^ "," ^ class_name ^ ")\n");
-         output return_type;
+         output return_type_str;
          output (" _hx_run(" ^ (ctx_arg_list ctx function_def.tf_args "__o_") ^ ")");
          gen_cpp_function_body ctx class_def is_static func_name function_def "" "" no_debug;
 
@@ -5669,6 +5795,16 @@ let generate_class_files baseCtx super_deps constructor_deps class_def inScripta
             "inCallProp == hx::paccAlways"
       in
 
+      let toCommon t f value =
+         t ^ "( " ^ ( match cpp_type_of ctx f.cf_type with
+           | TCppInst(t) as inst when (has_meta_key t.cl_meta Meta.StructAccess)
+              -> "cpp::Struct< " ^ (tcpp_to_string inst) ^ " >( " ^ value ^ " )"
+           | TCppStar(t,_) -> "cpp::Pointer<void *>( " ^ value ^ " )"
+           | _ -> value
+         ) ^  " )"
+      in
+      let toVal f value = toCommon "hx::Val" f value in
+      let toDynamic f value = toCommon "" f value in
 
 
       if (has_get_member_field class_def) then begin
@@ -5677,10 +5813,11 @@ let generate_class_files baseCtx super_deps constructor_deps class_def inScripta
          let get_field_dat = List.map (fun f ->
             (f.cf_name, String.length f.cf_name,
                (match f.cf_kind with
-               | Var { v_read = AccCall } when is_extern_field f -> "if (" ^ (checkPropCall f) ^ ") return hx::Val(" ^(keyword_remap ("get_" ^ f.cf_name)) ^ "());"
-               | Var { v_read = AccCall } -> "return hx::Val( " ^ (checkPropCall f) ^ " ? " ^ (keyword_remap ("get_" ^ f.cf_name)) ^ "() : " ^
-                     ((keyword_remap f.cf_name) ^ (if (variable_field f) then "" else "_dyn()")) ^ ");"
-               | _ -> "return hx::Val( " ^ ((keyword_remap f.cf_name) ^ if (variable_field f) then "" else "_dyn()") ^ ");"
+               | Var { v_read = AccCall } when is_extern_field f ->
+                     "if (" ^ (checkPropCall f) ^ ") return " ^ (toVal f ((keyword_remap ("get_" ^ f.cf_name)) ^ "()" ) ) ^ ";"
+               | Var { v_read = AccCall } -> "return " ^ (toVal f ((checkPropCall f) ^ " ? " ^ (keyword_remap ("get_" ^ f.cf_name)) ^ "() : " ^
+                     ((keyword_remap f.cf_name) ^ (if (variable_field f) then "" else "_dyn()")) ) ) ^ ";"
+               | _ -> "return " ^ (toVal f (((keyword_remap f.cf_name) ^ if (variable_field f) then "" else "_dyn()"))) ^ ";"
             ) ) )
          in
          dump_quick_field_test (get_field_dat reflect_member_readable);
@@ -5695,10 +5832,11 @@ let generate_class_files baseCtx super_deps constructor_deps class_def inScripta
          let get_field_dat = List.map (fun f ->
             (f.cf_name, String.length f.cf_name,
                (match f.cf_kind with
-               | Var { v_read = AccCall } when is_extern_field f -> "if (" ^ (checkPropCall f) ^ ") { outValue = " ^(keyword_remap ("get_" ^ f.cf_name)) ^ "(); return true; }"
-               | Var { v_read = AccCall } -> "outValue = " ^ (checkPropCall f) ^ " ? " ^ (keyword_remap ("get_" ^ f.cf_name)) ^ "() : " ^
-                     ((keyword_remap f.cf_name) ^ if (variable_field f) then "" else "_dyn()") ^ "; return true;";
-               | _ when variable_field f -> "outValue = " ^ (keyword_remap f.cf_name) ^ "; return true;"
+               | Var { v_read = AccCall } when is_extern_field f ->
+                     "if (" ^ (checkPropCall f) ^ ") { outValue = " ^ (toDynamic f (keyword_remap ("get_" ^ f.cf_name) ^ "()")) ^ "; return true; }"
+               | Var { v_read = AccCall } -> "outValue = " ^ (toDynamic f ((checkPropCall f) ^ " ? " ^ (keyword_remap ("get_" ^ f.cf_name)) ^ "() : " ^
+                     ((keyword_remap f.cf_name) ^ if (variable_field f) then "" else "_dyn()"))) ^ "; return true;";
+               | _ when variable_field f -> "outValue = " ^ (toDynamic f (keyword_remap f.cf_name)) ^ "; return true;"
                | _ -> "outValue = " ^ ((native_field_name_remap true f) ^ "_dyn(); return true;")
                )
             ) )
@@ -5707,6 +5845,14 @@ let generate_class_files baseCtx super_deps constructor_deps class_def inScripta
          output_cpp ("\treturn false;\n}\n\n");
       end;
 
+      let castable f =
+         match cpp_type_of ctx f.cf_type with
+           | TCppInst(t) as inst when (has_meta_key t.cl_meta Meta.StructAccess)
+              -> "cpp::Struct< " ^ (tcpp_to_string inst) ^ " > "
+           | TCppStar(t,_) -> "cpp::Pointer< " ^ ( tcpp_to_string t ) ^ " >"
+           | _ -> ctx_type_string ctx f.cf_type
+      in
+
       (* Dynamic "Set" Field function *)
       if (has_set_member_field class_def) then begin
 
@@ -5714,14 +5860,17 @@ let generate_class_files baseCtx super_deps constructor_deps class_def inScripta
 
          let set_field_dat = List.map (fun f ->
             let default_action = if is_gc_element ctx (cpp_type_of ctx f.cf_type) then
-                  "_hx_set_" ^ (keyword_remap f.cf_name) ^ "(HX_CTX_GET,inValue.Cast< " ^ (ctx_type_string ctx f.cf_type) ^ " >());" ^ " return inValue;"
+                  "_hx_set_" ^ (keyword_remap f.cf_name) ^ "(HX_CTX_GET,inValue.Cast< " ^ (castable f) ^ " >());" ^ " return inValue;"
                else
-                  (keyword_remap f.cf_name) ^ "=inValue.Cast< " ^ (ctx_type_string ctx f.cf_type) ^ " >();" ^ " return inValue;"
+                  (keyword_remap f.cf_name) ^ "=inValue.Cast< " ^ (castable f) ^ " >();" ^ " return inValue;"
             in
             (f.cf_name, String.length f.cf_name,
                (match f.cf_kind with
-               | Var { v_write = AccCall } -> "if (" ^ (checkPropCall f) ^ ") return hx::Val( " ^ (keyword_remap ("set_" ^ f.cf_name)) ^ "(inValue) );"
-                  ^ ( if is_extern_field f then "" else default_action )
+               | Var { v_write = AccCall } ->
+                  let inVal =  "(inValue.Cast< " ^ (castable f) ^ " >())" in
+                  let setter = keyword_remap ("set_" ^ f.cf_name) in
+                  "if (" ^ (checkPropCall f) ^ ") return " ^ (toVal f (setter ^inVal) ) ^ ";" ^
+                      ( if is_extern_field f then "" else default_action )
                | _ -> default_action
                )
             )
@@ -5742,11 +5891,14 @@ let generate_class_files baseCtx super_deps constructor_deps class_def inScripta
 
          let set_field_dat = List.map (fun f ->
             let default_action =
-               (keyword_remap f.cf_name) ^ "=ioValue.Cast< " ^ (ctx_type_string ctx f.cf_type) ^ " >(); return true;" in
+               (keyword_remap f.cf_name) ^ "=ioValue.Cast< " ^ (castable f) ^ " >(); return true;" in
             (f.cf_name, String.length f.cf_name,
                (match f.cf_kind with
-               | Var { v_write = AccCall } -> "if (" ^ (checkPropCall f) ^ ")  ioValue = " ^ (keyword_remap ("set_" ^ f.cf_name)) ^ "(ioValue);"
-                  ^ ( if is_extern_field f then "" else " else " ^ default_action )
+               | Var { v_write = AccCall } ->
+                  let inVal = "(ioValue.Cast< " ^ (castable f) ^ " >())" in
+                  let setter = keyword_remap ("set_" ^ f.cf_name) in
+                  "if (" ^ (checkPropCall f) ^ ")  ioValue = " ^ (toDynamic f (setter ^ inVal) ) ^ ";"
+                      ^ ( if is_extern_field f then "" else " else " ^ default_action )
                | _ -> default_action
                )
             )

+ 4 - 18
src/generators/genlua.ml

@@ -1742,15 +1742,13 @@ let generate_type ctx = function
 			| ([],_) -> ()
 			| _ -> generate_package_create ctx c.cl_path);
 		check_multireturn ctx c;
-	| TEnumDecl e when not e.e_extern -> generate_enum ctx e
-	| TTypeDecl _ | TAbstractDecl _ -> ()
+	| TEnumDecl e ->
+		if not e.e_extern then generate_enum ctx e
+		else ();
+	| TTypeDecl _ | TAbstractDecl _ | _ -> ()
 
 let generate_type_forward ctx = function
 	| TClassDecl c ->
-		(match c.cl_init with
-		| None -> ()
-		| Some e ->
-			ctx.inits <- e :: ctx.inits);
 		if not c.cl_extern then
 		    begin
 			generate_package_create ctx c.cl_path;
@@ -2015,18 +2013,6 @@ let generate com =
 	println ctx "end";
 	newline ctx;
 
-	let rec chk_features e =
-		if is_dynamic_iterator ctx e then add_feature ctx "use._iterator";
-		match e.eexpr with
-		| TField (_,FClosure _) ->
-			add_feature ctx "use._hx_bind"
-		| _ ->
-			Type.iter chk_features e
-	in
-
-	List.iter chk_features ctx.inits;
-
-	List.iter (fun (_,_,e) -> chk_features e) ctx.statics;
 	if has_feature ctx "use._iterator" then begin
 		add_feature ctx "use._hx_bind";
 		println ctx "function _hx_iterator(o)  if ( lua.Boot.__instanceof(o, Array) ) then return function() return HxOverrides.iter(o) end elseif (typeof(o.iterator) == 'function') then return  _hx_bind(o,o.iterator) else return  o.iterator end end";

+ 31 - 13
src/optimization/optimizer.ml

@@ -492,8 +492,8 @@ let rec type_inline ctx cf f ethis params tret config p ?(self_calling_closure=f
 			{ e with eexpr = TFunction { tf_args = args; tf_expr = expr; tf_type = f.tf_type } }
 		| TCall({eexpr = TConst TSuper; etype = t},el) ->
 			begin match follow t with
-			| TInst({ cl_constructor = Some ({cf_kind = Method MethInline; cf_expr = Some ({eexpr = TFunction tf})} as cf)},_) ->
-				begin match type_inline ctx cf tf ethis el ctx.t.tvoid None po true with
+			| TInst({ cl_constructor = Some ({cf_kind = Method MethInline; cf_expr = Some ({eexpr = TFunction tf})} as cf)} as c,_) ->
+				begin match type_inline_ctor ctx c cf tf ethis el po with
 				| Some e -> map term e
 				| None -> error "Could not inline super constructor call" po
 				end
@@ -651,6 +651,29 @@ let rec type_inline ctx cf f ethis params tret config p ?(self_calling_closure=f
 			let rec map_expr_type e = Type.map_expr_type map_expr_type map_type map_var e in
 			Some (map_expr_type e)
 
+(* Same as type_inline, but modifies the function body to add field inits *)
+and type_inline_ctor ctx c cf tf ethis el po =
+	let field_inits = 
+		let cparams = List.map snd c.cl_params in
+		let ethis = mk (TConst TThis) (TInst (c,cparams)) c.cl_pos in
+		let el = List.fold_left (fun acc cf -> 
+			match cf.cf_kind,cf.cf_expr with
+			| Var _,Some e ->
+				let lhs = mk (TField(ethis,FInstance (c,cparams,cf))) cf.cf_type e.epos in
+				let eassign = mk (TBinop(OpAssign,lhs,e)) cf.cf_type e.epos in
+				eassign :: acc
+			| _ -> acc
+		) [] c.cl_ordered_fields in
+		List.rev el
+	in
+	let tf =
+		if field_inits = [] then tf
+		else
+			let bl = match tf.tf_expr with {eexpr = TBlock b } -> b | x -> [x] in
+			{tf with tf_expr = mk (TBlock (field_inits @ bl)) ctx.t.tvoid c.cl_pos}
+	in
+	type_inline ctx cf tf ethis el ctx.t.tvoid None po true
+
 
 (* ---------------------------------------------------------------------- *)
 (* LOOPS *)
@@ -1222,6 +1245,7 @@ let inline_constructors ctx e =
 		if i < 0 then "n" ^ (string_of_int (-i))
 		else (string_of_int i)
 	in
+	let is_extern_ctor c cf = c.cl_extern || Meta.has Meta.Extern cf.cf_meta in
 	let rec find_locals e = match e.eexpr with
 		| TVar(v,Some e1) ->
 			find_locals e1;
@@ -1234,22 +1258,13 @@ let inline_constructors ctx e =
 						()
 					end
 				| TNew({ cl_constructor = Some ({cf_kind = Method MethInline; cf_expr = Some ({eexpr = TFunction tf})} as cf)} as c,tl,pl) when type_iseq v.v_type e1.etype ->
-					begin match type_inline ctx cf tf (mk (TLocal v) (TInst (c,tl)) e1.epos) pl ctx.t.tvoid None e1.epos true with
+					begin match type_inline_ctor ctx c cf tf (mk (TLocal v) (TInst (c,tl)) e1.epos) pl e1.epos with
 					| Some e ->
-						(* add field inits here because the filter has not run yet (issue #2336) *)
-						let ev = mk (TLocal v) v.v_type e.epos in
-						let el_init = List.fold_left (fun acc cf -> match cf.cf_kind,cf.cf_expr with
-							| Var _,Some e ->
-								let ef = mk (TField(ev,FInstance(c,tl,cf))) cf.cf_type e.epos in
-								let e = mk (TBinop(OpAssign,ef,e)) cf.cf_type e.epos in
-								e :: acc
-							| _ -> acc
-						) el_init c.cl_ordered_fields in
 						let e' = match el_init with
 							| [] -> e
 							| _ -> mk (TBlock (List.rev (e :: el_init))) e.etype e.epos
 						in
-						add v e' (IKCtor(cf,c.cl_extern || Meta.has Meta.Extern cf.cf_meta));
+						add v e' (IKCtor(cf,is_extern_ctor c cf));
 						find_locals e
 					| None ->
 						()
@@ -1399,6 +1414,9 @@ let inline_constructors ctx e =
 			in
 			let el = block [] el in
 			mk (TBlock (List.rev el)) e.etype e.epos
+		| TNew({ cl_constructor = Some ({cf_kind = Method MethInline; cf_expr = Some ({eexpr = TFunction _})} as cf)} as c,_,_) when is_extern_ctor c cf ->
+			display_error ctx "Extern constructor could not be inlined" e.epos;
+			Type.map_expr loop e
 		| _ ->
 			Type.map_expr loop e
 	in

+ 27 - 0
std/cpp/ConstStar.hx

@@ -0,0 +1,27 @@
+/*
+ * Copyright (C)2005-2017 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 cpp;
+
+// Allows haxe to type result correctly, and hxcpp can recognise this use the correct type
+typedef ConstStar<T> = T;
+
+

+ 28 - 0
std/cpp/Struct.hx

@@ -0,0 +1,28 @@
+/*
+ * Copyright (C)2005-2017 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 cpp;
+
+// Wrap external types with a class that integrates with Dynamic
+typedef Struct<T> = T;
+
+
+

+ 1 - 1
std/haxe/EnumFlags.hx

@@ -73,7 +73,7 @@ abstract EnumFlags<T:EnumValue>(Int) {
 		If `v` is null, the result is unspecified.
 	**/
 	public inline function unset( v : T ) : Void {
-		this &= 0xFFFFFFF - (1 << Type.enumIndex(v));
+		this &= 0xFFFFFFFF - (1 << Type.enumIndex(v));
 	}
 
 	/**

+ 1 - 0
std/haxe/io/Path.hx

@@ -301,6 +301,7 @@ class Path {
 	public static function isAbsolute ( path : String ) : Bool {
 		if (StringTools.startsWith(path, '/')) return true;
 		if (path.charAt(1) == ':') return true;
+		if (StringTools.startsWith(path, '\\\\')) return true;
 		return false;
 	}
 

+ 5 - 0
std/hl/UI.hx

@@ -28,6 +28,10 @@ abstract Sentinel(SentinelHandle) {
 	public function new( timeout, callback ) {
 		this = create_sentinel(timeout,callback);
 	}
+	
+	public function setPause( p : Bool ) {
+		_pause(this, p);
+	}
 
 	public function tick() {
 		_tick(this);
@@ -38,6 +42,7 @@ abstract Sentinel(SentinelHandle) {
 	}
 
 	@:hlNative("ui","ui_sentinel_tick") static function _tick( h : SentinelHandle ) : Void {}
+	@:hlNative("ui","ui_sentinel_pause") static function _pause( h : SentinelHandle, b : Bool ) : Void {}
 
 }
 

+ 0 - 1
std/java/Lib.hx

@@ -57,7 +57,6 @@ package java;
 
 	/**
 		Gets the native `java.lang.Class` from the supplied object. Will throw an exception in case of null being passed.
-		[deprecated] - use `getNativeType` instead
 	**/
 	inline public static function getNativeType<T>(obj:T):java.lang.Class<T>
 	{

+ 65 - 65
std/js/html/HTMLDocument.hx

@@ -36,7 +36,7 @@ extern class HTMLDocument extends Document
 {
 	var domain : String;
 	var cookie : String;
-	var body : Element;
+	var body : BodyElement;
 	var head(default,null) : HeadElement;
 	var images(default,null) : HTMLCollection;
 	var embeds(default,null) : HTMLCollection;
@@ -81,133 +81,133 @@ extern class HTMLDocument extends Document
 	function getSelection() : Selection;
 	function captureEvents() : Void;
 	function releaseEvents() : Void;
-	/** Shorthand for creating an HTML <td> element. */
+	/** Shorthand for creating an HTML `<td>` element. */
 	inline function createTableCellElement() : TableCellElement { return cast createElement("td"); }
-	/** Shorthand for creating an HTML <hr> element. */
+	/** Shorthand for creating an HTML `<hr>` element. */
 	inline function createHRElement() : HRElement { return cast createElement("hr"); }
-	/** Shorthand for creating an HTML <select> element. */
+	/** Shorthand for creating an HTML `<select>` element. */
 	inline function createSelectElement() : SelectElement { return cast createElement("select"); }
-	/** Shorthand for creating an HTML <map> element. */
+	/** Shorthand for creating an HTML `<map>` element. */
 	inline function createMapElement() : MapElement { return cast createElement("map"); }
-	/** Shorthand for creating an HTML <form> element. */
+	/** Shorthand for creating an HTML `<form>` element. */
 	inline function createFormElement() : FormElement { return cast createElement("form"); }
-	/** Shorthand for creating an HTML <option> element. */
+	/** Shorthand for creating an HTML `<option>` element. */
 	inline function createOptionElement() : OptionElement { return cast createElement("option"); }
-	/** Shorthand for creating an HTML <label> element. */
+	/** Shorthand for creating an HTML `<label>` element. */
 	inline function createLabelElement() : LabelElement { return cast createElement("label"); }
-	/** Shorthand for creating an HTML <meta> element. */
+	/** Shorthand for creating an HTML `<meta>` element. */
 	inline function createMetaElement() : MetaElement { return cast createElement("meta"); }
-	/** Shorthand for creating an HTML <img> element. */
+	/** Shorthand for creating an HTML `<img>` element. */
 	inline function createImageElement() : ImageElement { return cast createElement("img"); }
-	/** Shorthand for creating an HTML <dl> element. */
+	/** Shorthand for creating an HTML `<dl>` element. */
 	inline function createDListElement() : DListElement { return cast createElement("dl"); }
-	/** Shorthand for creating an HTML <frame> element. */
+	/** Shorthand for creating an HTML `<frame>` element. */
 	inline function createFrameElement() : FrameElement { return cast createElement("frame"); }
-	/** Shorthand for creating an HTML <mod> element. */
+	/** Shorthand for creating an HTML `<mod>` element. */
 	inline function createModElement() : ModElement { return cast createElement("mod"); }
-	/** Shorthand for creating an HTML <ul> element. */
+	/** Shorthand for creating an HTML `<ul>` element. */
 	inline function createUListElement() : UListElement { return cast createElement("ul"); }
-	/** Shorthand for creating an HTML <output> element. */
+	/** Shorthand for creating an HTML `<output>` element. */
 	inline function createOutputElement() : OutputElement { return cast createElement("output"); }
-	/** Shorthand for creating an HTML <ol> element. */
+	/** Shorthand for creating an HTML `<ol>` element. */
 	inline function createOListElement() : OListElement { return cast createElement("ol"); }
-	/** Shorthand for creating an HTML <shadow> element. */
+	/** Shorthand for creating an HTML `<shadow>` element. */
 	inline function createShadowElement() : ShadowElement { return cast createElement("shadow"); }
-	/** Shorthand for creating an HTML <li> element. */
+	/** Shorthand for creating an HTML `<li>` element. */
 	inline function createLIElement() : LIElement { return cast createElement("li"); }
-	/** Shorthand for creating an HTML <datalist> element. */
+	/** Shorthand for creating an HTML `<datalist>` element. */
 	inline function createDataListElement() : DataListElement { return cast createElement("datalist"); }
-	/** Shorthand for creating an HTML <param> element. */
+	/** Shorthand for creating an HTML `<param>` element. */
 	inline function createParamElement() : ParamElement { return cast createElement("param"); }
-	/** Shorthand for creating an HTML <font> element. */
+	/** Shorthand for creating an HTML `<font>` element. */
 	inline function createFontElement() : FontElement { return cast createElement("font"); }
-	/** Shorthand for creating an HTML <track> element. */
+	/** Shorthand for creating an HTML `<track>` element. */
 	inline function createTrackElement() : TrackElement { return cast createElement("track"); }
-	/** Shorthand for creating an HTML <applet> element. */
+	/** Shorthand for creating an HTML `<applet>` element. */
 	inline function createAppletElement() : AppletElement { return cast createElement("applet"); }
-	/** Shorthand for creating an HTML <area> element. */
+	/** Shorthand for creating an HTML `<area>` element. */
 	inline function createAreaElement() : AreaElement { return cast createElement("area"); }
-	/** Shorthand for creating an HTML <link> element. */
+	/** Shorthand for creating an HTML `<link>` element. */
 	inline function createLinkElement() : LinkElement { return cast createElement("link"); }
-	/** Shorthand for creating an HTML <div> element. */
+	/** Shorthand for creating an HTML `<div>` element. */
 	inline function createDivElement() : DivElement { return cast createElement("div"); }
-	/** Shorthand for creating an HTML <title> element. */
+	/** Shorthand for creating an HTML `<title>` element. */
 	inline function createTitleElement() : TitleElement { return cast createElement("title"); }
-	/** Shorthand for creating an HTML <style> element. */
+	/** Shorthand for creating an HTML `<style>` element. */
 	inline function createStyleElement() : StyleElement { return cast createElement("style"); }
-	/** Shorthand for creating an HTML <progress> element. */
+	/** Shorthand for creating an HTML `<progress>` element. */
 	inline function createProgressElement() : ProgressElement { return cast createElement("progress"); }
-	/** Shorthand for creating an HTML <button> element. */
+	/** Shorthand for creating an HTML `<button>` element. */
 	inline function createButtonElement() : ButtonElement { return cast createElement("button"); }
-	/** Shorthand for creating an HTML <fieldset> element. */
+	/** Shorthand for creating an HTML `<fieldset>` element. */
 	inline function createFieldSetElement() : FieldSetElement { return cast createElement("fieldset"); }
-	/** Shorthand for creating an HTML <a> element. */
+	/** Shorthand for creating an HTML `<a>` element. */
 	inline function createAnchorElement() : AnchorElement { return cast createElement("a"); }
-	/** Shorthand for creating an HTML <iframe> element. */
+	/** Shorthand for creating an HTML `<iframe>` element. */
 	inline function createIFrameElement() : IFrameElement { return cast createElement("iframe"); }
-	/** Shorthand for creating an HTML <span> element. */
+	/** Shorthand for creating an HTML `<span>` element. */
 	inline function createSpanElement() : SpanElement { return cast createElement("span"); }
-	/** Shorthand for creating an HTML <body> element. */
+	/** Shorthand for creating an HTML `<body>` element. */
 	inline function createBodyElement() : BodyElement { return cast createElement("body"); }
-	/** Shorthand for creating an HTML <input> element. */
+	/** Shorthand for creating an HTML `<input>` element. */
 	inline function createInputElement() : InputElement { return cast createElement("input"); }
-	/** Shorthand for creating an HTML <embed> element. */
+	/** Shorthand for creating an HTML `<embed>` element. */
 	inline function createEmbedElement() : EmbedElement { return cast createElement("embed"); }
-	/** Shorthand for creating an HTML <meter> element. */
+	/** Shorthand for creating an HTML `<meter>` element. */
 	inline function createMeterElement() : MeterElement { return cast createElement("meter"); }
-	/** Shorthand for creating an HTML <picture> element. */
+	/** Shorthand for creating an HTML `<picture>` element. */
 	inline function createPictureElement() : PictureElement { return cast createElement("picture"); }
-	/** Shorthand for creating an HTML <pre> element. */
+	/** Shorthand for creating an HTML `<pre>` element. */
 	inline function createPreElement() : PreElement { return cast createElement("pre"); }
-	/** Shorthand for creating an HTML <thead> element. */
+	/** Shorthand for creating an HTML `<thead>` element. */
 	inline function createTableSectionElement() : TableSectionElement { return cast createElement("thead"); }
-	/** Shorthand for creating an HTML <head> element. */
+	/** Shorthand for creating an HTML `<head>` element. */
 	inline function createHeadElement() : HeadElement { return cast createElement("head"); }
-	/** Shorthand for creating an HTML <base> element. */
+	/** Shorthand for creating an HTML `<base>` element. */
 	inline function createBaseElement() : BaseElement { return cast createElement("base"); }
-	/** Shorthand for creating an HTML <optgroup> element. */
+	/** Shorthand for creating an HTML `<optgroup>` element. */
 	inline function createOptGroupElement() : OptGroupElement { return cast createElement("optgroup"); }
-	/** Shorthand for creating an HTML <quote> element. */
+	/** Shorthand for creating an HTML `<quote>` element. */
 	inline function createQuoteElement() : QuoteElement { return cast createElement("quote"); }
-	/** Shorthand for creating an HTML <audio> element. */
+	/** Shorthand for creating an HTML `<audio>` element. */
 	inline function createAudioElement() : AudioElement { return cast createElement("audio"); }
-	/** Shorthand for creating an HTML <video> element. */
+	/** Shorthand for creating an HTML `<video>` element. */
 	inline function createVideoElement() : VideoElement { return cast createElement("video"); }
-	/** Shorthand for creating an HTML <legend> element. */
+	/** Shorthand for creating an HTML `<legend>` element. */
 	inline function createLegendElement() : LegendElement { return cast createElement("legend"); }
-	/** Shorthand for creating an HTML <menu> element. */
+	/** Shorthand for creating an HTML `<menu>` element. */
 	inline function createMenuElement() : MenuElement { return cast createElement("menu"); }
-	/** Shorthand for creating an HTML <frameset> element. */
+	/** Shorthand for creating an HTML `<frameset>` element. */
 	inline function createFrameSetElement() : FrameSetElement { return cast createElement("frameset"); }
-	/** Shorthand for creating an HTML <canvas> element. */
+	/** Shorthand for creating an HTML `<canvas>` element. */
 	inline function createCanvasElement() : CanvasElement { return cast createElement("canvas"); }
-	/** Shorthand for creating an HTML <p> element. */
+	/** Shorthand for creating an HTML `<p>` element. */
 	inline function createParagraphElement() : ParagraphElement { return cast createElement("p"); }
-	/** Shorthand for creating an HTML <col> element. */
+	/** Shorthand for creating an HTML `<col>` element. */
 	inline function createTableColElement() : TableColElement { return cast createElement("col"); }
-	/** Shorthand for creating an HTML <dir> element. */
+	/** Shorthand for creating an HTML `<dir>` element. */
 	inline function createDirectoryElement() : DirectoryElement { return cast createElement("dir"); }
-	/** Shorthand for creating an HTML <table> element. */
+	/** Shorthand for creating an HTML `<table>` element. */
 	inline function createTableElement() : TableElement { return cast createElement("table"); }
-	/** Shorthand for creating an HTML <tr> element. */
+	/** Shorthand for creating an HTML `<tr>` element. */
 	inline function createTableRowElement() : TableRowElement { return cast createElement("tr"); }
-	/** Shorthand for creating an HTML <script> element. */
+	/** Shorthand for creating an HTML `<script>` element. */
 	inline function createScriptElement() : ScriptElement { return cast createElement("script"); }
-	/** Shorthand for creating an HTML <source> element. */
+	/** Shorthand for creating an HTML `<source>` element. */
 	inline function createSourceElement() : SourceElement { return cast createElement("source"); }
-	/** Shorthand for creating an HTML <content> element. */
+	/** Shorthand for creating an HTML `<content>` element. */
 	inline function createContentElement() : ContentElement { return cast createElement("content"); }
-	/** Shorthand for creating an HTML <br> element. */
+	/** Shorthand for creating an HTML `<br>` element. */
 	inline function createBRElement() : BRElement { return cast createElement("br"); }
-	/** Shorthand for creating an HTML <html> element. */
+	/** Shorthand for creating an HTML `<html>` element. */
 	inline function createHtmlElement() : HtmlElement { return cast createElement("html"); }
-	/** Shorthand for creating an HTML <textarea> element. */
+	/** Shorthand for creating an HTML `<textarea>` element. */
 	inline function createTextAreaElement() : TextAreaElement { return cast createElement("textarea"); }
-	/** Shorthand for creating an HTML <media> element. */
+	/** Shorthand for creating an HTML `<media>` element. */
 	inline function createMediaElement() : MediaElement { return cast createElement("media"); }
-	/** Shorthand for creating an HTML <object> element. */
+	/** Shorthand for creating an HTML `<object>` element. */
 	inline function createObjectElement() : ObjectElement { return cast createElement("object"); }
-	/** Shorthand for creating an HTML <caption> element. */
+	/** Shorthand for creating an HTML `<caption>` element. */
 	inline function createTableCaptionElement() : TableCaptionElement { return cast createElement("caption"); }
 	
 }

+ 1 - 1
std/lua/Lua.hx

@@ -26,7 +26,7 @@ extern class Lua {
 		Pops a table from the stack and sets it as the new metatable for the value
 		at the given acceptable index.
 	**/
-	public static function setmetatable(tbl:Table<Dynamic,Dynamic>, mtbl: Table<Dynamic, Dynamic>): Void;
+	public static function setmetatable(tbl:Table<Dynamic,Dynamic>, mtbl: Table<Dynamic, Dynamic>): Table<Dynamic, Dynamic>;
 
 	/**
 		Pops a table from the stack and sets it as the new environment for the value

+ 0 - 89
std/lua/Map.hx

@@ -1,89 +0,0 @@
-/*
- * Copyright (C)2005-2017 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 lua;
-class Map<A,B> implements haxe.Constraints.IMap<A,B> {
-
-	private var h : Dynamic;
-	private var k : Dynamic;
-
-	public inline function new() : Void {
-		h = {};
-		k = {};
-	}
-
-	public inline function set( key : A, value : B ) : Void untyped {
-		 h[key] = value;
-		 k[key] = true;
-	}
-
-	public inline function get( key : A ) : Null<B> untyped {
-		return h[key];
-	}
-
-	public inline function exists( key : A ) : Bool untyped {
-		return k[key] != null;
-	}
-
-	public function remove( key : A ) : Bool untyped {
-		if ( k[key] == null) return false;
-		k[key] = null;
-		h[key] = null;
-		return true;
-	}
-
-	public function keys() : Iterator<A> untyped {
-		var cur = next(k,null);
-		return {
-			next : function() {
-				var ret = cur;
-				cur = untyped next(k, cur);
-				return ret;
-			},
-			hasNext : function() return cur != null
-		}
-	}
-
-	public function iterator() : Iterator<B> {
-		var itr = keys();
-		return untyped {
-			hasNext : itr.hasNext,
-			next : function() return h[itr.next()]
-		};
-	}
-
-	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();
-	}
-
-}
-

+ 0 - 1
std/lua/PairTools.hx

@@ -28,7 +28,6 @@ class PairTools {
 		return untyped __lua__("seed");
 	}
 
-
 	public static function ipairsConcat<T>(table1:Table<Int,T>, table2:Table<Int,T>){
 		var ret:Table<Int,T> = Table.create();
 		ipairsFold(table1, function(a,b,c:Table<Int,T>){ c[a] = b; return c;}, ret);

+ 7 - 2
std/lua/_std/sys/io/File.hx

@@ -30,6 +30,7 @@ import lua.Boot;
 class File {
 	public static function getContent( path : String ) : String {
 		var f = Io.open(path, "r");
+		if (f == null) throw 'Invalid path : $path';
 		var s = f.read("*all");
 		f.close();
 		return s;
@@ -55,11 +56,15 @@ class File {
 	}
 
 	public static function read( path : String, binary : Bool = true ) : FileInput {
-		return new FileInput(Io.open(path, binary ? 'rb' : 'r'));
+		var fh = Io.open(path, binary ? 'rb' : 'r');
+		if (fh == null) throw 'Invalid path : $path';
+		return new FileInput(fh);
 	}
 
 	public static function write( path : String, binary : Bool = true ) : FileOutput {
-		return new FileOutput(Io.open(path, binary ? 'wb' : 'w'));
+		var fh = Io.open(path, binary ? 'wb' : 'w');
+		if (fh == null) throw 'Invalid path : $path';
+		return new FileOutput(fh);
 	}
 
 	public static function saveBytes( path : String, bytes : haxe.io.Bytes ) : Void {

+ 1 - 0
std/lua/_std/sys/io/FileInput.hx

@@ -35,6 +35,7 @@ class FileInput extends haxe.io.Input {
 	var _eof:Bool;
 
 	public function new(f:FileHandle){
+		if (f == null) throw 'Invalid filehandle : $f';
 		this.bigEndian = Boot.platformBigEndian;
 		this.f = f;
 		this._eof = false;

+ 1 - 0
std/lua/_std/sys/io/FileOutput.hx

@@ -27,6 +27,7 @@ class FileOutput extends haxe.io.Output {
 	var f:FileHandle;
 
 	public function new(f:FileHandle){
+		if (f == null) throw 'Invalid filehandle : $f';
 		this.f = f;
 	}
 

+ 24 - 0
tests/optimization/src/issues/Issue6093.hx

@@ -0,0 +1,24 @@
+package issues;
+
+private class A {
+	public var x : Int = 1;
+	public inline function new () {};
+}
+
+private class B extends A {
+	public var y : Int = 2;
+	public inline function new () { super(); };
+}
+
+class Issue6093 {
+	@:js('
+		var a_y;
+		var a_x;
+		a_y = 2;
+		a_x = 1;
+	')
+	@:analyzer(ignore)
+	static public function main() {
+		var a = new B();
+	}
+}

+ 7 - 0
tests/unit/src/unit/TestSpecification.hx

@@ -113,6 +113,13 @@ enum EnumFlagTest {
 	EC;
 }
 
+enum EnumFlagTest2 {
+	EF_00; EF_01; EF_02; EF_03; EF_04; EF_05; EF_06; EF_07;
+	EF_08; EF_09; EF_10; EF_11; EF_12; EF_13; EF_14; EF_15;
+	EF_16; EF_17; EF_18; EF_19; EF_20; EF_21; EF_22; EF_23;
+	EF_24; EF_25; EF_26; EF_27; EF_28; EF_29; EF_30; EF_31;
+}
+
 enum EVMTest {
 	EVMA;
 	EVMB(?s:String);

+ 19 - 0
tests/unit/src/unit/issues/Issue6093.hx

@@ -0,0 +1,19 @@
+package unit.issues;
+
+private class A {
+	public var x : Int = 1;
+	public inline function new () {};
+}
+
+private class B extends A {
+	public var y : Int = 2;
+	public inline function new () { super(); };
+}
+
+class Issue6093 extends unit.Test {
+	function test() {
+		var b = new B();
+		eq(b.x, 1);
+		eq(b.y, 2);
+	}
+}

+ 9 - 1
tests/unit/src/unitstd/haxe/EnumFlags.unit.hx

@@ -40,4 +40,12 @@ flags.has(EC) == false;
 flags.unset(EA);
 flags.has(EA) == false;
 flags.has(EB) == true;
-flags.has(EC) == false;
+flags.has(EC) == false;
+
+// Big Enum (32)
+var bigFlags = new haxe.EnumFlags(1<<31);
+bigFlags.has( EF_31 ) == true;
+bigFlags.unset( EF_31 );
+bigFlags.has( EF_31 ) == false;
+bigFlags.set( EF_31 );
+bigFlags.has( EF_31 ) == true;