Browse Source

get a handle on FIdent positions

Dan Korostelev 8 năm trước cách đây
mục cha
commit
47797d442a

+ 2 - 2
src/macro/macroApi.ml

@@ -564,7 +564,7 @@ and encode_format_part part =
 	let part,pos = part in
 	let tag, pl = match part with
 		| FmtRaw s -> 0, [encode_string s]
-		| FmtIdent i -> 1, [encode_string i]
+		| FmtIdent (i,p) -> 1, [encode_string i; encode_pos p]
 		| FmtExpr e -> 2, [encode_expr e]
 	in
 	let kind = encode_enum IFormatSegmentKind tag pl in
@@ -838,7 +838,7 @@ and decode_format_part v =
 	let p = decode_pos (field v "pos") in
 	(match decode_enum (field v "kind") with
 	| 0, [vs] -> FmtRaw (decode_string vs)
-	| 1, [vs] -> FmtIdent (decode_string vs)
+	| 1, [vs;vp] -> FmtIdent (decode_string vs,decode_pos vp)
 	| 2, [ve] -> FmtExpr (decode_expr ve)
 	| _ -> raise Invalid_expr),p
 

+ 15 - 16
src/syntax/ast.ml

@@ -210,7 +210,7 @@ and expr = expr_def * pos
 
 and format_part =
 	| FmtRaw of string
-	| FmtIdent of string
+	| FmtIdent of string * pos
 	| FmtExpr of expr
 
 and type_param = {
@@ -599,17 +599,19 @@ let map_expr loop (e,p) =
 		let parts = List.map (fun p ->
 			match fst p with
 			| FmtRaw _ -> p
-			| FmtIdent i ->
-				let pos = snd p in
-				let fake_expr = (EConst (Ident i),{pos with pmin = pos.pmin + 1 (* omit dollar sign *)}) in
+			| FmtExpr e -> (FmtExpr (loop e), snd p)
+			| FmtIdent (i,pos) ->
+				let fake_expr = (EConst (Ident i),pos) in
 				let new_expr = loop fake_expr in
 				if new_expr == fake_expr then
 					p
-				else
-					(match new_expr with
-					| (EConst (Ident i),_) -> (FmtIdent i,pos)
-					| _ -> (FmtExpr new_expr,pos))
-			| FmtExpr e -> (FmtExpr (loop e), snd p)
+				else (
+					match new_expr with
+					| (EConst (Ident i),new_pos) ->
+						(FmtIdent (i,new_pos),snd p)
+					| _ ->
+						(FmtExpr new_expr,snd p)
+				)
 		) parts in
 		EFormat parts
 	| EArray (e1,e2) ->
@@ -722,9 +724,7 @@ let iter_expr loop (e,p) =
 	| EFormat parts ->
 		List.iter (fun p -> match fst p with
 			| FmtRaw _ -> ()
-			| FmtIdent i ->
-				let pos = snd p in
-				loop (EConst (Ident i),{pos with pmin = pos.pmin + 1 (* omit dollar sign *)})
+			| FmtIdent (i,pos) -> loop (EConst (Ident i),pos)
 			| FmtExpr e1 -> loop e1
 		) parts
 	| EFunction(_,f) ->
@@ -740,7 +740,7 @@ let s_expr e =
 			let parts = List.map (fun p ->
 				match fst p with
 				| FmtRaw s -> s
-				| FmtIdent i -> "$" ^ i
+				| FmtIdent (i,_) -> "$" ^ i
 				| FmtExpr e -> "${" ^ (s_expr_inner tabs e) ^ "}"
 			) parts in
 			Printf.sprintf "'%s'" (String.concat "" parts)
@@ -930,9 +930,8 @@ module Expr = struct
 			| FmtRaw s ->
 				let string_part_expr = (EConst (String s),pos) in
 				if expr == empty_string_expr then string_part_expr else concat expr string_part_expr
-			| FmtIdent i ->
-				let eident = EConst (Ident i), {pos with pmin = pos.pmin + 1 (* identifier position is after the $ *)} in
-				concat expr eident
+			| FmtIdent (i,pos) ->
+				concat expr (EConst (Ident i),pos)
 			| FmtExpr e ->
 				concat expr e
 		) empty_string_expr parts in

