Răsfoiți Sursa

Improved syntax of with-statement
WITH x: A DO
| x: B DO
ELSE
END;

replaced by

WITH x: A DO
| B DO
ELSE
END;

Improved implementation by reading the source variable x only once into a register.

git-svn-id: https://svn.inf.ethz.ch/svn/lecturers/a2/trunk@8336 8c9fc860-2736-0410-a75d-ab315db34111

felixf 7 ani în urmă
părinte
comite
3d126198fb

+ 1 - 1
source/FoxDocumentationBackend.Mod

@@ -224,7 +224,7 @@ TYPE
 
 		PROCEDURE Type*(x: SyntaxTree.Type);
 		BEGIN
-			IF x # NIL THEN x.Accept(SELF) END;
+			IF x # NIL THEN VType(x) END;
 		END Type;
 
 		PROCEDURE VisitType*(x: SyntaxTree.Type);

+ 8 - 8
source/FoxFingerPrinter.Mod

@@ -325,7 +325,7 @@ TYPE
 
 		PROCEDURE VisitQualifiedType*(x: SyntaxTree.QualifiedType);
 		BEGIN
-			x.resolved.Accept(SELF);
+			VType(x.resolved);
 		END VisitQualifiedType;
 
 		(*
@@ -369,7 +369,7 @@ TYPE
 				fingerprint.public := fingerprint.shallow;
 				fingerprint.deepAvailable := TRUE; (* to avoid circles during base finger printing *)
 				x.SetFingerPrint(fingerprint);
-				x.arrayBase.Accept(SELF); (* make sure that base pointer is also deeply fped *)
+				VType(x.arrayBase); (* make sure that base pointer is also deeply fped *)
 			END;
 
 			IF Trace THEN TraceExit("ArrayType",fingerprint) END;
@@ -415,7 +415,7 @@ TYPE
 			END;
 
 			IF deep & ~fingerprint.deepAvailable THEN
-				x.arrayBase.Accept(SELF);
+				VType(x.arrayBase);
 				fingerprint.private := fingerprint.shallow;
 				fingerprint.public := fingerprint.shallow;
 				fingerprint.deepAvailable := TRUE;
@@ -878,7 +878,7 @@ TYPE
 		BEGIN
 			INC(level); ASSERT(level <= 100);
 			IF t = NIL THEN FPNumber(fp,fpTypeNone);
-			ELSE t.Accept(SELF); FPNumber(fp,SELF.fingerprint.shallow);
+			ELSE VType(t); FPNumber(fp,SELF.fingerprint.shallow);
 			END;
 			DEC(level);
 		END FPType;
@@ -989,7 +989,7 @@ TYPE
 				FPName(fp,x.name);
 				IF Trace THEN TraceIndent; D.String("access="); D.Set(x.access); D.Ln;  END;
 				FPVisibility(fp, x.access);
-				x.declaredType.Accept(SELF);
+				VType(x.declaredType);
 				FPNumber(fp, SELF.fingerprint.shallow);
 				fingerprint.shallow := fp;
 				fingerprint.public := fp;
@@ -1064,7 +1064,7 @@ TYPE
 				Global.GetSymbolName(x,name);
 				FPString(fp,name);
 				FPVisibility(fp,x.access);
-				x.type.Accept(SELF);
+				VType(x.type);
 				FPNumber(fp,SELF.fingerprint.shallow);
 				fingerprint.shallow := fp;
 				fingerprint.public := fingerprint.shallow;
@@ -1098,7 +1098,7 @@ TYPE
 				Global.GetSymbolName(x,name);
 				FPString(fp,name);
 				FPVisibility(fp,x.access);
-				x.type.Accept(SELF);
+				VType(x.type);
 				FPNumber(fp,SELF.fingerprint.shallow);
 				fingerprint.shallow := fp;
 				fingerprint.public := fingerprint.shallow;
@@ -1275,7 +1275,7 @@ TYPE
 
 			deep := SELF.deep;
 			SELF.deep := TRUE;
-			this.Accept(SELF);
+			VType(this);
 			SELF.deep := deep;
 			ASSERT(fingerprint.deepAvailable,101);
 			ASSERT(fingerprint.shallow #0,102);

+ 41 - 25
source/FoxIntermediateBackend.Mod

@@ -203,7 +203,7 @@ TYPE
 
 		PROCEDURE Type(x: SyntaxTree.Type);
 		BEGIN
-			x.Accept(SELF);
+			VType(x);
 		END Type;
 
 		(** types **)
@@ -2460,7 +2460,7 @@ TYPE
 		END VisitUnaryExpression;
 
 		(* test if e is of type type, side effect: result of evaluation of e stays in the operand *)
-		PROCEDURE TypeTest(tag: IntermediateCode.Operand; type: SyntaxTree.Type; trueL,falseL: Label);
+		PROCEDURE TypeTest(tag: IntermediateCode.Operand; type: SyntaxTree.Type; trueL,falseL: Label; withPart: BOOLEAN);
 		VAR left,right: IntermediateCode.Operand; level,offset: LONGINT; repeatL: Label; originalType: SyntaxTree.Type;
 		BEGIN
 			type := type.resolved;
@@ -2477,7 +2477,11 @@ TYPE
 				(*
 				IntermediateCode.MakeMemory(tag,addressType); (*! already done during generation *)
 				*)
-				ReuseCopy(left,tag);
+				IF withPart THEN
+					left := tag;
+				ELSE
+					ReuseCopy(left,tag);
+				END;
 				right := TypeDescriptorAdr(type);
 				
 				IF backend.cooperative THEN
@@ -2504,8 +2508,11 @@ TYPE
 					IntermediateCode.MakeMemory(left,addressType);
 					BreqL(trueL,left,right);
 				END;
-				ReleaseIntermediateOperand(left); ReleaseIntermediateOperand(right);
-				BrL(falseL);
+				IF ~withPart THEN
+					ReleaseIntermediateOperand(left); 
+				END;
+				ReleaseIntermediateOperand(right);
+				IF falseL # NIL THEN BrL(falseL) END;
 			END;
 		END TypeTest;
 
@@ -3582,7 +3589,7 @@ TYPE
 					ELSE
 						Designate(x.left,left);
 					END;
-					TypeTest(left.tag,x.right(SyntaxTree.SymbolDesignator).symbol(SyntaxTree.TypeDeclaration).declaredType.resolved,trueLabel,falseLabel);
+					TypeTest(left.tag,x.right(SyntaxTree.SymbolDesignator).symbol(SyntaxTree.TypeDeclaration).declaredType.resolved,trueLabel,falseLabel,FALSE);
 					ReleaseOperand(left);
 				END;
 			|Scanner.Plus:
@@ -9365,7 +9372,7 @@ TYPE
 					tag := result.tag;
 					UseIntermediateOperand(tag);
 				END;
-				TypeTest(tag,x.type,trueL,falseL);
+				TypeTest(tag,x.type,trueL,falseL,FALSE);
 				ReleaseIntermediateOperand(tag);
 				SetLabel(falseL);
 				EmitTrap(position,TypeCheckTrap);
@@ -10579,35 +10586,44 @@ TYPE
 			IF Trace THEN TraceExit("VisitIfStatement") END;
 		END VisitIfStatement;
 
-		PROCEDURE WithPart(x: SyntaxTree.WithPart; VAR falseL, endL: Label);
-		VAR trueL: Label; res: Operand; recordType: SyntaxTree.RecordType;
+		PROCEDURE BrWithPart(CONST tag: IntermediateCode.Operand; x: SyntaxTree.WithPart; VAR trueL: Label);
 		BEGIN
-			(*IF x.variable.type.resolved = x.type.resolved THEN
-				(* always true, do nothing *)
-			ELSE*)
-			Designate(x.variable,res);
-			IF IsPointerToRecord(x.variable.type,recordType) THEN
-				Dereference(res,recordType,IsUnsafePointer(x.variable.type))
-			END;
 			trueL := NewLabel();
-			TypeTest(res.tag,x.type,trueL,falseL);
-			ReleaseOperand(res);
-			SetLabel(trueL);
+			TypeTest(tag, x.type, trueL, NIL,TRUE);
+		END BrWithPart;
+		
+		PROCEDURE EmitWithPart(x: SyntaxTree.WithPart);
+		BEGIN
 			StatementSequence(x.statements);
-			BrL(endL);
-		END WithPart;
+		END EmitWithPart;
 
 		PROCEDURE VisitWithStatement*(x: SyntaxTree.WithStatement);
-		VAR endL,falseL: Label;i: LONGINT;
+		VAR endL,elseL: Label;i: LONGINT; trueL: POINTER TO ARRAY OF Label; res: Operand; recordType: SyntaxTree.RecordType;
+			tag: IntermediateCode.Operand;
 		BEGIN
 			IF Trace THEN TraceEnter("VisitWithStatement") END;
 
 			endL := NewLabel();
+			elseL := NewLabel();
+			
+			Designate(x.variable,res);
+			IF IsPointerToRecord(x.variable.type,recordType) THEN
+				Dereference(res,recordType,IsUnsafePointer(x.variable.type))
+			END;
+			ReuseCopy(tag, res.tag);
+			ReleaseOperand(res);
+			NEW(trueL, x.WithParts());
 			FOR i := 0 TO x.WithParts()-1 DO
-				falseL := NewLabel();
-				WithPart(x.GetWithPart(i),falseL,endL);
-				SetLabel(falseL);
+				BrWithPart(tag, x.GetWithPart(i), trueL[i]); 
 			END;
+			ReleaseIntermediateOperand(tag);
+			BrL(elseL);			
+			FOR i := 0 TO x.WithParts()-1 DO
+				SetLabel(trueL[i]);
+				EmitWithPart(x.GetWithPart(i)); 
+				BrL(endL);
+			END;					
+			SetLabel(elseL);
 			IF x.elsePart = NIL THEN
 				IF ~isUnchecked THEN
 					EmitTrap(position,WithTrap);

+ 1 - 1
source/FoxInterpreter.Mod

@@ -643,7 +643,7 @@ TYPE
 		
 		PROCEDURE FindType(type: SyntaxTree.Type): Result;
 		BEGIN
-			type.Accept(SELF);
+			VType(type);
 			IF item.object # NIL THEN
 				RETURN item.object(Result);
 			END;

+ 14 - 7
source/FoxParser.Mod

@@ -1170,19 +1170,26 @@ TYPE
 					withStatement := SyntaxTree.NewWithStatement( symbol.position ,outer);
 					CommentStatement(withStatement);
 					NextSymbol;
+
+					identifier := Identifier(position);
+					IF Optional(Scanner.Period) & Optional(Scanner.Identifier) THEN
+						Error(position,Basic.InvalidCode,"forbidden qualified identifier in with statement");
+					END;
+					designator := SyntaxTree.NewIdentifierDesignator(position,identifier);
+					withStatement.SetVariable(designator);
+					Check( Scanner.Colon );
+
+					IF Optional(Scanner.Bar) THEN (* ignore *) END;
 					REPEAT
-						identifier := Identifier(position);
-						IF Optional(Scanner.Period) & Optional(Scanner.Identifier) THEN
-							Error(position,Basic.InvalidCode,"forbidden qualified identifier in with statement");
-						END;
 						withPart := SyntaxTree.NewWithPart();
 						withPart.SetPosition(symbol.position);
 						CommentWithPart(withPart);
 						withStatement.AddWithPart(withPart);
-						designator := SyntaxTree.NewIdentifierDesignator(position,identifier);
-						withPart.SetVariable( designator );
-						Check( Scanner.Colon );
 						qualifiedIdentifier := QualifiedIdentifier();
+						IF Optional(Scanner.Colon) THEN (* compatibility with old format *)
+							Basic.Warning(diagnostics, scanner.source^, position, "deprecate form of with statement, remove the repeated variable");
+							qualifiedIdentifier := QualifiedIdentifier();
+						END;
 						qualifiedType := SyntaxTree.NewQualifiedType(qualifiedIdentifier.position, currentScope, qualifiedIdentifier);
 						withPart.SetType(qualifiedType);
 						Check( Scanner.Do );

+ 3 - 3
source/FoxPrintout.Mod

@@ -86,7 +86,7 @@ TYPE
 			IF x= NIL THEN
 				AlertString("nil type");
 			ELSE
-				x.Accept(SELF);
+				VType(x);
 			END;
 		END Type;
 
@@ -1573,8 +1573,6 @@ TYPE
 		PROCEDURE WithPart(x: SyntaxTree.WithPart);
 		BEGIN
 			Comments(x.comment, x, FALSE);
-			Expression(x.variable);
-			w.String(" : ");
 			Type(x.type);
 			Keyword(" DO " );
 			Comments(x.comment,x, TRUE);
@@ -1585,6 +1583,8 @@ TYPE
 		VAR i: LONGINT;
 		BEGIN
 			Indent; Keyword("WITH " );
+			Expression(x.variable);
+			w.String(" : ");
 			WithPart(x.GetWithPart(0));
 			FOR i := 1 TO x.WithParts()-1 DO
 				Indent; w.String("| ");

+ 26 - 13
source/FoxSemanticChecker.Mod

@@ -1678,7 +1678,7 @@ TYPE
 			prev := resolvedType;
 			resolvedType := SyntaxTree.invalidType;
 			IF x = NIL THEN resolvedType := NIL
-			ELSE x.Accept(SELF); ASSERT(resolvedType # NIL); (* in error cases it must be invalidType *)
+			ELSE VType(x); ASSERT(resolvedType # NIL); (* in error cases it must be invalidType *)
 			END;
 			resolved := resolvedType;
 			resolvedType := prev;
@@ -7697,20 +7697,16 @@ TYPE
 			currentIsUnreachable := prevUnreachable;
 		END VisitIfStatement;
 
-		PROCEDURE WithPart(withPart: SyntaxTree.WithPart; VAR symbol: SyntaxTree.Symbol);
-		VAR variable: SyntaxTree.Designator;
+		PROCEDURE WithPart(withPart: SyntaxTree.WithPart; variable: SyntaxTree.Designator);
+		VAR 
 			type,variableType: SyntaxTree.Type;
 			withEntry: WithEntry;
+			symbol: SyntaxTree.Symbol
 		BEGIN
-			variable := ResolveDesignator(withPart.variable);
-			variableType := variable.type.resolved;
-			withPart.SetVariable(variable);
 			type := ResolveType(withPart.type);
 			withPart.SetType(type);
+			variableType := variable.type.resolved;
 
-			WHILE variable IS SyntaxTree.TypeGuardDesignator DO
-				variable := variable(SyntaxTree.TypeGuardDesignator).left(SyntaxTree.Designator);
-			END;
 
 			IF (type.resolved = SyntaxTree.invalidType) OR (variableType = SyntaxTree.invalidType) THEN (* error already reported *)
 			ELSIF ~(type.resolved = variableType) & ~IsExtensibleDesignator(variable) THEN
@@ -7758,12 +7754,29 @@ TYPE
 				WITH variable: type DO ... END; 	--> IF ~(variable IS type) THEN HALT(withTrap) ELSE ... END;
 		**)
 		PROCEDURE VisitWithStatement*(withStatement: SyntaxTree.WithStatement);
-		VAR i: LONGINT; prevScope: SyntaxTree.Scope; symbol: SyntaxTree.Symbol;
+		VAR i,j: LONGINT; prevScope: SyntaxTree.Scope; variable: SyntaxTree.Designator;
 		BEGIN
-			prevScope := currentScope; symbol := NIL;
+			prevScope := currentScope;
+			
+			variable := ResolveDesignator(withStatement.variable);
+			withStatement.SetVariable(variable);
+			WHILE variable IS SyntaxTree.TypeGuardDesignator DO
+				variable := variable(SyntaxTree.TypeGuardDesignator).left(SyntaxTree.Designator);
+			END;
+
+
 			FOR i := 0 TO withStatement.WithParts()-1 DO
-				WithPart(withStatement.GetWithPart(i),symbol);
+				WithPart(withStatement.GetWithPart(i),variable);
 			END;
+
+			FOR i := 0 TO withStatement.WithParts()-1 DO
+				FOR j := i+1 TO withStatement.WithParts()-1 DO
+					IF IsTypeExtension(withStatement.GetWithPart(i).type, withStatement.GetWithPart(j).type) THEN
+						Error(withStatement.GetWithPart(j).position, "unreachable extended type");
+					END;
+				END;
+			END;
+			
 			IF withStatement.elsePart # NIL THEN
 				StatementSequence(withStatement.elsePart)
 			END;
@@ -8783,7 +8796,7 @@ TYPE
 
 		(** types *)
 		PROCEDURE Type(x: SyntaxTree.Type);
-		BEGIN x.Accept(SELF)
+		BEGIN VType(x)
 		END Type;
 
 		PROCEDURE VisitType*(x: SyntaxTree.Type);

+ 128 - 10
source/FoxSyntaxTree.Mod

@@ -150,6 +150,37 @@ TYPE
 
 		PROCEDURE VisitProcedureType*(x: ProcedureType);
 		BEGIN HALT(100) (* abstract *) END VisitProcedureType;
+		
+		PROCEDURE VType*(x: Type);
+		BEGIN
+			(*x.Accept(SELF); RETURN;*)
+			WITH x: ProcedureType DO VisitProcedureType(x)
+			|x: CellType DO VisitCellType(x)
+			|x: RecordType DO VisitRecordType(x)
+			|x: PortType DO VisitPortType(x)
+			|x: PointerType DO VisitPointerType(x)
+			|x: MathArrayType DO VisitMathArrayType(x)
+			|x: ArrayType DO VisitArrayType(x)
+			|x: RangeType DO VisitRangeType(x)
+			|x: EnumerationType DO VisitEnumerationType(x)
+			|x: StringType DO VisitStringType(x)
+			|x: QualifiedType DO VisitQualifiedType(x)
+			|x: ComplexType DO VisitComplexType(x)
+			|x: FloatType DO VisitFloatType(x)
+			|x: IntegerType DO VisitIntegerType(x)
+			|x: CharacterType DO VisitCharacterType(x)
+			|x: SetType DO VisitSetType(x)
+			|x: BooleanType DO VisitBooleanType(x)
+			|x: SizeType DO VisitSizeType(x)
+			|x: AddressType DO VisitAddressType(x)
+			|x: NilType DO VisitNilType(x)
+			|x: ObjectType DO VisitObjectType(x)
+			|x: AnyType DO VisitAnyType(x)
+			|x: ByteType DO VisitByteType(x)
+			|x: BasicType DO VisitBasicType(x)
+			ELSE VisitType(x)
+			END;
+		END VType;
 
 		(** expressions *)
 		PROCEDURE VisitExpression*(x: Expression);
@@ -259,6 +290,49 @@ TYPE
 		PROCEDURE VisitEnumerationValue*(x: EnumerationValue);
 		BEGIN HALT(100) (* abstract *) END VisitEnumerationValue;
 
+		PROCEDURE VExpression*(x: Expression);
+		BEGIN
+			x.Accept(SELF); RETURN;
+			WITH 
+			  x: ResultDesignator DO VisitResultDesignator(x)
+			| x: SelfDesignator DO VisitSelfDesignator(x)
+			| x: SupercallDesignator DO VisitSupercallDesignator(x)
+			| x: DereferenceDesignator DO VisitDereferenceDesignator(x)
+			| x: TypeGuardDesignator DO VisitTypeGuardDesignator(x)
+			| x: BuiltinCallDesignator DO VisitBuiltinCallDesignator(x)
+			| x: StatementDesignator DO VisitStatementDesignator(x)
+			| x: ProcedureCallDesignator DO VisitProcedureCallDesignator(x)
+			| x: IndexDesignator DO VisitIndexDesignator(x)
+			| x: SymbolDesignator DO VisitSymbolDesignator(x)
+			| x: BracketDesignator DO VisitBracketDesignator(x)
+			| x: ArrowDesignator DO VisitArrowDesignator(x)
+			| x: ParameterDesignator DO VisitParameterDesignator(x)
+			| x: SelectorDesignator DO VisitSelectorDesignator(x)
+			| x: IdentifierDesignator DO VisitIdentifierDesignator(x)
+			| x: Designator DO VisitDesignator(x)
+			| x: Conversion DO VisitConversion(x)
+			| x: TensorRangeExpression DO VisitTensorRangeExpression(x)
+			| x: RangeExpression DO VisitRangeExpression(x)
+			| x: BinaryExpression DO VisitBinaryExpression(x)
+			| x: UnaryExpression DO VisitUnaryExpression(x)
+			| x: MathArrayExpression DO VisitMathArrayExpression(x)
+			| x: Set DO VisitSet(x)
+			| x: BooleanValue DO VisitBooleanValue(x)
+			| x: IntegerValue DO VisitIntegerValue(x)
+			| x: CharacterValue DO VisitCharacterValue(x)
+			| x: SetValue DO VisitSetValue(x)
+			| x: MathArrayValue DO VisitMathArrayValue(x)
+			| x: RealValue DO VisitRealValue(x)
+			| x: ComplexValue DO VisitComplexValue(x)
+			| x: StringValue DO VisitStringValue(x)
+			| x: NilValue DO VisitNilValue(x)
+			| x: EnumerationValue DO VisitEnumerationValue(x);
+			| x: Value DO VisitValue(x);
+			ELSE
+				VisitExpression(x)
+			END;		
+		END VExpression;
+
 		(** symbols *)
 		PROCEDURE VisitSymbol*(x: Symbol);
 		BEGIN HALT(100) (* abstract *) END VisitSymbol;
@@ -292,7 +366,26 @@ TYPE
 
 		PROCEDURE VisitImport*(x: Import);
 		BEGIN HALT(100) (* abstract *) END VisitImport;
-
+		
+		PROCEDURE VSymbol*(x: Symbol);
+		BEGIN
+			x.Accept(SELF); RETURN;
+			WITH 
+			  x: Module DO VisitModule(x)
+			| x: TypeDeclaration DO VisitTypeDeclaration(x)
+			| x: Constant DO VisitConstant(x)
+			| x: Parameter DO VisitParameter(x)
+			| x: Property DO VisitProperty(x)
+			| x: Variable DO VisitVariable(x)
+			| x: Operator DO VisitOperator(x)
+			| x: Procedure DO VisitProcedure(x)
+			| x: Builtin DO VisitBuiltin(x)
+			| x: Import DO VisitImport(x)
+			ELSE 
+				VisitSymbol(x)
+			END;
+		END VSymbol;
+	
 		(** statements *)
 		PROCEDURE VisitStatement*(x: Statement);
 		BEGIN HALT(100) (* abstract *) END VisitStatement;
@@ -344,7 +437,31 @@ TYPE
 
 		PROCEDURE VisitCode*(x: Code);
 		BEGIN HALT(100) (* abstract *) END VisitCode;
-
+		
+		PROCEDURE VStatement*(x: Statement);
+		BEGIN
+			x.Accept(SELF); RETURN;
+			WITH 
+			x: ProcedureCallStatement DO VisitProcedureCallStatement(x)
+			| x: Assignment DO VisitAssignment(x)
+			| x: CommunicationStatement DO VisitCommunicationStatement(x)
+			| x: IfStatement DO VisitIfStatement(x)
+			| x: WithStatement DO VisitWithStatement(x)
+			| x: CaseStatement DO VisitCaseStatement(x)
+			| x: WhileStatement DO VisitWhileStatement(x)
+			| x: RepeatStatement DO VisitRepeatStatement(x)
+			| x: ForStatement DO VisitForStatement(x)
+			| x: LoopStatement DO VisitLoopStatement(x)
+			| x: ExitableBlock DO VisitExitableBlock(x)
+			| x: ExitStatement DO VisitExitStatement(x)
+			| x: ReturnStatement DO VisitReturnStatement(x)
+			| x: AwaitStatement DO VisitAwaitStatement(x)
+			| x: StatementBlock DO VisitStatementBlock(x)
+			| x: Code DO VisitCode(x)
+			ELSE VisitStatement(x)
+			END;
+		END VStatement;
+		
 	END Visitor;
 
 	ArrayAccessOperators* = RECORD
@@ -3946,7 +4063,6 @@ TYPE
 
 	WithPart*= OBJECT (Part)
 	VAR
-		variable-: Designator;
 		type-: Type; (* initially is qualified type *)
 		statements-: StatementSequence;
 
@@ -3955,14 +4071,9 @@ TYPE
 		PROCEDURE &InitWithPart();
 		BEGIN
 			InitPart();
-			type := NIL; variable := NIL; statements := NIL; comment := NIL;
+			type := NIL; statements := NIL; comment := NIL;
 		END InitWithPart;
 
-		PROCEDURE SetVariable*( variable: Designator);
-		BEGIN
-			SELF.variable := variable
-		END SetVariable;
-
 		PROCEDURE SetType*( type: Type );
 		BEGIN
 			SELF.type := type
@@ -3981,7 +4092,6 @@ TYPE
 		VAR copy: WithPart;
 		BEGIN
 			NEW(copy);
-			copy.SetVariable(CloneDesignator(variable));
 			copy.SetType(type);
 			copy.SetStatements(CloneStatementSequence(statements));
 			RETURN copy
@@ -3992,6 +4102,7 @@ TYPE
 	(** << WITH variable : type DO statements END >> **)
 	WithStatement* = OBJECT (Statement)
 		VAR
+			variable-: Designator;
 			withParts-: Basic.List;
 			elsePart-: StatementSequence;
 
@@ -3999,8 +4110,14 @@ TYPE
 		BEGIN
 			InitStatement( position,outer );
 			NEW(withParts,4); elsePart := NIL;
+			variable := NIL;
 		END InitWithStatement;
 
+		PROCEDURE SetVariable*( variable: Designator);
+		BEGIN
+			SELF.variable := variable
+		END SetVariable;
+
 		PROCEDURE AddWithPart*( withPart: WithPart );
 		BEGIN withParts.Add( withPart );
 		END AddWithPart;
@@ -4027,6 +4144,7 @@ TYPE
 			FOR i := 0 TO WithParts()-1 DO
 				copy.AddWithPart(GetWithPart(i).Clone());
 			END;
+			copy.SetVariable(CloneDesignator(variable));
 			copy.SetElsePart(CloneStatementSequence(elsePart));
 			RETURN copy
 		END Clone;

+ 1 - 1
source/FoxTranspilerBackend.Mod

@@ -978,7 +978,7 @@ TYPE
 			FOR i := 0 TO statement.WithParts () - 1 DO
 				withPart := statement.GetWithPart (i); PrintIndent;
 				IF i > 0 THEN writer.String ("else ") END;
-				writer.String ("if ("); CompareTypeDescriptor (withPart.variable, withPart.type); writer.String (")"); writer.Ln;
+				writer.String ("if ("); CompareTypeDescriptor (statement.variable, withPart.type); writer.String (")"); writer.Ln;
 				BeginBlock; PrintStatements (withPart.statements); EndBlock;
 			END;
 			PrintIndent;