Browse Source

try to break something

Simon Krajewski 3 years ago
parent
commit
f90995b7b2

+ 2 - 2
src/codegen/dotnet.ml

@@ -595,7 +595,7 @@ let mk_special_call name p args =
 	mke (ECast( mke (EUntyped( mke (ECall( mke (EConst(Ident name)) p, args )) p )) p , None)) p
 
 let mk_this_call name p args =
-	mke (ECall( mke (EField(mke (EConst(Ident "this")) p ,name)) p, args )) p
+	mke (ECall( mke (efield(mke (EConst(Ident "this")) p ,name)) p, args )) p
 
 let mk_metas metas p =
 	List.map (fun m -> m,[],p) metas
@@ -653,7 +653,7 @@ let convert_delegate ctx p ilcls =
 		let clsname = match ilcls.cpath with
 			| (ns,inner,n) -> get_clsname ctx (ns,inner,"Delegate_"^n)
 		in
-		let expr = (ECall( (EField( (EConst(Ident (clsname)),p), fn_name ),p), [(EConst(Ident"arg1"),p);(EConst(Ident"arg2"),p)]),p) in
+		let expr = (ECall( (efield( (EConst(Ident (clsname)),p), fn_name ),p), [(EConst(Ident"arg1"),p);(EConst(Ident"arg2"),p)]),p) in
 		FFun {
 			f_params = types;
 			f_args = [("arg1",null_pos),false,[],Some (abs_type,null_pos),None;("arg2",null_pos),false,[],Some (abs_type,null_pos),None];

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

@@ -99,7 +99,7 @@ struct
 
 		(match gen.gcon.platform with
 			| Cs when Common.defined gen.gcon Define.CoreApiSerialize ->
-				cl.cl_meta <- ( Meta.Meta, [ (EField( (EConst (Ident "System"), null_pos ), "Serializable" ), null_pos) ], null_pos ) :: cl.cl_meta
+				cl.cl_meta <- ( Meta.Meta, [ (efield( (EConst (Ident "System"), null_pos ), "Serializable" ), null_pos) ], null_pos ) :: cl.cl_meta
 			| _ -> ());
 		let c_types =
 			if handle_type_params then

+ 1 - 1
src/context/display/syntaxExplorer.ml

@@ -56,7 +56,7 @@ let find_in_syntax symbols (pack,decls) =
 		begin match e with
 		| EConst(Ident s) ->
 			check KIdent s
-		| EField(e1,s) ->
+		| EField(e1,s,_) ->
 			expr e1;
 			check KAnyField s;
 		| EVars vl ->

+ 1 - 1
src/context/typecore.ml

@@ -473,7 +473,7 @@ let rec can_access ctx c cf stat =
 	in
 	let rec expr_path acc e =
 		match fst e with
-		| EField (e,f) -> expr_path (f :: acc) e
+		| EField (e,f,_) -> expr_path (f :: acc) e
 		| EConst (Ident n) -> n :: acc
 		| _ -> []
 	in

+ 16 - 9
src/core/ast.ml

@@ -198,11 +198,15 @@ and display_kind =
 	| DKMarked
 	| DKPattern of bool
 
+and efield_kind =
+	| EFNormal
+	| EFSafe
+
 and expr_def =
 	| EConst of constant
 	| EArray of expr * expr
 	| EBinop of binop * expr * expr
-	| EField of expr * string
+	| EField of expr * string * efield_kind
 	| EParenthesis of expr
 	| EObjectDecl of ((string * pos * quote_status) * expr) list
 	| EArrayDecl of expr list
@@ -601,6 +605,9 @@ let s_token = function
 
 exception Invalid_escape_sequence of char * int * (string option)
 
+let efield (e,s) =
+	EField(e,s,EFNormal)
+
 let unescape s =
 	let b = Buffer.create 0 in
 	let rec loop esc i =
@@ -730,7 +737,7 @@ let map_expr loop (e,p) =
 		let e1 = loop e1 in
 		let e2 = loop e2 in
 		EBinop (op,e1,e2)
-	| EField (e,f) -> EField (loop e, f)
+	| EField (e,f,efk) -> EField (loop e, f, efk)
 	| EParenthesis e -> EParenthesis (loop e)
 	| EObjectDecl fl -> EObjectDecl (List.map (fun (k,e) -> k,loop e) fl)
 	| EArrayDecl el -> EArrayDecl (List.map loop el)
@@ -810,7 +817,7 @@ let iter_expr loop (e,p) =
 	let exprs = List.iter loop in
 	match e with
 	| EConst _ | EContinue | EBreak | EReturn None -> ()
-	| EParenthesis e1 | EField(e1,_) | EUnop(_,_,e1) | EReturn(Some e1) | EThrow e1 | EMeta(_,e1)
+	| EParenthesis e1 | EField(e1,_,_) | EUnop(_,_,e1) | EReturn(Some e1) | EThrow e1 | EMeta(_,e1)
 	| ECheckType(e1,_) | EDisplay(e1,_) | ECast(e1,_) | EIs(e1,_) | EUntyped e1 -> loop e1;
 	| EArray(e1,e2) | EBinop(_,e1,e2) | EFor(e1,e2) | EWhile(e1,e2,_) | EIf(e1,e2,None) -> loop e1; loop e2;
 	| ETernary(e1,e2,e3) | EIf(e1,e2,Some e3) -> loop e1; loop e2; loop e3;
@@ -850,7 +857,7 @@ module Printer = struct
 		| EConst c -> s_constant c
 		| EArray (e1,e2) -> s_expr_inner tabs e1 ^ "[" ^ s_expr_inner tabs e2 ^ "]"
 		| EBinop (op,e1,e2) -> s_expr_inner tabs e1 ^ " " ^ s_binop op ^ " " ^ s_expr_inner tabs e2
-		| EField (e,f) -> s_expr_inner tabs e ^ "." ^ f
+		| EField (e,f,efk) -> s_expr_inner tabs e ^ (match efk with EFNormal -> "." | EFSafe -> "?.") ^ f
 		| EParenthesis e -> "(" ^ (s_expr_inner tabs e) ^ ")"
 		| EObjectDecl fl -> "{ " ^ (String.concat ", " (List.map (fun ((n,_,qs),e) -> (s_object_key_name n qs) ^ " : " ^ (s_expr_inner tabs e)) fl)) ^ " }"
 		| EArrayDecl el -> "[" ^ s_expr_list tabs el ", " ^ "]"
@@ -1002,13 +1009,13 @@ let get_value_meta meta =
 let rec string_list_of_expr_path_raise (e,p) =
 	match e with
 	| EConst (Ident i) -> [i]
-	| EField (e,f) -> f :: string_list_of_expr_path_raise e
+	| EField (e,f,_) -> f :: string_list_of_expr_path_raise e
 	| _ -> raise Exit
 
 let rec string_pos_list_of_expr_path_raise (e,p) =
 	match e with
 	| EConst (Ident i) -> [i,p]
-	| EField (e,f) -> (f,p) :: string_pos_list_of_expr_path_raise e (* wrong p? *)
+	| EField (e,f,_) -> (f,p) :: string_pos_list_of_expr_path_raise e (* wrong p? *)
 	| _ -> raise Exit
 
 let expr_of_type_path (sl,s) p =
@@ -1016,8 +1023,8 @@ let expr_of_type_path (sl,s) p =
 	| [] -> (EConst(Ident s),p)
 	| s1 :: sl ->
 		let e1 = (EConst(Ident s1),p) in
-		let e = List.fold_left (fun e s -> (EField(e,s),p)) e1 sl in
-		EField(e,s),p
+		let e = List.fold_left (fun e s -> (efield(e,s),p)) e1 sl in
+		efield(e,s),p
 
 let match_path recursive sl sl_pattern =
 	let rec loop top sl1 sl2 = match sl1,sl2 with
@@ -1088,7 +1095,7 @@ module Expr = struct
 				add ("EBinop " ^ (s_binop op));
 				loop e1;
 				loop e2;
-			| EField(e1,s) ->
+			| EField(e1,s,_) ->
 				add ("EField " ^ s);
 				loop e1
 			| EParenthesis e1 ->

+ 1 - 1
src/core/inheritDoc.ml

@@ -7,7 +7,7 @@ let expr_to_target e =
 	let rec loop (e,p) =
 		match e with
 		| EConst (Ident s) when s <> "" -> [s]
-		| EField (e,s) -> s :: loop e
+		| EField (e,s,_) -> s :: loop e
 		| _ -> Error.typing_error "Invalid target expression for @:inheritDoc" p
 	in
 	match loop e with

+ 1 - 1
src/core/tOther.ml

@@ -91,7 +91,7 @@ module TExprToExpr = struct
 		| TLocal v -> EConst (mk_ident v.v_name)
 		| TArray (e1,e2) -> EArray (convert_expr e1,convert_expr e2)
 		| TBinop (op,e1,e2) -> EBinop (op, convert_expr e1, convert_expr e2)
-		| TField (e,f) -> EField (convert_expr e, field_name f)
+		| TField (e,f) -> EField (convert_expr e, field_name f, EFNormal)
 		| TTypeExpr t -> fst (mk_path (full_type_path t) e.epos)
 		| TParenthesis e -> EParenthesis (convert_expr e)
 		| TObjectDecl fl -> EObjectDecl (List.map (fun (k,e) -> k, convert_expr e) fl)

+ 2 - 2
src/generators/gencs.ml

@@ -1890,7 +1890,7 @@ let generate con =
 		let rec gen_fpart_attrib w = function
 			| EConst( Ident i ), _ ->
 				write w i
-			| EField( ef, f ), _ ->
+			| EField( ef, f, _ ), _ ->
 				gen_fpart_attrib w ef;
 				write w ".";
 				write w f
@@ -1907,7 +1907,7 @@ let generate con =
 					write w (escape s);
 					write w "\""
 				| _ -> gen.gcon.error "Invalid expression inside @:meta metadata" p)