+ 6 - 6
src/syntax/parser.mly

@@ -498,8 +498,8 @@ let reify in_macro =
 			| _ ->
 				expr "EMeta" [to_obj [("name",to_string (Meta.to_string m) p);("params",to_expr_array ml p);("pos",to_pos p)] p;loop e1]
 	and to_formatsegment part _ =
-		let f name arg pos =
-			let kind = mk_enum "FormatSegmentKind" name [arg] pos in
+		let f name args pos =
+			let kind = mk_enum "FormatSegmentKind" name args pos in
 			to_obj [
 				"kind",kind;
 				"pos",to_pos pos;
@@ -507,9 +507,9 @@ let reify in_macro =
 		in
 		let part,p = part in
 		match part with
-		| FmtRaw s -> f "FRaw" (to_string s p) p
-		| FmtIdent s -> f "FIdent" (to_string s p) p
-		| FmtExpr e -> f "FExpr" (to_expr e p) p
+		| FmtRaw s -> f "FRaw" [(to_string s p)] p
+		| FmtIdent (s,pos) -> f "FIdent" [(to_string s p);(to_pos pos)] p
+		| FmtExpr e -> f "FExpr" [(to_expr e p)] p
 	and to_tparam_decl p t =
 		to_obj [
 			"name", to_placed_name t.tp_name;
@@ -1482,7 +1482,7 @@ and expr = parser
 and parse_format_parts parts =
 	List.map (fun (t,p) -> (match t with
 		| Raw s -> FmtRaw s
-		| Name s -> FmtIdent s
+		| Name s -> FmtIdent (s,{p with pmin = p.pmin + 1} (* omit dollar sign *))
 		| Code [] -> FmtRaw ""
 		| Code tokens ->
 			let s = Stream.of_list tokens in

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

@@ -530,8 +530,9 @@ enum FormatSegmentKind {
 
 	/**
 		Single identifier interpolation, e.g. `$name`.
+		Position points to the identifier after the `$`.
 	**/
-	FIdent(i:String);
+	FIdent(i:String, pos:Position);
 
 	/**
 		Expression interpolation, e.g. `${name.toUpperCase()}`.

+ 4 - 4
std/haxe/macro/ExprTools.hx

@@ -131,7 +131,7 @@ class ExprTools {
 			case EFormat(parts):
 				for (part in parts) switch part.kind {
 					case FRaw(_):
-					case FIdent(i): f({pos: part.pos, expr: EConst(CIdent(i))});
+					case FIdent(i,pos): f({pos: pos, expr: EConst(CIdent(i))});
 					case FExpr(e): f(e);
 				}
 		}
@@ -217,15 +217,15 @@ class ExprTools {
 			case EFormat(parts):
 				EFormat([for (part in parts) switch part.kind {
 					case FRaw(_): part;
-					case FIdent(i):
-						var efake = {pos: part.pos, expr: EConst(CIdent(i))};
+					case FIdent(i,pos):
+						var efake = {pos: pos, expr: EConst(CIdent(i))};
 						var enew = f(efake);
 						if (enew == efake)
 							part
 						else {
 							pos: part.pos,
 							kind: switch enew.expr {
-								case EConst(CIdent(i)): FIdent(i);
+								case EConst(CIdent(i)): FIdent(i, enew.pos);
 								case _: FExpr(enew);
 							}
 						}

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

@@ -231,7 +231,7 @@ class Printer {
 		case EMeta(meta, e1): printMetadata(meta) + " " +printExpr(e1);
 		case EFormat(parts): [for (part in parts) switch part.kind {
 			case FRaw(s): s;
-			case FIdent(s): '$$$s';
+			case FIdent(s,_): '$$$s';
 			case FExpr(e): '$${${printExpr(e)}}';
 		}].join("");
 	}

+ 1 - 1
tests/unit/src/unit/issues/Issue5803.hx

@@ -5,7 +5,7 @@ class Issue5803 extends Test {
 		var expr = macro 'a: $a';
 		t(expr.expr.match(EFormat([
 			{kind: FRaw("a: ")},
-			{kind: FIdent("a")}
+			{kind: FIdent("a",_)}
 		])));
 
 		var expr = macro 'a: ${a}';