Browse Source

Properly represent `final` on classes and fields (#7381)

* support `final class`

see #6584

* fix parsing so it allows both `extern final` and `final extern`

Also hold back on the warnings because the Flash API has `@:final` everywhere

* properly represent final fields as `cf_final`

* add missing isExtern on ClassField

* fix extends display handling of final classes

* ctrl s

* annoying

* don't require inits for extern final fields

* don't check for final inits on interfaces

* don't lose final on structure type fields
Simon Krajewski 7 years ago
parent
commit
ff7e220306

+ 5 - 4
src/codegen/dotnet.ml

@@ -412,11 +412,11 @@ let convert_ilmethod ctx p m is_explicit_impl =
 	if PMap.mem "net_loader_debug" ctx.ncom.defines.Define.values then
 	if PMap.mem "net_loader_debug" ctx.ncom.defines.Define.values then
 		Printf.printf "\t%smethod %s : %s\n" (if !is_static then "static " else "") cff_name (IlMetaDebug.ilsig_s m.msig.ssig);
 		Printf.printf "\t%smethod %s : %s\n" (if !is_static then "static " else "") cff_name (IlMetaDebug.ilsig_s m.msig.ssig);
 
 
-	let meta = match is_final with
+	let acc = match is_final with
 		| None | Some true when not force_check ->
 		| None | Some true when not force_check ->
-			(Meta.Final,[],p) :: meta
+			(AFinal,null_pos) :: acc
 		| _ ->
 		| _ ->
-			meta
+			acc
 	in
 	in
 	let meta = if is_explicit_impl then
 	let meta = if is_explicit_impl then
 			(Meta.NoCompletion,[],p) :: (Meta.SkipReflection,[],p) :: meta
 			(Meta.NoCompletion,[],p) :: (Meta.SkipReflection,[],p) :: meta
@@ -725,7 +725,8 @@ let convert_ilclass ctx p ?(delegate=false) ilcls = match ilcls.csuper with
 
 
 		let is_interface = ref false in
 		let is_interface = ref false in
 		List.iter (fun f -> match f with
 		List.iter (fun f -> match f with
-			| SSealed -> meta := (Meta.Final, [], p) :: !meta
+			| SSealed ->
+				flags := HFinal :: !flags
 			| SInterface ->
 			| SInterface ->
 				is_interface := true;
 				is_interface := true;
 				flags := HInterface :: !flags
 				flags := HInterface :: !flags

+ 1 - 1
src/codegen/gencommon/closuresToClass.ml

@@ -463,7 +463,7 @@ let configure gen ft =
 				let pos = cls.cl_pos in
 				let pos = cls.cl_pos in
 				let cf = mk_class_field "Delegate" (TFun(fun_args tfunc.tf_args, tfunc.tf_type)) true pos (Method MethNormal) [] in
 				let cf = mk_class_field "Delegate" (TFun(fun_args tfunc.tf_args, tfunc.tf_type)) true pos (Method MethNormal) [] in
 				cf.cf_expr <- Some { fexpr with eexpr = TFunction { tfunc with tf_expr = func_expr }; };
 				cf.cf_expr <- Some { fexpr with eexpr = TFunction { tfunc with tf_expr = func_expr }; };
-				cf.cf_meta <- (Meta.Final,[],pos) :: cf.cf_meta;
+				cf.cf_final <- true;
 				cls.cl_ordered_fields <- cf :: cls.cl_ordered_fields;
 				cls.cl_ordered_fields <- cf :: cls.cl_ordered_fields;
 				cls.cl_fields <- PMap.add cf.cf_name cf cls.cl_fields;
 				cls.cl_fields <- PMap.add cf.cf_name cf cls.cl_fields;
 				(* invoke function body: call Delegate function *)
 				(* invoke function body: call Delegate function *)

+ 1 - 1
src/codegen/gencommon/enumToClass.ml

@@ -182,7 +182,7 @@ struct
 
 
 		let getTag_cf_type = tfun [] basic.tstring in
 		let getTag_cf_type = tfun [] basic.tstring in
 		let getTag_cf = mk_class_field "getTag" getTag_cf_type true pos (Method MethNormal) [] in
 		let getTag_cf = mk_class_field "getTag" getTag_cf_type true pos (Method MethNormal) [] in
-		getTag_cf.cf_meta <- [(Meta.Final, [], pos)];
+		getTag_cf.cf_final <- true;
 		getTag_cf.cf_expr <- Some {
 		getTag_cf.cf_expr <- Some {
 			eexpr = TFunction {
 			eexpr = TFunction {
 				tf_args = [];
 				tf_args = [];

+ 1 - 1
src/codegen/gencommon/enumToClass2.ml

@@ -94,11 +94,11 @@ module EnumToClass2Modf = struct
 			let pos = ef.ef_pos in
 			let pos = ef.ef_pos in
 
 
 			let cl_ctor = mk_class en.e_module (e_pack, e_name ^ "_" ^ name) pos in
 			let cl_ctor = mk_class en.e_module (e_pack, e_name ^ "_" ^ name) pos in
+			cl_ctor.cl_final <- true;
 			cl_ctor.cl_super <- Some (cl_enum, []);
 			cl_ctor.cl_super <- Some (cl_enum, []);
 			cl_ctor.cl_meta <- [
 			cl_ctor.cl_meta <- [
 				(Meta.Enum,[],pos);
 				(Meta.Enum,[],pos);
 				(Meta.NativeGen,[],pos);
 				(Meta.NativeGen,[],pos);
-				(Meta.Final,[],pos);
 			] @ cl_ctor.cl_meta;
 			] @ cl_ctor.cl_meta;
 			ctors_map := PMap.add name cl_ctor !ctors_map;
 			ctors_map := PMap.add name cl_ctor !ctors_map;
 
 

+ 1 - 1
src/codegen/genxml.ml

@@ -172,7 +172,7 @@ and gen_field att f =
 			cf.cf_name
 			cf.cf_name
 	in
 	in
 	let att = if f.cf_public then ("public","1") :: att else att in
 	let att = if f.cf_public then ("public","1") :: att else att in
-	let att = if (Meta.has Meta.Final) f.cf_meta then ("final","1") :: att else att in
+	let att = if f.cf_final then ("final","1") :: att else att in
 	node (field_name f) att (gen_type ~values:(Some values) f.cf_type :: gen_meta f.cf_meta @ gen_doc_opt f.cf_doc @ overloads)
 	node (field_name f) att (gen_type ~values:(Some values) f.cf_type :: gen_meta f.cf_meta @ gen_doc_opt f.cf_doc @ overloads)
 
 
 let gen_constr e =
 let gen_constr e =

+ 2 - 2
src/codegen/java.ml

@@ -263,7 +263,7 @@ let convert_java_enum ctx p pe =
 				cff_access := (APrivate,null_pos) :: !cff_access
 				cff_access := (APrivate,null_pos) :: !cff_access
 			| JStatic -> cff_access := (AStatic,null_pos) :: !cff_access
 			| JStatic -> cff_access := (AStatic,null_pos) :: !cff_access
 			| JFinal ->
 			| JFinal ->
-				cff_meta := (Meta.Final, [], p) :: !cff_meta;
+				cff_access := (AFinal, p) :: !cff_access;
 				(match field.jf_kind, field.jf_vmsignature, field.jf_constant with
 				(match field.jf_kind, field.jf_vmsignature, field.jf_constant with
 				| JKField, TObject _, _ ->
 				| JKField, TObject _, _ ->
 					jf_constant := None
 					jf_constant := None
@@ -414,7 +414,7 @@ let convert_java_enum ctx p pe =
 
 
 			let is_interface = ref false in
 			let is_interface = ref false in
 			List.iter (fun f -> match f with
 			List.iter (fun f -> match f with
-				| JFinal -> meta := (Meta.Final, [], p) :: !meta
+				| JFinal -> flags := HFinal :: !flags
 				| JInterface ->
 				| JInterface ->
 						is_interface := true;
 						is_interface := true;
 						flags := HInterface :: !flags
 						flags := HInterface :: !flags

+ 2 - 1
src/codegen/swfLoader.ml

@@ -347,11 +347,12 @@ let build_class com c file =
 		} in
 		} in
 		(path.tpackage, [(EEnum enum_data,pos)])
 		(path.tpackage, [(EEnum enum_data,pos)])
 	with Exit ->
 	with Exit ->
+	let flags = if c.hlc_final && List.exists (fun f -> fst f.cff_name <> "new" && not (List.mem_assoc AStatic f.cff_access)) fields then HFinal :: flags else flags in
 	let class_data = {
 	let class_data = {
 		d_name = path.tname,null_pos;
 		d_name = path.tname,null_pos;
 		d_doc = None;
 		d_doc = None;
 		d_params = [];
 		d_params = [];
-		d_meta = if c.hlc_final && List.exists (fun f -> fst f.cff_name <> "new" && not (List.mem_assoc AStatic f.cff_access)) fields then [Meta.Final,[],pos] else [];
+		d_meta = [];
 		d_flags = flags;
 		d_flags = flags;
 		d_data = fields;
 		d_data = fields;
 	} in
 	} in

+ 1 - 0
src/core/ast.ml

@@ -264,6 +264,7 @@ type class_flag =
 	| HPrivate
 	| HPrivate
 	| HExtends of placed_type_path
 	| HExtends of placed_type_path
 	| HImplements of placed_type_path
 	| HImplements of placed_type_path
+	| HFinal
 
 
 type abstract_flag =
 type abstract_flag =
 	| AbPrivate
 	| AbPrivate

+ 12 - 6
src/core/display/completionItem.ml

@@ -66,6 +66,7 @@ module CompletionModuleType = struct
 		meta: metadata;
 		meta: metadata;
 		doc : documentation;
 		doc : documentation;
 		is_extern : bool;
 		is_extern : bool;
+		is_final : bool;
 		kind : CompletionModuleKind.t;
 		kind : CompletionModuleKind.t;
 		has_constructor : not_bool;
 		has_constructor : not_bool;
 		source : module_type_source;
 		source : module_type_source;
@@ -87,6 +88,7 @@ module CompletionModuleType = struct
 				meta = d.d_meta;
 				meta = d.d_meta;
 				doc = d.d_doc;
 				doc = d.d_doc;
 				is_extern = List.mem HExtern d.d_flags;
 				is_extern = List.mem HExtern d.d_flags;
+				is_final = List.mem HFinal d.d_flags;
 				kind = if List.mem HInterface d.d_flags then Interface else Class;
 				kind = if List.mem HInterface d.d_flags then Interface else Class;
 				has_constructor = ctor;
 				has_constructor = ctor;
 				source = Syntax td;
 				source = Syntax td;
@@ -101,6 +103,7 @@ module CompletionModuleType = struct
 				meta = d.d_meta;
 				meta = d.d_meta;
 				doc = d.d_doc;
 				doc = d.d_doc;
 				is_extern = List.mem EExtern d.d_flags;
 				is_extern = List.mem EExtern d.d_flags;
+				is_final = false;
 				kind = Enum;
 				kind = Enum;
 				has_constructor = No;
 				has_constructor = No;
 				source = Syntax td;
 				source = Syntax td;
@@ -117,6 +120,7 @@ module CompletionModuleType = struct
 				meta = d.d_meta;
 				meta = d.d_meta;
 				doc = d.d_doc;
 				doc = d.d_doc;
 				is_extern = List.mem EExtern d.d_flags;
 				is_extern = List.mem EExtern d.d_flags;
+				is_final = false;
 				kind = kind;
 				kind = kind;
 				has_constructor = if kind = Struct then No else Maybe;
 				has_constructor = if kind = Struct then No else Maybe;
 				source = Syntax td;
 				source = Syntax td;
@@ -131,6 +135,7 @@ module CompletionModuleType = struct
 				meta = d.d_meta;
 				meta = d.d_meta;
 				doc = d.d_doc;
 				doc = d.d_doc;
 				is_extern = List.mem AbExtern d.d_flags;
 				is_extern = List.mem AbExtern d.d_flags;
+				is_final = false;
 				kind = if Meta.has Meta.Enum d.d_meta then EnumAbstract else Abstract;
 				kind = if Meta.has Meta.Enum d.d_meta then EnumAbstract else Abstract;
 				has_constructor = if (List.exists (fun cff -> fst cff.cff_name = "new") d.d_data) then Yes else No;
 				has_constructor = if (List.exists (fun cff -> fst cff.cff_name = "new") d.d_data) then Yes else No;
 				source = Syntax td;
 				source = Syntax td;
@@ -143,11 +148,11 @@ module CompletionModuleType = struct
 			| None -> false
 			| None -> false
 			| Some c -> PMap.mem "_new" c.cl_statics
 			| Some c -> PMap.mem "_new" c.cl_statics
 		in
 		in
-		let is_extern,kind,has_ctor = match mt with
+		let is_extern,is_final,kind,has_ctor = match mt with
 			| TClassDecl c ->
 			| TClassDecl c ->
-				c.cl_extern,(if c.cl_interface then Interface else Class),has_constructor c
+				c.cl_extern,c.cl_final,(if c.cl_interface then Interface else Class),has_constructor c
 			| TEnumDecl en ->
 			| TEnumDecl en ->
-				en.e_extern,Enum,false
+				en.e_extern,false,Enum,false
 			| TTypeDecl td ->
 			| TTypeDecl td ->
 				let kind,has_ctor = match follow td.t_type with
 				let kind,has_ctor = match follow td.t_type with
 					| TAnon _ -> Struct,false
 					| TAnon _ -> Struct,false
@@ -155,9 +160,9 @@ module CompletionModuleType = struct
 					| TAbstract(a,_) -> TypeAlias,has_ctor a
 					| TAbstract(a,_) -> TypeAlias,has_ctor a
 					| _ -> TypeAlias,false
 					| _ -> TypeAlias,false
 				in
 				in
-				false,kind,has_ctor
+				false,false,kind,has_ctor
 			| TAbstractDecl a ->
 			| TAbstractDecl a ->
-				false,(if Meta.has Meta.Enum a.a_meta then EnumAbstract else Abstract),has_ctor a
+				false,false,(if Meta.has Meta.Enum a.a_meta then EnumAbstract else Abstract),has_ctor a
 		in
 		in
 		let infos = t_infos mt in
 		let infos = t_infos mt in
 		let convert_type_param (s,t) = match follow t with
 		let convert_type_param (s,t) = match follow t with
@@ -180,6 +185,7 @@ module CompletionModuleType = struct
 			meta = infos.mt_meta;
 			meta = infos.mt_meta;
 			doc = infos.mt_doc;
 			doc = infos.mt_doc;
 			is_extern = is_extern;
 			is_extern = is_extern;
+			is_final = is_final;
 			kind = kind;
 			kind = kind;
 			has_constructor = if has_ctor then Yes else No;
 			has_constructor = if has_ctor then Yes else No;
 			source = Typed mt;
 			source = Typed mt;
@@ -238,7 +244,7 @@ end
 let decl_of_class c = match c.cl_kind with
 let decl_of_class c = match c.cl_kind with
 	| KAbstractImpl a -> TAbstractDecl a
 	| KAbstractImpl a -> TAbstractDecl a
 	| _ -> TClassDecl c
 	| _ -> TClassDecl c
-	
+
 module CompletionClassField = struct
 module CompletionClassField = struct
 	type t = {
 	type t = {
 		field : tclass_field;
 		field : tclass_field;

+ 6 - 0
src/core/type.ml

@@ -190,6 +190,7 @@ and tclass_field = {
 	mutable cf_expr_unoptimized : tfunc option;
 	mutable cf_expr_unoptimized : tfunc option;
 	mutable cf_overloads : tclass_field list;
 	mutable cf_overloads : tclass_field list;
 	mutable cf_extern : bool; (* this is only true if the field itself is extern, not its class *)
 	mutable cf_extern : bool; (* this is only true if the field itself is extern, not its class *)
+	mutable cf_final : bool;
 }
 }
 
 
 and tclass_kind =
 and tclass_kind =
@@ -227,6 +228,7 @@ and tclass = {
 	(* do not insert any fields above *)
 	(* do not insert any fields above *)
 	mutable cl_kind : tclass_kind;
 	mutable cl_kind : tclass_kind;
 	mutable cl_extern : bool;
 	mutable cl_extern : bool;
+	mutable cl_final : bool;
 	mutable cl_interface : bool;
 	mutable cl_interface : bool;
 	mutable cl_super : (tclass * tparams) option;
 	mutable cl_super : (tclass * tparams) option;
 	mutable cl_implements : (tclass * tparams) list;
 	mutable cl_implements : (tclass * tparams) list;
@@ -422,6 +424,7 @@ let mk_class m path pos name_pos =
 		cl_private = false;
 		cl_private = false;
 		cl_kind = KNormal;
 		cl_kind = KNormal;
 		cl_extern = false;
 		cl_extern = false;
+		cl_final = false;
 		cl_interface = false;
 		cl_interface = false;
 		cl_params = [];
 		cl_params = [];
 		cl_super = None;
 		cl_super = None;
@@ -477,6 +480,7 @@ let mk_field name t p name_pos = {
 	cf_params = [];
 	cf_params = [];
 	cf_overloads = [];
 	cf_overloads = [];
 	cf_extern = false;
 	cf_extern = false;
+	cf_final = false;
 }
 }
 
 
 let null_module = {
 let null_module = {
@@ -1422,6 +1426,7 @@ module Printer = struct
 			"cl_params",s_type_params c.cl_params;
 			"cl_params",s_type_params c.cl_params;
 			"cl_kind",s_class_kind c.cl_kind;
 			"cl_kind",s_class_kind c.cl_kind;
 			"cl_extern",string_of_bool c.cl_extern;
 			"cl_extern",string_of_bool c.cl_extern;
+			"cl_final",string_of_bool c.cl_final;
 			"cl_interface",string_of_bool c.cl_interface;
 			"cl_interface",string_of_bool c.cl_interface;
 			"cl_super",s_opt (fun (c,tl) -> s_type (TInst(c,tl))) c.cl_super;
 			"cl_super",s_opt (fun (c,tl) -> s_type (TInst(c,tl))) c.cl_super;
 			"cl_implements",s_list ", " (fun (c,tl) -> s_type (TInst(c,tl))) c.cl_implements;
 			"cl_implements",s_list ", " (fun (c,tl) -> s_type (TInst(c,tl))) c.cl_implements;
@@ -1555,6 +1560,7 @@ module Printer = struct
 		| HPrivate -> "HPrivate"
 		| HPrivate -> "HPrivate"
 		| HExtends tp -> "HExtends " ^ (s_type_path (fst tp))
 		| HExtends tp -> "HExtends " ^ (s_type_path (fst tp))
 		| HImplements tp -> "HImplements " ^ (s_type_path (fst tp))
 		| HImplements tp -> "HImplements " ^ (s_type_path (fst tp))
+		| HFinal -> "HFinal"
 
 
 	let s_placed f (x,p) =
 	let s_placed f (x,p) =
 		s_pair (f x) (s_pos p)
 		s_pair (f x) (s_pos p)

+ 2 - 5
src/generators/genas3.ml

@@ -967,9 +967,6 @@ and gen_value ctx e =
 		)) e.etype e.epos);
 		)) e.etype e.epos);
 		v()
 		v()
 
 
-let final m =
-	if Meta.has Meta.Final m then " final " else ""
-
 let generate_field ctx static f =
 let generate_field ctx static f =
 	newline ctx;
 	newline ctx;
 	ctx.in_static <- static;
 	ctx.in_static <- static;
@@ -1006,7 +1003,7 @@ let generate_field ctx static f =
 	let p = ctx.curclass.cl_pos in
 	let p = ctx.curclass.cl_pos in
 	match f.cf_expr, f.cf_kind with
 	match f.cf_expr, f.cf_kind with
 	| Some { eexpr = TFunction fd }, Method (MethNormal | MethInline) ->
 	| Some { eexpr = TFunction fd }, Method (MethNormal | MethInline) ->
-		print ctx "%s%s " rights (if static then "" else final f.cf_meta);
+		print ctx "%s%s " rights (if static || not f.cf_final then "" else " final ");
 		let rec loop c =
 		let rec loop c =
 			match c.cl_super with
 			match c.cl_super with
 			| None -> ()
 			| None -> ()
@@ -1099,7 +1096,7 @@ let generate_class ctx c =
 	define_getset ctx false c;
 	define_getset ctx false c;
 	ctx.local_types <- List.map snd c.cl_params;
 	ctx.local_types <- List.map snd c.cl_params;
 	let pack = open_block ctx in
 	let pack = open_block ctx in
-	print ctx "\tpublic %s%s%s %s " (final c.cl_meta) (match c.cl_dynamic with None -> "" | Some _ -> if c.cl_interface then "" else "dynamic ") (if c.cl_interface then "interface" else "class") (snd c.cl_path);
+	print ctx "\tpublic %s%s%s %s " (if c.cl_final then " final " else "") (match c.cl_dynamic with None -> "" | Some _ -> if c.cl_interface then "" else "dynamic ") (if c.cl_interface then "interface" else "class") (snd c.cl_path);
 	(match c.cl_super with
 	(match c.cl_super with
 	| None -> ()
 	| None -> ()
 	| Some (csup,_) -> print ctx "extends %s " (s_path ctx true csup.cl_path c.cl_pos));
 	| Some (csup,_) -> print ctx "extends %s " (s_path ctx true csup.cl_path c.cl_pos));

+ 10 - 10
src/generators/gencs.ml

@@ -630,7 +630,6 @@ let rec get_class_modifiers meta cl_type cl_access cl_modifiers =
 		| (Meta.Internal,[],_) :: meta -> get_class_modifiers meta cl_type "internal" cl_modifiers
 		| (Meta.Internal,[],_) :: meta -> get_class_modifiers meta cl_type "internal" cl_modifiers
 		(* no abstract for now | (":abstract",[],_) :: meta -> get_class_modifiers meta cl_type cl_access ("abstract" :: cl_modifiers)
 		(* no abstract for now | (":abstract",[],_) :: meta -> get_class_modifiers meta cl_type cl_access ("abstract" :: cl_modifiers)
 		| (":static",[],_) :: meta -> get_class_modifiers meta cl_type cl_access ("static" :: cl_modifiers) TODO: support those types *)
 		| (":static",[],_) :: meta -> get_class_modifiers meta cl_type cl_access ("static" :: cl_modifiers) TODO: support those types *)
-		| (Meta.Final,[],_) :: meta -> get_class_modifiers meta cl_type cl_access ("sealed" :: cl_modifiers)
 		| (Meta.Unsafe,[],_) :: meta -> get_class_modifiers meta cl_type cl_access ("unsafe" :: cl_modifiers)
 		| (Meta.Unsafe,[],_) :: meta -> get_class_modifiers meta cl_type cl_access ("unsafe" :: cl_modifiers)
 		| _ :: meta -> get_class_modifiers meta cl_type cl_access cl_modifiers
 		| _ :: meta -> get_class_modifiers meta cl_type cl_access cl_modifiers
 
 
@@ -1847,7 +1846,7 @@ let generate con =
 													acc
 													acc
 
 
 												(* non-sealed class *)
 												(* non-sealed class *)
-												| TInst ({ cl_interface = false; cl_meta = meta},_) when not (Meta.has Meta.Final meta) ->
+												| TInst ({ cl_interface = false; cl_final = false},_) ->
 													base_class_constraints := (t_s t) :: !base_class_constraints;
 													base_class_constraints := (t_s t) :: !base_class_constraints;
 													acc;
 													acc;
 
 
@@ -1907,10 +1906,10 @@ let generate con =
 			let fn_is_final = function
 			let fn_is_final = function
 				| None -> true
 				| None -> true
 				| Some ({ cf_kind = Method mkind } as m) ->
 				| Some ({ cf_kind = Method mkind } as m) ->
-					(match mkind with | MethInline -> true | _ -> false) || Meta.has Meta.Final m.cf_meta
+					(match mkind with | MethInline -> true | _ -> false) || m.cf_final
 				| _ -> assert false
 				| _ -> assert false
 			in
 			in
-			let is_virtual = not (is_interface || is_final || Meta.has Meta.Final prop.cf_meta || fn_is_final get || fn_is_final set) in
+			let is_virtual = not (is_interface || is_final || prop.cf_final || fn_is_final get || fn_is_final set) in
 
 
 			let fn_is_override = function
 			let fn_is_override = function
 				| Some cf -> List.memq cf cl.cl_overrides
 				| Some cf -> List.memq cf cl.cl_overrides
@@ -2045,7 +2044,7 @@ let generate con =
 					end (* TODO see how (get,set) variable handle when they are interfaces *)
 					end (* TODO see how (get,set) variable handle when they are interfaces *)
 				| Method _ when not (Type.is_physical_field cf) || (match cl.cl_kind, cf.cf_expr with | KAbstractImpl _, None -> true | _ -> false) ->
 				| Method _ when not (Type.is_physical_field cf) || (match cl.cl_kind, cf.cf_expr with | KAbstractImpl _, None -> true | _ -> false) ->
 					List.iter (fun cf -> if cl.cl_interface || cf.cf_expr <> None then
 					List.iter (fun cf -> if cl.cl_interface || cf.cf_expr <> None then
-						gen_class_field w ~is_overload:true is_static cl (Meta.has Meta.Final cf.cf_meta) cf
+						gen_class_field w ~is_overload:true is_static cl cf.cf_final cf
 					) cf.cf_overloads
 					) cf.cf_overloads
 				| Var _ | Method MethDynamic -> ()
 				| Var _ | Method MethDynamic -> ()
 				| Method _ when is_new && Meta.has Meta.Struct cl.cl_meta && fst (get_fun cf.cf_type) = [] ->
 				| Method _ when is_new && Meta.has Meta.Struct cl.cl_meta && fst (get_fun cf.cf_type) = [] ->
@@ -2065,15 +2064,15 @@ let generate con =
 							| _ -> ());
 							| _ -> ());
 						List.iter (fun cf ->
 						List.iter (fun cf ->
 							if cl.cl_interface || cf.cf_expr <> None then
 							if cl.cl_interface || cf.cf_expr <> None then
-								gen_class_field w ~is_overload:true is_static cl (Meta.has Meta.Final cf.cf_meta) cf
+								gen_class_field w ~is_overload:true is_static cl cf.cf_final cf
 						) cf.cf_overloads;
 						) cf.cf_overloads;
 				| Method mkind ->
 				| Method mkind ->
 					List.iter (fun cf ->
 					List.iter (fun cf ->
 						if cl.cl_interface || cf.cf_expr <> None then
 						if cl.cl_interface || cf.cf_expr <> None then
-							gen_class_field w ~is_overload:true is_static cl (Meta.has Meta.Final cf.cf_meta) cf
+							gen_class_field w ~is_overload:true is_static cl cf.cf_final cf
 					) cf.cf_overloads;
 					) cf.cf_overloads;
 					let is_virtual = not is_final && match mkind with | MethInline -> false | _ when not is_new -> true | _ -> false in
 					let is_virtual = not is_final && match mkind with | MethInline -> false | _ when not is_new -> true | _ -> false in
-					let is_virtual = if not is_virtual || Meta.has Meta.Final cf.cf_meta then false else is_virtual in
+					let is_virtual = if not is_virtual || cf.cf_final then false else is_virtual in
 					let is_override = List.memq cf cl.cl_overrides in
 					let is_override = List.memq cf cl.cl_overrides in
 					let is_override = is_override || match cf.cf_name, follow cf.cf_type with
 					let is_override = is_override || match cf.cf_name, follow cf.cf_type with
 						| "Equals", TFun([_,_,targ], tret) ->
 						| "Equals", TFun([_,_,targ], tret) ->
@@ -2085,7 +2084,7 @@ let generate con =
 					in
 					in
 					let is_override = if Meta.has (Meta.Custom "?prop_impl") cf.cf_meta then false else is_override in
 					let is_override = if Meta.has (Meta.Custom "?prop_impl") cf.cf_meta then false else is_override in
 
 
-					let is_virtual = is_virtual && not (Meta.has Meta.Final cl.cl_meta) && not (is_interface) in
+					let is_virtual = is_virtual && not cl.cl_final && not (is_interface) in
 					let visibility = if is_interface then "" else "public" in
 					let visibility = if is_interface then "" else "public" in
 
 
 					let visibility, modifiers = get_fun_modifiers cf.cf_meta visibility [] in
 					let visibility, modifiers = get_fun_modifiers cf.cf_meta visibility [] in
@@ -2410,7 +2409,8 @@ let generate con =
 			in
 			in
 
 
 			let clt, access, modifiers = get_class_modifiers cl.cl_meta (if cl.cl_interface then "interface" else "class") "public" [] in
 			let clt, access, modifiers = get_class_modifiers cl.cl_meta (if cl.cl_interface then "interface" else "class") "public" [] in
-			let is_final = clt = "struct" || Meta.has Meta.Final cl.cl_meta in
+			let modifiers = if cl.cl_final then "sealed" :: modifiers else modifiers in
+			let is_final = clt = "struct" || cl.cl_final in
 
 
 			let modifiers = [access] @ modifiers in
 			let modifiers = [access] @ modifiers in
 			print w "%s %s %s" (String.concat " " modifiers) clt (change_clname (snd cl.cl_path));
 			print w "%s %s %s" (String.concat " " modifiers) clt (change_clname (snd cl.cl_path));

+ 4 - 4
src/generators/genjava.ml

@@ -940,7 +940,6 @@ let rec get_class_modifiers meta cl_type cl_access cl_modifiers =
 		| (Meta.Internal,[],_) :: meta -> get_class_modifiers meta cl_type "" cl_modifiers
 		| (Meta.Internal,[],_) :: meta -> get_class_modifiers meta cl_type "" cl_modifiers
 		(* no abstract for now | (":abstract",[],_) :: meta -> get_class_modifiers meta cl_type cl_access ("abstract" :: cl_modifiers)
 		(* no abstract for now | (":abstract",[],_) :: meta -> get_class_modifiers meta cl_type cl_access ("abstract" :: cl_modifiers)
 		| (Meta.Static,[],_) :: meta -> get_class_modifiers meta cl_type cl_access ("static" :: cl_modifiers) TODO: support those types *)
 		| (Meta.Static,[],_) :: meta -> get_class_modifiers meta cl_type cl_access ("static" :: cl_modifiers) TODO: support those types *)
-		| (Meta.Final,[],_) :: meta -> get_class_modifiers meta cl_type cl_access ("final" :: cl_modifiers)
 		| _ :: meta -> get_class_modifiers meta cl_type cl_access cl_modifiers
 		| _ :: meta -> get_class_modifiers meta cl_type cl_access cl_modifiers
 
 
 let rec get_fun_modifiers meta access modifiers =
 let rec get_fun_modifiers meta access modifiers =
@@ -1930,13 +1929,13 @@ let generate con =
 				end (* TODO see how (get,set) variable handle when they are interfaces *)
 				end (* TODO see how (get,set) variable handle when they are interfaces *)
 			| Method _ when not (Type.is_physical_field cf) || (match cl.cl_kind, cf.cf_expr with | KAbstractImpl _, None -> true | _ -> false) ->
 			| Method _ when not (Type.is_physical_field cf) || (match cl.cl_kind, cf.cf_expr with | KAbstractImpl _, None -> true | _ -> false) ->
 				List.iter (fun cf -> if cl.cl_interface || cf.cf_expr <> None then
 				List.iter (fun cf -> if cl.cl_interface || cf.cf_expr <> None then
-					gen_class_field w ~is_overload:true is_static cl (Meta.has Meta.Final cf.cf_meta) cf
+					gen_class_field w ~is_overload:true is_static cl cf.cf_final cf
 				) cf.cf_overloads
 				) cf.cf_overloads
 			| Var _ | Method MethDynamic -> ()
 			| Var _ | Method MethDynamic -> ()
 			| Method mkind ->
 			| Method mkind ->
 				List.iter (fun cf ->
 				List.iter (fun cf ->
 					if cl.cl_interface || cf.cf_expr <> None then
 					if cl.cl_interface || cf.cf_expr <> None then
-						gen_class_field w ~is_overload:true is_static cl (Meta.has Meta.Final cf.cf_meta) cf
+						gen_class_field w ~is_overload:true is_static cl cf.cf_final cf
 				) cf.cf_overloads;
 				) cf.cf_overloads;
 				let is_virtual = is_new || (not is_final && match mkind with | MethInline -> false | _ when not is_new -> true | _ -> false) in
 				let is_virtual = is_new || (not is_final && match mkind with | MethInline -> false | _ when not is_new -> true | _ -> false) in
 				let is_override = match cf.cf_name with
 				let is_override = match cf.cf_name with
@@ -2094,7 +2093,8 @@ let generate con =
 		gen_annotations w cl.cl_meta;
 		gen_annotations w cl.cl_meta;
 
 
 		let clt, access, modifiers = get_class_modifiers cl.cl_meta (if cl.cl_interface then "interface" else "class") "public" [] in
 		let clt, access, modifiers = get_class_modifiers cl.cl_meta (if cl.cl_interface then "interface" else "class") "public" [] in
-		let is_final = Meta.has Meta.Final cl.cl_meta in
+		let modifiers = if cl.cl_final then "final" :: modifiers else modifiers in
+		let is_final = cl.cl_final in
 
 
 		write_parts w (access :: modifiers @ [clt; (change_clname (snd cl.cl_path))]);
 		write_parts w (access :: modifiers @ [clt; (change_clname (snd cl.cl_path))]);
 
 

+ 2 - 2
src/generators/genphp7.ml

@@ -3219,7 +3219,7 @@ class class_builder ctx (cls:tclass) =
 			Indicates if type should be declared as `final`
 			Indicates if type should be declared as `final`
 		*)
 		*)
 		method is_final =
 		method is_final =
-			if not (Meta.has Meta.Final cls.cl_meta) then
+			if not cls.cl_final then
 				false
 				false
 			else begin
 			else begin
 				let hacked = ref false in
 				let hacked = ref false in
@@ -3238,7 +3238,7 @@ class class_builder ctx (cls:tclass) =
 			Indicates if `field` should be declared as `final`
 			Indicates if `field` should be declared as `final`
 		*)
 		*)
 		method is_final_field (field:tclass_field) : bool =
 		method is_final_field (field:tclass_field) : bool =