-			| EField( ef, f ), _ ->
+			| EField( ef, f, _ ), _ ->
 				gen_spart w ef;
 				write w ".";
 				write w f

+ 2 - 2
src/generators/genjava.ml

@@ -1824,7 +1824,7 @@ let generate con =
 	let rec gen_fpart_attrib w = function
 		| EConst( Ident i ), _ ->
 			write w i
-		| EField( ef, f ), _ ->
+		| EField( ef, f, _ ), _ ->
 			gen_fpart_attrib w ef;
 			write w ".";
 			write w f
@@ -1841,7 +1841,7 @@ let generate con =
 				write w (escape s);
 				write w "\""
 			| _ -> gen.gcon.error "Invalid expression inside @:meta metadata" p)
-		| EField( ef, f ), _ ->
+		| EField( ef, f, _ ), _ ->
 			gen_spart w ef;
 			write w ".";
 			write w f

+ 1 - 1
src/generators/genjvm.ml

@@ -232,7 +232,7 @@ module AnnotationHandler = struct
 			| EConst (Ident "true") -> ABool true
 			| EConst (Ident "false") -> ABool false
 			| EArrayDecl el -> AArray (List.map parse_value el)
-			| EField(e1,s) ->
+			| EField(e1,s,_) ->
 				let path = parse_path e1 in
 				AEnum(object_path_sig path,s)
 			| _ -> Error.typing_error "Expected value expression" (pos e)

