浏览代码

Added rich position to Scanner / Syntax Tree Elements
Not yet finished but preliminarily working

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

felixf 8 年之前
父节点
当前提交
1f8e6977a5

+ 5 - 3
source/FoxARMAssembler.Mod

@@ -1,6 +1,6 @@
 MODULE FoxARMAssembler; (** AUTHOR ""; PURPOSE ""; *)
 
-IMPORT InstructionSet := FoxARMInstructionSet, FoxAssembler,  (*D := Debugging,*) Scanner := FoxScanner, Diagnostics, Strings;
+IMPORT InstructionSet := FoxARMInstructionSet, FoxAssembler,  (*D := Debugging,*) Scanner := FoxScanner, Diagnostics, Strings, Basic := FoxBasic;
 
 CONST Trace = FoxAssembler.Trace;
 
@@ -169,7 +169,8 @@ TYPE
 		VAR
 			instruction: InstructionSet.Instruction;
 			operands: ARRAY InstructionSet.MaxOperands OF InstructionSet.Operand;
-			position, opCode, condition, i, operandNumber: LONGINT;
+			position: Basic.Position; 
+			opCode, condition, i, operandNumber: LONGINT;
 			flags: SET;
 			newOperandExpected: BOOLEAN;
 			result: FoxAssembler.Result;
@@ -182,7 +183,8 @@ TYPE
 			VAR
 				operand: InstructionSet.Operand;
 				indexingMode, fields: SET;
-				registerNumber, offsetRegisterNumber, shiftModeNumber, shiftRegisterNumber, shiftImmediateValue, position, offsetImmediateValue, value: LONGINT;
+				registerNumber, offsetRegisterNumber, shiftModeNumber, shiftRegisterNumber, shiftImmediateValue, offsetImmediateValue, value: LONGINT;
+				position: Basic.Position;
 				isImmediateOffset, bracketIsOpen: BOOLEAN;
 				registerList: SET;
 			BEGIN

+ 5 - 5
source/FoxARMBackend.Mod

@@ -3425,7 +3425,7 @@ TYPE
 			parameter: SyntaxTree.Parameter;
 
 			PROCEDURE New;
-			BEGIN procedureType := SyntaxTree.NewProcedureType(-1, NIL)
+			BEGIN procedureType := SyntaxTree.NewProcedureType(Basic.invalidPosition, NIL)
 			END New;
 
 			PROCEDURE BoolRet;
@@ -3438,25 +3438,25 @@ TYPE
 
 			PROCEDURE IntPar;
 			BEGIN
-				parameter := SyntaxTree.NewParameter(-1, procedureType, SyntaxTree.NewIdentifier(""), SyntaxTree.ValueParameter);
+				parameter := SyntaxTree.NewParameter(Basic.invalidPosition, procedureType, SyntaxTree.NewIdentifier(""), SyntaxTree.ValueParameter);
 				parameter.SetType(Global.Integer32); procedureType.AddParameter(parameter)
 			END IntPar;
 
 			PROCEDURE AddressPar;
 			BEGIN
-				parameter := SyntaxTree.NewParameter(-1, procedureType, SyntaxTree.NewIdentifier(""), SyntaxTree.ValueParameter);
+				parameter := SyntaxTree.NewParameter(Basic.invalidPosition, procedureType, SyntaxTree.NewIdentifier(""), SyntaxTree.ValueParameter);
 				parameter.SetType(Global.Unsigned32); procedureType.AddParameter(parameter)
 			END AddressPar;
 
 			PROCEDURE IntVarPar;
 			BEGIN
-				parameter := SyntaxTree.NewParameter(-1, procedureType, SyntaxTree.NewIdentifier(""), SyntaxTree.VarParameter);
+				parameter := SyntaxTree.NewParameter(Basic.invalidPosition, procedureType, SyntaxTree.NewIdentifier(""), SyntaxTree.VarParameter);
 				parameter.SetType(Global.Integer32); procedureType.AddParameter(parameter)
 			END IntVarPar;
 
 			PROCEDURE RealVarPar;
 			BEGIN
-				parameter := SyntaxTree.NewParameter(-1, procedureType, SyntaxTree.NewIdentifier(""), SyntaxTree.VarParameter);
+				parameter := SyntaxTree.NewParameter(Basic.invalidPosition, procedureType, SyntaxTree.NewIdentifier(""), SyntaxTree.VarParameter);
 				parameter.SetType(Global.Float32); procedureType.AddParameter(parameter)
 			END RealVarPar;
 

+ 26 - 25
source/FoxAssembler.Mod

@@ -27,6 +27,7 @@ CONST
 
 TYPE
 	OperandString=ARRAY 256 OF CHAR;
+	Position= Basic.Position;
 
 	FixupElement=POINTER TO RECORD
 		fixup: BinaryCode.Fixup; next: FixupElement;
@@ -155,7 +156,7 @@ TYPE
 	VAR
 		diagnostics: Diagnostics.Diagnostics;
 		error-: BOOLEAN;
-		errorPosition-: LONGINT;
+		errorPosition-: Position;
 		symbol-: Scanner.Symbol;
 		scanner: Scanner.AssemblerScanner;
 		orgOffset: LONGINT;
@@ -169,7 +170,7 @@ TYPE
 
 		PROCEDURE &Init*(diagnostics: Diagnostics.Diagnostics);
 		BEGIN
-			SELF.diagnostics := diagnostics; errorPosition := Diagnostics.Invalid; orgOffset := 0;
+			SELF.diagnostics := diagnostics; errorPosition := Basic.invalidPosition; orgOffset := 0;
 		END Init;
 
 		PROCEDURE SetContext(CONST context: Scanner.Context);
@@ -177,21 +178,21 @@ TYPE
 			scanner.SetContext(context); NextSymbol;
 		END SetContext;
 
-		PROCEDURE Error*(pos: LONGINT; CONST msg: ARRAY OF CHAR);
+		PROCEDURE Error*(pos: SyntaxTree.Position; CONST msg: ARRAY OF CHAR);
 		BEGIN
 			error := TRUE;
 			IF diagnostics # NIL THEN
-				diagnostics.Error(scanner.source^,pos,Diagnostics.Invalid,msg);
+				diagnostics.Error(scanner.source^,pos.start,Diagnostics.Invalid,msg);
 			END;
 		END Error;
 
-		PROCEDURE ErrorSS*(pos: LONGINT; CONST s1,s2: ARRAY OF CHAR);
+		PROCEDURE ErrorSS*(pos: SyntaxTree.Position; CONST s1,s2: ARRAY OF CHAR);
 		VAR msg: Basic.MessageString;
 		BEGIN COPY(s1,msg); Strings.Append(msg,s2); Error(pos, msg);
 		END ErrorSS;
 
 		PROCEDURE NextSymbol*;
-		BEGIN error := error OR ~scanner.GetNextSymbol(symbol); errorPosition := symbol.start;
+		BEGIN error := error OR ~scanner.GetNextSymbol(symbol); errorPosition := symbol.position;
 		END NextSymbol;
 
 		PROCEDURE ThisToken*(x: LONGINT): BOOLEAN;
@@ -199,9 +200,9 @@ TYPE
 			IF ~error & (symbol.token = x) THEN NextSymbol; RETURN TRUE ELSE RETURN FALSE END;
 		END ThisToken;
 
-		PROCEDURE GetIdentifier*(VAR pos: LONGINT; VAR identifier: ARRAY OF CHAR): BOOLEAN;
+		PROCEDURE GetIdentifier*(VAR pos: Position; VAR identifier: ARRAY OF CHAR): BOOLEAN;
 		BEGIN
-			pos := symbol.start;
+			pos := symbol.position;
 			IF symbol.token # Scanner.Identifier THEN RETURN FALSE
 			ELSE COPY(symbol.identifierString,identifier); NextSymbol; RETURN TRUE
 			END;
@@ -212,7 +213,7 @@ TYPE
 			IF ~error & (symbol.token = Scanner.Identifier) & (this = symbol.identifierString) THEN NextSymbol; RETURN TRUE ELSE RETURN FALSE END;
 		END ThisIdentifier;
 
-		PROCEDURE ExpectIdentifier*(VAR pos: LONGINT; VAR identifier: ARRAY OF CHAR): BOOLEAN;
+		PROCEDURE ExpectIdentifier*(VAR pos: Position; VAR identifier: ARRAY OF CHAR): BOOLEAN;
 		BEGIN
 			IF ~GetIdentifier(pos,identifier)THEN Error(errorPosition,"identifier expected"); RETURN FALSE
 			ELSE RETURN TRUE
@@ -241,7 +242,7 @@ TYPE
 		END ExpectConstantInteger;
 
 		PROCEDURE Section;
-		VAR sectionType: Scanner.IdentifierString; pos: LONGINT;
+		VAR sectionType: Scanner.IdentifierString; pos: Position;
 		BEGIN
 			IF ExpectToken(Scanner.Period) THEN
 				IF ExpectIdentifier(pos,sectionType) THEN
@@ -257,7 +258,7 @@ TYPE
 			END;
 		END Section;
 
-		PROCEDURE DefineLabel(pos: LONGINT; CONST name: ARRAY OF CHAR);
+		PROCEDURE DefineLabel(pos: Position; CONST name: ARRAY OF CHAR);
 		VAR label: NamedLabel;
 		BEGIN
 			IF Trace THEN D.String("define label: "); D.String(name); D.Ln END;
@@ -270,7 +271,7 @@ TYPE
 			END;
 		END DefineLabel;
 
-		PROCEDURE SetLabel(pos: LONGINT; CONST name: ARRAY OF CHAR);
+		PROCEDURE SetLabel(pos: Position; CONST name: ARRAY OF CHAR);
 		VAR label: NamedLabel;
 		BEGIN
 			IF Trace THEN D.String("set label: "); D.String(name); D.String(" "); D.Int(code.pc,1); D.Ln END;
@@ -287,7 +288,7 @@ TYPE
 			to.fixup := from.fixup;
 		END CopyResult;
 
-		PROCEDURE DefineResult(pos: LONGINT; CONST name: ARRAY OF CHAR; CONST r: Result);
+		PROCEDURE DefineResult(pos: Position; CONST name: ARRAY OF CHAR; CONST r: Result);
 		VAR result: NamedResult;
 		BEGIN
 			IF Trace THEN D.String("define result: "); D.String(name); D.Ln END;
@@ -341,7 +342,7 @@ TYPE
 			RETURN sym
 		END SymbolInScope;
 
-		PROCEDURE ConstantSymbol(pos: LONGINT; constant: SyntaxTree.Constant; VAR result: Result): BOOLEAN;
+		PROCEDURE ConstantSymbol(pos: Position; constant: SyntaxTree.Constant; VAR result: Result): BOOLEAN;
 		BEGIN
 			IF constant.type.resolved IS SyntaxTree.CharacterType THEN
 				result.value := ORD(constant.value.resolved(SyntaxTree.CharacterValue).value);
@@ -368,7 +369,7 @@ TYPE
 		END GetFingerprint;
 
 
-		PROCEDURE NonConstantSymbol(pos: LONGINT; symbol: SyntaxTree.Symbol; VAR result: Result): BOOLEAN;
+		PROCEDURE NonConstantSymbol(pos: Position; symbol: SyntaxTree.Symbol; VAR result: Result): BOOLEAN;
 		VAR
 			name: Basic.SegmentedName; moduleScope: SyntaxTree.Scope; fixupSection: IntermediateCode.Section;
 			fixupPatternList: ObjectFile.FixupPatterns; identifier: ObjectFile.Identifier;
@@ -423,7 +424,7 @@ TYPE
 			RETURN TRUE
 		END NonConstantSymbol;
 
-		PROCEDURE GetNonConstant*(pos: LONGINT; CONST ident: ARRAY OF CHAR; VAR result: Result): BOOLEAN;
+		PROCEDURE GetNonConstant*(pos: Position; CONST ident: ARRAY OF CHAR; VAR result: Result): BOOLEAN;
 		VAR symbol: SyntaxTree.Symbol; namedLabel: NamedLabel;
 			name: Basic.SegmentedName;fixupPatternList: ObjectFile.FixupPatterns;
 			string: ARRAY 256 OF CHAR;
@@ -456,7 +457,7 @@ TYPE
 			END;
 		END GetNonConstant;
 
-		PROCEDURE LocalOffset(pos: LONGINT; symbol: SyntaxTree.Symbol; VAR result: Result): BOOLEAN;
+		PROCEDURE LocalOffset(pos: Position; symbol: SyntaxTree.Symbol; VAR result: Result): BOOLEAN;
 		BEGIN
 			IF symbol.scope IS SyntaxTree.ProcedureScope THEN (* symbol in procedure (local) scope *)
 				IF symbol.scope = scope THEN
@@ -472,7 +473,7 @@ TYPE
 			RETURN FALSE
 		END LocalOffset;
 
-		PROCEDURE GetConstant*(pos: LONGINT; CONST ident: ARRAY OF CHAR; VAR result: Result): BOOLEAN;
+		PROCEDURE GetConstant*(pos: Position; CONST ident: ARRAY OF CHAR; VAR result: Result): BOOLEAN;
 		VAR symbol: SyntaxTree.Symbol; namedResult: NamedResult;
 		BEGIN
 			namedResult := results.Find(ident);
@@ -486,7 +487,7 @@ TYPE
 		END GetConstant;
 
 		PROCEDURE Factor (VAR x: Result; critical: BOOLEAN): BOOLEAN;
-		VAR label: NamedLabel; identifier: Scanner.IdentifierString; pos: LONGINT;
+		VAR label: NamedLabel; identifier: Scanner.IdentifierString; pos: Position;
 		BEGIN
 			IF ThisToken(Scanner.Number) THEN
 				(* ASSERT(symbol.numberType = Scanner.Integer); *)
@@ -614,7 +615,7 @@ TYPE
 		END Expression;
 
 		PROCEDURE Data(CONST ident: ARRAY OF CHAR): BOOLEAN;
-		VAR size,i,nr: LONGINT; x: Result; pos: LONGINT; result: Result; patterns: ObjectFile.FixupPatterns;
+		VAR size,i,nr: LONGINT; x: Result; pos: Position; result: Result; patterns: ObjectFile.FixupPatterns;
 			PROCEDURE Number(ch: CHAR; VAR nr: LONGINT): BOOLEAN;
 			BEGIN
 				IF (ch >= "0") & (ch <="9") THEN
@@ -726,7 +727,7 @@ TYPE
 		PROCEDURE Instruction*(CONST mnemonic: ARRAY OF CHAR);
 		VAR numberOperands: LONGINT;
 
-			PROCEDURE ParseOperand(pos: LONGINT; numberOperand: LONGINT);
+			PROCEDURE ParseOperand(pos: Position; numberOperand: LONGINT);
 			(* stub, must be overwritten by implementation *)
 			VAR operand: OperandString;
 				result: Result; first: BOOLEAN; str: ARRAY 256 OF CHAR;
@@ -773,7 +774,7 @@ TYPE
 		END IgnoreNewLines;
 
 		PROCEDURE DoAssemble();
-		VAR result: Result; line,pos, orgCodePos: LONGINT; identifier: Scanner.IdentifierString; context: Scanner.Context;
+		VAR result: Result; pos: Position; line,orgCodePos: LONGINT; identifier: Scanner.IdentifierString; context: Scanner.Context;
 		BEGIN
 			IF Trace THEN
 				D.Str("DoAssemble: ");
@@ -790,7 +791,7 @@ TYPE
 				IF ThisToken(Scanner.Number) THEN
 					line := symbol.integer;
 					IF ThisToken(Scanner.Colon) THEN (* line number *)
-					ELSE Error(symbol.start,"Identifier expected");
+					ELSE Error(symbol.position,"Identifier expected");
 					END;
 				END;
 				IF ExpectIdentifier(pos,identifier) THEN
@@ -814,7 +815,7 @@ TYPE
 					IF ThisToken(Scanner.Number) THEN
 						line := symbol.integer;
 						IF ThisToken(Scanner.Colon) THEN (* line number *)
-						ELSE Error(symbol.start,"Identifier expected");
+						ELSE Error(symbol.position,"Identifier expected");
 						END;
 					END;
 					IF ExpectIdentifier(pos,identifier) THEN
@@ -870,7 +871,7 @@ TYPE
 		END Assemble;
 
 		PROCEDURE AllSections*;
-		VAR pos: LONGINT; sectionType, sectionName: Scanner.IdentifierString;
+		VAR pos: Position; sectionType, sectionName: Scanner.IdentifierString;
 		BEGIN
 			IF Trace THEN D.String("AllSections"); D.Ln END;
 			SetContext(scanner.startContext);

+ 19 - 0
source/FoxBasic.Mod

@@ -62,6 +62,11 @@ TYPE
 	ErrorMsgs = POINTER TO ARRAY OF StringPool.Index;
 
 	ComparisonFunction = PROCEDURE {DELEGATE} (object1, object2: ANY): BOOLEAN;
+	
+	Position*= RECORD
+		start*, end*, line*, linepos*: LONGINT;
+	END;
+
 
 	List* = OBJECT  (* by Luc Bläser *)
 	VAR
@@ -1697,6 +1702,7 @@ VAR
 	getWriter: WriterFactory;
 	getDiagnostics: DiagnosticsFactory;
 	CRC32Table: ARRAY 256 OF SET;
+	invalidPosition-: Position;
 
 	(* Make a string out of a series of characters. *)
 	PROCEDURE MakeString*( CONST s: ARRAY OF CHAR ): String;
@@ -1735,6 +1741,15 @@ VAR
 		END;
 		Strings.Append(res, msg);
 	END GetErrorMessage;
+	
+	PROCEDURE AppendPosition*(VAR msg: ARRAY OF CHAR; pos: Position);
+	BEGIN
+		Strings.Append(msg, " in line "); 
+		Strings.AppendInt(msg, pos.line); 
+		Strings.Append(msg, ", col "); 
+		Strings.AppendInt(msg, pos.start- pos.linepos);
+	END AppendPosition;
+	
 
 	(** SetErrorMsg - Set message for error n *)
 
@@ -2227,6 +2242,10 @@ BEGIN
 	lists := 0;  enlarged := 0;  strings := 0;
 	emptyString := MakeString("");
 	debug := FALSE;
+	invalidPosition.start := -1;
+	invalidPosition.end := -1;
+	invalidPosition.line := -1;
+	invalidPosition.linepos := -1;
 	NEW(integerObjects, 128);
 END FoxBasic.
 

+ 49 - 49
source/FoxBinarySymbolFile.Mod

@@ -174,7 +174,7 @@ TYPE
 
 		PROCEDURE & InitTypeReference(nr: LONGINT);
 		BEGIN
-			InitType(-1); SELF.nr := nr;
+			InitType(Basic.invalidPosition); SELF.nr := nr;
 		END InitTypeReference;
 
 	END TypeReference;
@@ -491,7 +491,7 @@ TYPE
 			returnType := ResolveType(procedureType.returnType);
 			procedureType.SetReturnType(ResolveType(returnType));
 			IF returnType# NIL THEN
-				parameter := SyntaxTree.NewParameter(-1,procedureType,Global.ReturnParameterName,SyntaxTree.VarParameter);
+				parameter := SyntaxTree.NewParameter(Basic.invalidPosition,procedureType,Global.ReturnParameterName,SyntaxTree.VarParameter);
 				parameter.SetType(returnType);
 				parameter.SetState(SyntaxTree.Resolved);
 				procedureType.SetReturnParameter(parameter);
@@ -710,7 +710,7 @@ TYPE
 					ELSE
 						importedModule := Import(moduleName,importCache);
 						IF importedModule # NIL THEN
-							import := SyntaxTree.NewImport(-1,importedModule.name,importedModule.name,FALSE);
+							import := SyntaxTree.NewImport(Basic.invalidPosition,importedModule.name,importedModule.name,FALSE);
 							import.SetContext(importedModule.context);
 							import.SetModule(importedModule);
 							import.SetState(SyntaxTree.Resolved);
@@ -720,7 +720,7 @@ TYPE
 
 					(* create new import symbol for this module scope *)
 					IF importedModule # NIL THEN
-						import := SyntaxTree.NewImport(-1,moduleIdentifier,moduleIdentifier,TRUE);
+						import := SyntaxTree.NewImport(Basic.invalidPosition,moduleIdentifier,moduleIdentifier,TRUE);
 						import.SetModule(importedModule);
 						import.SetContext(moduleContext);
 						import.SetState(SyntaxTree.Resolved);
@@ -739,39 +739,39 @@ TYPE
 				size := type.sizeInBits;
 				IF type IS SyntaxTree.BooleanType THEN R.RawNum(i);
 					IF TraceImport IN Trace THEN D.Str("InConst / Bool / "); D.Int(i,1); D.Ln;  END;
-					IF	i = 0	THEN	value := Global.NewBooleanValue(system,-1,FALSE)	 ELSE value := Global.NewBooleanValue(system,-1,TRUE)	END
+					IF	i = 0	THEN	value := Global.NewBooleanValue(system,Basic.invalidPosition,FALSE)	 ELSE value := Global.NewBooleanValue(system,Basic.invalidPosition,TRUE)	END
 				ELSIF (type IS SyntaxTree.CharacterType) THEN
 					IF  (size=8) OR (size=16) OR (size=32) THEN
 						R.RawNum(i);
 						IF TraceImport IN Trace THEN D.Str("InConst / Char / "); D.Int(i,1); D.Ln;  END;
-						value := SyntaxTree.NewCharacterValue(-1,CHR(i));
+						value := SyntaxTree.NewCharacterValue(Basic.invalidPosition,CHR(i));
 					END;
 				ELSIF type IS SyntaxTree.IntegerType THEN
 					IF (size = 32) & ~type(SyntaxTree.IntegerType).signed THEN
 						R.RawHInt(huge);
 						IF TraceImport IN Trace THEN  D.Str("InConst / Unsigned32 / "); D.Ln END;
-						value := SyntaxTree.NewIntegerValue (-1,huge);
+						value := SyntaxTree.NewIntegerValue (Basic.invalidPosition,huge);
 					ELSIF size <=32 THEN
 						R.RawNum(i);
 						IF TraceImport IN Trace THEN  D.Str("InConst / Int"); D.Int(size,1); D.String(" "); D.Int(i,1); D.Ln END;
-						value := SyntaxTree.NewIntegerValue(-1,i);
+						value := SyntaxTree.NewIntegerValue(Basic.invalidPosition,i);
 					ELSIF size=64 THEN
 						R.RawHInt(huge);
 						IF TraceImport IN Trace THEN  D.Str("InConst / HInt / "); D.Ln END;
-						value := SyntaxTree.NewIntegerValue (-1,huge);
+						value := SyntaxTree.NewIntegerValue (Basic.invalidPosition,huge);
 					END;
 				ELSIF type IS SyntaxTree.SetType THEN R.RawNum(SYSTEM.VAL(LONGINT, set));
 					IF TraceImport IN Trace THEN  D.Str("InConst / Set / "); D.Hex(SYSTEM.VAL(LONGINT, set),1); D.Ln END;
-					value := SyntaxTree.NewSetValue(-1,set);
+					value := SyntaxTree.NewSetValue(Basic.invalidPosition,set);
 				ELSIF type IS SyntaxTree.FloatType THEN
 					IF size = 32 THEN
 						R.RawReal(r);
 						IF TraceImport IN Trace THEN  D.Str("InConst / Real / "); D.Ln END;
-						value := SyntaxTree.NewRealValue(-1,r);
+						value := SyntaxTree.NewRealValue(Basic.invalidPosition,r);
 					ELSIF size = 64 THEN
 						R.RawLReal(lr);
 						IF TraceImport IN Trace THEN  D.Str("InConst / LongReal / "); D.Ln END;
-						value := SyntaxTree.NewRealValue(-1,lr);
+						value := SyntaxTree.NewRealValue(Basic.invalidPosition,lr);
 					END;
 				ELSIF type IS SyntaxTree.StringType THEN
 					IF version <= FileVersionOC THEN NEW(string, 256)
@@ -779,15 +779,15 @@ TYPE
 					END;
 					R.RawString(string^);
 					IF TraceImport IN Trace THEN  D.Str("InConst / String / "); D.Str(string^); D.Ln END;
-					value := SyntaxTree.NewStringValue(-1,string);
+					value := SyntaxTree.NewStringValue(Basic.invalidPosition,string);
 					type(SyntaxTree.StringType).SetLength(value(SyntaxTree.StringValue).length);
 					type.SetState(SyntaxTree.Resolved);
 				ELSIF type IS SyntaxTree.EnumerationType THEN R.RawNum(i);
 					IF TraceImport IN Trace THEN  D.Str("InConst / LInt / "); D.Int(i,1); D.Ln END;