-			Meta.has Meta.Final field.cf_meta
+			field.cf_final
 		(**
 		(**
 			Check if there is no native php constructor in inheritance chain of this class.
 			Check if there is no native php constructor in inheritance chain of this class.
 			E.g. `StsClass` does have a constructor while still can be called with `new StdClass()`.
 			E.g. `StsClass` does have a constructor while still can be called with `new StdClass()`.

+ 2 - 2
src/generators/genswf9.ml

@@ -1991,7 +1991,7 @@ let generate_field_kind ctx f c stat =
 			let m = generate_method ctx fdata stat f.cf_meta in
 			let m = generate_method ctx fdata stat f.cf_meta in
 			Some (HFMethod {
 			Some (HFMethod {
 				hlm_type = m;
 				hlm_type = m;
-				hlm_final = stat || (Meta.has Meta.Final f.cf_meta);
+				hlm_final = stat || f.cf_final;
 				hlm_override = not stat && (loop c name || loop c f.cf_name);
 				hlm_override = not stat && (loop c name || loop c f.cf_name);
 				hlm_kind = kind;
 				hlm_kind = kind;
 			})
 			})
@@ -2182,7 +2182,7 @@ let generate_class ctx c =
 		hlc_name = name;
 		hlc_name = name;
 		hlc_super = (if c.cl_interface then None else Some (type_path ctx (match c.cl_super with None -> [],"Object" | Some (c,_) -> c.cl_path)));
 		hlc_super = (if c.cl_interface then None else Some (type_path ctx (match c.cl_super with None -> [],"Object" | Some (c,_) -> c.cl_path)));
 		hlc_sealed = not (is_dynamic c);
 		hlc_sealed = not (is_dynamic c);
-		hlc_final = Meta.has Meta.Final c.cl_meta;
+		hlc_final = c.cl_final;
 		hlc_interface = c.cl_interface;
 		hlc_interface = c.cl_interface;
 		hlc_namespace = (match !has_protected with None -> None | Some p -> Some (HNProtected p));
 		hlc_namespace = (match !has_protected with None -> None | Some p -> Some (HNProtected p));
 		hlc_implements = Array.of_list (List.map (fun (c,_) ->
 		hlc_implements = Array.of_list (List.map (fun (c,_) ->

+ 6 - 1
src/macro/macroApi.ml

@@ -982,6 +982,7 @@ and encode_cfield f =
 		"doc", null encode_string f.cf_doc;
 		"doc", null encode_string f.cf_doc;
 		"overloads", encode_ref f.cf_overloads (encode_and_map_array encode_cfield) (fun() -> "overloads");
 		"overloads", encode_ref f.cf_overloads (encode_and_map_array encode_cfield) (fun() -> "overloads");
 		"isExtern", vbool f.cf_extern;
 		"isExtern", vbool f.cf_extern;
+		"isFinal", vbool f.cf_final;
 	]
 	]
 
 
 and encode_field_kind k =
 and encode_field_kind k =
@@ -1034,6 +1035,7 @@ and encode_tclass c =
 		"isExtern", vbool c.cl_extern;
 		"isExtern", vbool c.cl_extern;
 		"exclude", vfun0 (fun() -> c.cl_extern <- true; c.cl_init <- None; vnull);
 		"exclude", vfun0 (fun() -> c.cl_extern <- true; c.cl_init <- None; vnull);
 		"isInterface", vbool c.cl_interface;
 		"isInterface", vbool c.cl_interface;
+		"isFinal", vbool c.cl_final;
 		"superClass", (match c.cl_super with
 		"superClass", (match c.cl_super with
 			| None -> vnull
 			| None -> vnull
 			| Some (c,pl) -> encode_obj OClassType_superClass ["t",encode_clref c;"params",encode_tparams pl]
 			| Some (c,pl) -> encode_obj OClassType_superClass ["t",encode_clref c;"params",encode_tparams pl]
@@ -1356,6 +1358,7 @@ let decode_cfield v =
 		cf_expr_unoptimized = None;
 		cf_expr_unoptimized = None;
 		cf_overloads = decode_ref (field v "overloads");
 		cf_overloads = decode_ref (field v "overloads");
 		cf_extern = decode_bool (field v "isExtern");
 		cf_extern = decode_bool (field v "isExtern");
+		cf_final = decode_bool (field v "isFinal");
 	}
 	}
 
 
 let decode_efield v =
 let decode_efield v =
@@ -1487,9 +1490,10 @@ let decode_type_def v =
 		EEnum (mk (if isExtern then [EExtern] else []) (List.map conv fields))
 		EEnum (mk (if isExtern then [EExtern] else []) (List.map conv fields))
 	| 1, [] ->
 	| 1, [] ->
 		ETypedef (mk (if isExtern then [EExtern] else []) (CTAnonymous fields,Globals.null_pos))
 		ETypedef (mk (if isExtern then [EExtern] else []) (CTAnonymous fields,Globals.null_pos))
-	| 2, [ext;impl;interf] ->
+	| 2, [ext;impl;interf;final] ->
 		let flags = if isExtern then [HExtern] else [] in
 		let flags = if isExtern then [HExtern] else [] in
 		let is_interface = decode_opt_bool interf in
 		let is_interface = decode_opt_bool interf in
+		let is_final = decode_opt_bool final in
 		let interfaces = (match opt (fun v -> List.map decode_path (decode_array v)) impl with Some l -> l | _ -> [] ) in
 		let interfaces = (match opt (fun v -> List.map decode_path (decode_array v)) impl with Some l -> l | _ -> [] ) in
 		let flags = (match opt decode_path ext with None -> flags | Some t -> HExtends t :: flags) in
 		let flags = (match opt decode_path ext with None -> flags | Some t -> HExtends t :: flags) in
 		let flags = if is_interface then begin
 		let flags = if is_interface then begin
@@ -1499,6 +1503,7 @@ let decode_type_def v =
 				List.map (fun t -> HImplements t) interfaces @ flags
 				List.map (fun t -> HImplements t) interfaces @ flags
 			end
 			end
 		in
 		in
+		let flags = if is_final then HFinal :: flags else flags in
 		EClass (mk flags fields)
 		EClass (mk flags fields)
 	| 3, [t] ->
 	| 3, [t] ->
 		ETypedef (mk (if isExtern then [EExtern] else []) (decode_ctype t))
 		ETypedef (mk (if isExtern then [EExtern] else []) (decode_ctype t))

+ 3 - 2
src/syntax/grammar.mly

@@ -389,8 +389,9 @@ and parse_class_field_resume tdecl s =
 		if resume tdecl true s then parse_class_field_resume tdecl s else []
 		if resume tdecl true s then parse_class_field_resume tdecl s else []
 
 
 and parse_common_flags = parser
 and parse_common_flags = parser
-	| [< '(Kwd Private,_); l = parse_common_flags >] -> DPrivate :: l
-	| [< '(Kwd Extern,_); l = parse_common_flags >] -> DExtern :: l
+	| [< '(Kwd Private,p); l = parse_common_flags >] -> (DPrivate,p) :: l
+	| [< '(Kwd Extern,p); l = parse_common_flags >] -> (DExtern,p) :: l
+	| [< '(Kwd Final,p); l = parse_common_flags >] -> (DFinal,p) :: l
 	| [< >] -> []
 	| [< >] -> []
 
 
 and parse_meta_argument_expr s =
 and parse_meta_argument_expr s =

+ 7 - 3
src/syntax/parser.ml

@@ -62,18 +62,22 @@ let special_identifier_files : (string,string) Hashtbl.t = Hashtbl.create 0
 type decl_flag =
 type decl_flag =
 	| DPrivate
 	| DPrivate
 	| DExtern
 	| DExtern
+	| DFinal
 
 
-let decl_flag_to_class_flag = function
+let decl_flag_to_class_flag (flag,p) = match flag with
 	| DPrivate -> HPrivate
 	| DPrivate -> HPrivate
 	| DExtern -> HExtern
 	| DExtern -> HExtern
+	| DFinal -> HFinal
 
 
-let decl_flag_to_enum_flag = function
+let decl_flag_to_enum_flag (flag,p) = match flag with
 	| DPrivate -> EPrivate
 	| DPrivate -> EPrivate
 	| DExtern -> EExtern
 	| DExtern -> EExtern
+	| DFinal -> error (Custom "final on enums is not allowed") p
 
 
-let decl_flag_to_abstract_flag = function
+let decl_flag_to_abstract_flag (flag,p) = match flag with
 	| DPrivate -> AbPrivate
 	| DPrivate -> AbPrivate
 	| DExtern -> AbExtern
 	| DExtern -> AbExtern
+	| DFinal -> error (Custom "final on abstracts is not allowed") p
 
 
 module TokenCache = struct
 module TokenCache = struct
 	let cache = ref (DynArray.create ())
 	let cache = ref (DynArray.create ())

+ 3 - 2
src/syntax/reification.ml

@@ -370,7 +370,7 @@ let reify in_macro =
 	and to_type_def (t,p) =
 	and to_type_def (t,p) =
 		match t with
 		match t with
 		| EClass d ->
 		| EClass d ->
-			let ext = ref None and impl = ref [] and interf = ref false in
+			let ext = ref None and impl = ref [] and interf = ref false and final = ref false in
 			List.iter (function
 			List.iter (function
 				| HExtern | HPrivate -> ()
 				| HExtern | HPrivate -> ()
 				| HInterface -> interf := true;
 				| HInterface -> interf := true;
@@ -381,6 +381,7 @@ let reify in_macro =
 						!ext
 						!ext
 						end)
 						end)
 				| HImplements i-> impl := (to_tpath i p) :: !impl
 				| HImplements i-> impl := (to_tpath i p) :: !impl
+				| HFinal -> final := true
 			) d.d_flags;
 			) d.d_flags;
 			to_obj [
 			to_obj [
 				"pack", (EArrayDecl [],p);
 				"pack", (EArrayDecl [],p);
@@ -389,7 +390,7 @@ let reify in_macro =
 				"meta", to_meta d.d_meta p;
 				"meta", to_meta d.d_meta p;
 				"params", (EArrayDecl (List.map (to_tparam_decl p) d.d_params),p);
 				"params", (EArrayDecl (List.map (to_tparam_decl p) d.d_params),p);
 				"isExtern", to_bool (List.mem HExtern d.d_flags) p;
 				"isExtern", to_bool (List.mem HExtern d.d_flags) p;
-				"kind", mk_enum "TypeDefKind" "TDClass" [(match !ext with None -> (EConst (Ident "null"),p) | Some t -> t);(EArrayDecl (List.rev !impl),p);to_bool !interf p] p;
+				"kind", mk_enum "TypeDefKind" "TDClass" [(match !ext with None -> (EConst (Ident "null"),p) | Some t -> t);(EArrayDecl (List.rev !impl),p);to_bool !interf p;to_bool !final p] p;
 				"fields", (EArrayDecl (List.map (fun f -> to_cfield f p) d.d_data),p)
 				"fields", (EArrayDecl (List.map (fun f -> to_cfield f p) d.d_data),p)
 			] p
 			] p
 		| _ -> assert false
 		| _ -> assert false

+ 1 - 0
src/typing/typeload.ml

@@ -493,6 +493,7 @@ and load_complex_type' ctx allow_display (t,p) =
 				cf_params = !params;
 				cf_params = !params;
 				cf_doc = f.cff_doc;
 				cf_doc = f.cff_doc;
 				cf_meta = f.cff_meta;
 				cf_meta = f.cff_meta;
+				cf_final = !final;
 			} in
 			} in
 			init_meta_overloads ctx None cf;
 			init_meta_overloads ctx None cf;
 			if ctx.is_display_file then begin
 			if ctx.is_display_file then begin

+ 6 - 5
src/typing/typeloadCheck.ml

@@ -154,7 +154,7 @@ let check_overriding ctx c f =
 				() (* allow to redefine a method as inlined *)
 				() (* allow to redefine a method as inlined *)
 			| _ ->
 			| _ ->
 				display_error ctx ("Field " ^ i ^ " has different property access than in superclass") p);
 				display_error ctx ("Field " ^ i ^ " has different property access than in superclass") p);
-			if has_meta Meta.Final f2.cf_meta then display_error ctx ("Cannot override final method " ^ i) p;
+			if f2.cf_final then display_error ctx ("Cannot override final method " ^ i) p;
 			try
 			try
 				let t = apply_params csup.cl_params params t in
 				let t = apply_params csup.cl_params params t in
 				valid_redefinition ctx f f.cf_type f2 t
 				valid_redefinition ctx f f.cf_type f2 t
@@ -365,10 +365,11 @@ module Inheritance = struct
 		let process_meta csup =
 		let process_meta csup =
 			List.iter (fun m ->
 			List.iter (fun m ->
 				match m with
 				match m with
-				| Meta.Final, _, _ -> if not (Meta.has Meta.Hack c.cl_meta || (match c.cl_kind with KTypeParameter _ -> true | _ -> false)) then error ("Cannot extend a final " ^ if c.cl_interface then "interface" else "class") p;
 				| Meta.AutoBuild, el, p -> c.cl_meta <- (Meta.Build,el,{ c.cl_pos with pmax = c.cl_pos.pmin }(* prevent display metadata *)) :: m :: c.cl_meta
 				| Meta.AutoBuild, el, p -> c.cl_meta <- (Meta.Build,el,{ c.cl_pos with pmax = c.cl_pos.pmin }(* prevent display metadata *)) :: m :: c.cl_meta
 				| _ -> ()
 				| _ -> ()
-			) csup.cl_meta
+			) csup.cl_meta;
+			if csup.cl_final && not (Meta.has Meta.Hack c.cl_meta || (match c.cl_kind with KTypeParameter _ -> true | _ -> false)) then
+				error ("Cannot extend a final " ^ if c.cl_interface then "interface" else "class") p;
 		in
 		in
 		let check_cancel_build csup =
 		let check_cancel_build csup =
 			match csup.cl_build() with
 			match csup.cl_build() with
@@ -464,7 +465,7 @@ module Inheritance = struct
 						| ITType({kind = Interface} as cm,_) -> (not is_extends || c.cl_interface) && CompletionModuleType.get_path cm <> c.cl_path
 						| ITType({kind = Interface} as cm,_) -> (not is_extends || c.cl_interface) && CompletionModuleType.get_path cm <> c.cl_path
 						| ITType({kind = Class} as cm,_) ->
 						| ITType({kind = Class} as cm,_) ->
 							is_extends && not c.cl_interface && CompletionModuleType.get_path cm <> c.cl_path &&
 							is_extends && not c.cl_interface && CompletionModuleType.get_path cm <> c.cl_path &&
-							(not (Meta.has Meta.Final cm.meta) || Meta.has Meta.Hack c.cl_meta) &&
+							(not cm.is_final || Meta.has Meta.Hack c.cl_meta) &&
 							(not (is_basic_class_path (cm.pack,cm.name)) || (c.cl_extern && cm.is_extern))
 							(not (is_basic_class_path (cm.pack,cm.name)) || (c.cl_extern && cm.is_extern))
 						| _ -> false
 						| _ -> false
 					) l in
 					) l in
@@ -481,7 +482,7 @@ end
 let check_final_vars ctx e =
 let check_final_vars ctx e =
 	let final_vars = Hashtbl.create 0 in
 	let final_vars = Hashtbl.create 0 in
 	List.iter (fun cf -> match cf.cf_kind with
 	List.iter (fun cf -> match cf.cf_kind with
-		| Var _ when Meta.has Meta.Final cf.cf_meta && cf.cf_expr = None ->
+		| Var _ when cf.cf_final && cf.cf_expr = None ->
 			Hashtbl.add final_vars cf.cf_name cf
 			Hashtbl.add final_vars cf.cf_name cf
 		| _ ->
 		| _ ->
 			()
 			()

+ 25 - 16
src/typing/typeloadFields.ml

@@ -429,7 +429,7 @@ let create_class_context ctx c context_init p =
 		is_lib = is_lib;
 		is_lib = is_lib;
 		is_native = is_native;
 		is_native = is_native;
 		is_core_api = Meta.has Meta.CoreApi c.cl_meta;
 		is_core_api = Meta.has Meta.CoreApi c.cl_meta;
-		is_class_debug = false;
+		is_class_debug = Meta.has (Meta.Custom ":debug.typeload") c.cl_meta;
 		extends_public = extends_public c;
 		extends_public = extends_public c;
 		abstract = abstract;
 		abstract = abstract;
 		context_init = context_init;
 		context_init = context_init;
@@ -447,16 +447,23 @@ let create_field_context (ctx,cctx) c cff =
 	} in
 	} in
 	let display_modifier = Typeload.check_field_access ctx cff in
 	let display_modifier = Typeload.check_field_access ctx cff in
 	let is_static = List.mem_assoc AStatic cff.cff_access in
 	let is_static = List.mem_assoc AStatic cff.cff_access in
-	let is_extern = List.mem_assoc AExtern cff.cff_access in
-	let is_extern = if Meta.has Meta.Extern cff.cff_meta then begin
-		(* if not (Define.is_haxe3_compat ctx.com.defines) then
-			ctx.com.warning "`@:extern` on fields is deprecated in favor of `extern`" (pos cff.cff_name); *)
-		true
-	end else
-		is_extern
-	in
+	let is_extern = ref (List.mem_assoc AExtern cff.cff_access) in
+	let is_final = ref (List.mem_assoc AFinal cff.cff_access) in
+	List.iter (fun (m,_,p) ->
+		match m with
+		| Meta.Final ->
+			is_final := true;
+			(* if p <> null_pos && not (Define.is_haxe3_compat ctx.com.defines) then
+				ctx.com.warning "`@:final` is deprecated in favor of `final`" p; *)
+		| Meta.Extern ->
+			(* if not (Define.is_haxe3_compat ctx.com.defines) then
+				ctx.com.warning "`@:extern` on fields is deprecated in favor of `extern`" (pos cff.cff_name); *)
+			is_extern := true;
+		| _ ->
+			()
+	) cff.cff_meta;
 	let allow_inline = cctx.abstract <> None || match cff.cff_kind with
 	let allow_inline = cctx.abstract <> None || match cff.cff_kind with
-		| FFun _ -> ctx.g.doinline || is_extern || c.cl_extern
+		| FFun _ -> ctx.g.doinline || !is_extern || c.cl_extern
 		| _ -> true
 		| _ -> true
 	in
 	in
 	let is_inline = allow_inline && List.mem_assoc AInline cff.cff_access in
 	let is_inline = allow_inline && List.mem_assoc AInline cff.cff_access in
@@ -472,10 +479,10 @@ let create_field_context (ctx,cctx) c cff =
 		is_static = is_static;
 		is_static = is_static;
 		override = override;
 		override = override;
 		is_macro = is_macro;
 		is_macro = is_macro;
-		is_extern = is_extern;
-		is_final = List.mem_assoc AFinal cff.cff_access;
+		is_extern = !is_extern;
+		is_final = !is_final;
 		is_display_field = ctx.is_display_file && DisplayPosition.encloses_display_position cff.cff_pos;
 		is_display_field = ctx.is_display_file && DisplayPosition.encloses_display_position cff.cff_pos;
-		is_field_debug = cctx.is_class_debug;
+		is_field_debug = cctx.is_class_debug || Meta.has (Meta.Custom ":debug.typeload") cff.cff_meta;
 		display_modifier = display_modifier;
 		display_modifier = display_modifier;
 		is_abstract_member = cctx.abstract <> None && Meta.has Meta.Impl cff.cff_meta;
 		is_abstract_member = cctx.abstract <> None && Meta.has Meta.Impl cff.cff_meta;
 		field_kind = field_kind;
 		field_kind = field_kind;
@@ -758,7 +765,7 @@ let create_variable (ctx,cctx,fctx) c f t eo p =
 	if not fctx.is_static && cctx.abstract <> None then error (fst f.cff_name ^ ": Cannot declare member variable in abstract") p;
 	if not fctx.is_static && cctx.abstract <> None then error (fst f.cff_name ^ ": Cannot declare member variable in abstract") p;
 	if fctx.is_inline && not fctx.is_static then error (fst f.cff_name ^ ": Inline variable must be static") p;
 	if fctx.is_inline && not fctx.is_static then error (fst f.cff_name ^ ": Inline variable must be static") p;
 	if fctx.is_inline && eo = None then error (fst f.cff_name ^ ": Inline variable must be initialized") p;
 	if fctx.is_inline && eo = None then error (fst f.cff_name ^ ": Inline variable must be initialized") p;
-	if fctx.is_final && eo = None then begin
+	if fctx.is_final && not (fctx.is_extern || c.cl_extern || c.cl_interface)  && eo = None then begin
 		if fctx.is_static then error (fst f.cff_name ^ ": Static final variable must be initialized") p
 		if fctx.is_static then error (fst f.cff_name ^ ": Static final variable must be initialized") p
 		else cctx.uninitialized_final <- Some f.cff_pos;
 		else cctx.uninitialized_final <- Some f.cff_pos;
 	end;
 	end;
@@ -780,10 +787,11 @@ let create_variable (ctx,cctx,fctx) c f t eo p =
 	let cf = {
 	let cf = {
 		(mk_field (fst f.cff_name) t f.cff_pos (pos f.cff_name)) with
 		(mk_field (fst f.cff_name) t f.cff_pos (pos f.cff_name)) with
 		cf_doc = f.cff_doc;
 		cf_doc = f.cff_doc;
-		cf_meta = (if fctx.is_final && not (Meta.has Meta.Final f.cff_meta) then (Meta.Final,[],null_pos) :: f.cff_meta else f.cff_meta);
+		cf_meta = f.cff_meta;
 		cf_kind = Var kind;
 		cf_kind = Var kind;
 		cf_public = is_public (ctx,cctx) f.cff_access None;
 		cf_public = is_public (ctx,cctx) f.cff_access None;
 		cf_extern = fctx.is_extern;
 		cf_extern = fctx.is_extern;
+		cf_final = fctx.is_final;
 	} in
 	} in
 	ctx.curfield <- cf;
 	ctx.curfield <- cf;
 	bind_var (ctx,cctx,fctx) cf eo;
 	bind_var (ctx,cctx,fctx) cf eo;
@@ -998,11 +1006,12 @@ let create_method (ctx,cctx,fctx) c f fd p =
 	let cf = {
 	let cf = {
 		(mk_field (fst f.cff_name) t f.cff_pos (pos f.cff_name)) with
 		(mk_field (fst f.cff_name) t f.cff_pos (pos f.cff_name)) with
 		cf_doc = f.cff_doc;
 		cf_doc = f.cff_doc;
-		cf_meta = (if fctx.is_final && not (Meta.has Meta.Final f.cff_meta) then (Meta.Final,[],null_pos) :: f.cff_meta else f.cff_meta);
+		cf_meta = f.cff_meta;
 		cf_kind = Method (if fctx.is_macro then MethMacro else if fctx.is_inline then MethInline else if dynamic then MethDynamic else MethNormal);
 		cf_kind = Method (if fctx.is_macro then MethMacro else if fctx.is_inline then MethInline else if dynamic then MethDynamic else MethNormal);
 		cf_public = is_public (ctx,cctx) f.cff_access parent;
 		cf_public = is_public (ctx,cctx) f.cff_access parent;
 		cf_params = params;
 		cf_params = params;
 		cf_extern = fctx.is_extern;
 		cf_extern = fctx.is_extern;
+		cf_final = fctx.is_final;
 	} in
 	} in
 	cf.cf_meta <- List.map (fun (m,el,p) -> match m,el with
 	cf.cf_meta <- List.map (fun (m,el,p) -> match m,el with
 		| Meta.AstSource,[] -> (m,(match fd.f_expr with None -> [] | Some e -> [e]),p)
 		| Meta.AstSource,[] -> (m,(match fd.f_expr with None -> [] | Some e -> [e]),p)

+ 14 - 3
src/typing/typeloadModule.ml

@@ -317,7 +317,7 @@ let module_pass_1 ctx m tdecls loadp =
 					) a.a_meta;
 					) a.a_meta;
 					a.a_impl <- Some c;
 					a.a_impl <- Some c;
 					c.cl_kind <- KAbstractImpl a;
 					c.cl_kind <- KAbstractImpl a;
-					c.cl_meta <- (Meta.Final,[],null_pos) :: c.cl_meta
+					c.cl_final <- true;
 				| _ -> assert false);
 				| _ -> assert false);
 				acc
 				acc
 		) in
 		) in