+ 3 - 3
src/macro/eval/evalDebugMisc.ml

@@ -224,7 +224,7 @@ let rec expr_to_value ctx env e =
 				| VEnumValue ev -> Array.get ev.eargs idx
 				| _ -> raise NoValueExpr
 			end
-		| EField(e1,s) ->
+		| EField(e1,s,_) ->
 			let v1 = loop e1 in
 			let s' = hash s in
 			begin match v1 with
@@ -294,7 +294,7 @@ let rec expr_to_value ctx env e =
 			end
 		| ECall(e1,el) ->
 			begin match fst e1 with
-			| EField(ethis,s) ->
+			| EField(ethis,s,_) ->
 				let vthis = loop ethis in
 				let v1 = EvalField.field vthis (hash s) in
 				let vl = List.map loop el in
@@ -370,7 +370,7 @@ let rec expr_to_value ctx env e =
 
 and write_expr ctx env expr value =
 	begin match fst expr with
-		| EField(e1,s) ->
+		| EField(e1,s,_) ->
 			let s' = hash s in
 			let v1 = expr_to_value ctx env e1 in
 			begin match v1 with

+ 1 - 0
src/macro/eval/evalEncode.ml

@@ -161,6 +161,7 @@ let encode_enum i pos index pl =
 	let open MacroApi in
 	let key = match i with
 		| IExpr -> key_haxe_macro_ExprDef
+		| IEFieldKind -> key_haxe_macro_EFieldKind
 		| IBinop -> key_haxe_macro_Binop
 		| IUnop -> key_haxe_macro_Unop
 		| IConst -> key_haxe_macro_Constant

+ 1 - 0
src/macro/eval/evalHash.ml

@@ -94,6 +94,7 @@ let key_sys_io_FileOutput = hash "sys.io.FileOutput"
 let key_sys_io_FileInput = hash "sys.io.FileInput"
 let key_haxe_io_Eof = hash "haxe.io.Eof"
 let key_haxe_macro_ExprDef = hash "haxe.macro.ExprDef"
+let key_haxe_macro_EFieldKind = hash "haxe.macro.EFieldKind"
 let key_haxe_macro_Binop = hash "haxe.macro.Binop"
 let key_haxe_macro_Unop = hash "haxe.macro.Unop"
 let key_haxe_macro_Constant = hash "haxe.macro.Constant"

+ 2 - 2
src/macro/eval/evalMain.ml

@@ -424,7 +424,7 @@ let rec value_to_expr v p =
 			let rec loop = function
 				| [] -> die "" __LOC__
 				| [name] -> (EConst (Ident name),p)
-				| name :: l -> (EField (loop l,name),p)
+				| name :: l -> (efield (loop l,name),p)
 			in
 			let t = t_infos t in
 			loop (List.rev (if t.mt_module.m_path = t.mt_path then fst t.mt_path @ [snd t.mt_path] else fst t.mt_module.m_path @ [snd t.mt_module.m_path;snd t.mt_path]))
@@ -459,7 +459,7 @@ let rec value_to_expr v p =
 				| PEnum names -> fst (List.nth names e.eindex)
 				| _ -> die "" __LOC__
 			in
-			(EField (expr, name), p)
+			(efield (expr, name), p)
 		in
 		begin
 			match e.eargs with

+ 23 - 43
src/macro/macroApi.ml

@@ -55,6 +55,7 @@ type 'value compiler_api = {
 
 type enum_type =
 	| IExpr
+	| IEFieldKind
 	| IBinop
 	| IUnop
 	| IConst