-					value := SyntaxTree.NewEnumerationValue(-1,i);
+					value := SyntaxTree.NewEnumerationValue(Basic.invalidPosition,i);
 				ELSIF type IS SyntaxTree.NilType THEN
 					IF TraceImport IN Trace THEN  D.Str("InConst / Nil"); D.Ln END;
-					value := SyntaxTree.NewNilValue(-1);
+					value := SyntaxTree.NewNilValue(Basic.invalidPosition);
 				END;
 				value.SetType(type);
 				value.SetState(SyntaxTree.Resolved);
@@ -802,7 +802,7 @@ TYPE
 				R.RawString(name);
 				WHILE name # "" DO
 					identifier := SyntaxTree.NewIdentifier(name);
-					enumerator := SyntaxTree.NewConstant(-1,identifier);
+					enumerator := SyntaxTree.NewConstant(Basic.invalidPosition,identifier);
 					enumerationScope.AddConstant(enumerator);
 					enumerationScope.EnterSymbol(enumerator,b);
 					IF name # "@" THEN enumerationScope.lastConstant.SetAccess(SyntaxTree.Public+SyntaxTree.Internal+SyntaxTree.Protected)
@@ -859,7 +859,7 @@ TYPE
 
 					R.RawString(name);
 
-					parameter := SyntaxTree.NewParameter(-1,procedureType,SyntaxTree.NewIdentifier(name),kind);
+					parameter := SyntaxTree.NewParameter(Basic.invalidPosition,procedureType,SyntaxTree.NewIdentifier(name),kind);
 					parameter.SetType(type);
 					parameter.SetState(SyntaxTree.Resolved);
 					(*! remove this after a rebuild of the release - for compatibility only *)