@@ -511,8 +511,19 @@ let init_module_type ctx context_init do_init (decl,p) =
 			DisplayEmitter.display_module_type ctx (match c.cl_kind with KAbstractImpl a -> TAbstractDecl a | _ -> TClassDecl c) (pos d.d_name);
 			DisplayEmitter.display_module_type ctx (match c.cl_kind with KAbstractImpl a -> TAbstractDecl a | _ -> TClassDecl c) (pos d.d_name);
 		TypeloadCheck.check_global_metadata ctx c.cl_meta (fun m -> c.cl_meta <- m :: c.cl_meta) c.cl_module.m_path c.cl_path None;
 		TypeloadCheck.check_global_metadata ctx c.cl_meta (fun m -> c.cl_meta <- m :: c.cl_meta) c.cl_module.m_path c.cl_path None;
 		let herits = d.d_flags in
 		let herits = d.d_flags in
-		c.cl_extern <- List.mem HExtern herits;
-		c.cl_interface <- List.mem HInterface herits;
+		List.iter (function
+			| HExtern -> c.cl_extern <- true
+			| HInterface -> c.cl_interface <- true
+			| HFinal -> c.cl_final <- true
+			| _ -> ()
+		) herits;
+		List.iter (fun (m,_,p) ->
+			if m = Meta.Final then begin
+				c.cl_final <- true;
+				(* if p <> null_pos && not (Define.is_haxe3_compat ctx.com.defines) then
+					ctx.com.warning "`@:final class` is deprecated in favor of `final class`" p; *)
+			end
+		) d.d_meta;
 		let prev_build_count = ref (!build_count - 1) in
 		let prev_build_count = ref (!build_count - 1) in
 		let build() =
 		let build() =
 			let fl = TypeloadCheck.Inheritance.set_heritance ctx c herits p in
 			let fl = TypeloadCheck.Inheritance.set_heritance ctx c herits p in