@@ -150,53 +151,18 @@ module type InterpApi = sig
 	val get_api_call_pos : unit -> pos
 end
 
-let enum_name = function
-	| IExpr -> "ExprDef"
-	| IBinop -> "Binop"
-	| IUnop -> "Unop"
-	| IConst -> "Constant"
-	| ITParam -> "TypeParam"
-	| ICType -> "ComplexType"
-	| IField -> "FieldType"
-	| IType -> "Type"
-	| IFieldKind -> "FieldKind"
-	| IMethodKind -> "MethodKind"
-	| IVarAccess -> "VarAccess"
-	| IAccess -> "Access"
-	| IClassKind -> "ClassKind"
-	| ITypedExpr -> "TypedExprDef"
-	| ITConstant -> "TConstant"
-	| IModuleType -> "ModuleType"
-	| IFieldAccess -> "FieldAccess"
-	| IAnonStatus -> "AnonStatus"
-	| IImportMode -> "ImportMode"
-	| IQuoteStatus -> "QuoteStatus"
-	| IDisplayKind -> "DisplayKind"
-	| IMessage -> "Message"
-	| IFunctionKind -> "FunctionKind"
-	| IStringLiteralKind -> "StringLiteralKind"
-
-let all_enums =
-	let last = IImportMode in
-	let rec loop i =
-		let e : enum_type = Obj.magic i in
-		if e = last then [e] else e :: loop (i + 1)
-	in
-	loop 0
-
-
 let s_type_path = Globals.s_type_path
 
 (* convert float value to haxe expression, handling inf/-inf/nan *)
 let haxe_float f p =
 	let std = (Ast.EConst (Ast.Ident "std"), p) in
-	let math = (Ast.EField (std, "Math"), p) in
+	let math = (efield (std, "Math"), p) in
 	if (f = infinity) then
-		(Ast.EField (math, "POSITIVE_INFINITY"), p)
+		(efield (math, "POSITIVE_INFINITY"), p)
 	else if (f = neg_infinity) then
-		(Ast.EField (math, "NEGATIVE_INFINITY"), p)
+		(efield (math, "NEGATIVE_INFINITY"), p)
 	else if (f <> f) then
-		(Ast.EField (math, "NaN"), p)
+		(efield (math, "NaN"), p)
 	else
 		(Ast.EConst (Ast.Float (Numeric.float_repres f, None)), p)
 
@@ -414,6 +380,13 @@ and encode_message msg =
 	in
 	encode_enum ~pos:None IMessage tag pl
 
+and encode_efield_kind efk =
+	let i = match efk with
+		| EFNormal -> 0
+		| EFSafe -> 1
+	in
+	encode_enum IEFieldKind i []
+
 and encode_expr e =
 	let rec loop (e,p) =
 		let tag, pl = match e with
@@ -423,8 +396,8 @@ and encode_expr e =
 				1, [loop e1;loop e2]
 			| EBinop (op,e1,e2) ->
 				2, [encode_binop op;loop e1;loop e2]
-			| EField (e,f) ->
-				3, [loop e;encode_string f]
+			| EField (e,f,efk) ->
+				3, [loop e;encode_string f;encode_efield_kind efk]
 			| EParenthesis e ->
 				4, [loop e]
 			| EObjectDecl fl ->
@@ -769,8 +742,15 @@ and decode_expr v =
 			EArray (loop e1, loop e2)
 		| 2, [op;e1;e2] ->
 			EBinop (decode_op op, loop e1, loop e2)
-		| 3, [e;f] ->
-			EField (loop e, decode_string f)
+		| 3, [e;f;efk] ->
+			let efk = if efk == vnull then
+				EFNormal
+			else match decode_enum efk with
+				| 0,[] -> EFNormal
+				| 1,[] -> EFSafe
+				| _ -> raise Invalid_expr
+			in
+			EField (loop e, decode_string f, efk)
 		| 4, [e] ->
 			EParenthesis (loop e)
 		| 5, [a] ->

+ 12 - 12
src/syntax/grammar.mly