@@ -940,7 +940,7 @@ TYPE
 					Symbol(recordScope,type,name,visibility,untraced, realtime, constructor, isOperator, isDynamic, isFictive, fOffset);
 					ASSERT(type # NIL);
 					IF  name = "" THEN visibility := SyntaxTree.Internal END;
-					variable := SyntaxTree.NewVariable(-1,SyntaxTree.NewIdentifier(name));
+					variable := SyntaxTree.NewVariable(Basic.invalidPosition,SyntaxTree.NewIdentifier(name));
 					variable.SetType(type);
 					variable.SetUntraced(untraced);
 					variable.SetAccess(visibility);
@@ -964,12 +964,12 @@ TYPE
 
 						procedureScope := SyntaxTree.NewProcedureScope(recordScope);
 						IF isOperator THEN
-							operator := SyntaxTree.NewOperator(-1,SyntaxTree.NewIdentifier(name),procedureScope);
+							operator := SyntaxTree.NewOperator(Basic.invalidPosition,SyntaxTree.NewIdentifier(name),procedureScope);
 							procedure := operator
 						ELSE
-							procedure := SyntaxTree.NewProcedure(-1,SyntaxTree.NewIdentifier(name),procedureScope);
+							procedure := SyntaxTree.NewProcedure(Basic.invalidPosition,SyntaxTree.NewIdentifier(name),procedureScope);
 						END;
-						procedureType := SyntaxTree.NewProcedureType(-1,recordScope);
+						procedureType := SyntaxTree.NewProcedureType(Basic.invalidPosition,recordScope);
 						procedureType.SetReturnType(type);
 						procedureType.SetRealtime(realtime);
 						procedure.SetConstructor(constructor);
@@ -1003,7 +1003,7 @@ TYPE
 						END;
 						IF (procedure.name=Global.RecordBodyName) THEN
 							recordScope.SetBodyProcedure(procedure);
-							recordBody := SyntaxTree.NewBody(-1,procedureScope);
+							recordBody := SyntaxTree.NewBody(Basic.invalidPosition,procedureScope);
 							recordBody.SetSafe(safe);
 							recordBody.SetActive(active);
 							procedureScope.SetBody(recordBody);
@@ -1087,7 +1087,7 @@ TYPE
 						D.Str("Type / OldStr "); D.Int(-tag,1); D.Ln
 					END
 				ELSIF tag = sfTypeString THEN
-					type := SyntaxTree.NewStringType(-1,system.characterType,0);
+					type := SyntaxTree.NewStringType(Basic.invalidPosition,system.characterType,0);
 					IF TraceImport IN Trace THEN
 						D.Str("Type / String "); D.Int(tag,1); D.Ln
 					END
@@ -1128,7 +1128,7 @@ TYPE
 						identifier := SyntaxTree.NewIdentifier(typeName);
 						typeDeclaration := importedModule.moduleScope.FindTypeDeclaration(identifier); (* find type in module *)
 						IF (typeDeclaration # NIL) THEN
-							qualifiedType := SyntaxTree.NewQualifiedType(-1,moduleScope,SyntaxTree.NewQualifiedIdentifier(-1,importedModule.name,identifier));
+							qualifiedType := SyntaxTree.NewQualifiedType(Basic.invalidPosition,moduleScope,SyntaxTree.NewQualifiedIdentifier(Basic.invalidPosition,importedModule.name,identifier));
 							qualifiedType.SetResolved(typeDeclaration.declaredType);
 							qualifiedType.SetTypeDeclaration(typeDeclaration);
 							type := qualifiedType;
@@ -1169,7 +1169,7 @@ TYPE
 								D.Str("Type / User / OpenArr "); D.Str(name); D.Ln
 							END;
 							ASSERT(baseType # NIL);
-							arrayType := SyntaxTree.NewArrayType(-1,moduleScope,SyntaxTree.Open);
+							arrayType := SyntaxTree.NewArrayType(Basic.invalidPosition,moduleScope,SyntaxTree.Open);
 							arrayType.SetArrayBase(baseType);
 							type := arrayType;
 							R.RawNum(SYSTEM.VAL(LONGINT,flags));
@@ -1180,13 +1180,13 @@ TYPE
 								D.Int(len,1); D.Str(name); D.Ln
 							END;
 							ASSERT(baseType # NIL);
-							arrayType :=SyntaxTree.NewArrayType(-1,moduleScope,SyntaxTree.Static);
+							arrayType :=SyntaxTree.NewArrayType(Basic.invalidPosition,moduleScope,SyntaxTree.Static);
 							arrayType.SetArrayBase(baseType);
 							type := arrayType;
 							R.RawNum(SYSTEM.VAL(LONGINT,flags));
 							IF sfRealtime IN flags THEN type.SetRealtime(TRUE) END;
 							R.RawNum(len);
-							size := SyntaxTree.NewIntegerValue(-1,len);
+							size := SyntaxTree.NewIntegerValue(Basic.invalidPosition,len);
 							size.SetType(system.longintType);
 							arrayType.SetLength(size);
 					| sfTypeOpenMathArray:
@@ -1194,7 +1194,7 @@ TYPE
 								D.Str("Type / User / MathArray (open) "); D.Str(name); D.Ln
 							END;
 							ASSERT(baseType # NIL);
-							mathArrayType := SyntaxTree.NewMathArrayType(-1,moduleScope,SyntaxTree.Open);
+							mathArrayType := SyntaxTree.NewMathArrayType(Basic.invalidPosition,moduleScope,SyntaxTree.Open);
 							mathArrayType.SetArrayBase(baseType);
 							type := mathArrayType;
 							R.RawNum(SYSTEM.VAL(LONGINT,flags));
@@ -1203,7 +1203,7 @@ TYPE
 							IF TraceImport IN Trace THEN
 								D.Str("Type / User / Tensor "); D.Str(name); D.Ln
 							END;
-							mathArrayType := SyntaxTree.NewMathArrayType(-1,moduleScope,SyntaxTree.Tensor);
+							mathArrayType := SyntaxTree.NewMathArrayType(Basic.invalidPosition,moduleScope,SyntaxTree.Tensor);
 							mathArrayType.SetArrayBase(baseType);
 							type := mathArrayType;
 							R.RawNum(SYSTEM.VAL(LONGINT,flags));
@@ -1214,20 +1214,20 @@ TYPE
 								D.Int(len,1); D.Str(name); D.Ln
 							END;
 							ASSERT(baseType # NIL);
-							mathArrayType :=SyntaxTree.NewMathArrayType(-1,moduleScope,SyntaxTree.Static);
+							mathArrayType :=SyntaxTree.NewMathArrayType(Basic.invalidPosition,moduleScope,SyntaxTree.Static);
 							mathArrayType.SetArrayBase(baseType);
 							type := mathArrayType;
 							R.RawNum(SYSTEM.VAL(LONGINT,flags));
 							IF sfRealtime IN flags THEN type.SetRealtime(TRUE) END;
 							R.RawNum(len);
-							size := SyntaxTree.NewIntegerValue(-1,len);
+							size := SyntaxTree.NewIntegerValue(Basic.invalidPosition,len);
 							size.SetType(system.longintType);
 							mathArrayType.SetLength(size);
 					| sfTypePointer:
 							IF TraceImport IN Trace THEN
 								D.Str("Type / User / Pointer "); D.Str(name); D.Ln
 							END;
-							pointerType := SyntaxTree.NewPointerType(-1,moduleScope);
+							pointerType := SyntaxTree.NewPointerType(Basic.invalidPosition,moduleScope);
 							type := pointerType;
 							pointerType.SetPointerBase(baseType);
 							R.RawNum(SYSTEM.VAL(LONGINT,flags));
@@ -1241,7 +1241,7 @@ TYPE
 								D.Str("Type / User / Record "); D.Str(name); D.Ln
 							END;
 							recordScope := SyntaxTree.NewRecordScope(moduleScope);
-							recordType := SyntaxTree.NewRecordType(-1,moduleScope,recordScope);
+							recordType := SyntaxTree.NewRecordType(Basic.invalidPosition,moduleScope,recordScope);
 							type := recordType;
 							R.RawNum(SYSTEM.VAL(LONGINT,flags));
 							IF sfRealtime IN flags THEN type.SetRealtime(TRUE) END;
@@ -1251,7 +1251,7 @@ TYPE
 								D.Str("Type / User / Proc "); D.Str(name); D.Ln
 							END;
 							procedureScope := SyntaxTree.NewProcedureScope(NIL);
-							procedureType := SyntaxTree.NewProcedureType(-1,moduleScope);
+							procedureType := SyntaxTree.NewProcedureType(Basic.invalidPosition,moduleScope);
 							procedureType.SetReturnType(baseType);
 							type := procedureType;
 
@@ -1270,19 +1270,19 @@ TYPE
 								D.Str("Type / User / Enumerator "); D.Str(name); D.Ln
 							END;
 							enumerationScope := SyntaxTree.NewEnumerationScope(moduleScope);
-							enumerationType := SyntaxTree.NewEnumerationType(-1,moduleScope,enumerationScope);
+							enumerationType := SyntaxTree.NewEnumerationType(Basic.invalidPosition,moduleScope,enumerationScope);
 							type := enumerationType;
 							enumerationType.SetEnumerationBase(baseType);
 							EnumerationList(enumerationScope);
 					END;
 
 					IF name # "" THEN
-						typeDeclaration := SyntaxTree.NewTypeDeclaration(-1,SyntaxTree.NewIdentifier(name));
+						typeDeclaration := SyntaxTree.NewTypeDeclaration(Basic.invalidPosition,SyntaxTree.NewIdentifier(name));
 						typeDeclaration.SetDeclaredType(type);
 						type.SetTypeDeclaration(typeDeclaration);
 						typeDeclaration.SetAccess(visibility);
 						typeDeclaration.SetState(SyntaxTree.Resolved);
-						qualifiedType := SyntaxTree.NewQualifiedType(-1,moduleScope, SyntaxTree.NewQualifiedIdentifier(-1,SyntaxTree.invalidIdentifier,typeDeclaration.name));
+						qualifiedType := SyntaxTree.NewQualifiedType(Basic.invalidPosition,moduleScope, SyntaxTree.NewQualifiedIdentifier(Basic.invalidPosition,SyntaxTree.invalidIdentifier,typeDeclaration.name));
 						qualifiedType.SetResolved(type);
 						type := qualifiedType;
 						type.SetTypeDeclaration(typeDeclaration);
@@ -1324,8 +1324,8 @@ TYPE
 					WHILE len > 0 DO  R.Char(ch); Append(ch);  DEC(len)  END;
 					R.Char(ch);
 				UNTIL ch = 0X;
-				body := SyntaxTree.NewBody(-1,scope);
-				newcode := SyntaxTree.NewCode(-1,body);
+				body := SyntaxTree.NewBody(Basic.invalidPosition,scope);
+				newcode := SyntaxTree.NewCode(Basic.invalidPosition,body);
 				body.SetCode(newcode);
 				scope.SetBody(body);
 				newcode.SetBinaryCode(array);
@@ -1403,7 +1403,7 @@ TYPE
 						Symbol(moduleScope,type,name, visibility,untraced,realtime,constructor,operator, isDynamic, isFictive, fOffset);
 						ASSERT(type # NIL);
 						value := Value(type);
-						constant := SyntaxTree.NewConstant(-1,SyntaxTree.NewIdentifier(name));
+						constant := SyntaxTree.NewConstant(Basic.invalidPosition,SyntaxTree.NewIdentifier(name));
 						constant.SetValue(value);
 						constant.SetType(value.type);
 						constant.SetAccess(visibility);
@@ -1420,7 +1420,7 @@ TYPE
 						operator := FALSE;
 						Symbol(moduleScope,type,name, visibility,untraced,realtime,constructor,operator, isDynamic,isFictive, fOffset);
 						ASSERT(type # NIL);
-						variable := SyntaxTree.NewVariable(-1,SyntaxTree.NewIdentifier(name));
+						variable := SyntaxTree.NewVariable(Basic.invalidPosition,SyntaxTree.NewIdentifier(name));
 						variable.SetType(type);
 						variable.SetAccess(visibility);
 						variable.SetState(SyntaxTree.Resolved);
@@ -1442,9 +1442,9 @@ TYPE
 						Symbol(moduleScope,type,name, visibility,untraced,realtime,constructor,operator, isDynamic, isFictive, fOffset);
 						ASSERT(~(constructor));
 						procedureScope := SyntaxTree.NewProcedureScope(moduleScope);
-						procedureType := SyntaxTree.NewProcedureType(-1,moduleScope);
+						procedureType := SyntaxTree.NewProcedureType(Basic.invalidPosition,moduleScope);
 						procedureType.SetReturnType(type);
-						procedure := SyntaxTree.NewProcedure(-1,SyntaxTree.NewIdentifier(name),procedureScope);
+						procedure := SyntaxTree.NewProcedure(Basic.invalidPosition,SyntaxTree.NewIdentifier(name),procedureScope);
 						procedure.SetType(procedureType);
 						procedure.SetAccess(visibility);
 						ParameterList(callingConvention,procedureScope,procedureType);
@@ -1464,10 +1464,10 @@ TYPE
 						Symbol(moduleScope,type,name, visibility,untraced,realtime,constructor,operator, isDynamic, isFictive, fOffset);
 						ASSERT(~(constructor));
 						procedureScope := SyntaxTree.NewProcedureScope(moduleScope);
-						procedureType := SyntaxTree.NewProcedureType(-1,moduleScope);
+						procedureType := SyntaxTree.NewProcedureType(Basic.invalidPosition,moduleScope);
 						procedureType.SetReturnType(type);
 						procedureType.SetRealtime(realtime);
-						procedure := SyntaxTree.NewOperator(-1,SyntaxTree.NewIdentifier(name),procedureScope);
+						procedure := SyntaxTree.NewOperator(Basic.invalidPosition,SyntaxTree.NewIdentifier(name),procedureScope);
 						procedure.SetType(procedureType);
 						procedure.SetAccess(visibility);
 						procedure(SyntaxTree.Operator).SetDynamic(isDynamic);
@@ -1492,8 +1492,8 @@ TYPE
 						Symbol(moduleScope,type,name, visibility,untraced, realtime, constructor,operator, isDynamic, isFictive, fOffset);
 						ASSERT(~(constructor));
 						procedureScope := SyntaxTree.NewProcedureScope(moduleScope);
-						procedureType := SyntaxTree.NewProcedureType(-1,moduleScope);
-						procedure := SyntaxTree.NewProcedure(-1,SyntaxTree.NewIdentifier(name),procedureScope);
+						procedureType := SyntaxTree.NewProcedureType(Basic.invalidPosition,moduleScope);
+						procedure := SyntaxTree.NewProcedure(Basic.invalidPosition,SyntaxTree.NewIdentifier(name),procedureScope);
 						procedureType.SetReturnType(type);
 						procedure.SetInline(TRUE);
 						procedure.SetType(procedureType);
@@ -1512,7 +1512,7 @@ TYPE
 						type := Type();
 						R.RawString(name);
 						IF TraceImport IN Trace  THEN  D.Str("alias:"); D.Str(name); D.Ln  END;
-						typeDeclaration := SyntaxTree.NewTypeDeclaration(-1,SyntaxTree.NewIdentifier(name));
+						typeDeclaration := SyntaxTree.NewTypeDeclaration(Basic.invalidPosition,SyntaxTree.NewIdentifier(name));
 						typeDeclaration.SetDeclaredType(type);
 						visibility := SyntaxTree.Public+SyntaxTree.Protected+SyntaxTree.Internal;
 						typeDeclaration.SetAccess(visibility);
@@ -1588,7 +1588,7 @@ TYPE
 			Global.ContextFromName(moduleName,moduleIdentifier,contextIdentifier);
 
 			moduleScope := SyntaxTree.NewModuleScope();
-			module:= SyntaxTree.NewModule(fileName,-1,moduleIdentifier,moduleScope,Scanner.Uppercase);
+			module:= SyntaxTree.NewModule(fileName,Basic.invalidPosition,moduleIdentifier,moduleScope,Scanner.Uppercase);
 			module.SetContext(contextIdentifier);
 			IF importCache = NIL THEN importCache := SyntaxTree.NewModuleScope(); END;
 

文件差异内容过多而无法显示
+ 117 - 124
source/FoxCSharpParser.Mod


+ 13 - 15
source/FoxCSharpScanner.Mod

@@ -155,13 +155,13 @@ TYPE
 
 TYPE
     Token* = LONGINT;
-
+	Position* = Basic.Position;
     (**
         symbol: data structure for the data transfer of 
         the last read input from the scanner to the parser
     **)
     Symbol* = RECORD
-        start*, end*, line-: LONGINT;
+    	position*: Position;
         token*: Token;
         identifier*: IdentifierType;
         identifierString*: IdentifierString;
@@ -182,8 +182,7 @@ TYPE
         reader: Streams.Reader;
         diagnostics: Diagnostics.Diagnostics;
         ch: CHAR;
-        position: LONGINT;
-        line-: LONGINT;
+        position-: Position;
         error-: BOOLEAN;
         stringWriter: Streams.Writer;
         stringMaker: StringMaker;
@@ -217,15 +216,15 @@ TYPE
                 D.Str("New scanner  ");
                 D.Ln;  
             END;
-            SELF.position := position;
-            line := 0;
+            SELF.position.start := position;
+            SELF.position.line := 0;
         END InitializeScanner;
 
         (** report an error occured during scanning **)
         PROCEDURE ErrorS(CONST msg: ARRAY OF CHAR);
         BEGIN
             IF diagnostics # NIL THEN
-                diagnostics.Error(source^, position, Diagnostics.Invalid, msg)
+                diagnostics.Error(source^, position.start, Diagnostics.Invalid, msg)
             END;
             error := TRUE;
         END ErrorS;
@@ -236,7 +235,7 @@ TYPE
         BEGIN
             IF diagnostics # NIL THEN
                 Basic.GetErrorMessage(code, "", errorMessage);
-                diagnostics.Error(source^, position, code, errorMessage)
+                diagnostics.Error(source^, position.start, code, errorMessage)
             END;
             error := TRUE;
         END Error;
@@ -245,9 +244,9 @@ TYPE
         PROCEDURE GetNextCharacter;
         BEGIN
             reader.Char(ch); 
-            INC(position);
+            INC(position.start);
             IF ch = LF THEN 
-                INC(line) 
+                INC(position.line); position.linepos := position.start;
             END;
         END GetNextCharacter;
 
@@ -835,8 +834,7 @@ TYPE
             VAR s, token: LONGINT;
         BEGIN
             SkipBlanks;
-            symbol.start := position;
-            symbol.line := line;
+            symbol.position := position;
             stringMaker.Clear;
 (* @@@ *)
 (*
@@ -1048,7 +1046,7 @@ KernelLog.Ln();
             END;
 
             symbol.token := s;
-            symbol.end := position;
+            symbol.position.end := position.start;
 
             IF Trace THEN 
                 OutSymbol(D.Log, symbol); 
@@ -1130,9 +1128,9 @@ KernelLog.Ln();
         END OutChar;
 
     BEGIN
-        w.Int(symbol.start, 1); 
+        w.Int(symbol.position.start, 1); 
         w.String("-");
-        w.Int(symbol.end, 1); 
+        w.Int(symbol.position.end, 1); 
         w.String(":");
         w.String(tokens[symbol.token]);
         IF (symbol.token = IntegerLiteral) OR (symbol.token = RealLiteral) THEN

+ 1 - 1
source/FoxFingerPrinter.Mod

@@ -462,7 +462,7 @@ TYPE
 						D.Str0(typeDeclaration.name);
 					END;
 				ELSIF (typeDeclaration # NIL) & (typeDeclaration.scope = NIL) THEN
-					D.Str("typedeclaration without scope: "); D.Str0(x.typeDeclaration.name); D.Int(x.typeDeclaration.position,5); D.Ln;
+					D.Str("typedeclaration without scope: "); D.Str0(x.typeDeclaration.name); D.Int(x.typeDeclaration.position.start,5); D.Ln;
 					D.Update;
 				ELSE
 					FPNumber(fp,0);

+ 21 - 18
source/FoxGlobal.Mod

@@ -205,10 +205,13 @@ VAR
 	Byte32: SyntaxTree.ByteType;
 
 TYPE
+	Position = SyntaxTree.Position;
+	
 	Alignment* = RECORD
 		min, max: LONGINT; (* alignments in bits *)
 	END;
 
+
 	PassInRegisterProc = PROCEDURE {DELEGATE} (type: SyntaxTree.Type): BOOLEAN;
 
 	System*= OBJECT
@@ -688,12 +691,12 @@ TYPE
 		END;
 		system.globalScope[Scanner.Uppercase] := SyntaxTree.NewModuleScope();
 		system.globalScope[Scanner.Lowercase] := SyntaxTree.NewModuleScope();
-		system.globalModule[Scanner.Uppercase] := SyntaxTree.NewModule("",-1,SyntaxTree.NewIdentifier("@GLOBAL"),system.globalScope[Scanner.Uppercase],Scanner.Uppercase);
-		system.globalModule[Scanner.Lowercase] := SyntaxTree.NewModule("",-1,SyntaxTree.NewIdentifier("@global"),system.globalScope[Scanner.Lowercase],Scanner.Lowercase);
+		system.globalModule[Scanner.Uppercase] := SyntaxTree.NewModule("",SyntaxTree.invalidPosition,SyntaxTree.NewIdentifier("@GLOBAL"),system.globalScope[Scanner.Uppercase],Scanner.Uppercase);
+		system.globalModule[Scanner.Lowercase] := SyntaxTree.NewModule("",SyntaxTree.invalidPosition,SyntaxTree.NewIdentifier("@global"),system.globalScope[Scanner.Lowercase],Scanner.Lowercase);
 		system.systemScope[Scanner.Uppercase] := SyntaxTree.NewModuleScope();
 		system.systemScope[Scanner.Lowercase] := SyntaxTree.NewModuleScope();
-		system.systemModule[Scanner.Uppercase] := SyntaxTree.NewModule("",-1,SystemName,system.systemScope[Scanner.Uppercase],Scanner.Uppercase);
-		system.systemModule[Scanner.Lowercase] := SyntaxTree.NewModule("",-1,systemName,system.systemScope[Scanner.Lowercase],Scanner.Lowercase);
+		system.systemModule[Scanner.Uppercase] := SyntaxTree.NewModule("",SyntaxTree.invalidPosition,SystemName,system.systemScope[Scanner.Uppercase],Scanner.Uppercase);
+		system.systemModule[Scanner.Lowercase] := SyntaxTree.NewModule("",SyntaxTree.invalidPosition,systemName,system.systemScope[Scanner.Lowercase],Scanner.Lowercase);
 	END BuildScopes;
 
 	PROCEDURE SetDefaultDeclarations*(system: System; minBits: LONGINT);
@@ -1017,7 +1020,7 @@ TYPE
 	PROCEDURE DeclareType0(type: SyntaxTree.Type; CONST name: ARRAY OF CHAR; in: SyntaxTree.Scope);
 	VAR basic: SyntaxTree.TypeDeclaration; duplicate: BOOLEAN;
 	BEGIN
-		basic := SyntaxTree.NewTypeDeclaration(-1,SyntaxTree.NewIdentifier(name));
+		basic := SyntaxTree.NewTypeDeclaration(SyntaxTree.invalidPosition,SyntaxTree.NewIdentifier(name));
 		basic.SetDeclaredType(type);
 		basic.SetState(SyntaxTree.Resolved);
 		basic.SetAccess(SyntaxTree.ReadOnly);
@@ -1048,9 +1051,9 @@ TYPE
 	PROCEDURE NewConstant0(CONST name: ARRAY OF CHAR; int: LONGINT; type: SyntaxTree.Type; in: SyntaxTree.Scope);
 	VAR constant: SyntaxTree.Constant; value: SyntaxTree.IntegerValue;duplicate: BOOLEAN;
 	BEGIN
-		value := SyntaxTree.NewIntegerValue(-1,int);
+		value := SyntaxTree.NewIntegerValue(SyntaxTree.invalidPosition,int);
 		value.SetType(type);
-		constant := SyntaxTree.NewConstant(-1,SyntaxTree.NewIdentifier(name));
+		constant := SyntaxTree.NewConstant(SyntaxTree.invalidPosition,SyntaxTree.NewIdentifier(name));
 		constant.SetValue(value);
 		constant.SetType(value.type);
 		constant.SetAccess(SyntaxTree.ReadOnly);
@@ -1072,9 +1075,9 @@ TYPE
 	PROCEDURE NewStringConstant0(CONST name: ARRAY OF CHAR; string: SyntaxTree.String; baseType: SyntaxTree.Type; in: SyntaxTree.Scope);
 	VAR constant: SyntaxTree.Constant; value: SyntaxTree.StringValue;duplicate: BOOLEAN;
 	BEGIN
-		value := SyntaxTree.NewStringValue(-1,string);
-		value.SetType(SyntaxTree.NewStringType(-1,baseType,value.length));
-		constant := SyntaxTree.NewConstant(-1,SyntaxTree.NewIdentifier(name));
+		value := SyntaxTree.NewStringValue(SyntaxTree.invalidPosition,string);
+		value.SetType(SyntaxTree.NewStringType(SyntaxTree.invalidPosition,baseType,value.length));
+		constant := SyntaxTree.NewConstant(SyntaxTree.invalidPosition,SyntaxTree.NewIdentifier(name));
 		constant.SetValue(value);
 		constant.SetType(value.type);
 		constant.SetAccess(SyntaxTree.ReadOnly);
@@ -1102,9 +1105,9 @@ TYPE
 	PROCEDURE NewBuiltin0( id: LONGINT; CONST name: ARRAY OF CHAR; in:  SyntaxTree.ModuleScope; realtime: BOOLEAN);
 	VAR basic: SyntaxTree.Builtin; duplicate: BOOLEAN; type: SyntaxTree.ProcedureType;
 	BEGIN
-		basic := SyntaxTree.NewBuiltin(-1,SyntaxTree.NewIdentifier(name),id);
+		basic := SyntaxTree.NewBuiltin(SyntaxTree.invalidPosition,SyntaxTree.NewIdentifier(name),id);
 		basic.SetAccess(SyntaxTree.ReadOnly);
-		type := SyntaxTree.NewProcedureType(-1,in);
+		type := SyntaxTree.NewProcedureType(SyntaxTree.invalidPosition,in);
 		type.SetRealtime(realtime);
 		type.SetReturnType(SyntaxTree.invalidType); (* make incompatible to any procedure *)
 		basic.SetType(type);
@@ -1134,7 +1137,7 @@ TYPE
 		isDuplicate: BOOLEAN;
 		customBuiltin: SyntaxTree.CustomBuiltin;
 	BEGIN
-		customBuiltin := SyntaxTree.NewCustomBuiltin(-1, SyntaxTree.NewIdentifier(name), systemSpecial, subType);
+		customBuiltin := SyntaxTree.NewCustomBuiltin(SyntaxTree.invalidPosition, SyntaxTree.NewIdentifier(name), systemSpecial, subType);
 		customBuiltin.SetAccess(SyntaxTree.ReadOnly); (* TODO: this might be changed *)
 		procedureType.SetRealtime(TRUE);
 		customBuiltin.SetType(procedureType); (* TODO: make incompatible to any procedure *)
@@ -1465,7 +1468,7 @@ TYPE
 		END;
 	END GetIntegerType;
 	
-	PROCEDURE NewIntegerValue*(system: System; position: LONGINT; hugeint: HUGEINT): SyntaxTree.Value;
+	PROCEDURE NewIntegerValue*(system: System; position: Position; hugeint: HUGEINT): SyntaxTree.Value;
 	VAR value: SyntaxTree.IntegerValue;
 	BEGIN
 		value := SyntaxTree.NewIntegerValue(position,hugeint);
@@ -1473,7 +1476,7 @@ TYPE
 		RETURN value
 	END NewIntegerValue;
 
-	PROCEDURE NewBooleanValue*(system: System; position: LONGINT; b: BOOLEAN): SyntaxTree.Value;
+	PROCEDURE NewBooleanValue*(system: System; position: Position; b: BOOLEAN): SyntaxTree.Value;
 	VAR value: SyntaxTree.BooleanValue;
 	BEGIN
 		value := SyntaxTree.NewBooleanValue(position,b);
@@ -1481,7 +1484,7 @@ TYPE
 		RETURN value
 	END NewBooleanValue;
 
-	PROCEDURE NewSetValue*(system: System; position: LONGINT; s: SET): SyntaxTree.Value;
+	PROCEDURE NewSetValue*(system: System; position: Position; s: SET): SyntaxTree.Value;
 	VAR value: SyntaxTree.SetValue;
 	BEGIN
 		value := SyntaxTree.NewSetValue(position,s);
@@ -1489,7 +1492,7 @@ TYPE
 		RETURN value
 	END NewSetValue;
 
-	PROCEDURE NewCharacterValue*(system: System; position: LONGINT; c: CHAR): SyntaxTree.Value;
+	PROCEDURE NewCharacterValue*(system: System; position: Position; c: CHAR): SyntaxTree.Value;
 	VAR value: SyntaxTree.CharacterValue;
 	BEGIN
 		value := SyntaxTree.NewCharacterValue(position,c);
@@ -1497,7 +1500,7 @@ TYPE
 		RETURN value
 	END NewCharacterValue;
 
-	PROCEDURE NewNilValue*(system: System; position: LONGINT): SyntaxTree.Value;
+	PROCEDURE NewNilValue*(system: System; position: Position): SyntaxTree.Value;
 	VAR value: SyntaxTree.NilValue;
 	BEGIN
 		value := SyntaxTree.NewNilValue(position);

+ 4 - 4
source/FoxInterfaceComparison.Mod

@@ -60,13 +60,13 @@ CONST
 		RETURN TRUE
 	END CompareSymbols;
 
-	PROCEDURE ErrorSS(pos: LONGINT; CONST s1,s2: ARRAY OF CHAR);
+	PROCEDURE ErrorSS(pos: SyntaxTree.Position; CONST s1,s2: ARRAY OF CHAR);
 	VAR msg: ARRAY 256 OF CHAR;
 	BEGIN
 		COPY(s1,msg);
 		Strings.Append(msg,s2);
 		IF (diagnostics # NIL) & (module # NIL) THEN
-			diagnostics.Information(module.sourceName,pos,Diagnostics.Invalid,msg);
+			diagnostics.Information(module.sourceName,pos.start,Diagnostics.Invalid,msg);
 		END;
 	END ErrorSS;
 
@@ -110,7 +110,7 @@ CONST
 				newSymbol := NextSymbol(newSymbol.nextSymbol);
 			ELSIF oldName < newName THEN
 				IF oldPublic THEN
-					ErrorSS(Diagnostics.Invalid,oldName," is no longer visible");
+					ErrorSS(Basic.invalidPosition,oldName," is no longer visible");
 					INCL(flags,Redefined);
 				END;
 				oldSymbol := NextSymbol(oldSymbol.nextSymbol);
@@ -127,7 +127,7 @@ CONST
 			oldSymbol.GetName(oldName);
 			oldPublic := oldSymbol.access * SyntaxTree.Public # {};
 			IF oldSymbol.access * SyntaxTree.Public # {} THEN
-				ErrorSS(Diagnostics.Invalid,oldName," is no longer visible");
+				ErrorSS(Basic.invalidPosition,oldName," is no longer visible");
 				INCL(flags,Redefined);
 			END;
 			oldSymbol := NextSymbol(oldSymbol.nextSymbol);

+ 2 - 2
source/FoxIntermediateAssembler.Mod

@@ -1,6 +1,6 @@
 MODULE FoxIntermediateAssembler; (** AUTHOR ""; PURPOSE ""; *)
 
-IMPORT IntermediateCode := FoxIntermediateCode, FoxAssembler, D := Debugging, Scanner := FoxScanner;
+IMPORT IntermediateCode := FoxIntermediateCode, FoxAssembler, D := Debugging, Scanner := FoxScanner, Basic := FoxBasic;
 
 CONST Trace=FoxAssembler.Trace;
 TYPE
@@ -11,7 +11,7 @@ TYPE
 	Assembler*= OBJECT (FoxAssembler.Assembler)
 
 		PROCEDURE Instruction*(CONST mnemonic: ARRAY OF CHAR);
-		VAR i,numberOperands,mnem,pos: LONGINT; VAR operands: ARRAY 3 OF Operand; instruction: IntermediateCode.Instruction;
+		VAR i,numberOperands,mnem: LONGINT; pos: Basic.Position; VAR operands: ARRAY 3 OF Operand; instruction: IntermediateCode.Instruction;
 
 			PROCEDURE ParseOperand;
 			(* stub, must be overwritten by implementation *)

文件差异内容过多而无法显示
+ 180 - 179
source/FoxIntermediateBackend.Mod


+ 26 - 23
source/FoxIntermediateParser.Mod

@@ -9,6 +9,7 @@ CONST
 
 TYPE
 	MessageString= ARRAY 256 OF CHAR;
+	Position = Basic.Position;
 
 	(** the intermediate code parser **)
 	IntermediateCodeParser* = OBJECT
@@ -31,11 +32,11 @@ TYPE
 			error := FALSE
 		END Init;
 
-		PROCEDURE Error(pos: LONGINT; CONST msg: ARRAY OF CHAR);
+		PROCEDURE Error(pos: Position; CONST msg: ARRAY OF CHAR);
 		BEGIN
 			error := TRUE;
 			IF diagnostics # NIL THEN
-				diagnostics.Error(scanner.source^,pos,Diagnostics.Invalid,msg);
+				diagnostics.Error(scanner.source^,pos.start,Diagnostics.Invalid,msg);
 			END;
 
 			D.Update;
@@ -51,9 +52,9 @@ TYPE
 			IF ~error & (symbol.token = x) THEN NextSymbol; RETURN TRUE ELSE RETURN FALSE END;
 		END ThisToken;
 
-		PROCEDURE GetIdentifier(VAR pos: LONGINT; VAR identifier: ARRAY OF CHAR): BOOLEAN;
+		PROCEDURE GetIdentifier(VAR pos: Position; VAR identifier: ARRAY OF CHAR): BOOLEAN;
 		BEGIN
-			pos := symbol.start;
+			pos := symbol.position;
 			IF symbol.token # Scanner.Identifier THEN RETURN FALSE
 			ELSE COPY(symbol.identifierString,identifier); NextSymbol; RETURN TRUE
 			END;
@@ -66,7 +67,7 @@ TYPE
 			IF ThisToken(x) THEN RETURN TRUE
 			ELSE
 				s := "expected token "; Strings.Append(s,Scanner.tokens[x]); Strings.Append(s," but got "); Strings.Append(s,Scanner.tokens[symbol.token]);
-				Error(symbol.start, s);RETURN FALSE
+				Error(symbol.position, s);RETURN FALSE
 			END;
 		END ExpectToken;
 
@@ -75,7 +76,7 @@ TYPE
 			IF ~error & (symbol.token = Scanner.Identifier) & (this = symbol.identifierString) THEN NextSymbol; RETURN TRUE ELSE RETURN FALSE END;
 		END ThisIdentifier;
 
-		PROCEDURE ExpectAnyIdentifier(VAR pos: LONGINT; VAR identifier: ARRAY OF CHAR): BOOLEAN;
+		PROCEDURE ExpectAnyIdentifier(VAR pos: Position; VAR identifier: ARRAY OF CHAR): BOOLEAN;
 		BEGIN
 			IF ~GetIdentifier(pos,identifier)THEN Error(pos,"identifier expected"); RETURN FALSE
 			ELSE RETURN TRUE
@@ -125,7 +126,7 @@ TYPE
 				NextSymbol;
 				RETURN TRUE
 			ELSE
-				Error(symbol.start, "end of line/text expected");
+				Error(symbol.position, "end of line/text expected");
 				RETURN FALSE
 			END;
 		END ExpectLineDelimiter;
@@ -133,12 +134,13 @@ TYPE
 		(** parse an optional line number **)
 		PROCEDURE ParseLineNumber(expectedLineNumber: LONGINT);
 		VAR
-			positionOfLine, specifiedLineNumber: LONGINT;
+			positionOfLine: Position;
+			specifiedLineNumber: LONGINT;
 			message, tempString: MessageString;
 		BEGIN
 			IF Trace THEN D.String(">>> ParseLineNumber"); D.Ln END;
 
-			positionOfLine := symbol.start;
+			positionOfLine := symbol.position;
 			IF ThisToken(Scanner.Number) THEN (* note: line numbers are optional *)
 				specifiedLineNumber := symbol.integer;
 				IF ExpectToken(Scanner.Colon) THEN
@@ -157,7 +159,7 @@ TYPE
 		(** parse an intermediate code operand **)
 		PROCEDURE ParseOperand(VAR operand: IntermediateCode.Operand; sectionList: Sections.SectionList);
 		VAR
-			positionOfOperand, pos, registerNumber, symbolOffset, someLongint, integer: LONGINT;
+			positionOfOperand, pos: Position;  registerNumber, symbolOffset, someLongint, integer: LONGINT;
 			someHugeint: HUGEINT;
 			hasTypeDescriptor, isMemoryOperand, lastWasIdentifier, isNegated: BOOLEAN;
 			someLongreal: LONGREAL;
@@ -169,7 +171,7 @@ TYPE
 		BEGIN
 			IF Trace THEN D.String(">>> ParseOperand"); D.Ln END;
 
-			positionOfOperand := symbol.start;
+			positionOfOperand := symbol.position;
 
 			(* defaults *)
 			hasTypeDescriptor := FALSE;
@@ -203,7 +205,7 @@ TYPE
 						IF ExpectIntegerWithSign(integer) THEN
 							symbolOffset := integer
 						ELSE
-							Error(symbol.start, "invalid symbol offset")
+							Error(symbol.position, "invalid symbol offset")
 						END
 					END;
 
@@ -270,13 +272,13 @@ TYPE
 				IF ExpectIntegerWithoutSign(integer) THEN
 					IntermediateCode.SetOffset(operand, integer)
 				ELSE
-					Error(symbol.start, "invalid offset")
+					Error(symbol.position, "invalid offset")
 				END
 			ELSIF ThisToken(Scanner.Minus) THEN
 				IF ExpectIntegerWithoutSign(integer) THEN
 					IntermediateCode.SetOffset(operand, -integer)
 				ELSE
-					Error(symbol.start, "invalid offset")
+					Error(symbol.position, "invalid offset")
 				END
 			END;
 
@@ -294,7 +296,8 @@ TYPE
 		PROCEDURE ParseInstruction(VAR instruction: IntermediateCode.Instruction; sectionList: Sections.SectionList);
 		VAR
 			opCode: SHORTINT;
-			positionOfInstruction, positionOfOperand, operandNumber: LONGINT;
+			positionOfInstruction, positionOfOperand: Position; 
+			operandNumber: LONGINT;
 			operand: IntermediateCode.Operand;
 			operands: ARRAY 3 OF IntermediateCode.Operand;
 			operandType: IntermediateCode.Type;
@@ -302,7 +305,7 @@ TYPE
 		BEGIN
 			IF Trace THEN D.String(">>> ParseInstruction"); D.Ln END;
 
-			positionOfInstruction := symbol.start;
+			positionOfInstruction := symbol.position;
 			IF ExpectAnyIdentifier(positionOfInstruction, identifier) THEN
 				(* TODO: detect labels of the form << labelName: >> *)
 				opCode := IntermediateCode.FindMnemonic(identifier);
@@ -319,7 +322,7 @@ TYPE
 					operandNumber := 0;
 					IF ~ThisToken(Scanner.Ln) & ~ThisToken(Scanner.EndOfText) THEN
 						REPEAT
-							positionOfOperand := symbol.start;
+							positionOfOperand := symbol.position;
 							IF operandNumber > 2 THEN
 								Error(positionOfInstruction, "instruction has too many operands")
 							ELSE
@@ -339,7 +342,7 @@ TYPE
 					END;
 
 					IF ~error THEN
-						IntermediateCode.InitInstruction(instruction, positionOfInstruction, opCode, operands[0], operands[1], operands[2]);
+						IntermediateCode.InitInstruction(instruction, positionOfInstruction.start, opCode, operands[0], operands[1], operands[2]);
 						IF Strict & ~IntermediateCode.CheckInstruction(instruction, message) THEN
 							Error(positionOfInstruction, message)
 						END
@@ -379,12 +382,12 @@ TYPE
 		(** parse a list of section properties **)
 		PROCEDURE ParseSectionProperties(VAR section: IntermediateCode.Section);
 		VAR
-			positionOfProperty, integer: LONGINT;
+			positionOfProperty: Position;  integer: LONGINT;
 		BEGIN
 			IF Trace THEN D.Ln; D.String(">>> ParseSectionProperties"); D.Ln END;
 
 			WHILE ~error & (symbol.token # Scanner.EndOfText) & (symbol.token # Scanner.Ln) DO
-				positionOfProperty := symbol.start;
+				positionOfProperty := symbol.position;
 
 				(* fingerprint *)
 				IF ThisIdentifier("fingerprint") & ExpectToken(Scanner.Equal) THEN
@@ -446,7 +449,7 @@ TYPE
 		(** parse the content of an intermediate code module **)
 		PROCEDURE ParseModuleContent*(scanner: Scanner.AssemblerScanner ; module: Sections.Module (* sectionList: Sections.SectionList; VAR moduleName: SyntaxTree.IdentifierString; VAR backend: Backend.Backend; loader: ModuleLoader*) ): BOOLEAN;
 		VAR
-			pos, positionOfDirective: LONGINT;
+			pos, positionOfDirective:Position;
 			identifier: Scanner.IdentifierString;
 			afterModuleDirective, afterImportsDirective, afterFirstSection, isExternalSection: BOOLEAN;
 			sectionType: SHORTINT;
@@ -469,7 +472,7 @@ TYPE
 			afterFirstSection := FALSE;
 			IgnoreNewLines;
 			WHILE ~error & (symbol.token # Scanner.EndOfText) DO
-				positionOfDirective := symbol.start;
+				positionOfDirective := symbol.position;
 				IF ExpectToken(Scanner.Period) & ExpectAnyIdentifier(pos, identifier) THEN
 					(* 'module' directive *)
 					IF identifier = "module" THEN
@@ -518,7 +521,7 @@ TYPE
 					ELSE
 						(* determine if section is external *)
 						IF identifier = "external" THEN
-							positionOfDirective := symbol.start;
+							positionOfDirective := symbol.position;
 							IF ExpectToken(Scanner.Period) & ExpectAnyIdentifier(pos, identifier) THEN END;
 							isExternalSection := TRUE
 						ELSE

+ 2 - 2
source/FoxInterpreter.Mod

@@ -663,7 +663,7 @@ TYPE
 			parameter: SyntaxTree.Parameter;
 			name: Basic.SectionName;
 			modifier: SyntaxTree.Modifier;
-			position: LONGINT;
+			position: SyntaxTree.Position;
 			value: Value;
 			result: Result;
 			address: ADDRESS;
@@ -1103,7 +1103,7 @@ TYPE
 		PROCEDURE VisitCaseStatement*(x: SyntaxTree.CaseStatement);
 		VAR binary: SyntaxTree.BinaryExpression; i: LONGINT;
 		BEGIN
-			binary := SyntaxTree.NewBinaryExpression(0, x.variable, x.variable, Scanner.Equal);
+			binary := SyntaxTree.NewBinaryExpression(Basic.invalidPosition, x.variable, x.variable, Scanner.Equal);
 			FOR i := 0 TO x.CaseParts()-1 DO
 				IF CasePart(x.GetCasePart(i), binary) THEN RETURN END;
 			END;

+ 116 - 120
source/FoxParser.Mod

@@ -165,6 +165,8 @@ CONST
 	**)
 
 TYPE
+	Position*=Scanner.Position;
+
 	Parser* = OBJECT
 	VAR scanner-: Scanner.Scanner;
 		symbol-: Scanner.Symbol;
@@ -184,7 +186,7 @@ TYPE
 		BEGIN
 			D.Ln;  INC( indent );  D.Int( indent,1 );
 			FOR i := 1 TO indent DO D.Str( "  " );  END;
-			D.Str( "start: " );  D.Str( s );  D.Str( " at pos " );  D.Int( symbol.start,1 );
+			D.Str( "start: " );  D.Str( s );  D.Str( " at pos " );  D.Int( symbol.position.start,1 );
 		END S;
 
 		PROCEDURE E( CONST s: ARRAY OF CHAR );   (* for debugging purposes only *)
@@ -192,7 +194,7 @@ TYPE
 		BEGIN
 			D.Ln;  D.Int( indent,1 );
 			FOR i := 1 TO indent DO D.Str( "  " );  END;
-			D.Str( "end : " );  D.Str( s );  D.Str( " at pos " );  D.Int( symbol.start,1 );
+			D.Str( "end : " );  D.Str( s );  D.Str( " at pos " );  D.Int( symbol.position.start,1 );
 			DEC(indent);
 		END E;
 
@@ -232,12 +234,13 @@ TYPE
 		
 
 		(** output error message and / or given code *)
-		PROCEDURE Error(position: LONGINT; code: LONGINT; CONST message: ARRAY OF CHAR);
+		PROCEDURE Error(position: Position; code: LONGINT; CONST message: ARRAY OF CHAR);
 		VAR errorMessage: ARRAY 256 OF CHAR;
 		BEGIN
 			IF diagnostics # NIL THEN
 				Basic.GetErrorMessage(code,message,errorMessage);
-				diagnostics.Error(scanner.source^, position, code, errorMessage);
+				Basic.AppendPosition(errorMessage, position);
+				diagnostics.Error(scanner.source^, position.start, code, errorMessage);
 			END;
 			error := TRUE
 		END Error;
@@ -248,13 +251,13 @@ TYPE
 		VAR comment: SyntaxTree.Comment;
 		BEGIN
 			WHILE ~error & (b & (TokenB()= Scanner.Comment) OR ~b & (Token() = Scanner.Comment)) DO
-				comment := SyntaxTree.NewComment(symbol.start, currentScope, symbol.string^,symbol.stringLength);
+				comment := SyntaxTree.NewComment(symbol.position, currentScope, symbol.string^,symbol.stringLength);
 				IF moduleScope # NIL THEN
 					moduleScope.AddComment(comment);
 				END;
 				IF recentComment = NIL THEN
 					recentComment := comment;
-					IF symbol.line = recentLine THEN
+					IF symbol.position.line = recentLine THEN
 						IF recentCommentItem # NIL THEN
 							IF (recentCommentItem IS SyntaxTree.Symbol) THEN
 								IF recentCommentItem(SyntaxTree.Symbol).comment = NIL THEN
@@ -344,7 +347,7 @@ TYPE
 		BEGIN
 			ASSERT( token # Scanner.Identifier );  ASSERT( token # Scanner.String );  ASSERT( token # Scanner.Number );   (* because of NextSymbol ! *)
 			IF ~Peek(token) THEN
-				Error( symbol.start, token, "" );
+				Error( symbol.position, token, "" );
 				RETURN FALSE
 			ELSE
 				NextSymbol;
@@ -368,17 +371,17 @@ TYPE
 				NextSymbol;
 				RETURN TRUE
 			ELSE
-				Error( symbol.start, Scanner.Identifier, "" );
+				Error( symbol.position, Scanner.Identifier, "" );
 				name := SyntaxTree.invalidIdentifier;
 				RETURN FALSE
 			END
 		END MandatoryIdentifier;
 
 		(** Expect an identifier (using MandatoryIdentifier) and return identifier object **)
-		PROCEDURE Identifier(VAR position: LONGINT): SyntaxTree.Identifier;
+		PROCEDURE Identifier(VAR position: Position): SyntaxTree.Identifier;
 		VAR name: SyntaxTree.Identifier; identifier: SyntaxTree.Identifier;
 		BEGIN
-			position := symbol.start;
+			position := symbol.position;
 			IF MandatoryIdentifier(name) THEN
 				identifier := name;
 			ELSE
@@ -400,7 +403,7 @@ TYPE
 				NextSymbol;
 				RETURN TRUE
 			ELSE
-				Error( symbol.start, Scanner.String, "" );
+				Error( symbol.position, Scanner.String, "" );
 				NEW(name,1); name^ := "";
 				RETURN FALSE
 			END
@@ -414,7 +417,7 @@ TYPE
 				RETURN TRUE
 			ELSIF (Token() # Scanner.Identifier) OR (symbol.identifier # name) THEN
 				Basic.GetString(name,string);
-				Error( symbol.start, Scanner.Identifier, string );
+				Error( symbol.position, Scanner.Identifier, string );
 				RETURN FALSE
 			ELSE
 				NextSymbol;
@@ -429,7 +432,7 @@ TYPE
 				NextSymbol;
 				RETURN TRUE
 			ELSE
-				Error( symbol.start, Scanner.String, name );
+				Error( symbol.position, Scanner.String, name );
 				RETURN FALSE
 			END
 		END ExpectThisString;
@@ -466,7 +469,7 @@ TYPE
 
 		(** QualifiedIdentifier = Identifier ['.' Identifier]. **)
 		PROCEDURE QualifiedIdentifier*( ): SyntaxTree.QualifiedIdentifier;
-		VAR prefix,suffix: SyntaxTree.Identifier; qualifiedIdentifier: SyntaxTree.QualifiedIdentifier;  position0,position1: LONGINT;
+		VAR prefix,suffix: SyntaxTree.Identifier; qualifiedIdentifier: SyntaxTree.QualifiedIdentifier;  position0,position1: Position;
 		BEGIN
 			IF Trace THEN S( "QualifiedIdentifier" ) END;
 			prefix := Identifier(position0);
@@ -486,7 +489,7 @@ TYPE
 
 		(** IdentifierDefinition = Identifier [ '*' | '-' ].  **)
 		PROCEDURE IdentifierDefinition( VAR name: SyntaxTree.Identifier;  VAR access: SET; allowedReadOnly: BOOLEAN);
-		VAR position: LONGINT;
+		VAR position: Position;
 		BEGIN
 			IF Trace THEN S( "IdentifierDefinition" ) END;
 			name := Identifier(position);
@@ -495,7 +498,7 @@ TYPE
 				access := SyntaxTree.Public + SyntaxTree.Protected + SyntaxTree.Internal;
 			ELSIF Optional( Scanner.Minus ) THEN
 				IF ~allowedReadOnly THEN
-					Error( symbol.start, Diagnostics.Invalid, "may not be defined read-only" )
+					Error( symbol.position, Diagnostics.Invalid, "may not be defined read-only" )
 				ELSE
 					access :=  SyntaxTree.ReadOnly + {SyntaxTree.InternalWrite};
 				END;
@@ -520,11 +523,11 @@ TYPE
 		(** IndexList = '?' [',' ExpressionList ] | ExpressionList [',' '?']. **)
 		PROCEDURE IndexList(expressionList: SyntaxTree.ExpressionList);
 		VAR
-			position: LONGINT;
+			position: Position;
 			done: BOOLEAN;
 		BEGIN
 			IF Trace THEN S( "IndexList" ) END;
-			position := symbol.start;
+			position := symbol.position;
 
 			IF Optional(Scanner.Questionmark) THEN
 				expressionList.AddExpression(SyntaxTree.NewTensorRangeExpression(position));
@@ -569,7 +572,7 @@ TYPE
 		PROCEDURE RangeExpression(): SyntaxTree.Expression;
 		VAR
 			expression, first, last, step: SyntaxTree.Expression;
-			position: LONGINT;
+			position: Position;
 
 			PROCEDURE HasDelimiter(): BOOLEAN;
 			BEGIN RETURN
@@ -580,7 +583,7 @@ TYPE
 
 		BEGIN
 			IF Trace THEN S( "RangeExpression" ) END;
-			position := symbol.start;
+			position := symbol.position;
 
 			IF Optional(Scanner.Times) THEN
 				expression := SyntaxTree.NewRangeExpression(position, NIL, NIL, NIL)
@@ -637,12 +640,12 @@ TYPE
 		PROCEDURE Designator( ): SyntaxTree.Designator;
 		VAR
 			designator: SyntaxTree.Designator;  expressionList: SyntaxTree.ExpressionList;
-			identifier: SyntaxTree.Identifier; position: LONGINT;
+			identifier: SyntaxTree.Identifier; position: Position;
 			qualifiedIdentifier: SyntaxTree.QualifiedIdentifier;
 			qualifiedType : SyntaxTree.QualifiedType;
 		BEGIN
 			IF Trace THEN S( "Designator" ) END;
-			position := symbol.start;
+			position := symbol.position;
 			IF Optional(Scanner.Self) THEN
 				designator := SyntaxTree.NewSelfDesignator(position);
 			ELSIF Optional(Scanner.Result) THEN
@@ -675,7 +678,7 @@ TYPE
 			END;
 
 			LOOP
-				position := symbol.start;
+				position := symbol.position;
 				IF OptionalB( Scanner.LeftParenthesis ) THEN
 					expressionList := SyntaxTree.NewExpressionList();
 					IF ~Optional( Scanner.RightParenthesis ) THEN
@@ -721,7 +724,7 @@ TYPE
 		BEGIN
 			IF Trace THEN S( "Set" ) END;
 
-			set := SyntaxTree.NewSet(symbol.start);
+			set := SyntaxTree.NewSet(symbol.position);
 			Check(Scanner.LeftBrace);
 			IF ~Optional(Scanner.RightBrace) THEN
 				REPEAT
@@ -729,7 +732,7 @@ TYPE
 				UNTIL ~Optional(Scanner.Comma);
 				Check(Scanner.RightBrace);
 			END;
-			set.End(symbol.start);
+			set.End(symbol.position.end);
 
 			IF Trace THEN E( "Set" ) END;
 			RETURN set
@@ -739,7 +742,7 @@ TYPE
 		PROCEDURE MathArray(): SyntaxTree.Expression;
 		VAR array: SyntaxTree.MathArrayExpression; element: SyntaxTree.Expression;
 		BEGIN
-			array := SyntaxTree.NewMathArrayExpression(symbol.start);
+			array := SyntaxTree.NewMathArrayExpression(symbol.position);
 			IF ~Optional(Scanner.RightBracket) THEN
 				REPEAT
 					element := Expression();
@@ -755,32 +758,27 @@ TYPE
 			 			  | 'SIZE' 'OF' Designator | 'ADDRESS' 'OF' Designator
 			 			  **)
 		PROCEDURE Factor( ): SyntaxTree.Expression;
-		VAR factor: SyntaxTree.Expression; position,operator: LONGINT;
+		VAR factor: SyntaxTree.Expression; position: Position; operator: LONGINT;
 		BEGIN
 			IF Trace THEN S( "Factor" ) END;
-			position := symbol.start;
+			position := symbol.position;
 			CASE Token() OF
 			| Scanner.Number:
 					IF (symbol.numberType = Scanner.Integer) THEN
 						factor := SyntaxTree.NewIntegerValue( position, symbol.integer);
-						factor.End( symbol.end );
 					ELSIF (symbol.numberType = Scanner.Hugeint) THEN
 						factor := SyntaxTree.NewIntegerValue(position, symbol.hugeint);
-						factor.End( symbol.end );
 					ELSIF (symbol.numberType = Scanner.Real) OR (symbol.numberType = Scanner.Longreal) THEN
 						factor := SyntaxTree.NewRealValue( position, symbol.real);
 						factor(SyntaxTree.RealValue).SetSubtype(symbol.numberType);
-						factor.End( symbol.end );
 					ELSE HALT( 100 )
 					END;
 					NextSymbol;
 			| Scanner.Character:
 					factor := SyntaxTree.NewCharacterValue(position,symbol.character);
-					factor.End(symbol.end);
 					NextSymbol;
 			| Scanner.String:
 					factor := SyntaxTree.NewStringValue( position, symbol.string );
-					factor.End( symbol.end );
 					NextSymbol;
 					WHILE (Token() = Scanner.String) OR (Token() = Scanner.Character) DO
 						IF Token() = Scanner.Character THEN
@@ -788,25 +786,21 @@ TYPE
 						ELSE
 							factor(SyntaxTree.StringValue).Append(symbol.string);
 						END;
-						factor.End(symbol.end);
+						factor.End(symbol.position.end);
 						NextSymbol;
 					END;
 			| Scanner.Nil:
 					factor := SyntaxTree.NewNilValue( position );
-					factor.End( symbol.end );
 					NextSymbol;
 			| Scanner.Imag:
 					factor := SyntaxTree.NewComplexValue(position, 0, 1);
 					factor(SyntaxTree.ComplexValue).SetSubtype(Scanner.Real);
-					factor.End( symbol.end );
 					NextSymbol;
 			| Scanner.True:
 					factor := SyntaxTree.NewBooleanValue( position, TRUE );
-					factor.End( symbol.end );
 					NextSymbol;
 			| Scanner.False:
 					factor := SyntaxTree.NewBooleanValue( position, FALSE );
-					factor.End( symbol.end );
 					NextSymbol;
 			| Scanner.LeftBrace:
 					factor := Set();
@@ -814,12 +808,12 @@ TYPE
 					NextSymbol;
 					factor := Expression();
 					Check( Scanner.RightParenthesis );
-					factor.End( symbol.end );
+					factor.End( symbol.position.end );
 			| Scanner.Not:
 					NextSymbol;
 					factor := Factor();
 					factor := SyntaxTree.NewUnaryExpression( position, factor, Scanner.Not );
-					factor.End( symbol.end );
+					factor.End( symbol.position.end );
 			| Scanner.Address, Scanner.Size, Scanner.Alias:
 					operator := Token();
 					factor := Designator();
@@ -827,14 +821,14 @@ TYPE
 						factor := Designator();
 						factor := SyntaxTree.NewUnaryExpression( position, factor, operator );
 					END;
-					factor.End (symbol.end)
+					factor.End (symbol.position.end)
 			| Scanner.Self, Scanner.Result, Scanner.Identifier, Scanner.New:
 					factor := Designator();
-					factor.End( symbol.end );
+					factor.End( symbol.position.end );
 			| Scanner.LeftBracket:
 					NextSymbol;
 					factor := MathArray();
-					factor.End(symbol.end);
+					factor.End(symbol.position.end);
 			ELSE
 				Error( position, Basic.ValueStartIncorrectSymbol, "" );
 				NextSymbol;  factor := SyntaxTree.invalidExpression;
@@ -858,10 +852,10 @@ TYPE
 		   MulOp = '*' | '**' | '.*' | '+*' | '/' | '\' | './' | 'div' | 'mod' | '&'.
 		**)
 		PROCEDURE Term( ): SyntaxTree.Expression;
-		VAR term, factor: SyntaxTree.Expression;  operator: LONGINT; position: LONGINT;
+		VAR term, factor: SyntaxTree.Expression;  operator: LONGINT; position: Position;
 		BEGIN
 			IF Trace THEN S( "Term" ) END;
-			position := symbol.start;
+			position := symbol.position;
 			term := Factor();
 			WHILE (TokenB() >= Scanner.Times) & (TokenB() <= Scanner.And)  DO
 				operator := Token();
@@ -869,7 +863,7 @@ TYPE
 				factor := Factor();
 				term := SyntaxTree.NewBinaryExpression( position, term, factor, operator );
 			END;
-			term.End( symbol.end );
+			term.End( symbol.position.end );
 			IF Trace THEN E( "Term" ) END;
 			RETURN term
 		END Term;
@@ -878,10 +872,10 @@ TYPE
 			AddOp                = '+' | '-' | 'or'.
 		**)
 		PROCEDURE SimpleExpression( ): SyntaxTree.Expression;
-		VAR operator: LONGINT;  term, expression: SyntaxTree.Expression;  position: LONGINT;
+		VAR operator: LONGINT;  term, expression: SyntaxTree.Expression;  position: Position;
 		BEGIN
 			IF Trace THEN S( "SimpleExpression" ) END;
-			position := symbol.start;
+			position := symbol.position;
 			IF Peek(Scanner.Plus) OR Peek(Scanner.Minus) THEN (* sign should be part of the factor *)
 				operator := Token();
 				NextSymbol;
@@ -907,10 +901,10 @@ TYPE
 			                     | 'in' | 'is'
 		**)
 		PROCEDURE Expression*( ): SyntaxTree.Expression;
-		VAR expression, rightExpression: SyntaxTree.Expression;  operator: LONGINT;  position: LONGINT;
+		VAR expression, rightExpression: SyntaxTree.Expression;  operator: LONGINT;  position: Position;
 		BEGIN
 			IF Trace THEN S( "Expression" ) END;
-			position := symbol.start;
+			position := symbol.position;
 			expression := RangeExpression();
 			IF (TokenB() >= Scanner.Equal) & (TokenB() <= Scanner.Is) THEN
 				operator := Token();
@@ -975,14 +969,14 @@ TYPE
 			withPart: SyntaxTree.WithPart; caller: SyntaxTree.ProcedureCallStatement;
 			caseStatement: SyntaxTree.CaseStatement;  whileStatement: SyntaxTree.WhileStatement;  repeatStatement: SyntaxTree.RepeatStatement;  forStatement: SyntaxTree.ForStatement;
 			identifier: SyntaxTree.Identifier;  loopStatement: SyntaxTree.LoopStatement;  returnStatement: SyntaxTree.ReturnStatement;  awaitStatement: SyntaxTree.AwaitStatement;
-			qualifiedType: SyntaxTree.QualifiedType; code : SyntaxTree.Code; position: LONGINT; result: BOOLEAN;
+			qualifiedType: SyntaxTree.QualifiedType; code : SyntaxTree.Code; position: Position; result: BOOLEAN;
 			commToken: Scanner.Token;
 		BEGIN
 			IF Trace THEN S( "Statement" ) END;
 			CASE Token() OF
 			| Scanner.Identifier, Scanner.Self, Scanner.Result, Scanner.New:
 					designator := Designator();
-					position := symbol.start;
+					position := symbol.position;
 					IF OptionalB( Scanner.Becomes ) THEN
 						expression := Expression();
 						statement := SyntaxTree.NewAssignment( position, designator, expression,outer );
@@ -1003,7 +997,7 @@ TYPE
 					result := TRUE
 			| Scanner.If:
 					NextSymbol;
-					ifStatement := SyntaxTree.NewIfStatement( symbol.start ,outer);
+					ifStatement := SyntaxTree.NewIfStatement( symbol.position ,outer);
 					CommentStatement(ifStatement);
 					expression := Expression();
 					ifStatement.ifPart.SetCondition( expression );
@@ -1027,7 +1021,7 @@ TYPE
 					Check( Scanner.End );  statements.AddStatement( ifStatement );
 					result := TRUE
 			| Scanner.With:
-					withStatement := SyntaxTree.NewWithStatement( symbol.start ,outer);
+					withStatement := SyntaxTree.NewWithStatement( symbol.position ,outer);
 					CommentStatement(withStatement);
 					NextSymbol;
 					REPEAT
@@ -1056,7 +1050,7 @@ TYPE
 					statements.AddStatement( withStatement );
 					result := TRUE
 			| Scanner.Case:
-					caseStatement := SyntaxTree.NewCaseStatement( symbol.start,outer );
+					caseStatement := SyntaxTree.NewCaseStatement( symbol.position,outer );
 					CommentStatement(caseStatement);
 					NextSymbol;
 					expression := Expression();
@@ -1075,7 +1069,7 @@ TYPE
 					result := TRUE
 			| Scanner.While:
 					NextSymbol;
-					whileStatement := SyntaxTree.NewWhileStatement( symbol.start, outer );
+					whileStatement := SyntaxTree.NewWhileStatement( symbol.position, outer );
 					CommentStatement(whileStatement);
 					expression := Expression();
 					Check( Scanner.Do );
@@ -1087,7 +1081,7 @@ TYPE
 					result := TRUE
 			| Scanner.Repeat:
 					NextSymbol;
-					repeatStatement := SyntaxTree.NewRepeatStatement( symbol.start, outer );
+					repeatStatement := SyntaxTree.NewRepeatStatement( symbol.position, outer );
 					CommentStatement(repeatStatement);
 					statementSequence := StatementSequence(repeatStatement);
 					repeatStatement.SetStatements( statementSequence );
@@ -1098,7 +1092,7 @@ TYPE
 					result := TRUE
 			| Scanner.For:
 					NextSymbol;
-					forStatement := SyntaxTree.NewForStatement( symbol.start, outer);
+					forStatement := SyntaxTree.NewForStatement( symbol.position, outer);
 					CommentStatement(forStatement);
 					identifier := Identifier(position);
 					IF Optional(Scanner.Period) & Optional(Scanner.Identifier) THEN
@@ -1124,7 +1118,7 @@ TYPE
 					result := TRUE
 			| Scanner.Loop:
 					NextSymbol;
-					loopStatement := SyntaxTree.NewLoopStatement( symbol.start ,outer);
+					loopStatement := SyntaxTree.NewLoopStatement( symbol.position ,outer);
 					CommentStatement(loopStatement);
 					statementSequence := StatementSequence(loopStatement);
 					loopStatement.SetStatements( statementSequence );
@@ -1133,13 +1127,13 @@ TYPE
 					result := TRUE;
 			| Scanner.Exit:
 					NextSymbol;
-					statement := SyntaxTree.NewExitStatement( symbol.start, outer);
+					statement := SyntaxTree.NewExitStatement( symbol.position, outer);
 					CommentStatement(statement);
 					statements.AddStatement( statement );
 					result := TRUE;
 			| Scanner.Return:
 					NextSymbol;
-					returnStatement := SyntaxTree.NewReturnStatement( symbol.start, outer);
+					returnStatement := SyntaxTree.NewReturnStatement( symbol.position, outer);
 					CommentStatement(returnStatement);
 					IF (Token() >= Scanner.Plus) & (Token() <= Scanner.Identifier) THEN
 						expression := Expression();
@@ -1151,7 +1145,7 @@ TYPE
 					NextSymbol;  statement := StatementBlock(outer);  statements.AddStatement( statement );  Check( Scanner.End );
 					result := TRUE;
 			| Scanner.Await:
-					awaitStatement := SyntaxTree.NewAwaitStatement( symbol.start, outer );
+					awaitStatement := SyntaxTree.NewAwaitStatement( symbol.position, outer );
 					CommentStatement(awaitStatement);
 					NextSymbol;
 					expression := Expression();
@@ -1209,10 +1203,12 @@ TYPE
 
 		(** StatementBlock = [Flags] StatementSequence. **)
 		PROCEDURE StatementBlock(outer: SyntaxTree.Statement): SyntaxTree.StatementBlock;
-		VAR block: SyntaxTree.StatementBlock;
+		VAR block: SyntaxTree.StatementBlock; position: Position;
 		BEGIN
 			IF Trace THEN S( "StatementBlock" ) END;
-			block := SyntaxTree.NewStatementBlock( symbol.end, outer );
+			position := symbol.position;
+			position.start := position.end;
+			block := SyntaxTree.NewStatementBlock( position, outer );
 			CommentStatement(block);
 			IF Optional( Scanner.LeftBrace ) THEN
 				block.SetModifier(Flags());
@@ -1224,12 +1220,12 @@ TYPE
 
 		(** Code = {  any \ 'end' \ 'with' } ['with' {('in'|'out') StatementSequence}] . **)
 		PROCEDURE Code(outer: SyntaxTree.Statement): SyntaxTree.Code;
-		VAR startPos, endPos, i ,len: LONGINT; codeString: Scanner.StringType; code: SyntaxTree.Code;
+		VAR startPos: Position; endPos, i ,len: LONGINT; codeString: Scanner.StringType; code: SyntaxTree.Code;
 			end: Scanner.Token; in, out: BOOLEAN; left, right: SyntaxTree.Identifier;
 			statements, rules: SyntaxTree.StatementSequence;
 		BEGIN
-			startPos := symbol.start;
-			end := scanner.SkipToEndOfCode(startPos, endPos, symbol);
+			startPos := symbol.position;
+			end := scanner.SkipToEndOfCode(startPos.start, endPos, symbol);
 			IF (end = Scanner.End) OR (end = Scanner.With) THEN
 				codeString := symbol.string;
 				code := SyntaxTree.NewCode(startPos,outer);
@@ -1255,22 +1251,22 @@ TYPE
 		(** Body = 'begin' [Flags] StatementSequence ['finally' StatementSequence]
 		         			| 'code' Code. **)
 		PROCEDURE Body( scope: SyntaxTree.ProcedureScope ): SyntaxTree.Body;
-		VAR body: SyntaxTree.Body; code: SyntaxTree.Code; position: LONGINT;  previousScope: SyntaxTree.Scope;
+		VAR body: SyntaxTree.Body; code: SyntaxTree.Code; position: Position;  previousScope: SyntaxTree.Scope;
 		BEGIN
 			previousScope := currentScope;
 			currentScope := scope;
 			IF Trace THEN S( "Body" ) END;
 			IF Peek( Scanner.Code ) THEN
-				body := SyntaxTree.NewBody(symbol.start,scope); (* empty body for the time being *)
+				body := SyntaxTree.NewBody(symbol.position,scope); (* empty body for the time being *)
 				(* assemble *)
 				code := Code(body);
 				body.SetCode(code);
 			ELSIF Mandatory( Scanner.Begin ) THEN
-				body := SyntaxTree.NewBody(symbol.start,scope);
+				body := SyntaxTree.NewBody(symbol.position,scope);
 				IF Optional( Scanner.LeftBrace ) THEN
 					body.SetModifier(Flags());
 				END;
-				position := symbol.start;
+				position := symbol.position;
 				body.SetStatementSequence(StatementSequence(body));
 				IF Optional( Scanner.Finally ) THEN
 					body.SetFinally(StatementSequence(body));
@@ -1287,22 +1283,22 @@ TYPE
 		BEGIN
 			procedureScope := SyntaxTree.NewProcedureScope(parentScope);
 			IF parentScope IS SyntaxTree.ModuleScope THEN
-				procedure := SyntaxTree.NewProcedure( symbol.start, Global.ModuleBodyName,procedureScope);
+				procedure := SyntaxTree.NewProcedure( symbol.position, Global.ModuleBodyName,procedureScope);
 				procedure.SetAccess(SyntaxTree.Hidden);
 			ELSE
-				procedure := SyntaxTree.NewProcedure( symbol.start, Global.RecordBodyName,procedureScope);
+				procedure := SyntaxTree.NewProcedure( symbol.position, Global.RecordBodyName,procedureScope);
 				(*! todo: make this a hidden symbol. Problematic when used with paco. *)
 				procedure.SetAccess(SyntaxTree.Public + SyntaxTree.Protected + SyntaxTree.Internal);
 			END;
 			parentScope.AddProcedure(procedure);
-			procedure.SetType(SyntaxTree.NewProcedureType(-1,parentScope));
+			procedure.SetType(SyntaxTree.NewProcedureType(SyntaxTree.invalidPosition,parentScope));
 			procedure.SetBodyProcedure(TRUE);
 			procedureScope.SetBody(Body(procedureScope));
 			RETURN procedure
 		END BodyProcedure;
 
 		(* ProcedureType = 'procedure' [Flags] [FormalParameters]. *)
-		PROCEDURE ProcedureType(position: LONGINT;  parentScope: SyntaxTree.Scope): SyntaxTree.ProcedureType;
+		PROCEDURE ProcedureType(position: Position;  parentScope: SyntaxTree.Scope): SyntaxTree.ProcedureType;
 		VAR procedureType: SyntaxTree.ProcedureType;
 		BEGIN
 			IF Trace THEN S( "ProcedureType" ) END;
@@ -1318,7 +1314,7 @@ TYPE
 		END ProcedureType;
 
 		(** ObjectType = 'object' | 'object' [Flags] ['(' (QualifiedIdentifier | ArrayType) ')'] DeclarationSequence [Body] 'end' [Identifier] . **)
-		PROCEDURE ObjectType(position: LONGINT;  name: SyntaxTree.Identifier; parentScope: SyntaxTree.Scope ): SyntaxTree.Type;
+		PROCEDURE ObjectType(position: Position;  name: SyntaxTree.Identifier; parentScope: SyntaxTree.Scope ): SyntaxTree.Type;
 		VAR
 			objectType: SyntaxTree.RecordType;
 			pointerType: SyntaxTree.PointerType;
@@ -1372,7 +1368,7 @@ TYPE
 			*)
 
 			IF Optional( Scanner.Semicolon ) THEN
-				(*Warning(symbol.start,Diagnostics.Invalid,"no semicolon allowed here");*)
+				(*Warning(symbol.position,Diagnostics.Invalid,"no semicolon allowed here");*)
 			END;
 
 			DeclarationSequence( recordScope);
@@ -1390,7 +1386,7 @@ TYPE
 		
 		(** CellType = 'cell' [Flags] [PortList] [';'] DeclarationSequence [Body] 'end' [Identifier]
               | 'object'. **)
-		PROCEDURE CellType(position: LONGINT;  name: SyntaxTree.Identifier; parentScope: SyntaxTree.Scope; isCellNet: BOOLEAN): SyntaxTree.Type;
+		PROCEDURE CellType(position: Position;  name: SyntaxTree.Identifier; parentScope: SyntaxTree.Scope; isCellNet: BOOLEAN): SyntaxTree.Type;
 		VAR
 			cellType: SyntaxTree.CellType;
 			cellScope: SyntaxTree.CellScope;
@@ -1440,7 +1436,7 @@ TYPE
 		END CellType;
 
 		(** PointerType = 'pointer' [Flags] 'to' Type. **)
-		PROCEDURE PointerType( position: LONGINT; parentScope: SyntaxTree.Scope ): SyntaxTree.PointerType;
+		PROCEDURE PointerType( position: Position; parentScope: SyntaxTree.Scope ): SyntaxTree.PointerType;
 		VAR pointerType: SyntaxTree.PointerType;  base: SyntaxTree.Type; 	modifiers: SyntaxTree.Modifier;
 		BEGIN
 			IF Trace THEN S( "PointerType" ) END;
@@ -1463,7 +1459,7 @@ TYPE
 		(**
 			RecordType = 'record' [Flags] ['(' QualifiedIdentifier ')'] [VariableDeclaration {';' VariableDeclaration}] 'end'.
 		**)
-		PROCEDURE RecordType(position: LONGINT;  parentScope:SyntaxTree.Scope ): SyntaxTree.RecordType;
+		PROCEDURE RecordType(position: Position;  parentScope:SyntaxTree.Scope ): SyntaxTree.RecordType;
 		VAR
 			recordType: SyntaxTree.RecordType;
 			recordScope: SyntaxTree.RecordScope;
@@ -1502,7 +1498,7 @@ TYPE
 													| 'array' '[' MathArraySize {',' MathArraySize} ']' ['of' Type].
 	  		 MathArraySize = Expression | '*' | '?'.
 		**)
-		PROCEDURE ArrayType(position: LONGINT;   parentScope: SyntaxTree.Scope ): SyntaxTree.Type;
+		PROCEDURE ArrayType(position: Position;   parentScope: SyntaxTree.Scope ): SyntaxTree.Type;
 		VAR
 			arrayType: SyntaxTree.ArrayType;
 			type: SyntaxTree.Type;
@@ -1547,7 +1543,7 @@ TYPE
 				type := arrayType;
 				expression := SimpleExpression();
 				arrayType.SetLength( expression );
-				position := symbol.start;
+				position := symbol.position;
 				IF Optional( Scanner.Comma ) THEN
 					base := ArrayType( position,parentScope);
 					arrayType.SetArrayBase( base )
@@ -1562,7 +1558,7 @@ TYPE
 
 		(** EnumerationType = 'enum' ['('QualifiedIdentifier')'] IdentifierDefinition ['=' Expression] 
                                 {',' IdentifierDefinition ['=' Expression]} 'end'. *) 
-		PROCEDURE EnumerationType(position: LONGINT; parentScope: SyntaxTree.Scope): SyntaxTree.Type;
+		PROCEDURE EnumerationType(position: Position; parentScope: SyntaxTree.Scope): SyntaxTree.Type;
 		VAR type: SyntaxTree.EnumerationType; scope: SyntaxTree.EnumerationScope; identifier: SyntaxTree.Identifier;
 			qualifiedIdentifier: SyntaxTree.QualifiedIdentifier; qualifiedType: SyntaxTree.QualifiedType; access: SET;
 			constant: SyntaxTree.Constant; expression: SyntaxTree.Expression;
@@ -1578,7 +1574,7 @@ TYPE
 			END;
 			REPEAT
 				IdentifierDefinition(identifier,access,FALSE);
-				position := symbol.start;
+				position := symbol.position;
 				constant := SyntaxTree.NewConstant( position, identifier );
 				CommentSymbol(constant);
 				constant.SetAccess(access);
@@ -1593,7 +1589,7 @@ TYPE
 		END EnumerationType;
 
 		(** PortType = 'port' ('in'|'out') ['(' Expression ')'] *)
-		PROCEDURE PortType(position: LONGINT; parentScope: SyntaxTree.Scope): SyntaxTree.Type;
+		PROCEDURE PortType(position: Position; parentScope: SyntaxTree.Scope): SyntaxTree.Type;
 		VAR type: SyntaxTree.Type; direction: LONGINT; sizeExpression: SyntaxTree.Expression;
 		BEGIN
 			(* port symbol already consumed *)
@@ -1616,10 +1612,10 @@ TYPE
 		(** Type = ArrayType | RecordType | PointerType | ObjectType | CellType | CellnetType | PortType 
 							| ProcedureType | EnumerationType | QualifiedIdentifier. *)
 		PROCEDURE Type( name: SyntaxTree.Identifier; parentScope: SyntaxTree.Scope ): SyntaxTree.Type;
-		VAR type: SyntaxTree.Type;  qualifiedIdentifier: SyntaxTree.QualifiedIdentifier;  position: LONGINT;
+		VAR type: SyntaxTree.Type;  qualifiedIdentifier: SyntaxTree.QualifiedIdentifier;  position: Position;
 		BEGIN
 			IF Trace THEN S( "Type" ) END;
-			position := symbol.start;
+			position := symbol.position;
 			IF Optional( Scanner.Array ) THEN type := ArrayType( position,parentScope );
 			ELSIF Optional( Scanner.Record ) THEN type := RecordType( position,parentScope );
 			ELSIF Optional( Scanner.Pointer ) THEN type := PointerType( position,parentScope );
@@ -1645,7 +1641,7 @@ TYPE
 		VAR
 			type: SyntaxTree.Type; name: SyntaxTree.Identifier;
 			firstParameter, parameter: SyntaxTree.Parameter;
-			position: LONGINT; modifiers: SyntaxTree.Modifier;
+			position: Position; modifiers: SyntaxTree.Modifier;
 		BEGIN
 			IF Trace THEN S( "PortDeclaration" ) END;
 			firstParameter := cell.lastParameter;
@@ -1692,7 +1688,7 @@ TYPE
 		PROCEDURE ParameterDeclaration( procedureType: SyntaxTree.ProcedureType ; parentScope: SyntaxTree.Scope);
 		VAR
 			type: SyntaxTree.Type; name: SyntaxTree.Identifier;
-			firstParameter, parameter: SyntaxTree.Parameter;   kind,position: LONGINT;
+			firstParameter, parameter: SyntaxTree.Parameter;   kind: LONGINT; position: Position;
 		BEGIN
 			IF Trace THEN S( "ParameterDeclaration" ) END;
 			IF Optional( Scanner.Var ) THEN (* var parameter *)
@@ -1700,7 +1696,7 @@ TYPE
 			ELSIF Optional( Scanner.Const ) THEN (* const parameter *)
 				kind := SyntaxTree.ConstParameter
 			ELSIF Token() # Scanner.Identifier THEN
-				Error(symbol.start,Scanner.Identifier,"");
+				Error(symbol.position,Scanner.Identifier,"");
 				RETURN
 			ELSE kind := SyntaxTree.ValueParameter
 			END;
@@ -1730,7 +1726,7 @@ TYPE
 
 		(** FormalParameters = '(' [ParameterDeclaration {';' ParameterDeclaration}] ')' [':' [Flags] Type]. **)
 		PROCEDURE FormalParameters( procedureType: SyntaxTree.ProcedureType ; parentScope: SyntaxTree.Scope);
-		VAR type: SyntaxTree.Type; position: LONGINT;
+		VAR type: SyntaxTree.Type; position: Position;
 		BEGIN
 			IF Trace THEN S( "FormalParameters" ) END;
 			(* left parenthesis already consumed *)
@@ -1745,7 +1741,7 @@ TYPE
 				Check( Scanner.RightParenthesis );
 			END;
 			IF Optional( Scanner.Colon ) THEN
-				position:= symbol.start;
+				position:= symbol.position;
 				IF Optional( Scanner.LeftBrace) THEN
 					procedureType.SetReturnTypeModifiers(Flags());
 				END;
@@ -1758,7 +1754,7 @@ TYPE
 
 		(** Flags = '{' [Identifier ['(' Expression ')'|'=' Expression]  {',' Identifier ['(' Expression ')' | '=' Expression ] } ]  '}'. **)
 		PROCEDURE Flags(): SyntaxTree.Modifier;
-		VAR identifier: SyntaxTree.Identifier; modifier,list: SyntaxTree.Modifier; position: LONGINT; expression: SyntaxTree.Expression;
+		VAR identifier: SyntaxTree.Identifier; modifier,list: SyntaxTree.Modifier; position: Position; expression: SyntaxTree.Expression;
 		BEGIN
 			IF Trace THEN S( "Flags" ) END;
 			(* left brace already consumed *)
@@ -1766,7 +1762,7 @@ TYPE
 			IF Peek(Scanner.RightBrace) THEN (* empty flags *)
 			ELSE
 				REPEAT
-					position := symbol.start;
+					position := symbol.position;
 					identifier := Identifier(position);
 					IF Optional(Scanner.LeftParenthesis) THEN
 						expression := Expression();
@@ -1800,7 +1796,7 @@ TYPE
 				SetNextInComment(recentComment, symbol);
 				recentComment := NIL
 			END;
-			recentLine := scanner.line;
+			recentLine := scanner.position.line;
 			recentCommentItem := symbol;
 		END CommentSymbol;
 
@@ -1811,7 +1807,7 @@ TYPE
 				SetNextInComment(recentComment, symbol);
 				recentComment := NIL
 			END;
-			recentLine := scanner.line;
+			recentLine := scanner.position.line;
 			recentCommentItem := symbol
 		END CommentStatement;
 
@@ -1822,7 +1818,7 @@ TYPE
 				SetNextInComment(recentComment, symbol);
 				recentComment := NIL
 			END;
-			recentLine := scanner.line;
+			recentLine := scanner.position.line;
 			recentCommentItem := symbol
 		END CommentCasePart;
 
@@ -1833,7 +1829,7 @@ TYPE
 				SetNextInComment(recentComment, symbol);
 				recentComment := NIL
 			END;
-			recentLine := scanner.line;
+			recentLine := scanner.position.line;
 			recentCommentItem := symbol
 		END CommentIfPart;
 
@@ -1844,7 +1840,7 @@ TYPE
 				SetNextInComment(recentComment, symbol);
 				recentComment := NIL
 			END;
-			recentLine := scanner.line;
+			recentLine := scanner.position.line;
 			recentCommentItem := symbol
 		END CommentWithPart;
 
@@ -1858,7 +1854,7 @@ TYPE
 			procedureType: SyntaxTree.ProcedureType;
 			procedureScope : SyntaxTree.ProcedureScope;
 			access: SET;
-			position: LONGINT;
+			position: Position;
 			isConstructor: BOOLEAN;
 			isFinalizer: BOOLEAN;
 			isInline: BOOLEAN;
@@ -1872,7 +1868,7 @@ TYPE
 			modifiers := NIL;
 			isConstructor := FALSE; isFinalizer := FALSE; isInline := FALSE;
 
-			procedureType := SyntaxTree.NewProcedureType(symbol.start, parentScope);
+			procedureType := SyntaxTree.NewProcedureType(symbol.position, parentScope);
 
 			IF Optional( Scanner.Arrow) THEN (* ignore forward declarations *)
 				forwardDeclaration := TRUE;
@@ -1896,7 +1892,7 @@ TYPE
 				OperatorDeclaration( parentScope );  RETURN
 			END;
 
-			position:= symbol.start;
+			position:= symbol.position;
 			IdentifierDefinition( name, access,TRUE);
 
 			procedureScope := SyntaxTree.NewProcedureScope(parentScope);
@@ -1936,13 +1932,13 @@ TYPE
 			procedureType: SyntaxTree.ProcedureType;
 			operator: SyntaxTree.Operator;
 			access: SET;
-			i: LONGINT; ch: CHAR; position: LONGINT;
+			i: LONGINT; ch: CHAR; position: Position;
 			modifiers: SyntaxTree.Modifier; (* nopov *)
 			isInline, forward: BOOLEAN;
 		BEGIN
 			IF Trace THEN S( "Operator" ) END;
 			(* symbol operator already consumed *)
-			position := symbol.start;
+			position := symbol.position;
 
 			forward := Optional(Scanner.Arrow);			
 
@@ -1959,7 +1955,7 @@ TYPE
 				(* copy string to name and check for length. LEN(name)>0, LEN(string)>0 can be presumed  *)
 				i := 0; WHILE (string^[i] # 0X) DO INC(i) END;
 				IF i >= Scanner.MaxIdentifierLength THEN (* string too long to act as operator identifier *)
-					Error(symbol.start,Basic.StringTooLong,"");
+					Error(symbol.position,Basic.StringTooLong,"");
 				END
 			END;
 
@@ -1968,10 +1964,10 @@ TYPE
 			ELSE access := SyntaxTree.Internal;
 			END;
 			procedureScope := SyntaxTree.NewProcedureScope(parentScope);
-			operator := SyntaxTree.NewOperator( symbol.start, SyntaxTree.NewIdentifier(string^), procedureScope);
+			operator := SyntaxTree.NewOperator( symbol.position, SyntaxTree.NewIdentifier(string^), procedureScope);
 			CommentSymbol(operator);
 			operator.SetAccess(access);
-			procedureType := SyntaxTree.NewProcedureType(symbol.start,parentScope);
+			procedureType := SyntaxTree.NewProcedureType(symbol.position,parentScope);
 			IF Mandatory(Scanner.LeftParenthesis) THEN FormalParameters( procedureType, procedureScope ) END;
 			procedureType.SetModifiers(modifiers); (* nopov *)
 			operator.SetType( procedureType );
@@ -1997,12 +1993,12 @@ TYPE
 
 		(** VariableNameList = IdentifierDefinition [Flags] [':=' Expression | 'extern' String] {',' IdentifierDefinition [Flags] [':=' Expression | 'extern' String] }.**)
 		PROCEDURE VariableNameList( scope: SyntaxTree.Scope );
-		VAR varname: SyntaxTree.Identifier;  position: LONGINT; variable: SyntaxTree.Variable;  flags,access: SET; string: Scanner.StringType;
+		VAR varname: SyntaxTree.Identifier;  position: Position; variable: SyntaxTree.Variable;  flags,access: SET; string: Scanner.StringType;
 		BEGIN
 			IF Trace THEN S( "VariableNameList" ) END;
 			REPEAT
 				flags := {};
-				position := symbol.start;
+				position := symbol.position;
 				IdentifierDefinition( varname, access,TRUE);
 				variable := SyntaxTree.NewVariable( position, varname );
 				CommentSymbol(variable);
@@ -2037,10 +2033,10 @@ TYPE
 
 		(** TypeDeclaration = IdentifierDefinition '=' Type.**)
 		PROCEDURE TypeDeclaration(parentScope: SyntaxTree.Scope);
-		VAR name: SyntaxTree.Identifier;  position: LONGINT; type: SyntaxTree.Type; typeDeclaration: SyntaxTree.TypeDeclaration;   access: SET;
+		VAR name: SyntaxTree.Identifier;  position: Position; type: SyntaxTree.Type; typeDeclaration: SyntaxTree.TypeDeclaration;   access: SET;
 		BEGIN
 			IF Trace THEN S( "TypeDeclaration" ) END;
-			position := symbol.start;
+			position := symbol.position;
 			IdentifierDefinition( name, access,FALSE);
 			typeDeclaration := SyntaxTree.NewTypeDeclaration( position,name);
 			CommentSymbol(typeDeclaration);
@@ -2058,11 +2054,11 @@ TYPE
 
 		(** ConstDeclaration = IdentifierDefinition '=' Expression. **)
 		PROCEDURE ConstDeclaration(parentScope: SyntaxTree.Scope );
-		VAR name: SyntaxTree.Identifier;  position: LONGINT; constant: SyntaxTree.Constant;  expression: SyntaxTree.Expression;  access: SET;
+		VAR name: SyntaxTree.Identifier;  position: Position; constant: SyntaxTree.Constant;  expression: SyntaxTree.Expression;  access: SET;
 		BEGIN
 			IF Trace THEN S( "ConstDeclaration" ) END;
 			IdentifierDefinition( name, access, FALSE);
-			position := symbol.start;
+			position := symbol.position;
 			constant := SyntaxTree.NewConstant( position, name );
 			CommentSymbol(constant);
 			constant.SetAccess(access);
@@ -2136,19 +2132,19 @@ TYPE
 			Import     = Identifier [':=' Identifier] ['in' Identifier].
 		**)
 		PROCEDURE ImportList( scope: SyntaxTree.Scope );
-		VAR alias, name, context: SyntaxTree.Identifier;  import: SyntaxTree.Import; position,idPosition: LONGINT;
+		VAR alias, name, context: SyntaxTree.Identifier;  import: SyntaxTree.Import; position, idPosition: Position;
 		BEGIN
 			IF Trace THEN S( "ImportList" ) END;
 			(* import symbol already consumed *)
 			REPEAT
-				position := symbol.start;
+				position := symbol.position;
 				alias := Identifier(idPosition);
 				IF alias # SyntaxTree.invalidIdentifier THEN
 					IF Optional( Scanner.Becomes ) THEN name := Identifier(idPosition) ELSE name := alias;  END;
 					import := SyntaxTree.NewImport( position, alias, name, TRUE );
 					CommentSymbol(import);
 					IF Optional(Scanner.In) THEN
-						position := symbol.start;
+						position := symbol.position;
 						context := Identifier(idPosition);
 						IF context # SyntaxTree.invalidIdentifier THEN  import.SetContext(context) END;
 					END;
@@ -2169,11 +2165,11 @@ TYPE
 		**)
 
 		PROCEDURE Module*(): SyntaxTree.Module;
-		VAR moduleName, context: SyntaxTree.Identifier;  module: SyntaxTree.Module;  position: LONGINT; isCellNet: BOOLEAN;
+		VAR moduleName, context: SyntaxTree.Identifier;  module: SyntaxTree.Module;  position: Position; isCellNet: BOOLEAN;
 			scannerDiagnostics: Diagnostics.Diagnostics; modifiers: SyntaxTree.Modifier; c: SyntaxTree.Comment;
 		BEGIN
 			IF Trace THEN S( "Module" ) END;
-			position := symbol.start;
+			position := symbol.position;
 			moduleScope := SyntaxTree.NewModuleScope(); (* needed to feed in comment already before module starts *)
 			currentScope := moduleScope;
 			isCellNet := Optional(Scanner.CellNet);
@@ -2193,7 +2189,7 @@ TYPE
 
 				module.SetType(SyntaxTree.moduleType);
 				IF Optional(Scanner.In) THEN
-					position := symbol.start;
+					position := symbol.position;
 					context := Identifier(position);
 					module.SetContext(context);
 				END;
@@ -2213,7 +2209,7 @@ TYPE
 				Check(Scanner.End);
 				IF ExpectThisIdentifier( moduleName ) THEN
 					IF Token() # Scanner.Period THEN
-						Error(  symbol.start, Scanner.Period, "" )
+						Error(  symbol.position, Scanner.Period, "" )
 					ELSIF ~error & ~scanner.error THEN (* read ahead to read comments and to check for next module *)
 						scanner.ResetCase;
 						scannerDiagnostics := NIL;

+ 1 - 1
source/FoxPrintout.Mod

@@ -1473,7 +1473,7 @@ TYPE
 			IF info THEN
 				WHILE (x#NIL) DO
 					Indent;
-					w.String("comment at position "); w.Int(x.position,1);
+					w.String("comment at position "); w.Int(x.position.start,1);
 					IF x.sameLine THEN w.String("(in line with item)") END;
 					IF x.item = NIL THEN w.String("(no item)"); END;
 					w.String(":");

+ 41 - 33
source/FoxScanner.Mod

@@ -170,12 +170,13 @@ TYPE
 TYPE
 
 	Token*=LONGINT;
+	Position*= Basic.Position;
 
 	(**
 		symbol: data structure for the data transfer of the last read input from the scanner to the parser
 	**)
 	Symbol*= RECORD
-		start*,end*,line-: LONGINT; (* start and end position of symbol *)
+		position*: Position;
 		token*: Token; (* token of symbol *)
 		identifier*: IdentifierType; (* identifier *)
 		identifierString*: IdentifierString; (* cache of identifier's string *)
@@ -285,8 +286,11 @@ TYPE
 		diagnostics: Diagnostics.Diagnostics;   (* error logging *)
 
 		ch-: CHAR;   (* look-ahead character *)
+		position-: Position;
+		(*
 		position-: LONGINT;   (* current position *)
 		line-: LONGINT;
+		*)
 
 		error-: BOOLEAN;   (* if error occured during scanning *)
 
@@ -317,8 +321,9 @@ TYPE
 			firstIdentifier := TRUE;
 			IF reader = NIL THEN ch := EOT ELSE 	GetNextCharacter END;
 			IF Trace THEN D.Str( "New scanner  " );   D.Ln;  END;
-			SELF.position := position;
-			SELF.line := position;
+			SELF.position.start := position;
+			SELF.position.line := 1;
+			SELF.position.linepos := 0;
 			useLineNumbers := FALSE;
 		END InitializeScanner;
 
@@ -334,13 +339,14 @@ TYPE
 
 		(** report an error occured during scanning **)
 		PROCEDURE ErrorS(CONST msg: ARRAY OF CHAR);
+		VAR errorMessage: ARRAY 256 OF CHAR;
 		BEGIN
 			IF diagnostics # NIL THEN
+				COPY(msg, errorMessage); 
 				IF useLineNumbers THEN
-				diagnostics.Error(source^, line+1, Diagnostics.Invalid, msg)
-				ELSE
-				diagnostics.Error(source^, position, Diagnostics.Invalid, msg)
+					Basic.AppendPosition(errorMessage, position);
 				END;
+				diagnostics.Error(source^, position.start, Diagnostics.Invalid, errorMessage)
 			END;
 			error := TRUE;
 		END ErrorS;
@@ -351,11 +357,8 @@ TYPE
 		BEGIN
 			IF diagnostics # NIL THEN
 				Basic.GetErrorMessage(code,"",errorMessage);
-				IF useLineNumbers THEN
-				diagnostics.Error(source^, line+1, code, errorMessage)
-				ELSE
-				diagnostics.Error(source^, position, code, errorMessage)
-				END;
+				IF useLineNumbers THEN Basic.AppendPosition(errorMessage, position) END;
+				diagnostics.Error(source^, position.start, code, errorMessage)
 			END;
 			error := TRUE;
 		END Error;
@@ -363,8 +366,8 @@ TYPE
 		(** get next character, end of text results in ch = EOT **)
 		PROCEDURE GetNextCharacter*;
 		BEGIN
-			reader.Char(ch); INC(position);
-			IF ch = LF THEN INC(line) END;
+			reader.Char(ch); INC(position.start);
+			IF ch = LF THEN INC(position.line); position.linepos := position.start END;
 			(*
 			(* not necessary, as Streams returns 0X if reading failed, but in case Streams.Reader.Char is modified ...  *)
 			IF reader.res # Streams.Ok THEN ch := EOT END;
@@ -469,7 +472,7 @@ TYPE
 
 		BEGIN
 			(* traverse *)
-			escapePos := 0; ech := endString[0]; startPosition := position;
+			escapePos := 0; ech := endString[0]; startPosition := position.start;
 			GetNextCharacter;
 			REPEAT
 				IF ch = ech THEN
@@ -498,7 +501,7 @@ TYPE
 					ech := endString[0]; escapePos := 0;
 				END;
 			UNTIL (ch = EOT) OR (ech = 0X) OR error;
-			IF ch = EOT THEN position := startPosition; ErrorS("Unexpected end of text in string") END;
+			IF ch = EOT THEN position.start := startPosition; ErrorS("Unexpected end of text in string") END;
 		END ConsumeStringUntil;
 
 		PROCEDURE GetEscapedString(VAR symbol: Symbol);
@@ -813,12 +816,12 @@ TYPE
 		BEGIN
 			ASSERT(case # Unknown);
 			stringMaker.Clear;
-			startPos := symbol.end;
-			IF useLineNumbers THEN startPos := line END;
+			startPos := symbol.position.end;
+			IF useLineNumbers THEN startPos := position.line END;
 			s := symbol.token;
 			WHILE (s # EndOfText) & (s # End) & (s # With) DO
-				symbol.start := position;
-				endPos := position;
+				symbol.position := position;
+				endPos := position.start;
 				CASE ch OF
 				'A' .. 'Z','a'..'z': s := Identifier;
 					GetIdentifier(symbol);
@@ -833,7 +836,7 @@ TYPE
 					stringWriter.Char(ch);
 					GetNextCharacter;
 				END;
-				symbol.end := position;
+				symbol.position.end := position.start;
 			END;
 			stringWriter.Update;
 			symbol.string := stringMaker.GetStringCopy(symbol.stringLength);
@@ -862,12 +865,15 @@ TYPE
 		VAR s,token: LONGINT;
 		BEGIN
 			SkipBlanks;
+			symbol.position := position;
+			(*
 			IF useLineNumbers THEN
-				symbol.start := line+1; 
+				symbol.position.start := position.line+1; 
 			ELSE
-				symbol.start := position
+				symbol.position.start := position.start
 			END;
-			symbol.line := line;
+			symbol.position.line := position.line;
+			*)
 			stringMaker.Clear;
 			CASE ch OF  (* ch > " " *)
 			EOT: s := EndOfText
@@ -968,7 +974,7 @@ TYPE
 			firstIdentifier := FALSE;
 
 			symbol.token := s;
-			symbol.end := position;
+			symbol.position.end := position.start;
 
 			IF Trace THEN OutSymbol(D.Log,symbol); D.Ln; END;
 
@@ -991,7 +997,8 @@ TYPE
 	END Scanner;
 
 	Context*=RECORD
-		position, readerPosition, line : LONGINT;
+		position: Position;
+		readerPosition : LONGINT;
 		ch: CHAR;
 	END;
 
@@ -1024,7 +1031,6 @@ TYPE
 		BEGIN
 			context.ch := ch;
 			context.position := position;
-			context.line := line;
 			context.readerPosition := reader.Pos();
 		END GetContext;
 
@@ -1032,7 +1038,6 @@ TYPE
 		BEGIN
 			reader.SetPos(context.readerPosition);
 			ch := context.ch;
-			line := context.line;
 			position := context.position;
 		END SetContext;
 
@@ -1141,12 +1146,15 @@ TYPE
 		BEGIN
 			REPEAT
 				SkipBlanks;
+				symbol.position := position;
+				(*
 				IF useLineNumbers THEN
-					symbol.start := line+1; 
+					symbol.position.start := position.line+1; 
 				ELSE
-					symbol.start := position
+					symbol.position.start := position.start;
 				END;
-				symbol.line := line;
+				symbol.position.line := position.line;
+				*)
 				CASE ch OF  (* ch > ' ' *)
 				| EOT: 	s := EndOfText;
 				| DoubleQuote:
@@ -1190,12 +1198,12 @@ TYPE
 					IF ch = '$' THEN s := PCOffset; GetNextCharacter ELSE s := PC; END
 				ELSE s := None; GetNextCharacter;
 				END;
-				symbol.end := position;
+				symbol.position.end := position.start;
 			UNTIL s # Comment;
 
 			symbol.token := s;
 
-			IF Trace THEN D.Ln;  D.Str( "Scan at " );  D.Int( symbol.start,1 );  D.Str( ": " );  OutSymbol(D.Log,symbol); D.Update;  END;
+			IF Trace THEN D.Ln;  D.Str( "Scan at " );  D.Int( symbol.position.start,1 );  D.Str( ": " );  OutSymbol(D.Log,symbol); D.Update;  END;
 			RETURN ~error
 		END GetNextSymbol;
 
@@ -1237,7 +1245,7 @@ TYPE
 	PROCEDURE OutSymbol*(w: Streams.Writer; CONST symbol: Symbol);
 	VAR str: ARRAY 256 OF CHAR;
 	BEGIN
-		w.Int(symbol.start,1); w.String("-");w.Int(symbol.end,1); w.String(":");
+		w.Int(symbol.position.start,1); w.String("-");w.Int(symbol.position.end,1); w.String(":");
 		w.String(tokens[symbol.token]);
 		IF symbol.token= Number THEN
 			CASE symbol.numberType OF

+ 131 - 129
source/FoxSemanticChecker.Mod

@@ -9,11 +9,11 @@ CONST
 	Trace = FALSE;
 
 	Infinity = MAX(LONGINT); (* for type distance *)
-	InvalidPosition* = Diagnostics.Invalid;
 	MaxTensorIndexOperatorSize = 4;
 	UndefinedPhase = 0; DeclarationPhase=1; InlinePhase=2; ImplementationPhase=3;
 
 TYPE
+	Position=SyntaxTree.Position;
 	FileName=ARRAY 256 OF CHAR;
 
 	LateFix= POINTER TO RECORD (* contains a late fix to be resolved in a later step: type fixes and implementations *)
@@ -141,39 +141,41 @@ TYPE
 		END InitChecker;
 
 		(** report error **)
-		PROCEDURE Error(position: LONGINT; code: LONGINT; CONST message: ARRAY OF CHAR);
+		PROCEDURE Error(position: Position; code: LONGINT; CONST message: ARRAY OF CHAR);
 		VAR errorMessage: ARRAY 256 OF CHAR; errModule: SyntaxTree.Module;
 		BEGIN
 			IF diagnostics # NIL THEN
 				Basic.GetErrorMessage(code,message,errorMessage);
 				ASSERT(currentScope # NIL);
 				IF module # NIL THEN errModule := module ELSE errModule := currentScope.ownerModule END;
-				diagnostics.Error(errModule.sourceName, position, code, errorMessage);
+				Basic.AppendPosition(errorMessage, position);
+				diagnostics.Error(errModule.sourceName, position.start, code, errorMessage);
 			END;
 			error := TRUE;
 		END Error;
 
-		PROCEDURE Warning(position: LONGINT; CONST message: ARRAY OF CHAR);
+		PROCEDURE Warning(position: Position; CONST message: ARRAY OF CHAR);
 		VAR errModule: SyntaxTree.Module;
 		BEGIN
 			IF diagnostics # NIL THEN
 				IF module # NIL THEN errModule := module ELSE errModule := currentScope.ownerModule END;
-				diagnostics.Warning(errModule.sourceName, position, Diagnostics.Invalid, message);
+				diagnostics.Warning(errModule.sourceName, position.start, Diagnostics.Invalid, message);
 			END;
 		END Warning;
 
 
-		PROCEDURE ErrorSS(position: LONGINT; CONST msg,msg2: ARRAY OF CHAR);
+		PROCEDURE ErrorSS(position: Position; CONST msg,msg2: ARRAY OF CHAR);
 		VAR errorMessage: ARRAY 256 OF CHAR;
 		BEGIN
 			IF diagnostics # NIL THEN
 				Basic.Concat(errorMessage,msg," ", msg2);
-				diagnostics.Error(currentScope.ownerModule.sourceName, position, Diagnostics.Invalid, errorMessage);
+				Basic.AppendPosition(errorMessage, position);
+				diagnostics.Error(currentScope.ownerModule.sourceName, position.start, Diagnostics.Invalid, errorMessage);
 			END;
 			error := TRUE;
 		END ErrorSS;
 
-		PROCEDURE InfoSS(position: LONGINT; CONST msg1: ARRAY OF CHAR; CONST s: Basic.String);
+		PROCEDURE InfoSS(position: Position; CONST msg1: ARRAY OF CHAR; CONST s: Basic.String);
 		VAR msg, msg2: ARRAY 256 OF CHAR;
 		BEGIN
 			IF diagnostics # NIL THEN
@@ -181,7 +183,7 @@ TYPE
 				Strings.Append(msg, " = ");
 				Basic.GetString(s, msg2);
 				Strings.Append(msg, msg2);
-				diagnostics.Information(currentScope.ownerModule.sourceName, position, Diagnostics.Invalid, msg);
+				diagnostics.Information(currentScope.ownerModule.sourceName, position.start, Diagnostics.Invalid, msg);
 			END;
 		END InfoSS;
 
@@ -461,7 +463,7 @@ TYPE
 			resolve enumeration type: check enumeration scope
 		**)
 		PROCEDURE VisitEnumerationType(x: SyntaxTree.EnumerationType);
-		VAR position: LONGINT; baseScope: SyntaxTree.EnumerationScope; baseType,resolved: SyntaxTree.Type; enumerationBase: SyntaxTree.EnumerationType;
+		VAR position: Position; baseScope: SyntaxTree.EnumerationScope; baseType,resolved: SyntaxTree.Type; enumerationBase: SyntaxTree.EnumerationType;
 			lowest, highest: LONGINT;
 		BEGIN
 			IF TypeNeedsResolution(x) THEN
@@ -568,7 +570,7 @@ TYPE
 			resolvedType := ResolvedType(x);
 		END VisitArrayType;
 
-		PROCEDURE ImportModule(name: SyntaxTree.Identifier; position: LONGINT);
+		PROCEDURE ImportModule(name: SyntaxTree.Identifier; position: Position);
 		VAR module: SyntaxTree.Module; import, duplicate: SyntaxTree.Import; moduleScope: SyntaxTree.ModuleScope;
 		BEGIN
 			module := currentScope.ownerModule;
@@ -587,7 +589,7 @@ TYPE
 					import.SetScope(module.moduleScope);
 					import.SetDirect(TRUE);
 					IF moduleScope.FindSymbol(import.name) = NIL THEN
-						duplicate := SyntaxTree.NewImport(InvalidPosition,import.name, import.name,FALSE);
+						duplicate := SyntaxTree.NewImport(Basic.invalidPosition,import.name, import.name,FALSE);
 						duplicate.SetContext(import.context);
 						duplicate.SetModule(import.module);
 						Register(duplicate,moduleScope,TRUE);
@@ -655,7 +657,7 @@ TYPE
 		PROCEDURE AnonymousTypeDeclaration(x: SyntaxTree.Type; CONST prefix: ARRAY OF CHAR);
 		VAR typeDeclaration: SyntaxTree.TypeDeclaration; name,number: Scanner.IdentifierString;
 		BEGIN
-			Strings.IntToStr(x.position,number);
+			Strings.IntToStr(x.position.start,number);
 			COPY(prefix,name);
 			Strings.Append(name,"@");
 			Strings.Append(name,number);
@@ -675,7 +677,7 @@ TYPE
 			- if error then set base type to invalid type
 		**)
 		PROCEDURE FixPointerType(type: SyntaxTree.PointerType);
-		VAR resolved, base: SyntaxTree.Type; position: LONGINT; recordType: SyntaxTree.RecordType;
+		VAR resolved, base: SyntaxTree.Type; position: Position; recordType: SyntaxTree.RecordType;
 		BEGIN
 			ASSERT(type.pointerBase # NIL);
 			position := type.pointerBase.position;
@@ -724,7 +726,7 @@ TYPE
 		**)
 		PROCEDURE VisitPointerType(x: SyntaxTree.PointerType);
 		VAR recordType: SyntaxTree.RecordType; recordBaseType: SyntaxTree.Type;
-		modifiers: SyntaxTree.Modifier; position: LONGINT;
+		modifiers: SyntaxTree.Modifier; position: Position;
 		BEGIN
 			IF TypeNeedsResolution(x) THEN
 				modifiers := x.modifiers;
@@ -804,7 +806,7 @@ TYPE
 				END;
 		END FixProcedureType;
 
-		PROCEDURE HasFlag(VAR modifiers: SyntaxTree.Modifier; name: SyntaxTree.Identifier; VAR position: LONGINT): BOOLEAN;
+		PROCEDURE HasFlag(VAR modifiers: SyntaxTree.Modifier; name: SyntaxTree.Identifier; VAR position: Position): BOOLEAN;
 		VAR prev,this: SyntaxTree.Modifier;
 		BEGIN
 			this := modifiers;prev := NIL;
@@ -823,7 +825,7 @@ TYPE
 			END;
 		END HasFlag;
 
-		PROCEDURE HasValue(modifiers: SyntaxTree.Modifier; name: SyntaxTree.Identifier; VAR position: LONGINT; VAR value: LONGINT): BOOLEAN;
+		PROCEDURE HasValue(modifiers: SyntaxTree.Modifier; name: SyntaxTree.Identifier; VAR position: Position; VAR value: LONGINT): BOOLEAN;
 		VAR prev,this: SyntaxTree.Modifier;
 		BEGIN
 			this := modifiers;prev := NIL;
@@ -844,7 +846,7 @@ TYPE
 			END;
 		END HasValue;
 
-		PROCEDURE HasStringValue(modifiers: SyntaxTree.Modifier; name: SyntaxTree.Identifier; VAR position: LONGINT; VAR value: ARRAY OF CHAR): BOOLEAN;
+		PROCEDURE HasStringValue(modifiers: SyntaxTree.Modifier; name: SyntaxTree.Identifier; VAR position: Position; VAR value: ARRAY OF CHAR): BOOLEAN;
 		VAR prev,this: SyntaxTree.Modifier;
 		BEGIN
 			this := modifiers;prev := NIL;
@@ -866,7 +868,7 @@ TYPE
 		END HasStringValue;
 
 		PROCEDURE SkipImplementation*(x: SyntaxTree.CellType): BOOLEAN;
-		VAR svalue: ARRAY 32 OF CHAR; position: LONGINT;
+		VAR svalue: ARRAY 32 OF CHAR; position: Position;
 		BEGIN
 			IF cellsAreObjects THEN RETURN FALSE END;
 			IF HasStringValue(x.modifiers, Global.NameRuntime, position, svalue) THEN
@@ -922,7 +924,7 @@ TYPE
 			- enter procedure to list of deferred fixes (to avoid infinite loops in the declaration phase)
 		**)
 		PROCEDURE VisitProcedureType(procedureType: SyntaxTree.ProcedureType);
-		VAR modifiers: SyntaxTree.Modifier; value,position: LONGINT;
+		VAR modifiers: SyntaxTree.Modifier; value: LONGINT; position: Position;
 		BEGIN
 			IF TypeNeedsResolution(procedureType) THEN
 				modifiers := procedureType.modifiers;
@@ -961,7 +963,7 @@ TYPE
 			- every record type is guaranteed to have a type declaration in the module scope (anonymous or not)
 		**)
 		PROCEDURE VisitRecordType(x: SyntaxTree.RecordType);
-		VAR resolved, baseType: SyntaxTree.Type; position: LONGINT;
+		VAR resolved, baseType: SyntaxTree.Type; position: Position;
 			numberMethods: LONGINT; recordBase, recordType: SyntaxTree.RecordType; procedure: SyntaxTree.Procedure;
 			symbol: SyntaxTree.Symbol; isRealtime: BOOLEAN;
 			hasPointers: BOOLEAN;
@@ -1114,7 +1116,7 @@ TYPE
 		PROCEDURE VisitCellType(x: SyntaxTree.CellType);
 		VAR
 			symbol: SyntaxTree.Symbol; isRealtime: BOOLEAN; parameter: SyntaxTree.Parameter; type: SyntaxTree.Type; len: LONGINT;
-			modifier: SyntaxTree.Modifier; position,value: LONGINT; isEngine: BOOLEAN; property: SyntaxTree.Property;
+			modifier: SyntaxTree.Modifier; position: Position; value: LONGINT; isEngine: BOOLEAN; property: SyntaxTree.Property;
 			qualifiedIdentifier: SyntaxTree.QualifiedIdentifier;
 			recordBase: SyntaxTree.RecordType;
 			numberMethods, int: LONGINT;
@@ -1191,9 +1193,9 @@ TYPE
 								property.SetType(system.setType);
 							ELSIF IsStringValue(modifier.expression, str) THEN
 								(*property.SetValue(modifier.expression);*)
-								atype := SyntaxTree.NewArrayType(-1, NIL, SyntaxTree.Static);
+								atype := SyntaxTree.NewArrayType(Basic.invalidPosition, NIL, SyntaxTree.Static);
 								atype.SetArrayBase(modifier.expression.type(SyntaxTree.StringType).baseType);
-								atype.SetLength(Global.NewIntegerValue(system,-1, (* type(SyntaxTree.StringType).length *) 256 (*! check if this is a good idea *) ));
+								atype.SetLength(Global.NewIntegerValue(system,Basic.invalidPosition, (* type(SyntaxTree.StringType).length *) 256 (*! check if this is a good idea *) ));
 								property.SetType(atype);
 								
 							ELSE
@@ -1674,7 +1676,7 @@ TYPE
 		(**
 			return a regular type: if type is invalid, NIL, importType or typeDeclarationType then return invalidType else return type
 		**)
-		PROCEDURE RegularType(position: LONGINT; type: SyntaxTree.Type): SyntaxTree.Type;
+		PROCEDURE RegularType(position: Position; type: SyntaxTree.Type): SyntaxTree.Type;
 		VAR result: SyntaxTree.Type;
 		BEGIN
 			result := SyntaxTree.invalidType;
@@ -1692,7 +1694,7 @@ TYPE
 			- if not compatible then error is reported
 			- compatibility means type equality
 		**)
-		PROCEDURE SignatureCompatible(position: LONGINT; this, to: SyntaxTree.ProcedureType): BOOLEAN;
+		PROCEDURE SignatureCompatible(position: Position; this, to: SyntaxTree.ProcedureType): BOOLEAN;
 		VAR result: BOOLEAN;
 		BEGIN
 			result := SameType(to,this);
@@ -2093,7 +2095,7 @@ TYPE
 			value: SyntaxTree.MathArrayValue; arrayType: SyntaxTree.Type;
 
 			PROCEDURE RecursivelyFindType(x: SyntaxTree.MathArrayExpression);
-			VAR position,numberElements,i: LONGINT; expression: SyntaxTree.Expression;
+			VAR position: Position; numberElements,i: LONGINT; expression: SyntaxTree.Expression;
 			BEGIN
 				numberElements := x.elements.Length();
 				FOR i := 0 TO numberElements-1 DO
@@ -2119,7 +2121,7 @@ TYPE
 			END RecursivelyFindType;
 
 			PROCEDURE RecursivelySetExpression(x: SyntaxTree.MathArrayExpression);
-			VAR position,numberElements,i: LONGINT; expression: SyntaxTree.Expression;
+			VAR position: Position; numberElements,i: LONGINT; expression: SyntaxTree.Expression;
 			BEGIN
 				numberElements := x.elements.Length();
 				FOR i := 0 TO numberElements-1 DO
@@ -2316,7 +2318,7 @@ TYPE
 			resolvedExpression := result
 		END VisitUnaryExpression;
 
-		PROCEDURE MathArrayConversion(position: LONGINT; expression: SyntaxTree.Expression; type: SyntaxTree.Type): SyntaxTree.Expression;
+		PROCEDURE MathArrayConversion(position: Position; expression: SyntaxTree.Expression; type: SyntaxTree.Type): SyntaxTree.Expression;
 		VAR
 			result: SyntaxTree.Expression;
 			array: SyntaxTree.MathArrayExpression;
@@ -2336,7 +2338,7 @@ TYPE
 			END BaseType;
 
 			PROCEDURE RecursivelyConvert(x, to: SyntaxTree.MathArrayExpression);
-			VAR position,numberElements,i: LONGINT; expression: SyntaxTree.Expression; array: SyntaxTree.MathArrayExpression;
+			VAR position: Position; numberElements,i: LONGINT; expression: SyntaxTree.Expression; array: SyntaxTree.MathArrayExpression;
 			BEGIN
 				numberElements := x.elements.Length();
 				FOR i := 0 TO numberElements-1 DO
@@ -2410,7 +2412,7 @@ TYPE
 			RETURN result
 		END MathArrayConversion;
 
-		PROCEDURE ConvertValue(position: LONGINT; expression: SyntaxTree.Value; type: SyntaxTree.Type): SyntaxTree.Expression;
+		PROCEDURE ConvertValue(position: Position; expression: SyntaxTree.Value; type: SyntaxTree.Type): SyntaxTree.Expression;
 		VAR result: SyntaxTree.Expression; int: HUGEINT; real, imaginary: LONGREAL; set: SET; char: CHAR; string: Scanner.StringType;
 		BEGIN
 			result := expression; type := type.resolved;
@@ -2511,7 +2513,7 @@ TYPE
 			ELSIF IsCharacterValue(expression,char) THEN
 				IF (type IS SyntaxTree.StringType) OR (type IS SyntaxTree.ArrayType) & (type(SyntaxTree.ArrayType).arrayBase.resolved IS SyntaxTree.CharacterType) THEN
 					string[0] := char; string[1] := 0X;
-					type := SyntaxTree.NewStringType(InvalidPosition,system.characterType,2);
+					type := SyntaxTree.NewStringType(Basic.invalidPosition,system.characterType,2);
 					result := SyntaxTree.NewStringValue(expression.position,string);
 					result.SetType(type);
 				ELSIF (type IS SyntaxTree.ByteType) THEN
@@ -2569,7 +2571,7 @@ TYPE
 				- if expression is already of same type then return expression
 				- if incompatible conversion then report error and return invalidExpression
 		**)
-		PROCEDURE NewConversion*(position: LONGINT; expression: SyntaxTree.Expression; type: SyntaxTree.Type; reference: SyntaxTree.Expression): SyntaxTree.Expression;
+		PROCEDURE NewConversion*(position: Position; expression: SyntaxTree.Expression; type: SyntaxTree.Type; reference: SyntaxTree.Expression): SyntaxTree.Expression;
 		VAR result: SyntaxTree.Expression; value: SyntaxTree.Expression; expressionList: SyntaxTree.ExpressionList; typeDeclaration: SyntaxTree.TypeDeclaration; typeSymbol: SyntaxTree.Designator;
 		BEGIN
 			type := type.resolved;
@@ -2598,7 +2600,7 @@ TYPE
 				expressionList := SyntaxTree.NewExpressionList();
 				typeDeclaration := SyntaxTree.NewTypeDeclaration(expression.position,SyntaxTree.NewIdentifier("@byte"));
 				typeDeclaration.SetDeclaredType(type);
-				typeSymbol := SyntaxTree.NewSymbolDesignator(InvalidPosition,NIL,typeDeclaration);
+				typeSymbol := SyntaxTree.NewSymbolDesignator(Basic.invalidPosition,NIL,typeDeclaration);
 				typeSymbol.SetType(typeDeclaration.type);
 				expressionList.AddExpression(typeSymbol); (* type declaration symbol skipped *)
 				expressionList.AddExpression(expression);
@@ -2636,7 +2638,7 @@ TYPE
 			RETURN result
 		END NewConversion;
 
-		PROCEDURE CompatibleConversion(position: LONGINT; expression: SyntaxTree.Expression; type: SyntaxTree.Type): SyntaxTree.Expression;
+		PROCEDURE CompatibleConversion(position: Position; expression: SyntaxTree.Expression; type: SyntaxTree.Type): SyntaxTree.Expression;
 		BEGIN
 			IF CompatibleTo(system,expression.type, type) THEN
 				RETURN NewConversion(position, expression, type, NIL);
@@ -2758,7 +2760,7 @@ TYPE
 				- create symbol designator for operator
 			- if error then return invalidExpression, if no operator then return NIL
 		**)
-		PROCEDURE NewOperatorCall*(position: LONGINT; op: LONGINT; leftExpression, rightExpression: SyntaxTree.Expression; resultType: SyntaxTree.Type): SyntaxTree.Expression;
+		PROCEDURE NewOperatorCall*(position: Position; op: LONGINT; leftExpression, rightExpression: SyntaxTree.Expression; resultType: SyntaxTree.Type): SyntaxTree.Expression;
 		VAR
 			operator: SyntaxTree.Operator;
 			import: SyntaxTree.Import;
@@ -2784,9 +2786,9 @@ TYPE
 				ELSE
 					ASSERT(leftExpression IS SyntaxTree.Designator);
 					designator := leftExpression(SyntaxTree.Designator);
-					expression := NewSymbolDesignator(InvalidPosition, NewDereferenceDesignator(position, designator), recordType.arrayAccessOperators.len);
+					expression := NewSymbolDesignator(Basic.invalidPosition, NewDereferenceDesignator(position, designator), recordType.arrayAccessOperators.len);
 					ASSERT(expression IS SyntaxTree.Designator);
-					designator := NewProcedureCallDesignator(InvalidPosition, expression(SyntaxTree.Designator), SyntaxTree.NewExpressionList());
+					designator := NewProcedureCallDesignator(Basic.invalidPosition, expression(SyntaxTree.Designator), SyntaxTree.NewExpressionList());
 
 					IF (op = Global.Len) & (rightExpression = NIL) THEN
 						(* LEN(OBJECT) -> OBJECT^."LEN"() *)
@@ -2796,15 +2798,15 @@ TYPE
 						(* LEN(OBJECT, LONGINT) -> OBJECT^."LEN"()[LONGINT] *)
 						tempList := SyntaxTree.NewExpressionList();
 						tempList.AddExpression(rightExpression);
-						result := ResolveDesignator(SyntaxTree.NewBracketDesignator(InvalidPosition, designator, tempList))
+						result := ResolveDesignator(SyntaxTree.NewBracketDesignator(Basic.invalidPosition, designator, tempList))
 
 					ELSIF (op = Global.Dim) & (rightExpression = NIL) THEN
 						(* DIM(OBJECT) -> LEN(OBJECT^."LEN"(), 0) *)
 						tempList := SyntaxTree.NewExpressionList();
 						tempList.AddExpression(designator);
-						tempList.AddExpression(SyntaxTree.NewIntegerValue(InvalidPosition, 0));
-						designator := SyntaxTree.NewIdentifierDesignator(InvalidPosition, Global.GetIdentifier(Global.Len, module.case));
-						result := ResolveExpression(SyntaxTree.NewParameterDesignator(InvalidPosition, designator, tempList))
+						tempList.AddExpression(SyntaxTree.NewIntegerValue(Basic.invalidPosition, 0));
+						designator := SyntaxTree.NewIdentifierDesignator(Basic.invalidPosition, Global.GetIdentifier(Global.Len, module.case));
+						result := ResolveExpression(SyntaxTree.NewParameterDesignator(Basic.invalidPosition, designator, tempList))
 					END
 				END;
 			ELSE
@@ -2854,7 +2856,7 @@ TYPE
 					designator := expression(SyntaxTree.Designator);
 					result := NewProcedureCallDesignator(position,designator,actualParameters);
 					IF op = Scanner.Alias THEN (* hard type cast to same type *)
-						castReturnType := SyntaxTree.NewMathArrayType(Diagnostics.Invalid, expression.type.scope,SyntaxTree.Tensor);
+						castReturnType := SyntaxTree.NewMathArrayType(Basic.invalidPosition, expression.type.scope,SyntaxTree.Tensor);
 						castReturnType.SetArrayBase(ArrayBase(leftExpression.type.resolved,MAX(LONGINT)));
 						result.SetType(castReturnType);
 					END;
@@ -3619,7 +3621,7 @@ TYPE
 				- if symbol is a guarded variable then return a TypeGuardDesignator
 				- else return a symbol designator
 		**)
-		PROCEDURE NewSymbolDesignator*(position: LONGINT; left: SyntaxTree.Designator; symbol: SyntaxTree.Symbol): SyntaxTree.Expression;
+		PROCEDURE NewSymbolDesignator*(position: Position; left: SyntaxTree.Designator; symbol: SyntaxTree.Symbol): SyntaxTree.Expression;
 		VAR result: SyntaxTree.Expression; assignable: BOOLEAN; scope: SyntaxTree.Scope;
 		guardType: SyntaxTree.Type;
 		BEGIN
@@ -3855,7 +3857,7 @@ TYPE
 				- otherwise take sourceArray.arrayBase as new type
 				- type is not only replaced but might have to be inserted when resolving expressions of the form A[*,i,j,*]
 		**)
-		PROCEDURE AppendMathIndex(position: LONGINT; indexDesignator: SyntaxTree.IndexDesignator; indexListItem: SyntaxTree.Expression; sourceArray: SyntaxTree.MathArrayType);
+		PROCEDURE AppendMathIndex(position: Position; indexDesignator: SyntaxTree.IndexDesignator; indexListItem: SyntaxTree.Expression; sourceArray: SyntaxTree.MathArrayType);
 		VAR
 			targetArray: SyntaxTree.MathArrayType;
 			first, last, step: SyntaxTree.Expression;
@@ -3874,7 +3876,7 @@ TYPE
 
 			ELSIF indexListItem.type.resolved IS SyntaxTree.IntegerType THEN
 				IndexCheck(indexListItem, sourceArray.length);
-				indexListItem := NewConversion(InvalidPosition, indexListItem, system.sizeType, NIL);
+				indexListItem := NewConversion(Basic.invalidPosition, indexListItem, system.sizeType, NIL);
 				indexDesignator.parameters.AddExpression(indexListItem)
 
 			ELSIF indexListItem.type.resolved IS SyntaxTree.RangeType THEN
@@ -3903,9 +3905,9 @@ TYPE
 
 					(* add conversions to size type *)
 					(* TODO: needed? *)
-					rangeExpression.SetFirst(NewConversion(InvalidPosition, first, system.sizeType, NIL));
-					rangeExpression.SetLast(NewConversion(InvalidPosition, last, system.sizeType, NIL));
-					rangeExpression.SetStep(NewConversion(InvalidPosition, step, system.sizeType, NIL));
+					rangeExpression.SetFirst(NewConversion(Basic.invalidPosition, first, system.sizeType, NIL));
+					rangeExpression.SetLast(NewConversion(Basic.invalidPosition, last, system.sizeType, NIL));
+					rangeExpression.SetStep(NewConversion(Basic.invalidPosition, step, system.sizeType, NIL));
 				END;
 
 				IF indexDesignator.hasTensorRange THEN
@@ -3965,7 +3967,7 @@ TYPE
 			END;
 		END AppendMathIndex;
 
-		PROCEDURE AppendIndex(position: LONGINT; index: SyntaxTree.IndexDesignator; expression: SyntaxTree.Expression; over: SyntaxTree.Type);
+		PROCEDURE AppendIndex(position: Position; index: SyntaxTree.IndexDesignator; expression: SyntaxTree.Expression; over: SyntaxTree.Type);
 		VAR  parameters: SyntaxTree.ExpressionList;
 		BEGIN
 			parameters := index.parameters;
@@ -3977,7 +3979,7 @@ TYPE
 				ELSIF over IS SyntaxTree.StringType THEN
 					IndexCheck(expression,Global.NewIntegerValue(system, position, over(SyntaxTree.StringType).length));
 				END;
-				expression := NewConversion(InvalidPosition,expression,system.sizeType,NIL);
+				expression := NewConversion(Basic.invalidPosition,expression,system.sizeType,NIL);
 				parameters.AddExpression(expression);
 			ELSE
 				Error(position,Diagnostics.Invalid,"invalid index");
@@ -4003,7 +4005,7 @@ TYPE
 			ELSIF IsArrayStructuredObjectType(expression.type) THEN
 				(* expression of array-structured object type *)
 				mathArrayType := MathArrayStructureOfType(expression.type);
-				result := NewIndexOperatorCall(InvalidPosition, expression, ListOfOpenRanges(mathArrayType.Dimensionality()), NIL)
+				result := NewIndexOperatorCall(Basic.invalidPosition, expression, ListOfOpenRanges(mathArrayType.Dimensionality()), NIL)
 			ELSE
 				result := SyntaxTree.invalidExpression
 			END;
@@ -4018,7 +4020,7 @@ TYPE
 		BEGIN
 			result := SyntaxTree.NewExpressionList();
 			FOR i := 1 TO itemCount DO
-				result.AddExpression(ResolveExpression(SyntaxTree.NewRangeExpression(InvalidPosition, NIL, NIL, NIL)))
+				result.AddExpression(ResolveExpression(SyntaxTree.NewRangeExpression(Basic.invalidPosition, NIL, NIL, NIL)))
 			END;
 			RETURN result
 		END ListOfOpenRanges;
@@ -4027,7 +4029,7 @@ TYPE
 			- use given index list as actual parameters
 			- if rhs parameter is not NIL: call write operator, otherwise read operator
 		**)
-		PROCEDURE NewIndexOperatorCall*(position: LONGINT; left: SyntaxTree.Expression; indexList: SyntaxTree.ExpressionList; rhs: SyntaxTree.Expression): SyntaxTree.Designator;
+		PROCEDURE NewIndexOperatorCall*(position: Position; left: SyntaxTree.Expression; indexList: SyntaxTree.ExpressionList; rhs: SyntaxTree.Expression): SyntaxTree.Designator;
 		VAR
 			operator: SyntaxTree.Operator;
 			expression: SyntaxTree.Expression;
@@ -4110,7 +4112,7 @@ TYPE
 
 				(* import OCArrayBase if reshaping is needed *)
 				IF needsReshaping & ~arrayBaseImported THEN
-					ImportModule(Global.ArrayBaseName, InvalidPosition);
+					ImportModule(Global.ArrayBaseName, Basic.invalidPosition);
 					arrayBaseImported := TRUE
 				END;
 
@@ -4120,7 +4122,7 @@ TYPE
 				 *)
 				actualParameters := SyntaxTree.NewExpressionList();
 				IF usesGeneralOperator THEN
-					tempMathArrayExpression := SyntaxTree.NewMathArrayExpression(InvalidPosition);
+					tempMathArrayExpression := SyntaxTree.NewMathArrayExpression(Basic.invalidPosition);
 				END;
 				FOR i := 0 TO indexListSize - 1 DO
 					expression := indexList.GetExpression(i);
@@ -4128,9 +4130,9 @@ TYPE
 						(* convert integer to range using OCArrayBase.RangeFromInteger *)
 						tempList := SyntaxTree.NewExpressionList();
 						tempList.AddExpression(expression);
-						tempDesignator := SyntaxTree.NewIdentifierDesignator(InvalidPosition, Global.ArrayBaseName);
-						tempDesignator := SyntaxTree.NewSelectorDesignator(InvalidPosition, tempDesignator, SyntaxTree.NewIdentifier("RangeFromInteger"));
-						expression := ResolveExpression(SyntaxTree.NewParameterDesignator(InvalidPosition, tempDesignator, tempList));
+						tempDesignator := SyntaxTree.NewIdentifierDesignator(Basic.invalidPosition, Global.ArrayBaseName);
+						tempDesignator := SyntaxTree.NewSelectorDesignator(Basic.invalidPosition, tempDesignator, SyntaxTree.NewIdentifier("RangeFromInteger"));
+						expression := ResolveExpression(SyntaxTree.NewParameterDesignator(Basic.invalidPosition, tempDesignator, tempList));
 					END;
 					IF usesGeneralOperator THEN
 						tempMathArrayExpression.elements.AddExpression(expression);
@@ -4154,29 +4156,29 @@ TYPE
 							tempList.AddExpression(rhs);
 						ELSE
 							(* convert scalar to one-dimensional array *)
-							tempMathArrayExpression := SyntaxTree.NewMathArrayExpression(InvalidPosition);
+							tempMathArrayExpression := SyntaxTree.NewMathArrayExpression(Basic.invalidPosition);
 							tempMathArrayExpression.elements.AddExpression(rhs);
 							tempList.AddExpression(tempMathArrayExpression)
 						END;
 
 						(* list of kept dimensions *)
-						tempMathArrayExpression := SyntaxTree.NewMathArrayExpression(InvalidPosition);
+						tempMathArrayExpression := SyntaxTree.NewMathArrayExpression(Basic.invalidPosition);
 						FOR i := 0 TO indexListSize - 1 DO
 							expression := indexList.GetExpression(i);
 							IF expression.type.resolved IS SyntaxTree.IntegerType THEN
-								tempMathArrayExpression.elements.AddExpression(SyntaxTree.NewBooleanValue(InvalidPosition, FALSE)) (* insert dimension *)
+								tempMathArrayExpression.elements.AddExpression(SyntaxTree.NewBooleanValue(Basic.invalidPosition, FALSE)) (* insert dimension *)
 							ELSE
-								tempMathArrayExpression.elements.AddExpression(SyntaxTree.NewBooleanValue(InvalidPosition, TRUE)) (* keep dimension *)
+								tempMathArrayExpression.elements.AddExpression(SyntaxTree.NewBooleanValue(Basic.invalidPosition, TRUE)) (* keep dimension *)
 							END
 						END;
 						tempList.AddExpression(tempMathArrayExpression);
-						tempDesignator := SyntaxTree.NewIdentifierDesignator(InvalidPosition, Global.ArrayBaseName);
-						tempDesignator := SyntaxTree.NewSelectorDesignator(InvalidPosition, tempDesignator, SyntaxTree.NewIdentifier("ExpandDimensions"));
-						expression := ResolveExpression(SyntaxTree.NewParameterDesignator(InvalidPosition, tempDesignator, tempList));
+						tempDesignator := SyntaxTree.NewIdentifierDesignator(Basic.invalidPosition, Global.ArrayBaseName);
+						tempDesignator := SyntaxTree.NewSelectorDesignator(Basic.invalidPosition, tempDesignator, SyntaxTree.NewIdentifier("ExpandDimensions"));
+						expression := ResolveExpression(SyntaxTree.NewParameterDesignator(Basic.invalidPosition, tempDesignator, tempList));
 
 						IF expression.type.resolved IS SyntaxTree.MathArrayType THEN
 							(* change the base type of the returned tensor from SYSTEM.ALL to the array structure's element type *)
-							castReturnType := SyntaxTree.NewMathArrayType(Diagnostics.Invalid, expression.type.scope,SyntaxTree.Tensor);
+							castReturnType := SyntaxTree.NewMathArrayType(Basic.invalidPosition,expression.type.scope,SyntaxTree.Tensor);
 							castReturnType.SetArrayBase(ArrayBase(rhs.type.resolved,MAX(LONGINT)));
 							expression.SetType(castReturnType);
 						ELSE
@@ -4191,10 +4193,10 @@ TYPE
 
 				(* add dereference operator and create procedure call designator *)
 				ASSERT(left IS SyntaxTree.Designator);
-				expression := NewSymbolDesignator(InvalidPosition, NewDereferenceDesignator(InvalidPosition, left(SyntaxTree.Designator)), operator);
+				expression := NewSymbolDesignator(Basic.invalidPosition, NewDereferenceDesignator(Basic.invalidPosition, left(SyntaxTree.Designator)), operator);
 
 				ASSERT(expression IS SyntaxTree.Designator);
-				result := NewProcedureCallDesignator(InvalidPosition, expression(SyntaxTree.Designator), actualParameters);
+				result := NewProcedureCallDesignator(Basic.invalidPosition, expression(SyntaxTree.Designator), actualParameters);
 
 				IF (rhs = NIL) & needsReshaping THEN
 					(* reshape using an additional bracket designator with zeros and open ranges at the end; e.g. designator[0, *, *, 0] *)
@@ -4202,12 +4204,12 @@ TYPE
 					FOR i := 0 TO indexList.Length() - 1 DO
 						expression := indexList.GetExpression(i);
 						IF expression.type.resolved IS SyntaxTree.IntegerType THEN
-							tempList.AddExpression(SyntaxTree.NewIntegerValue(InvalidPosition, 0))
+							tempList.AddExpression(SyntaxTree.NewIntegerValue(Basic.invalidPosition, 0))
 						ELSE
-							tempList.AddExpression(SyntaxTree.NewRangeExpression(InvalidPosition, NIL, NIL, NIL))
+							tempList.AddExpression(SyntaxTree.NewRangeExpression(Basic.invalidPosition, NIL, NIL, NIL))
 						END
 					END;
-					result := ResolveDesignator(SyntaxTree.NewBracketDesignator(InvalidPosition, result, tempList))
+					result := ResolveDesignator(SyntaxTree.NewBracketDesignator(Basic.invalidPosition, result, tempList))
 				END;
 
 				IF rhs = NIL THEN
@@ -4223,7 +4225,7 @@ TYPE
 			RETURN result
 		END NewIndexOperatorCall;
 
-		PROCEDURE NewObjectOperatorCall*(position: LONGINT; left: SyntaxTree.Expression; oper: LONGINT; parameters: SyntaxTree.ExpressionList; rhs: SyntaxTree.Expression): SyntaxTree.Designator;
+		PROCEDURE NewObjectOperatorCall*(position: Position; left: SyntaxTree.Expression; oper: LONGINT; parameters: SyntaxTree.ExpressionList; rhs: SyntaxTree.Expression): SyntaxTree.Designator;
 		VAR type: SyntaxTree.Type; expression: SyntaxTree.Expression; op: SyntaxTree.Operator; recordType: SyntaxTree.RecordType;
 			actualParameters: SyntaxTree.ExpressionList; i: LONGINT; result: SyntaxTree.Designator;
 
@@ -4285,7 +4287,7 @@ TYPE
 
 			op := FindOperator(recordType, SyntaxTree.NewIdentifier("[]"), actualParameters);
 			IF op # NIL THEN
-				expression := NewSymbolDesignator(position, NewDereferenceDesignator(InvalidPosition, left(SyntaxTree.Designator)) , op);
+				expression := NewSymbolDesignator(position, NewDereferenceDesignator(Basic.invalidPosition, left(SyntaxTree.Designator)) , op);
 				ASSERT(expression IS SyntaxTree.Designator);
 				result := NewProcedureCallDesignator(position, expression(SyntaxTree.Designator), actualParameters);
 				result.SetRelatedAsot(left);
@@ -4516,7 +4518,7 @@ TYPE
 									IF i <= bracketDesignator.parameters.Length() - 1 THEN
 										expression := bracketDesignator.parameters.GetExpression(i);
 									ELSE
-										expression := SyntaxTree.NewRangeExpression(InvalidPosition, NIL, NIL, NIL)
+										expression := SyntaxTree.NewRangeExpression(Basic.invalidPosition, NIL, NIL, NIL)
 									END;
 									IF expression # SyntaxTree.indexListSeparator THEN
 										expression := ResolveExpression(expression);
@@ -4602,7 +4604,7 @@ TYPE
 			- check parameter compatibility
 			return invalidDesignator if error
 		**)
-		PROCEDURE NewProcedureCallDesignator(position: LONGINT; left: SyntaxTree.Designator; actualParameters:SyntaxTree.ExpressionList): SyntaxTree.Designator;
+		PROCEDURE NewProcedureCallDesignator(position: Position; left: SyntaxTree.Designator; actualParameters:SyntaxTree.ExpressionList): SyntaxTree.Designator;
 		VAR result: SyntaxTree.Designator;
 			numberFormalParameters, numberActualParameters: LONGINT;
 			formalType: SyntaxTree.ProcedureType;
@@ -5044,7 +5046,7 @@ TYPE
 				(* move to builtin procedure call statement ?
 			remove builtin procedure call designator ?
 		*)
-		PROCEDURE NewBuiltinCallDesignator(position: LONGINT; builtin: SyntaxTree.Builtin; actualParameters:SyntaxTree.ExpressionList; left: SyntaxTree.Designator; returnType: SyntaxTree.Type): SyntaxTree.Expression;
+		PROCEDURE NewBuiltinCallDesignator(position: Position; builtin: SyntaxTree.Builtin; actualParameters:SyntaxTree.ExpressionList; left: SyntaxTree.Designator; returnType: SyntaxTree.Type): SyntaxTree.Expression;
 		VAR
 			numberActualParameters,numberFormalParameters: LONGINT;
 			formalParameter: SyntaxTree.Parameter;
@@ -5172,7 +5174,7 @@ TYPE
 						IF ~CompatibleTo(system,parameter1.type,parameter0.type) THEN
 							Error(position,Diagnostics.Invalid,"incompatible increment");
 						ELSE
-							parameter1 := NewConversion(0,parameter1,parameter0.type,NIL);
+							parameter1 := NewConversion(Basic.invalidPosition,parameter1,parameter0.type,NIL);
 							actualParameters.SetExpression(1,parameter1);
 						END;
 					END;
@@ -5184,7 +5186,7 @@ TYPE
 								Error(position,Diagnostics.Invalid,"parameter out of SET range")
 							END;
 						END;
-						parameter1 := NewConversion(0,parameter1,system.longintType,NIL);
+						parameter1 := NewConversion(Basic.invalidPosition,parameter1,system.longintType,NIL);
 						actualParameters.SetExpression(1,parameter1);
 					END;
 				(* ---- HALT, SYSTEM.HALT ----- *)
@@ -5231,7 +5233,7 @@ TYPE
 								REPEAT
 									actualParameter := actualParameters.GetExpression(i);
 									IF CheckSizeType(actualParameter) THEN
-										actualParameter := NewConversion(0,actualParameter,system.longintType,NIL);
+										actualParameter := NewConversion(Basic.invalidPosition,actualParameter,system.longintType,NIL);
 										actualParameters.SetExpression(i,actualParameter);
 									END;
 									INC(i);
@@ -5290,22 +5292,22 @@ TYPE
 									(* use type checking facilities of procedure calls: artificially build parameters here and call checker *)
 									base := ArrayBase(type0,MAX(LONGINT));
 
-									parameterType := SyntaxTree.NewMathArrayType(Diagnostics.Invalid,currentScope,SyntaxTree.Tensor);
+									parameterType := SyntaxTree.NewMathArrayType(Basic.invalidPosition,currentScope,SyntaxTree.Tensor);
 									parameterType(SyntaxTree.MathArrayType).SetArrayBase(base);
 									IF ~CompatibleTo(system,type0,parameterType) THEN
 										Error(parameter0.position,Diagnostics.Invalid,"incompatible parameter in new");
 										result := SyntaxTree.invalidExpression;
 									ELSE
-										parameter0 := NewConversion(Diagnostics.Invalid,parameter0,parameterType,NIL); actualParameters.SetExpression(0,parameter0);
+										parameter0 := NewConversion(Basic.invalidPosition,parameter0,parameterType,NIL); actualParameters.SetExpression(0,parameter0);
 									END;
 
-									parameterType := SyntaxTree.NewMathArrayType(Diagnostics.Invalid,currentScope,SyntaxTree.Open);
+									parameterType := SyntaxTree.NewMathArrayType(Basic.invalidPosition,currentScope,SyntaxTree.Open);
 									parameterType(SyntaxTree.MathArrayType).SetArrayBase(system.longintType);
 									IF ~CompatibleTo(system,type1,parameterType) THEN
 										Error(parameter1.position,Diagnostics.Invalid,"parameter incompatible to math array of longint");
 										result := SyntaxTree.invalidExpression;
 									ELSE
-										parameter1 := NewConversion(Diagnostics.Invalid,parameter1,parameterType,NIL); actualParameters.SetExpression(1,parameter1);
+										parameter1 := NewConversion(Basic.invalidPosition,parameter1,parameterType,NIL); actualParameters.SetExpression(1,parameter1);
 									END;
 								ELSE
 									IF CheckArity(i0,i1) & (numberActualParameters >first) THEN
@@ -5313,7 +5315,7 @@ TYPE
 										REPEAT
 											actualParameter := actualParameters.GetExpression(i);
 											IF CheckSizeType(actualParameter) THEN
-												actualParameter := NewConversion(0,actualParameter,system.sizeType,NIL);
+												actualParameter := NewConversion(Basic.invalidPosition,actualParameter,system.sizeType,NIL);
 												actualParameters.SetExpression(i,actualParameter);
 											END;
 											INC(i);
@@ -5600,7 +5602,7 @@ TYPE
 							ELSIF type IS SyntaxTree.FloatType THEN result.SetResolved(SyntaxTree.NewRealValue(position,Global.MaxFloat(system,type(SyntaxTree.FloatType))));
 							ELSIF type IS SyntaxTree.SetType THEN result.SetResolved(SyntaxTree.NewIntegerValue(position,system.SizeOf(type)-1)); type := system.shortintType;
 							ELSIF type IS SyntaxTree.SizeType THEN result.SetResolved(SyntaxTree.NewIntegerValue(position,Global.MaxInteger(system,type(SyntaxTree.BasicType))));
-							ELSE Error(Diagnostics.Invalid,parameter0.position,"builtin function not applicable to this type");
+							ELSE Error(parameter0.position,Diagnostics.Invalid, "builtin function not applicable to this type");
 							END;
 						ELSE
 							Error(parameter0.position,Diagnostics.Invalid,"is not a type symbol");
@@ -5796,28 +5798,28 @@ TYPE
 				(* ---- SYSTEM.GET64 ----- *)
 				ELSIF (id = Global.systemGet64) & CheckArity(1,1) THEN
 					IF CheckAddressType(parameter0) THEN
-						parameter0 := NewConversion(0,parameter0,system.addressType,NIL);
+						parameter0 := NewConversion(Basic.invalidPosition,parameter0,system.addressType,NIL);
 						actualParameters.SetExpression(0,parameter0);
 					END;
 					type := system.hugeintType;
 				(* ---- SYSTEM.GET32 ----- *)
 				ELSIF (id = Global.systemGet32) & CheckArity(1,1) THEN
 					IF CheckAddressType(parameter0) THEN
-						parameter0 := NewConversion(0,parameter0,system.addressType,NIL);
+						parameter0 := NewConversion(Basic.invalidPosition,parameter0,system.addressType,NIL);
 						actualParameters.SetExpression(0,parameter0);
 					END;
 					type := system.longintType;
 				(* ---- SYSTEM.GET16 ----- *)
 				ELSIF (id = Global.systemGet16) & CheckArity(1,1) THEN
 					IF CheckAddressType(parameter0) THEN
-						parameter0 := NewConversion(0,parameter0,system.addressType,NIL);
+						parameter0 := NewConversion(Basic.invalidPosition,parameter0,system.addressType,NIL);
 						actualParameters.SetExpression(0,parameter0);
 					END;
 					type := system.integerType;
 				(* ---- SYSTEM.GET8 ----- *)
 				ELSIF (id = Global.systemGet8) & CheckArity(1,1) THEN
 					IF CheckAddressType(parameter0) THEN
-						parameter0 := NewConversion(0,parameter0,system.addressType,NIL);
+						parameter0 := NewConversion(Basic.invalidPosition,parameter0,system.addressType,NIL);
 						actualParameters.SetExpression(0,parameter0);
 					END;
 					type := system.shortintType;
@@ -5833,19 +5835,19 @@ TYPE
 				(* ---- SYSTEM.SetStackPointer ----- *)
 				ELSIF (id = Global.systemSetStackPointer) & CheckArity(1,1) THEN
 					IF CheckAddressType(parameter0) THEN
-						parameter0 := NewConversion(0,parameter0,system.addressType,NIL);
+						parameter0 := NewConversion(Basic.invalidPosition,parameter0,system.addressType,NIL);
 						actualParameters.SetExpression(0,parameter0);
 					END;
 				(* ---- SYSTEM.SetFramePointer ----- *)
 				ELSIF (id = Global.systemSetFramePointer) & CheckArity(1,1) THEN
 					IF CheckAddressType(parameter0) THEN
-						parameter0 := NewConversion(0,parameter0,system.addressType,NIL);
+						parameter0 := NewConversion(Basic.invalidPosition,parameter0,system.addressType,NIL);
 						actualParameters.SetExpression(0,parameter0);
 					END;
 				(* ---- SYSTEM.SetActivity ----- *)
 				ELSIF cooperative & (id = Global.systemSetActivity) & CheckArity(1,1) THEN
 					IF CheckObjectType(parameter0) THEN
-						parameter0 := NewConversion(0,parameter0,system.addressType,NIL);
+						parameter0 := NewConversion(Basic.invalidPosition,parameter0,system.addressType,NIL);
 						actualParameters.SetExpression(0,parameter0);
 					END;
 				(* ---- LSH, LSL, ROT, ROR ----- *)
@@ -5884,13 +5886,13 @@ TYPE
 				(* ---- SYSTEM.GET ----- *)
 				ELSIF (id = Global.systemGet) & CheckArity(2,2) THEN
 					IF CheckAddressType(parameter0) & CheckBasicType(parameter1) & CheckVariable(parameter1) THEN
-						parameter0 := NewConversion(0,parameter0,system.addressType,NIL);
+						parameter0 := NewConversion(Basic.invalidPosition,parameter0,system.addressType,NIL);
 						actualParameters.SetExpression(0,parameter0);
 					END;
 				(* ---- SYSTEM.PUT ----- *)
 				ELSIF (id = Global.systemPut) & CheckArity(2,2) THEN
 					IF CheckAddressType(parameter0) & CheckBasicType(parameter1) THEN
-						parameter0 := NewConversion(0,parameter0,system.addressType,NIL);
+						parameter0 := NewConversion(Basic.invalidPosition,parameter0,system.addressType,NIL);
 						actualParameters.SetExpression(0,parameter0);
 					END;
 				(* ---- SYSTEM.PUT64 ----- *)
@@ -5928,9 +5930,9 @@ TYPE
 				(* ---- SYSTEM.MOVE ----- *)
 				ELSIF (id = Global.systemMove) & CheckArity(3,3) THEN
 					IF CheckAddressType(parameter0) & CheckAddressType(parameter1) & CheckAddressType(parameter2) THEN
-						parameter0 := NewConversion(0,parameter0,system.addressType,NIL);
-						parameter1 := NewConversion(0,parameter1,system.addressType,NIL);
-						parameter2 := NewConversion(0,parameter2,system.addressType,NIL);
+						parameter0 := NewConversion(Basic.invalidPosition,parameter0,system.addressType,NIL);
+						parameter1 := NewConversion(Basic.invalidPosition,parameter1,system.addressType,NIL);
+						parameter2 := NewConversion(Basic.invalidPosition,parameter2,system.addressType,NIL);
 						actualParameters.SetExpression(0,parameter0);
 						actualParameters.SetExpression(1,parameter1);
 						actualParameters.SetExpression(2,parameter2);
@@ -5940,7 +5942,7 @@ TYPE
 					IF ~IsPointerType(parameter0.type) THEN
 						Error(parameter0.position,Diagnostics.Invalid,"is not a pointer")
 					ELSIF CheckSizeType(parameter1) THEN
-						parameter1 := NewConversion(Diagnostics.Invalid, parameter1, system.sizeType,NIL);
+						parameter1 := NewConversion(Basic.invalidPosition, parameter1, system.sizeType,NIL);
 						actualParameters.SetExpression(1,parameter1);
 					END;
 				(* ----SYSTEM.REF ---- *)
@@ -6012,8 +6014,8 @@ TYPE
 						Error(position,Diagnostics.Invalid,"third parameter incompatible");
 						result := SyntaxTree.invalidExpression;
 					ELSE
-						parameter1 := NewConversion(Diagnostics.Invalid,parameter1,type0,NIL); actualParameters.SetExpression(1,parameter1);
-						parameter2 := NewConversion(Diagnostics.Invalid,parameter2,type0,NIL); actualParameters.SetExpression(2,parameter2);
+						parameter1 := NewConversion(Basic.invalidPosition,parameter1,type0,NIL); actualParameters.SetExpression(1,parameter1);
+						parameter2 := NewConversion(Basic.invalidPosition,parameter2,type0,NIL); actualParameters.SetExpression(2,parameter2);
 						type := type0;
 					END;
 				(* ---- RESHAPE ----- *)
@@ -6021,25 +6023,25 @@ TYPE
 					IF type0 IS SyntaxTree.MathArrayType THEN
 						(* use type checking facilities of procedure calls: artificially build parameters here and call checker *)
 						base := ArrayBase(type0,MAX(LONGINT));
-						type := SyntaxTree.NewMathArrayType(Diagnostics.Invalid,currentScope,SyntaxTree.Tensor);
+						type := SyntaxTree.NewMathArrayType(Basic.invalidPosition,currentScope,SyntaxTree.Tensor);
 						type(SyntaxTree.MathArrayType).SetArrayBase(base);
 
-						parameterType := SyntaxTree.NewMathArrayType(Diagnostics.Invalid,currentScope,SyntaxTree.Tensor);
+						parameterType := SyntaxTree.NewMathArrayType(Basic.invalidPosition,currentScope,SyntaxTree.Tensor);
 						parameterType(SyntaxTree.MathArrayType).SetArrayBase(base);
 						IF ~CompatibleTo(system,type0,parameterType) THEN
 							Error(parameter0.position,Diagnostics.Invalid,"incompatible parameter in reshape");
 							result := SyntaxTree.invalidExpression;
 						ELSE
-							parameter0 := NewConversion(Diagnostics.Invalid,parameter0,parameterType,NIL); actualParameters.SetExpression(0,parameter0);
+							parameter0 := NewConversion(Basic.invalidPosition,parameter0,parameterType,NIL); actualParameters.SetExpression(0,parameter0);
 						END;
 
-						parameterType := SyntaxTree.NewMathArrayType(Diagnostics.Invalid,currentScope,SyntaxTree.Open);
+						parameterType := SyntaxTree.NewMathArrayType(Basic.invalidPosition,currentScope,SyntaxTree.Open);
 						parameterType(SyntaxTree.MathArrayType).SetArrayBase(system.longintType);
 						IF ~CompatibleTo(system,type1,parameterType) THEN
 							Error(parameter1.position,Diagnostics.Invalid,"parameter incompatible to math array of longint");
 							result := SyntaxTree.invalidExpression;
 						ELSE
-							parameter1 := NewConversion(Diagnostics.Invalid,parameter1,parameterType,NIL); actualParameters.SetExpression(1,parameter1);
+							parameter1 := NewConversion(Basic.invalidPosition,parameter1,parameterType,NIL); actualParameters.SetExpression(1,parameter1);
 						END;
 					ELSE
 						Error(position, Diagnostics.Invalid,"reshape on non math array type");
@@ -6095,7 +6097,7 @@ TYPE
 							Error(position,Diagnostics.Invalid,"incompatible channel size parameter");
 						END;
 						*)
-						parameter2 := NewConversion(Diagnostics.Invalid,parameter2,system.longintType,NIL);
+						parameter2 := NewConversion(Basic.invalidPosition,parameter2,system.longintType,NIL);
 						actualParameters.SetExpression(2,parameter2);
 					END;
 
@@ -6188,7 +6190,7 @@ TYPE
 			- returns new type guard designator
 			returns invalidDesignator = invalidExpression if error
 		**)