+ 1 - 1
std/haxe/macro/Expr.hx

@@ -926,7 +926,7 @@ enum TypeDefKind {
 	/**
 	/**
 		Represents a class kind.
 		Represents a class kind.
 	**/
 	**/
-	TDClass( ?superClass : TypePath, ?interfaces : Array<TypePath>, ?isInterface : Bool );
+	TDClass( ?superClass : TypePath, ?interfaces : Array<TypePath>, ?isInterface : Bool, ?isFinal : Bool );
 
 
 	/**
 	/**
 		Represents an alias/typedef kind.
 		Represents an alias/typedef kind.

+ 15 - 0
std/haxe/macro/Type.hx

@@ -200,6 +200,16 @@ typedef ClassField = {
 	**/
 	**/
 	var isPublic : Bool;
 	var isPublic : Bool;
 
 
+	/**
+		Whether or not the class field is extern.
+	**/
+	var isExtern : Bool;
+
+	/**
+		Whether or not the class field is final.
+	**/
+	var isFinal : Bool;
+
 	/**
 	/**
 		The type parameters of the class field.
 		The type parameters of the class field.
 	**/
 	**/
@@ -404,6 +414,11 @@ typedef ClassType = BaseType & {
 	**/
 	**/
 	var isInterface : Bool;
 	var isInterface : Bool;
 
 
+	/**
+		If true the class is final and cannot be extended.
+	**/
+	var isFinal : Bool;
+
 	/**
 	/**
 		The parent class and its type parameters, if available.
 		The parent class and its type parameters, if available.
 	**/
 	**/