@@ -1331,7 +1331,7 @@ and expr = parser
 		expr_next (EConst (Ident (s_keyword k)), p) s
 	| [< '(Kwd Macro,p); s >] ->
 		begin match s with parser
-		| [< '(Dot,pd); e = parse_field (EConst (Ident "macro"),p) pd >] -> e
+		| [< '(Dot,pd); e = parse_field (EConst (Ident "macro"),p) EFNormal pd >] -> e
 		| [< e = parse_macro_expr p >] -> e
 		| [< >] -> serror()
 		end
@@ -1493,8 +1493,8 @@ and expr_next' e1 = parser
 		(match fst e1 with
 		| EConst(Ident n) -> expr_next (EMeta((Meta.from_string n,[],snd e1),eparam), punion p1 p2) s
 		| _ -> die "" __LOC__)
-	| [< '(Dot,p); e = parse_field e1 p >] -> e
-	| [< '(QuestionDot,p); e = parse_field e1 p >] -> e
+	| [< '(Dot,p); e = parse_field e1 EFNormal p >] -> e
+	| [< '(QuestionDot,p); e = parse_field e1 EFSafe p >] -> e
 	| [< '(POpen,p1); e = parse_call_params (fun el p2 -> (ECall(e1,el)),punion (pos e1) p2) p1; s >] -> expr_next e s
 	| [< '(BkOpen,p1); e2 = secure_expr; s >] ->
 		let p2 = expect_unless_resume_p BkClose s in
@@ -1535,16 +1535,16 @@ and expr_next' e1 = parser
 		expr_next e_is s
 	| [< >] -> e1
 
-and parse_field e1 p s =
+and parse_field e1 efk p s =
 	check_resume p (fun () -> (EDisplay (e1,DKDot),p)) (fun () ->
 		begin match s with parser
-		| [< '(Kwd Macro,p2) when p.pmax = p2.pmin; s >] -> expr_next (EField (e1,"macro") , punion (pos e1) p2) s
-		| [< '(Kwd Extern,p2) when p.pmax = p2.pmin; s >] -> expr_next (EField (e1,"extern") , punion (pos e1) p2) s
-		| [< '(Kwd Function,p2) when p.pmax = p2.pmin; s >] -> expr_next (EField (e1,"function") , punion (pos e1) p2) s
-		| [< '(Kwd New,p2) when p.pmax = p2.pmin; s >] -> expr_next (EField (e1,"new") , punion (pos e1) p2) s
-		| [< '(Kwd k,p2) when !parsing_macro_cond && p.pmax = p2.pmin; s >] -> expr_next (EField (e1,s_keyword k) , punion (pos e1) p2) s
-		| [< '(Const (Ident f),p2) when p.pmax = p2.pmin; s >] -> expr_next (EField (e1,f) , punion (pos e1) p2) s
-		| [< '(Dollar v,p2); s >] -> expr_next (EField (e1,"$"^v) , punion (pos e1) p2) s
+		| [< '(Kwd Macro,p2) when p.pmax = p2.pmin; s >] -> expr_next (EField (e1,"macro",efk) , punion (pos e1) p2) s
+		| [< '(Kwd Extern,p2) when p.pmax = p2.pmin; s >] -> expr_next (EField (e1,"extern",efk) , punion (pos e1) p2) s
+		| [< '(Kwd Function,p2) when p.pmax = p2.pmin; s >] -> expr_next (EField (e1,"function",efk) , punion (pos e1) p2) s
+		| [< '(Kwd New,p2) when p.pmax = p2.pmin; s >] -> expr_next (EField (e1,"new",efk) , punion (pos e1) p2) s
+		| [< '(Kwd k,p2) when !parsing_macro_cond && p.pmax = p2.pmin; s >] -> expr_next (EField (e1,s_keyword k,efk) , punion (pos e1) p2) s
+		| [< '(Const (Ident f),p2) when p.pmax = p2.pmin; s >] -> expr_next (EField (e1,f,efk) , punion (pos e1) p2) s
+		| [< '(Dollar v,p2); s >] -> expr_next (EField (e1,"$"^v,efk) , punion (pos e1) p2) s
 		| [< >] ->
 			(* turn an integer followed by a dot into a float *)
 			match e1 with
@@ -1664,7 +1664,7 @@ let rec validate_macro_cond s e = match fst e with
 	| EUnop (op,p,e1) -> (EUnop (op, p, validate_macro_cond s e1), snd e)
 	| EBinop (op,e1,e2) -> (EBinop(op, (validate_macro_cond s e1), (validate_macro_cond s e2)), snd e)
 	| EParenthesis (e1) -> (EParenthesis (validate_macro_cond s e1), snd e)
-	| EField(e1,name) -> (EField(validate_macro_cond s e1,name), snd e)
+	| EField(e1,name,efk) -> (EField(validate_macro_cond s e1,name,efk), snd e)
 	| ECall ((EConst (Ident _),_) as i, args) -> (ECall (i,List.map (validate_macro_cond s) args),snd e)
 	| _ -> syntax_error (Custom ("Invalid conditional expression")) ~pos:(Some (pos e)) s ((EConst (Ident "false"),(pos e)))
 

+ 12 - 8
src/syntax/reification.ml

@@ -117,9 +117,9 @@ let reify in_macro =
 					 type parameters. *)
 				let ea = to_array to_tparam t.tparams p in
 				let fields = [
-					("pack", (EField(ei,"pack"),p));
-					("name", (EField(ei,"name"),p));
-					("sub", (EField(ei,"sub"),p));
+					("pack", (efield(ei,"pack"),p));
+					("name", (efield(ei,"name"),p));
+					("sub", (efield(ei,"sub"),p));
 					("params", ea);
 				] in
 				to_obj fields p
@@ -234,7 +234,7 @@ let reify in_macro =
 		match !cur_pos with
 		| Some p -> p
 		| None when in_macro -> to_pos p
-		| None -> (ECall ((EField ((EField ((EField ((EConst (Ident "haxe"),p),"macro"),p),"Context"),p),"makePosition"),p),[to_pos p]),p)
+		| None -> (ECall ((efield ((efield ((efield ((EConst (Ident "haxe"),p),"macro"),p),"Context"),p),"makePosition"),p),[to_pos p]),p)
 	and to_expr_array a p = match a with
 		| [EMeta ((Meta.Dollar "a",[],_),e1),_] -> (match fst e1 with EArrayDecl el -> to_expr_array el p | _ -> e1)
 		| _ -> to_array to_expr a p
@@ -254,9 +254,13 @@ let reify in_macro =
 			expr "EArray" [loop e1;loop e2]
 		| EBinop (op,e1,e2) ->
 			expr "EBinop" [to_binop op p; loop e1; loop e2]
-		| EField (e,s) ->
+		| EField (e,s,efk) ->
 			let p = {p with pmin = p.pmax - String.length s} in
-			expr "EField" [loop e; to_string s p]
+			let efk = match efk with
+				| EFNormal -> "Normal"
+				| EFSafe -> "Safe"
+			in
+			expr "EField" [loop e; to_string s p; mk_enum "EFieldKind" efk [] p]
 		| EParenthesis e ->
 			expr "EParenthesis" [loop e]
 		| EObjectDecl fl ->
@@ -359,12 +363,12 @@ let reify in_macro =
 				| EConst (Int (s, Some "i64")) ->
 					expr "EConst" [mk_enum "Constant" "CInt" [ (EConst(String (s, SDoubleQuotes)),(pos e1)); (EConst(String ("i64", SDoubleQuotes)),(pos e1)) ] (pos e1)]
 				| _ ->
-					(ECall ((EField ((EField ((EField ((EConst (Ident "haxe"),p),"macro"),p),"Context"),p),"makeExpr"),p),[e1; to_enc_pos (pos e1)]),p)
+					(ECall ((efield ((efield ((efield ((EConst (Ident "haxe"),p),"macro"),p),"Context"),p),"makeExpr"),p),[e1; to_enc_pos (pos e1)]),p)
 				end
 			| Meta.Dollar "i", _ ->
 				expr "EConst" [mk_enum "Constant" "CIdent" [e1] (pos e1)]
 			| Meta.Dollar "p", _ ->
-				(ECall ((EField ((EField ((EField ((EConst (Ident "haxe"),p),"macro"),p),"MacroStringTools"),p),"toFieldExpr"),p),[e]),p)
+				(ECall ((efield ((efield ((efield ((EConst (Ident "haxe"),p),"macro"),p),"MacroStringTools"),p),"toFieldExpr"),p),[e]),p)
 			| Meta.Pos, [pexpr] ->
 				let old = !cur_pos in
 				cur_pos := Some pexpr;

+ 1 - 1
src/typing/instanceBuilder.ml

@@ -7,7 +7,7 @@ open Error
 let get_macro_path ctx e args p =
 	let rec loop e =
 		match fst e with
-		| EField (e,f) -> f :: loop e
+		| EField (e,f,_) -> f :: loop e
 		| EConst (Ident i) -> [i]
 		| _ -> typing_error "Invalid macro call" p
 	in

+ 1 - 1
src/typing/macroContext.ml

@@ -790,7 +790,7 @@ let call_init_macro ctx e =
 	| ECall (e,args) ->
 		let rec loop e =
 			match fst e with
-			| EField (e,f) -> f :: loop e
+			| EField (e,f,_) -> f :: loop e
 			| EConst (Ident i) -> [i]
 			| _ -> typing_error "Invalid macro call" p
 		in

+ 2 - 2
src/typing/magicTypes.ml

@@ -53,8 +53,8 @@ let extend_remoting ctx c t p async prot =
 			let id = (EConst (String (fst f.cff_name,SDoubleQuotes)), p) in
 			let id = if prot then id else ECall ((EConst (Ident "__unprotect__"),p),[id]),p in
 			let expr = ECall (
-				(EField (
-					(ECall ((EField ((EConst (Ident "__cnx"),p),"resolve"),p),[id]),p),
+				(efield (
+					(ECall ((efield ((EConst (Ident "__cnx"),p),"resolve"),p),[id]),p),
 					"call")
 				,p),eargs),p
 			in

+ 2 - 2
src/typing/typeload.ml

@@ -754,13 +754,13 @@ let load_type_hint ?(opt=false) ctx pcur t =
 
 let field_to_type_path ctx e =
 	let rec loop e pack name = match e with
-		| EField(e,f),p when Char.lowercase (String.get f 0) <> String.get f 0 -> (match name with
+		| EField(e,f,_),p when Char.lowercase (String.get f 0) <> String.get f 0 -> (match name with
 			| [] | _ :: [] ->
 				loop e pack (f :: name)
 			| _ -> (* too many name paths *)
 				display_error ctx ("Unexpected " ^ f) p;
 				raise Exit)
-		| EField(e,f),_ ->
+		| EField(e,f,_),_ ->
 			loop e (f :: pack) name
 		| EConst(Ident f),_ ->
 			let pack, name, sub = match name with

+ 5 - 5
src/typing/typeloadModule.ml

@@ -73,15 +73,15 @@ module StrictMeta = struct
 			| hd :: tl ->
 				let rec loop pack expr = match pack with
 					| hd :: tl ->
-						loop tl (EField(expr,hd),pos)
+						loop tl (efield(expr,hd),pos)
 					| [] ->
-						(EField(expr,name),pos)
+						(efield(expr,name),pos)
 				in
 				loop tl (EConst(Ident(hd)),pos)
 
 	let rec process_meta_argument ?(toplevel=true) ctx expr = match expr.eexpr with
 		| TField(e,f) ->
-			(EField(process_meta_argument ~toplevel:false ctx e,field_name f),expr.epos)
+			(efield(process_meta_argument ~toplevel:false ctx e,field_name f),expr.epos)
 		| TConst(TInt i) ->
 			(EConst(Int (Int32.to_string i, None)), expr.epos)
 		| TConst(TFloat f) ->
@@ -99,7 +99,7 @@ module StrictMeta = struct
 			if ctx.com.platform = Cs then
 				(ECall( (EConst(Ident "typeof"), p), [get_native_repr md expr.epos] ), p)
 			else
-				(EField(get_native_repr md expr.epos, "class"), p)
+				(efield(get_native_repr md expr.epos, "class"), p)
 		| TTypeExpr md ->
 			get_native_repr md expr.epos
 		| _ ->
@@ -109,7 +109,7 @@ module StrictMeta = struct
 	let handle_fields ctx fields_to_check with_type_expr =
 		List.map (fun ((name,_,_),expr) ->
 			let pos = snd expr in
-			let field = (EField(with_type_expr,name), pos) in
+			let field = (efield(with_type_expr,name), pos) in
 			let fieldexpr = (EConst(Ident name),pos) in
 			let left_side = match ctx.com.platform with
 				| Cs -> field

+ 11 - 11
src/typing/typer.ml

@@ -538,7 +538,7 @@ and handle_efield ctx e p0 mode with_type =
 	   or a simple field access chain *)
 	let rec loop dot_path_acc (e,p) =
 		match e with
-		| EField (e,s) ->
+		| EField (e,s,efk_todo) ->
 			(* field access - accumulate and check further *)
 			loop ((mk_dot_path_part s p) :: dot_path_acc) e
 		| EConst (Ident i) ->
@@ -557,7 +557,7 @@ and type_access ctx e p mode with_type =
 	match e with
 	| EConst (Ident s) ->
 		type_ident ctx s p mode with_type
-	| EField (e1,"new") ->
+	| EField (e1,"new",efk_todo) ->
 		let e1 = type_expr ctx e1 WithType.value in
 		begin match e1.eexpr with
 			| TTypeExpr (TClassDecl c) ->
@@ -1412,10 +1412,10 @@ and type_array_comprehension ctx e with_type p =
 		| EParenthesis e2 -> (EParenthesis (map_compr e2),p)
 		| EBinop(OpArrow,a,b) ->
 			et := (ENew(({tpackage=["haxe";"ds"];tname="Map";tparams=[];tsub=None},null_pos),[]),comprehension_pos);
-			(ECall ((EField ((EConst (Ident v.v_name),p),"set"),p),[a;b]),p)
+			(ECall ((efield ((EConst (Ident v.v_name),p),"set"),p),[a;b]),p)
 		| _ ->
 			et := (EArrayDecl [],comprehension_pos);
-			(ECall ((EField ((EConst (Ident v.v_name),p),"push"),p),[(e,p)]),p)
+			(ECall ((efield ((EConst (Ident v.v_name),p),"push"),p),[(e,p)]),p)
 	in
 	let e = map_compr e in
 	let ea = type_expr ctx !et with_type in
@@ -1652,15 +1652,15 @@ and type_call ?(mode=MGet) ctx e el (with_type:WithType.t) inline p =
 			let e_trace = mk (TIdent "`trace") t_dynamic p in
 			mk (TCall (e_trace,[e;infos])) ctx.t.tvoid p
 		else
-			type_expr ctx (ECall ((EField ((EField ((EConst (Ident "haxe"),p),"Log"),p),"trace"),p),[mk_to_string_meta e;infos]),p) WithType.NoValue
-	| (EField ((EConst (Ident "super"),_),_),_), _ ->
+			type_expr ctx (ECall ((efield ((efield ((EConst (Ident "haxe"),p),"Log"),p),"trace"),p),[mk_to_string_meta e;infos]),p) WithType.NoValue
+	| (EField ((EConst (Ident "super"),_),_,_),_), _ -> (* <- ??? *)
 		(match def() with
 			| { eexpr = TCall ({ eexpr = TField (_, FInstance(_, _, { cf_kind = Method MethDynamic; cf_name = name })); epos = p }, _) } as e ->
 				ctx.com.error ("Cannot call super." ^ name ^ " since it's a dynamic method") p;
 				e
 			| e -> e
 		)
-	| (EField (e,"bind"),p), args ->
+	| (EField (e,"bind",efk_todo),p), args ->
 		let e = type_expr ctx e WithType.value in
 		(match follow e.etype with
 			| TFun signature -> type_bind ctx e signature args p
@@ -1676,7 +1676,7 @@ and type_call ?(mode=MGet) ctx e el (with_type:WithType.t) inline p =
 			let e = Diagnostics.secure_generated_code ctx e in
 			e
 		end
-	| (EField(e,"match"),p), [epat] ->
+	| (EField(e,"match",efk_todo),p), [epat] ->
 		let et = type_expr ctx e WithType.value in
 		let rec has_enum_match t = match follow t with
 			| TEnum _ -> true
@@ -1721,10 +1721,10 @@ and type_call ?(mode=MGet) ctx e el (with_type:WithType.t) inline p =
 
 and type_expr ?(mode=MGet) ctx (e,p) (with_type:WithType.t) =
 	match e with
-	| EField ((EConst (String(s,_)),ps),"code") ->
+	| EField ((EConst (String(s,_)),ps),"code",EFNormal) ->
 		if UTF8.length s <> 1 then typing_error "String must be a single UTF8 char" ps;
 		mk (TConst (TInt (Int32.of_int (UCharExt.code (UTF8.get s 0))))) ctx.t.tint p
-	| EField(_,n) when starts_with n '$' ->
+	| EField(_,n,_) when starts_with n '$' ->
 		typing_error "Field names starting with $ are not allowed" p
 	| EConst (Ident s) ->
 		if s = "super" && with_type <> WithType.NoValue && not ctx.in_display then typing_error "Cannot use super as value" p;
@@ -1753,7 +1753,7 @@ and type_expr ?(mode=MGet) ctx (e,p) (with_type:WithType.t) =
 			let low  = Int64.to_int32 i64 in
 
 			let ident = EConst (Ident "haxe"), p in
-			let field = EField ((EField (ident, "Int64"), p), "make"), p in
+			let field = efield ((efield (ident, "Int64"), p), "make"), p in
 
 			let arg_high = EConst (Int (Int32.to_string high, None)), p in
 			let arg_low  = EConst (Int (Int32.to_string low, None)), p in

+ 3 - 3
src/typing/typerDisplay.ml

@@ -260,7 +260,7 @@ let rec handle_signature_display ctx e_ast with_type =
 					display_dollar_type ctx p (fun t -> t,(CompletionType.from_type (get_import_status ctx) t))
 			in
 			let e1 = match e1 with
-				| (EField (e,"bind"),p) ->
+				| (EField (e,"bind",_),p) ->
 					let e = type_expr ctx e WithType.value in
 					(match follow e.etype with
 						| TFun signature -> e
@@ -450,7 +450,7 @@ and display_expr ctx e_ast e dk mode with_type p =
 			raise_fields fields (CRField(item,e1.epos,None,None)) (make_subject so ~start_pos:(Some (pos e_ast)) {e.epos with pmin = e.epos.pmax - l;})
 		in
 		begin match fst e_ast,e.eexpr with
-			| EField(e1,s),TField(e2,_) ->
+			| EField(e1,s,_),TField(e2,_) ->
 				display_fields e1 e2 (Some s)
 			| EObjectDecl [(name,pn,_),(EConst (Ident "null"),pe)],_ when pe.pmin = -1 ->
 				(* This is what the parser emits for #8651. Bit of a dodgy heuristic but should be fine. *)
@@ -588,7 +588,7 @@ let handle_display ctx e_ast dk mode with_type =
 	in
 	let e = match e_ast, e.eexpr with
 		| _, TField(e1,FDynamic "bind") when (match follow e1.etype with TFun _ -> true | _ -> false) -> e1
-		| (EField(_,"new"),_), TFunction { tf_expr = { eexpr = TReturn (Some ({ eexpr = TNew _ } as e1))} } -> e1
+		| (EField(_,"new",_),_), TFunction { tf_expr = { eexpr = TReturn (Some ({ eexpr = TNew _ } as e1))} } -> e1
 		| _ -> e
 	in
 	let is_display_debug = Meta.has (Meta.Custom ":debug.display") ctx.curfield.cf_meta in

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

@@ -257,6 +257,11 @@ enum Unop {
 	OpSpread;
 }
 
+enum EFieldKind {
+	Normal;
+	Safe;
+}
+
 /**
 	Represents a node in the AST.
 	@see https://haxe.org/manual/macro-reification-expression.html
@@ -434,8 +439,10 @@ enum ExprDef {
 
 	/**
 		Field access on `e.field`.
+
+		If `kind` is null, it is equal to Normal.
 	**/
-	EField(e:Expr, field:String);
+	EField(e:Expr, field:String, ?kind:EFieldKind);
 
 	/**
 		Parentheses `(e)`.