Browse Source

add CfOverload

Simon Krajewski 5 năm trước cách đây
mục cha
commit
9bbad040eb

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

@@ -758,7 +758,7 @@ let handle_type_parameter gen e e1 ef ~clean_ef ~overloads_cast_to_base f elist
 
 			let ecall = get e in
 			let ef = ref ef in
-			let is_overload = cf.cf_overloads <> [] || Meta.has Meta.Overload cf.cf_meta || (is_static && is_static_overload cl (field_name f)) in
+			let is_overload = cf.cf_overloads <> [] || has_class_field_flag cf CfOverload || (is_static && is_static_overload cl (field_name f)) in
 			let cf, actual_t, error = match is_overload with
 				| false ->
 						(* since actual_t from FClassField already applies greal_type, we're using the get_overloads helper to get this info *)

+ 6 - 6
src/codegen/gencommon/fixOverrides.ml

@@ -51,7 +51,7 @@ let run ~explicit_fn_name ~get_vmtype gen =
 			(* overrides can be removed from interfaces *)
 			c.cl_ordered_fields <- List.filter (fun f ->
 				try
-					if Meta.has Meta.Overload f.cf_meta then raise Not_found;
+					if has_class_field_flag f CfOverload then raise Not_found;
 					let f2 = Codegen.find_field gen.gcon c f in
 					if f2 == f then raise Not_found;
 					c.cl_fields <- PMap.remove f.cf_name c.cl_fields;
@@ -75,7 +75,7 @@ let run ~explicit_fn_name ~get_vmtype gen =
 					try
 						let t2, f2 =
 							match overloads with
-							| (_, cf) :: _ when Meta.has Meta.Overload cf.cf_meta -> (* overloaded function *)
+							| (_, cf) :: _ when has_class_field_flag cf CfOverload -> (* overloaded function *)
 								(* try to find exact function *)
 								List.find (fun (t,f2) ->
 									Overloads.same_overload_args ~get_vmtype ftype t f f2
@@ -163,7 +163,7 @@ let run ~explicit_fn_name ~get_vmtype gen =
 			(* now go through all overrides, *)
 			let rec check_f f =
 				(* find the first declared field *)
-				let is_overload = Meta.has Meta.Overload f.cf_meta in
+				let is_overload = has_class_field_flag f CfOverload in
 				let decl = if is_overload then
 					find_first_declared_field gen c ~get_vmtype ~exact_field:f f.cf_name
 				else
@@ -203,9 +203,9 @@ let run ~explicit_fn_name ~get_vmtype gen =
 										with Unify_error _ -> false) current_args original_args
 								| _ -> Globals.die "" __LOC__
 							in
-							if (not (Meta.has Meta.Overload f.cf_meta) && has_contravariant_args) then
-								f.cf_meta <- (Meta.Overload, [], f.cf_pos) :: f.cf_meta;
-							if Meta.has Meta.Overload f.cf_meta then begin
+							if (not (has_class_field_flag f CfOverload) && has_contravariant_args) then
+								add_class_field_flag f CfOverload;
+							if has_class_field_flag f CfOverload then begin
 								(* if it is overload, create another field with the requested type *)
 								let f3 = mk_class_field f.cf_name t (has_class_field_flag f CfPublic) f.cf_pos f.cf_kind f.cf_params in
 								let p = f.cf_pos in

+ 3 - 3
src/codegen/gencommon/gencommon.ml

@@ -1101,7 +1101,7 @@ let find_first_declared_field gen orig_cl ?get_vmtype ?exact_field field =
 	let rec loop_cl depth c tl tlch =
 		(try
 			let ret = PMap.find field c.cl_fields in
-			if Meta.has Meta.Overload ret.cf_meta then is_overload := true;
+			if has_class_field_flag ret CfOverload then is_overload := true;
 			match !chosen, exact_field with
 			| Some(d,f,_,_,_), _ when depth <= d || (is_var ret && not (is_var f)) -> ()
 			| _, None ->
@@ -1133,8 +1133,8 @@ let find_first_declared_field gen orig_cl ?get_vmtype ?exact_field field =
 	| None ->
 		None
 	| Some(_,f,c,tl,tlch) ->
-		if !is_overload && not (Meta.has Meta.Overload f.cf_meta) then
-			f.cf_meta <- (Meta.Overload,[],f.cf_pos) :: f.cf_meta;
+		if !is_overload && not (has_class_field_flag f CfOverload) then
+			add_class_field_flag f CfOverload;
 		let declared_t = apply_params c.cl_params tl f.cf_type in
 		let params_t = apply_params c.cl_params tlch f.cf_type in
 		let actual_t = match follow params_t with

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

@@ -260,7 +260,7 @@ let clone_ctors com ctor sup stl cl =
 		Globals.die "" __LOC__ (* should never happen *)
 	| cf :: [] -> cf
 	| cf :: overl ->
-		cf.cf_meta <- (Meta.Overload,[],cf.cf_pos) :: cf.cf_meta;
+		add_class_field_flag cf CfOverload;
 		cf.cf_overloads <- overl; cf
 
 let rec descends_from_native_or_skipctor cl =

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

@@ -710,7 +710,7 @@ struct
 						| Method _ when has_class_field_flag cf CfAbstract -> false
 						| _ ->
 							let is_override = has_class_field_flag cf CfOverride in
-							let cf_type = if is_override && not (Meta.has Meta.Overload cf.cf_meta) then
+							let cf_type = if is_override && not (has_class_field_flag cf CfOverload) then
 								match find_first_declared_field gen cl cf.cf_name with
 									| Some(_,_,declared_t,_,_,_,_) -> declared_t
 									| _ -> Globals.die "" __LOC__

+ 1 - 0
src/core/tType.ml

@@ -392,6 +392,7 @@ type flag_tclass_field =
 	| CfModifiesThis (* This is set for methods which reassign `this`. E.g. `this = value` *)
 	| CfOverride
 	| CfAbstract
+	| CfOverload
 
 type flag_tvar =
 	| VCaptured

+ 1 - 1
src/generators/gencs.ml

@@ -2286,7 +2286,7 @@ let generate con =
 					let modifiers = if is_abstract then "abstract" :: modifiers else modifiers in
 					let visibility, is_virtual = if is_explicit_iface then "",false else if visibility = "private" then "private",false else visibility, is_virtual in
 					let v_n = if is_static then "static" else if is_override && not is_interface then "override" else if is_virtual then "virtual" else "" in
-					let cf_type = if is_override && not is_overload && not (Meta.has Meta.Overload cf.cf_meta) then match field_access gen (TInst(cl, List.map snd cl.cl_params)) cf.cf_name with | FClassField(_,_,_,_,_,actual_t,_) -> actual_t | _ -> die "" __LOC__ else cf.cf_type in
+					let cf_type = if is_override && not is_overload && not (has_class_field_flag cf CfOverload) then match field_access gen (TInst(cl, List.map snd cl.cl_params)) cf.cf_name with | FClassField(_,_,_,_,_,actual_t,_) -> actual_t | _ -> die "" __LOC__ else cf.cf_type in
 					let ret_type, args = match follow cf_type with | TFun (strbtl, t) -> (t, strbtl) | _ -> die "" __LOC__ in
 					gen_nocompletion w cf.cf_meta;
 

+ 1 - 1
src/generators/genhxold.ml

@@ -202,7 +202,7 @@ let generate_type com t =
 			p "function %s%s(%s) : %s" name tparams (String.concat ", " (List.map sparam params)) (stype ret);
 		);
 		p ";\n";
-		if Meta.has Meta.Overload f.cf_meta then List.iter (fun f -> print_field stat f) f.cf_overloads
+		if has_class_field_flag f CfOverload then List.iter (fun f -> print_field stat f) f.cf_overloads
 	in
 	(match t with
 	| TClassDecl c ->

+ 1 - 1
src/generators/genjava.ml

@@ -1991,7 +1991,7 @@ let generate con =
 				let modifiers = if is_abstract then "abstract" :: modifiers else modifiers in
 				let visibility, is_virtual = if is_explicit_iface then "",false else visibility, is_virtual in
 				let v_n = if is_static then "static" else if is_override && not is_interface then "" else if not is_virtual then "final" else "" in
-				let cf_type = if is_override && not is_overload && not (Meta.has Meta.Overload cf.cf_meta) then match field_access gen (TInst(cl, List.map snd cl.cl_params)) cf.cf_name with | FClassField(_,_,_,_,_,actual_t,_) -> actual_t | _ -> die "" __LOC__ else cf.cf_type in
+				let cf_type = if is_override && not is_overload && not (has_class_field_flag cf CfOverload) then match field_access gen (TInst(cl, List.map snd cl.cl_params)) cf.cf_name with | FClassField(_,_,_,_,_,actual_t,_) -> actual_t | _ -> die "" __LOC__ else cf.cf_type in
 
 				let params = List.map snd cl.cl_params in
 				let ret_type, args = match follow cf_type, follow cf.cf_type with

+ 1 - 1
src/generators/genjvm.ml

@@ -2475,7 +2475,7 @@ class tclass_to_jvm gctx c = object(self)
 			| Method (MethNormal | MethInline) ->
 				List.iter (fun cf ->
 					failsafe cf.cf_pos (fun () -> self#generate_method gctx jc c mtype cf);
-				) (cf :: List.filter (fun cf -> Meta.has Meta.Overload cf.cf_meta) cf.cf_overloads)
+				) (cf :: List.filter (fun cf -> has_class_field_flag cf CfOverload) cf.cf_overloads)
 			| _ ->
 				if not (has_class_flag c CInterface) && is_physical_field cf then failsafe cf.cf_pos (fun () -> self#generate_field gctx jc c mtype cf)
 		in

+ 2 - 2
src/typing/calls.ml

@@ -247,7 +247,7 @@ let unify_field_call ctx fa el args ret p inline =
 			expand_overloads (fun t -> t) cf,None,false,cf,(fun cf -> FAnon cf)
 		| FInstance(c,tl,cf) ->
 			let map = apply_params c.cl_params tl in
-			let cfl = if cf.cf_name = "new" || not (Meta.has Meta.Overload cf.cf_meta && ctx.com.config.pf_overload) then
+			let cfl = if cf.cf_name = "new" || not (has_class_field_flag cf CfOverload && ctx.com.config.pf_overload) then
 				(TFun(args,ret),cf) :: List.map (map_cf cf map) cf.cf_overloads
 			else
 				List.map (fun (t,cf) ->
@@ -263,7 +263,7 @@ let unify_field_call ctx fa el args ret p inline =
 			error "Invalid field call" p
 	in
 	let is_forced_inline = is_forced_inline co cf in
-	let is_overload = Meta.has Meta.Overload cf.cf_meta in
+	let is_overload = has_class_field_flag cf CfOverload in
 	let attempt_call t cf = match follow t with
 		| TFun(args,ret) ->
 			let el,tf = unify_call_args' ctx el args ret p inline is_forced_inline in

+ 2 - 2
src/typing/fields.ml

@@ -393,7 +393,7 @@ let rec type_field cfg ctx e i p mode (with_type : WithType.t) =
 					display_error ctx "Normal variables cannot be accessed with 'super', use 'this' instead" pfield);
 			(* For overloads we have to resolve the actual field before we can check accessibility. *)
 			begin match mode with
-			| MCall _ when Meta.has Meta.Overload f.cf_meta ->
+			| MCall _ when has_class_field_flag f CfOverload ->
 				()
 			| _ ->
 				check_field_access ctx c f false pfield;
@@ -439,7 +439,7 @@ let rec type_field cfg ctx e i p mode (with_type : WithType.t) =
 			let f = PMap.find i a.a_fields in
 			if Meta.has Meta.Impl f.cf_meta && not (Meta.has Meta.Enum f.cf_meta) then display_error ctx "Cannot access non-static abstract field statically" pfield;
 			begin match mode with
-			| MCall _ when Meta.has Meta.Overload f.cf_meta ->
+			| MCall _ when has_class_field_flag f CfOverload ->
 				()
 			| _ ->
 				if not (has_class_field_flag f CfPublic) && not ctx.untyped then begin

+ 2 - 2
src/typing/overloadResolution.ml

@@ -83,7 +83,7 @@ let resolve_instance_overload is_ctor map_type c name el =
 					if not (List.exists (has_function fcc.fc_type) !candidates) then candidates := fcc :: !candidates
 				) l
 			end;
-			if Meta.has Meta.Overload cf.cf_meta || cf.cf_overloads <> [] then raise Not_found
+			if has_class_field_flag cf CfOverload || cf.cf_overloads <> [] then raise Not_found
 		with Not_found ->
 			if (has_class_flag c CInterface) then
 				List.iter (fun (c,tl) -> loop (fun t -> apply_params c.cl_params (List.map map_type tl) t) c) c.cl_implements
@@ -96,7 +96,7 @@ let resolve_instance_overload is_ctor map_type c name el =
 	filter_overloads (List.rev !candidates)
 
 let maybe_resolve_instance_overload is_ctor map_type c cf el =
-	if Meta.has Meta.Overload cf.cf_meta || cf.cf_overloads <> [] then
+	if has_class_field_flag cf CfOverload || cf.cf_overloads <> [] then
 		resolve_instance_overload is_ctor map_type c cf.cf_name el
 	else match unify_cf map_type c cf el with
 		| Some fcc -> Some (fcc.fc_data)

+ 1 - 0
src/typing/typeload.ml

@@ -667,6 +667,7 @@ and init_meta_overloads ctx co cf =
 			ctx.type_params <- old;
 			false
 		| (Meta.Overload,[],_) when ctx.com.config.pf_overload ->
+			add_class_field_flag cf CfOverload;
 			let topt (n,_,t) = match t with | TMono t when t.tm_type = None -> error ("Explicit type required for overload functions\n... For function argument '" ^ n ^ "'") cf.cf_pos | _ -> () in
 			(match follow cf.cf_type with
 			| TFun (args,_) -> List.iter topt args

+ 4 - 4
src/typing/typeloadCheck.ml

@@ -172,7 +172,7 @@ let check_overriding ctx c f =
 		let p = f.cf_name_pos in
 		let i = f.cf_name in
 		let check_field f get_super_field is_overload = try
-			(if is_overload && not (Meta.has Meta.Overload f.cf_meta) then
+			(if is_overload && not (has_class_field_flag f CfOverload) then
 				display_error ctx ("Missing @:overload declaration for field " ^ i) p);
 			let t, f2 = get_super_field csup i in
 			check_native_name_override ctx f f2;
@@ -180,7 +180,7 @@ let check_overriding ctx c f =
 			(match f2.cf_kind with
 			| Var { v_read = AccRequire _ } -> raise Not_found;
 			| _ -> ());
-			if ctx.com.config.pf_overload && (Meta.has Meta.Overload f2.cf_meta && not (Meta.has Meta.Overload f.cf_meta)) then
+			if ctx.com.config.pf_overload && (has_class_field_flag f2 CfOverload && not (has_class_field_flag f CfOverload)) then
 				display_error ctx ("Field " ^ i ^ " should be declared with @:overload since it was already declared as @:overload in superclass") p
 			else if not (has_class_field_flag f CfOverride) then
 				display_error ctx ("Field " ^ i ^ " should be declared with 'override' since it is inherited from superclass " ^ s_type_path csup.cl_path) p
@@ -218,7 +218,7 @@ let check_overriding ctx c f =
 					end in
 					display_error ctx msg p
 		in
-		if ctx.com.config.pf_overload && Meta.has Meta.Overload f.cf_meta then begin
+		if ctx.com.config.pf_overload && has_class_field_flag f CfOverload then begin
 			let overloads = Overloads.get_overloads ctx.com csup i in
 			List.iter (fun (t,f2) ->
 				(* check if any super class fields are vars *)
@@ -346,7 +346,7 @@ module Inheritance = struct
 			try
 				let t2, f2 = class_field_no_interf c i in
 				let t2, f2 =
-					if ctx.com.config.pf_overload && (f2.cf_overloads <> [] || Meta.has Meta.Overload f2.cf_meta) then
+					if ctx.com.config.pf_overload && (f2.cf_overloads <> [] || has_class_field_flag f2 CfOverload) then
 						let overloads = Overloads.get_overloads ctx.com c i in
 						is_overload := true;
 						List.find (fun (t1,f1) -> Overloads.same_overload_args t t1 f f1) overloads

+ 5 - 5
src/typing/typeloadFields.ml

@@ -1475,7 +1475,7 @@ let check_overload ctx f fs =
 let check_overloads ctx c =
 	(* check if field with same signature was declared more than once *)
 	List.iter (fun f ->
-		if Meta.has Meta.Overload f.cf_meta then
+		if has_class_field_flag f CfOverload then
 			check_overload ctx f (f :: f.cf_overloads)
 	) (c.cl_ordered_fields @ c.cl_ordered_statics)
 
@@ -1557,10 +1557,10 @@ let init_class ctx c p context_init herits fields =
 				| None ->
 						c.cl_constructor <- Some cf
 				| Some ctor when ctx.com.config.pf_overload ->
-						if Meta.has Meta.Overload cf.cf_meta && Meta.has Meta.Overload ctor.cf_meta then
+						if has_class_field_flag cf CfOverload && has_class_field_flag ctor CfOverload then
 							ctor.cf_overloads <- cf :: ctor.cf_overloads
 						else
-							display_error ctx ("If using overloaded constructors, all constructors must be declared with @:overload") (if Meta.has Meta.Overload cf.cf_meta then ctor.cf_pos else cf.cf_pos)
+							display_error ctx ("If using overloaded constructors, all constructors must be declared with @:overload") (if has_class_field_flag cf CfOverload then ctor.cf_pos else cf.cf_pos)
 				| Some ctor ->
 							display_error ctx "Duplicate constructor" p
 				end
@@ -1573,10 +1573,10 @@ let init_class ctx c p context_init herits fields =
 					add_class_field_flag cf CfOverride;
 				let is_var cf = match cf.cf_kind with | Var _ -> true | _ -> false in
 				if PMap.mem cf.cf_name (if fctx.is_static then c.cl_statics else c.cl_fields) then
-					if ctx.com.config.pf_overload && Meta.has Meta.Overload cf.cf_meta && not (is_var cf) then
+					if ctx.com.config.pf_overload && has_class_field_flag cf CfOverload && not (is_var cf) then
 						let mainf = PMap.find cf.cf_name (if fctx.is_static then c.cl_statics else c.cl_fields) in
 						if is_var mainf then display_error ctx "Cannot declare a variable with same name as a method" mainf.cf_pos;
-						(if not (Meta.has Meta.Overload mainf.cf_meta) then display_error ctx ("Overloaded methods must have @:overload metadata") mainf.cf_pos);
+						(if not (has_class_field_flag mainf CfOverload) then display_error ctx ("Overloaded methods must have @:overload metadata") mainf.cf_pos);
 						mainf.cf_overloads <- cf :: mainf.cf_overloads
 					else
 						let type_kind,path = match c.cl_kind with