-		PROCEDURE NewTypeGuardDesignator(position: LONGINT; left: SyntaxTree.Designator; type: SyntaxTree.Type; typeExpression: SyntaxTree.Expression): SyntaxTree.Designator;
+		PROCEDURE NewTypeGuardDesignator(position: Position; left: SyntaxTree.Designator; type: SyntaxTree.Type; typeExpression: SyntaxTree.Expression): SyntaxTree.Designator;
 		VAR result: SyntaxTree.Designator;
 		BEGIN
 			result := SyntaxTree.invalidDesignator;
@@ -6286,7 +6288,7 @@ TYPE
 			with error handling
 			returns invalidDesignator = invalidExpression if error
 		**)
-		PROCEDURE NewDereferenceDesignator(position: LONGINT; left: SyntaxTree.Designator): SyntaxTree.Designator;
+		PROCEDURE NewDereferenceDesignator(position: Position; left: SyntaxTree.Designator): SyntaxTree.Designator;
 		VAR type: SyntaxTree.Type; result: SyntaxTree.Designator;
 		BEGIN
 			result := SyntaxTree.invalidDesignator;
@@ -6323,7 +6325,7 @@ TYPE
 				- return new supercall designator with type = left.type
 			with error handling
 		**)
-		PROCEDURE NewSupercallDesignator(position: LONGINT; left: SyntaxTree.Designator): SyntaxTree.Designator;
+		PROCEDURE NewSupercallDesignator(position: Position; left: SyntaxTree.Designator): SyntaxTree.Designator;
 		VAR result: SyntaxTree.Designator; symbol: SyntaxTree.Symbol; procedure: SyntaxTree.Procedure;
 			objectScope: SyntaxTree.Scope;
 		BEGIN
@@ -6431,7 +6433,7 @@ TYPE
 			report error and return invalidExpression if anything fails
 		**)
 		PROCEDURE ConstantExpression(expression: SyntaxTree.Expression): SyntaxTree.Expression;
-		VAR position: LONGINT;
+		VAR position: Position;
 		BEGIN
 			position := expression.position;
 			expression := ResolveExpression(expression);
@@ -6450,7 +6452,7 @@ TYPE
 			report error and return invalidExpression if anything fails
 		**)
 		PROCEDURE ConstantInteger(expression: SyntaxTree.Expression): SyntaxTree.Expression;
-		VAR position: LONGINT;
+		VAR position: Position;
 		BEGIN
 			position := expression.position;
 			expression := ResolveExpression(expression);
@@ -6469,7 +6471,7 @@ TYPE
 			report error and return invalidExpression if anything fails
 		**)
 		PROCEDURE ConstantIntegerGeq0(expression: SyntaxTree.Expression): SyntaxTree.Expression;
-		VAR position: LONGINT;
+		VAR position: Position;
 		BEGIN
 			position := expression.position;
 			expression := ConstantExpression(expression);
@@ -6490,7 +6492,7 @@ TYPE
 			report error and return invalidExpression if anything fails
 		**)
 		PROCEDURE ResolveCondition(expression: SyntaxTree.Expression): SyntaxTree.Expression;
-		VAR position: LONGINT;
+		VAR position: Position;
 		BEGIN
 			position := expression.position;
 			expression := ResolveExpression(expression);
@@ -6652,7 +6654,7 @@ TYPE
 			- check symbol
 		**)
 		PROCEDURE VisitVariable(variable: SyntaxTree.Variable);
-		VAR modifiers: SyntaxTree.Modifier; value,position: LONGINT; pointerType: SyntaxTree.PointerType;
+		VAR modifiers: SyntaxTree.Modifier; value: LONGINT; position: Position; pointerType: SyntaxTree.PointerType;
 		BEGIN
 			IF Trace THEN D.Str("VisitVariable "); D.Str0(variable.name);  D.Ln;  END;
 			IF SymbolNeedsResolution(variable) THEN
@@ -6731,7 +6733,7 @@ TYPE
 			- check parameter kind and set read-only flags if appropriate
 		**)
 		PROCEDURE VisitParameter(parameter: SyntaxTree.Parameter);
-		VAR modifiers: SyntaxTree.Modifier; expression: SyntaxTree.Expression; position: LONGINT;
+		VAR modifiers: SyntaxTree.Modifier; expression: SyntaxTree.Expression; position: Position;
 		BEGIN
 			IF Trace THEN D.Str("VisitParameter "); D.Str0(parameter.name);  D.Ln;  END;
 			IF SymbolNeedsResolution(parameter) THEN
@@ -6790,7 +6792,7 @@ TYPE
 			qualifiedType: SyntaxTree.QualifiedType;
 			value: LONGINT;
 			modifiers: SyntaxTree.Modifier; recentIsRealtime, recentIsBodyProcedure: BOOLEAN;
-			position: LONGINT;
+			position: Position;
 		BEGIN
 			IF Trace THEN D.Str("VisitProcedure "); D.Str0(procedure.name);  D.Ln;  END;
 			IF IsOberonInline(procedure) THEN
@@ -6982,7 +6984,7 @@ TYPE
 		VAR
 			procedureType: SyntaxTree.ProcedureType;
 			leftType, rightType: SyntaxTree.Type;
-			identifierNumber, position: LONGINT;
+			identifierNumber: LONGINT;  position: Position;
 			hasReturnType, mustBeUnary, mustBeBinary, mustReturnBoolean, mustReturnInteger, mustHaveEquitypedOperands: BOOLEAN;
 			modifiers: SyntaxTree.Modifier;
 
@@ -7225,7 +7227,7 @@ TYPE
 								*)
 								x.SetModule(module);
 								IF importCache # NIL THEN
-									import := SyntaxTree.NewImport(InvalidPosition,x.moduleName,x.moduleName,FALSE);
+									import := SyntaxTree.NewImport(Basic.invalidPosition,x.moduleName,x.moduleName,FALSE);
 									import.SetContext(x.context);
 									import.SetModule(module);
 									importCache.AddImport(import);
@@ -7251,7 +7253,7 @@ TYPE
 								IF import.context = SyntaxTree.invalidIdentifier THEN import.SetContext(x.context) END;
 								reimport := moduleScope.ImportByModuleName(import.moduleName,import.context);
 								IF reimport = NIL THEN  (* indirect import *)
-									reimport := SyntaxTree.NewImport(InvalidPosition,import.moduleName,import.moduleName,FALSE);
+									reimport := SyntaxTree.NewImport(Basic.invalidPosition,import.moduleName,import.moduleName,FALSE);
 									reimport.SetContext(import.context);
 									reimport.SetModule(import.module);
 									moduleScope.AddImport(reimport);
@@ -7410,7 +7412,7 @@ TYPE
 					IF IsArrayStructuredObjectType(left.type) & (left.type.resolved # right.type.resolved) THEN
 						mathArrayType := MathArrayStructureOfType(left.type);
 						right := NewConversion(right.position, right, mathArrayType, NIL);
-						designator := NewIndexOperatorCall(InvalidPosition, left, ListOfOpenRanges(mathArrayType.Dimensionality()), right);
+						designator := NewIndexOperatorCall(Basic.invalidPosition, left, ListOfOpenRanges(mathArrayType.Dimensionality()), right);
 						resolvedStatement := SyntaxTree.NewProcedureCallStatement(assignment.position, designator, assignment.outer)
 					ELSE
 						right := NewConversion(right.position, right, left.type.resolved, NIL);
@@ -7632,7 +7634,7 @@ TYPE
 		PROCEDURE CasePart(casePart: SyntaxTree.CasePart; type: SyntaxTree.Type; VAR allcases: SyntaxTree.CaseConstant; VAR min,max: LONGINT);
 		VAR
 			i: LONGINT;
-			position: LONGINT;
+			position: Position;
 			expression, left, right: SyntaxTree.Expression;
 			expressionType: SyntaxTree.Type;
 			l, r: LONGINT;
@@ -7854,7 +7856,7 @@ TYPE
 			IF forStatement.by # NIL THEN
 				expression := ConstantInteger(forStatement.by);
 			ELSE
-				expression := Global.NewIntegerValue(system,InvalidPosition,1);
+				expression := Global.NewIntegerValue(system,Basic.invalidPosition,1);
 			END;
 
 
@@ -7907,7 +7909,7 @@ TYPE
 				- if not in procecdure scope then check on return without expression
 		**)
 		PROCEDURE VisitReturnStatement(returnStatement: SyntaxTree.ReturnStatement);
-		VAR expression: SyntaxTree.Expression; position: LONGINT; procedure: SyntaxTree.Procedure;
+		VAR expression: SyntaxTree.Expression; position: Position; procedure: SyntaxTree.Procedure;
 			returnType: SyntaxTree.Type; outer: SyntaxTree.Statement; scope: SyntaxTree.Scope;
 		BEGIN
 			position := returnStatement.position;
@@ -7971,7 +7973,7 @@ TYPE
 			awaitStatement.SetCondition(condition);
 		END VisitAwaitStatement;
 
-		PROCEDURE CheckSystemImport(position: LONGINT);
+		PROCEDURE CheckSystemImport(position: Position);
 		VAR import: SyntaxTree.Import;
 		BEGIN
 			import := currentScope.ownerModule.moduleScope.firstImport;
@@ -8022,7 +8024,7 @@ TYPE
 			- check for valid names
 		**)
 		PROCEDURE BlockFlags(block: SyntaxTree.StatementBlock);
-		VAR blockModifier: SyntaxTree.Modifier; expression: SyntaxTree.Expression; name: SyntaxTree.Identifier; flags: SET; position: LONGINT;
+		VAR blockModifier: SyntaxTree.Modifier; expression: SyntaxTree.Expression; name: SyntaxTree.Identifier; flags: SET; position: Position;
 			flag: LONGINT; recordBody: SyntaxTree.Body;
 
 			PROCEDURE SetProtectedRecord;
@@ -8424,7 +8426,7 @@ TYPE
 			END;
 
 			IF ~error & ~system.GenerateVariableOffsets(scope) THEN
-				Error(Diagnostics.Invalid,Diagnostics.Invalid,"problems during offset computation in module");
+				Error(Basic.invalidPosition,Diagnostics.Invalid,"problems during offset computation in module");
 			END;
 
 			IF  (scope.ownerModule # NIL) THEN
@@ -8528,7 +8530,7 @@ TYPE
 		**)
 		PROCEDURE Module*(x: SyntaxTree.Module);
 		VAR (* nopov *)
-			import: SyntaxTree.Import; modifier: SyntaxTree.Modifier; value,position: LONGINT; prevIsCellNet: BOOLEAN; prevScope: SyntaxTree.Scope;
+			import: SyntaxTree.Import; modifier: SyntaxTree.Modifier; value: LONGINT; position: Position; prevIsCellNet: BOOLEAN; prevScope: SyntaxTree.Scope;
 		BEGIN
 			prevScope := currentScope;
 			prevIsCellNet := currentIsCellNet;
@@ -8657,7 +8659,7 @@ TYPE
 			Global.GetSymbolName(x,msg);
 			Strings.Append(msg," ");
 			Strings.Append(msg,text);
-			diagnostics.Warning(module.sourceName,x.position,Diagnostics.Invalid,msg);
+			diagnostics.Warning(module.sourceName,x.position.start,Diagnostics.Invalid,msg);
 		END Warning;
 
 		(** symbols *)

文件差异内容过多而无法显示
+ 113 - 112
source/FoxSyntaxTree.Mod


+ 3 - 2
source/FoxTRMAssembler.Mod

@@ -1,6 +1,6 @@
 MODULE FoxTRMAssembler; (** AUTHOR ""; PURPOSE ""; *)
 
-IMPORT InstructionSet := FoxTRMInstructionSet, FoxAssembler, D := Debugging, Scanner := FoxScanner, Diagnostics;
+IMPORT InstructionSet := FoxTRMInstructionSet, FoxAssembler, D := Debugging, Scanner := FoxScanner, Diagnostics, Basic := FoxBasic;
 
 CONST Trace=FoxAssembler.Trace;
 
@@ -21,7 +21,8 @@ TYPE
 		END Init2;
 
 		PROCEDURE Instruction*(CONST mnemonic: ARRAY OF CHAR);
-		VAR i,numberOperands,mnem,pos: LONGINT; VAR operands: ARRAY 3 OF Operand; instruction: InstructionSet.Instruction;
+		VAR i,numberOperands,mnem: LONGINT; VAR operands: ARRAY 3 OF Operand; instruction: InstructionSet.Instruction;
+			pos: Basic.Position;
 
 			PROCEDURE ParseOperand;
 			(* stub, must be overwritten by implementation *)

+ 2 - 2
source/FoxTranspilerBackend.Mod

@@ -370,7 +370,7 @@ TYPE
 		BEGIN
 			BeginRuntimeCall (backend.traceModule, "String"); writer.Char ('"'); pos := writer.Pos ();
 			currentProcedureScope.ownerModule.GetName (name); writer.String (name); writer.Char ('@');
-			writer.Int (expression.position, 0); writer.Char (':'); writer.Char (' ');
+			writer.Int (expression.position.start, 0); writer.Char (':'); writer.Char (' ');
 			printer := Printout.NewPrinter (writer, Printout.SourceCode, FALSE);
 			printer.Expression (expression); writer.Char (' '); writer.Char ('=');
 			writer.Char (' '); writer.Char ('"'); writer.Char (','); writer.Char (' ');
@@ -1143,7 +1143,7 @@ TYPE
 			FOR i := 0 TO LEN (argument) - 1 DO
 				IF i < expression.parameters.Length () THEN argument[i] := expression.parameters.GetExpression (i); ELSE argument[i] := NIL; END;
 			END;
-			position := expression.position;
+			position := expression.position.start;
 			CASE expression.id OF
 			| Global.Incl: PrintExpression (argument[0]); writer.String (" |= 1 << ("); PrintExpression (argument[1]); writer.Char (')');
 			| Global.Excl: PrintExpression (argument[0]); writer.String (" &= ~(1 << ("); PrintExpression (argument[1]); writer.Char (')'); writer.Char (')');

部分文件因为文件数量过多而无法显示