浏览代码

Improved error handling: line/column position now available everywhere
Added an indirection for calls to diagnsotics in order to be able to pass position information from everywhere
Line / col Position info also available for FindPC

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

felixf 8 年之前
父节点
当前提交
6849ac77e4

+ 19 - 24
source/FoxAMD64Assembler.Mod

@@ -238,16 +238,14 @@ TYPE
 		END SetBits;
 		END SetBits;
 
 
 		PROCEDURE Error(CONST message: ARRAY OF CHAR);
 		PROCEDURE Error(CONST message: ARRAY OF CHAR);
-		VAR msg,name: ARRAY 256 OF CHAR; errPos: LONGINT;
+		VAR msg,name: ARRAY 256 OF CHAR; errPos: Basic.Position;
 		BEGIN
 		BEGIN
 			COPY(message,msg);
 			COPY(message,msg);
 			Strings.Append(msg," in ");
 			Strings.Append(msg," in ");
 			ObjectFile.SegmentedNameToString(code.os.identifier.name,name);
 			ObjectFile.SegmentedNameToString(code.os.identifier.name,name);
 			Strings.Append(msg, name);
 			Strings.Append(msg, name);
-			IF diagnostics # NIL THEN
-				IF assembly # NIL THEN errPos := assembly.errPos ELSE errPos := Diagnostics.Invalid END;
-				diagnostics.Error("",Diagnostics.Invalid,errPos,msg);
-			END;
+			IF assembly # NIL THEN errPos := assembly.errPos ELSE errPos := Basic.invalidPosition END;
+			Basic.Error(diagnostics,"",errPos,msg);
 			error := TRUE;
 			error := TRUE;
 			IF dump # NIL THEN dump.Update; END;
 			IF dump # NIL THEN dump.Update; END;
 		END Error;
 		END Error;
@@ -1067,7 +1065,7 @@ TYPE
 	Assembly* = OBJECT
 	Assembly* = OBJECT
 	VAR
 	VAR
 		(* output *)
 		(* output *)
-		errPos: LONGINT;
+		errPos: Basic.Position;
 		error-: BOOLEAN;
 		error-: BOOLEAN;
 		useLineNumbers*: BOOLEAN;
 		useLineNumbers*: BOOLEAN;
 		emitter: Emitter;
 		emitter: Emitter;
@@ -1086,24 +1084,24 @@ TYPE
 		PROCEDURE & InitAssembly*(diagnostics: Diagnostics.Diagnostics; emit: Emitter);
 		PROCEDURE & InitAssembly*(diagnostics: Diagnostics.Diagnostics; emit: Emitter);
 		BEGIN
 		BEGIN
 			SELF.diagnostics := diagnostics;
 			SELF.diagnostics := diagnostics;
-			errPos := Diagnostics.Invalid;
+			errPos := Basic.invalidPosition;
 			error := FALSE;
 			error := FALSE;
 			SELF.emitter := emit;
 			SELF.emitter := emit;
 			sourceName := "";
 			sourceName := "";
 		END InitAssembly;
 		END InitAssembly;
 
 
 		PROCEDURE Error( CONST message: ARRAY OF CHAR);
 		PROCEDURE Error( CONST message: ARRAY OF CHAR);
-		VAR pos: LONGINT; msg,name: ARRAY 256 OF CHAR;
+		VAR pos: Basic.Position; msg,name: ARRAY 256 OF CHAR;
 		BEGIN
 		BEGIN
 			pos := errPos;
 			pos := errPos;
-			IF (pos = Diagnostics.Invalid) OR (sourceName = "") THEN
-				COPY(message,msg);
+			COPY(message,msg);
+			IF (pos.start = Diagnostics.Invalid) OR (sourceName = "") THEN
 				Strings.Append(msg," in ");
 				Strings.Append(msg," in ");
 				ObjectFile.SegmentedNameToString(emitter.code.os.identifier.name, name);
 				ObjectFile.SegmentedNameToString(emitter.code.os.identifier.name, name);
 				Strings.Append(msg, name);
 				Strings.Append(msg, name);
-				diagnostics.Error(sourceName,errPos,Diagnostics.Invalid,msg);
+				Basic.Error(diagnostics, sourceName,errPos,msg);
 			ELSE
 			ELSE
-				diagnostics.Error(sourceName,errPos,Diagnostics.Invalid,message);
+				Basic.Error(diagnostics, sourceName,errPos,msg);
 			END;
 			END;
 			error := TRUE;
 			error := TRUE;
 			IF dump # NIL THEN dump.Update; END;
 			IF dump # NIL THEN dump.Update; END;
@@ -1119,7 +1117,7 @@ TYPE
 		END ErrorSS;
 		END ErrorSS;
 
 
 
 
-		PROCEDURE Assemble* (reader: Streams.Reader;  orgPos: LONGINT; scope: SyntaxTree.Scope; in: IntermediateCode.Section; out: IntermediateCode.Section; module: Sections.Module; exported, inlined: BOOLEAN;
+		PROCEDURE Assemble* (reader: Streams.Reader;  orgPos: Basic.Position; scope: SyntaxTree.Scope; in: IntermediateCode.Section; out: IntermediateCode.Section; module: Sections.Module; exported, inlined: BOOLEAN;
 			map: RegisterMap
 			map: RegisterMap
 		);
 		);
 		CONST maxPasses = 2;
 		CONST maxPasses = 2;
@@ -1141,8 +1139,7 @@ TYPE
 			orgReaderPos: LONGINT;
 			orgReaderPos: LONGINT;
 			orgCodePos: LONGINT;
 			orgCodePos: LONGINT;
 			prevSourceName: Basic.FileName;
 			prevSourceName: Basic.FileName;
-			position: LONGINT;
-			line: LONGINT;
+			position: Basic.Position;
 			prevCpuBits: Size;
 			prevCpuBits: Size;
 			prevCpuOptions: InstructionSet.CPUOptions;
 			prevCpuOptions: InstructionSet.CPUOptions;
 			prevAssembly: Assembly;
 			prevAssembly: Assembly;
@@ -1151,7 +1148,7 @@ TYPE
 				(*
 				(*
 				IF (dump # NIL) & (pass = maxPasses) THEN dump.Char (char) END;
 				IF (dump # NIL) & (pass = maxPasses) THEN dump.Char (char) END;
 				*)
 				*)
-				reader.Char(char); INC(position);
+				reader.Char(char); INC(position.start);
 			END NextChar;
 			END NextChar;
 
 
 			PROCEDURE SkipBlanks;
 			PROCEDURE SkipBlanks;
@@ -1219,11 +1216,8 @@ TYPE
 			PROCEDURE NextSymbol;
 			PROCEDURE NextSymbol;
 			BEGIN
 			BEGIN
 				SkipBlanks;
 				SkipBlanks;
-				IF useLineNumbers THEN
-					errPos := line
-				ELSE
-					errPos := position- 1;
-				END;
+				errPos := position;
+
 
 
 				CASE char OF
 				CASE char OF
 				'A' .. 'Z', 'a' .. 'z', '_' :
 				'A' .. 'Z', 'a' .. 'z', '_' :
@@ -1246,10 +1240,12 @@ TYPE
 				| ':': symbol := symColon;
 				| ':': symbol := symColon;
 					NextChar;
 					NextChar;
 				| CR: symbol := symLn;
 				| CR: symbol := symLn;
-					NextChar; INC(line);
+					NextChar; INC(position.line);
+					position.linepos := position.start;
 					IF char = LF THEN NextChar END;
 					IF char = LF THEN NextChar END;
 				| LF: symbol := symLn;
 				| LF: symbol := symLn;
-					NextChar;INC(line);
+					NextChar;INC(position.line);
+					position.linepos := position.start;
 					IF char = CR THEN NextChar END;
 					IF char = CR THEN NextChar END;
 				| ',': symbol := symComma;
 				| ',': symbol := symComma;
 					NextChar;
 					NextChar;
@@ -1920,7 +1916,6 @@ TYPE
 			PROCEDURE Reset;
 			PROCEDURE Reset;
 			BEGIN
 			BEGIN
 				position := orgPos;
 				position := orgPos;
-				IF useLineNumbers THEN line := orgPos END;
 				reader.SetPos(orgReaderPos);
 				reader.SetPos(orgReaderPos);
 				emitter.code.SetPC(orgCodePos);
 				emitter.code.SetPC(orgCodePos);
 				NextChar;
 				NextChar;

+ 9 - 9
source/FoxAMDBackend.Mod

@@ -552,7 +552,7 @@ TYPE
 
 
 			PROCEDURE CheckEmptySpillStack;
 			PROCEDURE CheckEmptySpillStack;
 			BEGIN
 			BEGIN
-				IF spillStack.Size()#0 THEN Error(inPC,"implementation error, spill stack not cleared") END;
+				IF spillStack.Size()#0 THEN Error(Basic.invalidPosition,"implementation error, spill stack not cleared") END;
 			END CheckEmptySpillStack;
 			END CheckEmptySpillStack;
 
 
 		BEGIN
 		BEGIN
@@ -2126,7 +2126,7 @@ TYPE
 		BEGIN
 		BEGIN
 			IF IntermediateCode.IsConstantInteger(instruction.op3,value) & IntermediateBackend.PowerOf2(value,exp) THEN
 			IF IntermediateCode.IsConstantInteger(instruction.op3,value) & IntermediateBackend.PowerOf2(value,exp) THEN
 				IntermediateCode.InitImmediate(iop3, IntermediateCode.uint32, exp);
 				IntermediateCode.InitImmediate(iop3, IntermediateCode.uint32, exp);
-				IntermediateCode.InitInstruction(inst, -1, IntermediateCode.shl, instruction.op1, instruction.op2, iop3);
+				IntermediateCode.InitInstruction(inst, Basic.invalidPosition, IntermediateCode.shl, instruction.op1, instruction.op2, iop3);
 				EmitShift(inst);
 				EmitShift(inst);
 				RETURN;
 				RETURN;
 			END;
 			END;
@@ -2217,12 +2217,12 @@ TYPE
 			IF IntermediateCode.IsConstantInteger(instruction.op3,value) & IntermediateBackend.PowerOf2(value,exp) THEN
 			IF IntermediateCode.IsConstantInteger(instruction.op3,value) & IntermediateBackend.PowerOf2(value,exp) THEN
 				IF instruction.opcode = IntermediateCode.div THEN					
 				IF instruction.opcode = IntermediateCode.div THEN					
 					IntermediateCode.InitImmediate(iop3, IntermediateCode.uint32, exp);
 					IntermediateCode.InitImmediate(iop3, IntermediateCode.uint32, exp);
-					IntermediateCode.InitInstruction(inst, -1, IntermediateCode.shr, instruction.op1, instruction.op2, iop3);
+					IntermediateCode.InitInstruction(inst, Basic.invalidPosition, IntermediateCode.shr, instruction.op1, instruction.op2, iop3);
 					EmitShift(inst);
 					EmitShift(inst);
 					RETURN;
 					RETURN;
 				ELSE
 				ELSE
 					IntermediateCode.InitImmediate(iop3, instruction.op3.type, value-1);
 					IntermediateCode.InitImmediate(iop3, instruction.op3.type, value-1);
-					IntermediateCode.InitInstruction(inst, -1, IntermediateCode.and, instruction.op1, instruction.op2, iop3);
+					IntermediateCode.InitInstruction(inst, Basic.invalidPosition, IntermediateCode.and, instruction.op1, instruction.op2, iop3);
 					EmitArithmetic3(inst,InstructionSet.opAND);
 					EmitArithmetic3(inst,InstructionSet.opAND);
 					RETURN;					
 					RETURN;					
 				END;
 				END;
@@ -3115,7 +3115,7 @@ TYPE
 			scope := procedure.procedureScope;
 			scope := procedure.procedureScope;
 			NEW(assembler,diagnostics,emitter);
 			NEW(assembler,diagnostics,emitter);
 			assembler.useLineNumbers := Compiler.UseLineNumbers IN backend.flags;
 			assembler.useLineNumbers := Compiler.UseLineNumbers IN backend.flags;
-			assembler.Assemble(reader,SHORT(instruction.op1.intValue),scope,in,in,module,procedure.access * SyntaxTree.Public # {}, procedure.isInline, map)	;
+			assembler.Assemble(reader,instruction.textPosition,scope,in,in,module,procedure.access * SyntaxTree.Public # {}, procedure.isInline, map)	;
 			error := error OR assembler.error;
 			error := error OR assembler.error;
 
 
 			IF outr # NIL THEN
 			IF outr # NIL THEN
@@ -3364,7 +3364,7 @@ TYPE
 		 	END;
 		 	END;
 			*)
 			*)
 
 
-			IF cg.error THEN Error("",Diagnostics.Invalid, Diagnostics.Invalid,"") END;
+			IF cg.error THEN Error("",Basic.invalidPosition, Diagnostics.Invalid,"") END;
 		END GenerateBinary;
 		END GenerateBinary;
 
 
 		(* genasm *)
 		(* genasm *)
@@ -3420,7 +3420,7 @@ TYPE
 			UNTIL (i = module(Sections.Module).allSections.Length()) OR (section.name = pooledName);
 			UNTIL (i = module(Sections.Module).allSections.Length()) OR (section.name = pooledName);
 
 
 			IF section.name # pooledName THEN
 			IF section.name # pooledName THEN
-				diagnostics.Error(module.module.sourceName,Diagnostics.Invalid,Diagnostics.Invalid," could not locate pc");
+				Basic.Error(diagnostics, module.module.sourceName,Basic.invalidPosition, " could not locate pc");
 			ELSE
 			ELSE
 				binarySection := section(IntermediateCode.Section).resolved;
 				binarySection := section(IntermediateCode.Section).resolved;
 				label := binarySection.labels;
 				label := binarySection.labels;
@@ -3428,9 +3428,9 @@ TYPE
 					label := label.prev;
 					label := label.prev;
 				END;
 				END;
 				IF label # NIL THEN
 				IF label # NIL THEN
-					diagnostics.Information(module.module.sourceName,label.position,Diagnostics.Invalid," pc position");
+					Basic.Information(diagnostics, module.module.sourceName,label.position, " pc position");
 				ELSE
 				ELSE
-					diagnostics.Error(module.module.sourceName,Diagnostics.Invalid,Diagnostics.Invalid," could not locate pc");
+					Basic.Error(diagnostics, module.module.sourceName,Basic.invalidPosition, " could not locate pc");
 				END;
 				END;
 			END;
 			END;
 		END FindPC;
 		END FindPC;

+ 8 - 8
source/FoxARMBackend.Mod

@@ -594,7 +594,7 @@ TYPE
 			PROCEDURE CheckEmptySpillStack(): BOOLEAN;
 			PROCEDURE CheckEmptySpillStack(): BOOLEAN;
 			BEGIN
 			BEGIN
 				IF spillStack.Size() # 0 THEN
 				IF spillStack.Size() # 0 THEN
-					Error(inPC,"implementation error, spill stack not cleared");
+					Error(Basic.invalidPosition,"implementation error, spill stack not cleared");
 					IF dump # NIL THEN
 					IF dump # NIL THEN
 						spillStack.Dump(dump);
 						spillStack.Dump(dump);
 						tickets.Dump(dump)
 						tickets.Dump(dump)
@@ -2217,7 +2217,7 @@ TYPE
 		BEGIN
 		BEGIN
 			IF IntermediateCode.IsConstantInteger(irInstruction.op3,value) & IntermediateBackend.PowerOf2(value,exp) THEN
 			IF IntermediateCode.IsConstantInteger(irInstruction.op3,value) & IntermediateBackend.PowerOf2(value,exp) THEN
 				IntermediateCode.InitImmediate(op3, IntermediateCode.uint32, exp);
 				IntermediateCode.InitImmediate(op3, IntermediateCode.uint32, exp);
-				IntermediateCode.InitInstruction(inst, -1, IntermediateCode.shl, irInstruction.op1, irInstruction.op2, op3);
+				IntermediateCode.InitInstruction(inst, Basic.invalidPosition, IntermediateCode.shl, irInstruction.op1, irInstruction.op2, op3);
 				EmitShiftOrRotation(inst);
 				EmitShiftOrRotation(inst);
 				RETURN;
 				RETURN;
 			END;
 			END;
@@ -2269,7 +2269,7 @@ TYPE
 		BEGIN
 		BEGIN
 			IF IntermediateCode.IsConstantInteger(irInstruction.op3,value) & IntermediateBackend.PowerOf2(value,exp) THEN
 			IF IntermediateCode.IsConstantInteger(irInstruction.op3,value) & IntermediateBackend.PowerOf2(value,exp) THEN
 				IntermediateCode.InitImmediate(op3, IntermediateCode.uint32, exp);
 				IntermediateCode.InitImmediate(op3, IntermediateCode.uint32, exp);
-				IntermediateCode.InitInstruction(inst, -1, IntermediateCode.shr, irInstruction.op1, irInstruction.op2, op3);
+				IntermediateCode.InitInstruction(inst, Basic.invalidPosition, IntermediateCode.shr, irInstruction.op1, irInstruction.op2, op3);
 				EmitShiftOrRotation(inst);
 				EmitShiftOrRotation(inst);
 				RETURN;
 				RETURN;
 			END;
 			END;
@@ -2327,7 +2327,7 @@ TYPE
 		BEGIN
 		BEGIN
 			IF IntermediateCode.IsConstantInteger(irInstruction.op3,value) & IntermediateBackend.PowerOf2(value,exp) THEN
 			IF IntermediateCode.IsConstantInteger(irInstruction.op3,value) & IntermediateBackend.PowerOf2(value,exp) THEN
 				IntermediateCode.InitImmediate(op3, irInstruction.op3.type, value-1);
 				IntermediateCode.InitImmediate(op3, irInstruction.op3.type, value-1);
-				IntermediateCode.InitInstruction(inst, -1, IntermediateCode.and, irInstruction.op1, irInstruction.op2, op3);
+				IntermediateCode.InitInstruction(inst, Basic.invalidPosition, IntermediateCode.and, irInstruction.op1, irInstruction.op2, op3);
 				EmitAnd(inst);
 				EmitAnd(inst);
 				RETURN;
 				RETURN;
 			END;
 			END;
@@ -3685,7 +3685,7 @@ TYPE
 		 		PatchFixups(in(IntermediateCode.Section).resolved)
 		 		PatchFixups(in(IntermediateCode.Section).resolved)
 		 	END;
 		 	END;
 
 
-			IF cg.error THEN Error("", Diagnostics.Invalid, Diagnostics.Invalid,  "") END
+			IF cg.error THEN Error("", Basic.invalidPosition, Diagnostics.Invalid,  "") END
 		END GenerateBinary;
 		END GenerateBinary;
 
 
 		(** create an ARM code module from an intermediate code module **)
 		(** create an ARM code module from an intermediate code module **)
@@ -3769,7 +3769,7 @@ TYPE
 			UNTIL (i = module(Sections.Module).allSections.Length()) OR (section.name = pooledName);
 			UNTIL (i = module(Sections.Module).allSections.Length()) OR (section.name = pooledName);
 
 
 			IF section.name # pooledName THEN
 			IF section.name # pooledName THEN
-				diagnostics.Error(module.module.sourceName,Diagnostics.Invalid,Diagnostics.Invalid," could not locate pc");
+					Basic.Error(diagnostics, module.module.sourceName,Basic.invalidPosition, " could not locate pc");
 			ELSE
 			ELSE
 				binarySection := section(IntermediateCode.Section).resolved;
 				binarySection := section(IntermediateCode.Section).resolved;
 				label := binarySection.labels;
 				label := binarySection.labels;
@@ -3777,9 +3777,9 @@ TYPE
 					label := label.prev;
 					label := label.prev;
 				END;
 				END;
 				IF label # NIL THEN
 				IF label # NIL THEN
-					diagnostics.Information(module.module.sourceName,label.position,Diagnostics.Invalid," pc position");
+					Basic.Information(diagnostics, module.module.sourceName,label.position, " pc position");
 				ELSE
 				ELSE
-					diagnostics.Error(module.module.sourceName,Diagnostics.Invalid,Diagnostics.Invalid," could not locate pc");
+					Basic.Error(diagnostics, module.module.sourceName, Basic.invalidPosition, " could not locate pc");
 				END;
 				END;
 			END;
 			END;
 		END FindPC;
 		END FindPC;

+ 1 - 3
source/FoxAssembler.Mod

@@ -181,9 +181,7 @@ TYPE
 		PROCEDURE Error*(pos: SyntaxTree.Position; CONST msg: ARRAY OF CHAR);
 		PROCEDURE Error*(pos: SyntaxTree.Position; CONST msg: ARRAY OF CHAR);
 		BEGIN
 		BEGIN
 			error := TRUE;
 			error := TRUE;
-			IF diagnostics # NIL THEN
-				diagnostics.Error(scanner.source^,pos.start,Diagnostics.Invalid,msg);
-			END;
+			Basic.Error(diagnostics, scanner.source^,pos, msg);
 		END Error;
 		END Error;
 
 
 		PROCEDURE ErrorSS*(pos: SyntaxTree.Position; CONST s1,s2: ARRAY OF CHAR);
 		PROCEDURE ErrorSS*(pos: SyntaxTree.Position; CONST s1,s2: ARRAY OF CHAR);

+ 4 - 4
source/FoxBackend.Mod

@@ -1,7 +1,7 @@
 MODULE FoxBackend; (**  AUTHOR "kaeserm,fof"; PURPOSE "Oberon Compiler: Common backend module";  **)
 MODULE FoxBackend; (**  AUTHOR "kaeserm,fof"; PURPOSE "Oberon Compiler: Common backend module";  **)
 
 
 IMPORT
 IMPORT
-	Streams, Diagnostics, Global := FoxGlobal, Formats := FoxFormats, SyntaxTree := FoxSyntaxTree, SemanticChecker := FoxSemanticChecker, Options, Strings;
+	Streams, Diagnostics, Basic := FoxBasic, Global := FoxGlobal, Formats := FoxFormats, SyntaxTree := FoxSyntaxTree, SemanticChecker := FoxSemanticChecker, Options, Strings;
 
 
 
 
 TYPE
 TYPE
@@ -95,10 +95,10 @@ TYPE
 			RETURN NIL; (* default case: no parameter registers *)
 			RETURN NIL; (* default case: no parameter registers *)
 		END GetParameterRegisters;
 		END GetParameterRegisters;
 
 
-		PROCEDURE Error*(CONST source: ARRAY OF CHAR; errorNumber, errorPosition: LONGINT; CONST err: ARRAY OF CHAR);
+		PROCEDURE Error*(CONST source: ARRAY OF CHAR; position: Basic.Position; errorNumber: LONGINT; CONST err: ARRAY OF CHAR);
 		BEGIN
 		BEGIN
-			IF (err # "") & (diagnostics # NIL) THEN
-				diagnostics.Error(source,errorNumber, errorPosition,err);
+			IF (errorNumber # Basic.InvalidCode) OR (err # "") THEN
+				Basic.ErrorC(diagnostics, source, position, errorNumber, err);
 			END;
 			END;
 			error := TRUE;
 			error := TRUE;
 		END Error;
 		END Error;

+ 50 - 5
source/FoxBasic.Mod

@@ -45,7 +45,7 @@ CONST
 	MaxSet* = 31;   (* must be >= 15, else the bootstraped compiler cannot run (IN-tests) *)
 	MaxSet* = 31;   (* must be >= 15, else the bootstraped compiler cannot run (IN-tests) *)
 
 
 	invalidString*=-1;
 	invalidString*=-1;
-
+	InvalidCode*=Diagnostics.Invalid;
 TYPE
 TYPE
 	(*
 	(*
 	String* = POINTER TO ARRAY OF CHAR;
 	String* = POINTER TO ARRAY OF CHAR;
@@ -66,6 +66,8 @@ TYPE
 	Position*= RECORD
 	Position*= RECORD
 		start*, end*, line*, linepos*: LONGINT;
 		start*, end*, line*, linepos*: LONGINT;
 	END;
 	END;
+	
+	ErrorCode*=LONGINT;
 
 
 
 
 	List* = OBJECT  (* by Luc Bläser *)
 	List* = OBJECT  (* by Luc Bläser *)
@@ -1744,12 +1746,55 @@ VAR
 	
 	
 	PROCEDURE AppendPosition*(VAR msg: ARRAY OF CHAR; pos: Position);
 	PROCEDURE AppendPosition*(VAR msg: ARRAY OF CHAR; pos: Position);
 	BEGIN
 	BEGIN
-		Strings.Append(msg, " in line "); 
-		Strings.AppendInt(msg, pos.line); 
-		Strings.Append(msg, ", col "); 
-		Strings.AppendInt(msg, pos.start- pos.linepos);
+		IF pos.line >= 0 THEN
+			Strings.Append(msg, " in line "); 
+			Strings.AppendInt(msg, pos.line); 
+			Strings.Append(msg, ", col "); 
+			Strings.AppendInt(msg, pos.start- pos.linepos);
+		END;
 	END AppendPosition;
 	END AppendPosition;
 	
 	
+	PROCEDURE MakeMessage(pos: Position; code: ErrorCode; CONST msg: ARRAY OF CHAR; VAR message: ARRAY OF CHAR);
+	BEGIN
+		GetErrorMessage(code, msg, message);
+		AppendPosition(message, pos);
+	END MakeMessage;
+	
+	(* error message with code *)
+	PROCEDURE ErrorC*(diagnostics: Diagnostics.Diagnostics; CONST source: ARRAY OF CHAR; pos: Position; code: ErrorCode; CONST msg: ARRAY OF CHAR);
+	VAR message: ARRAY 256 OF CHAR;
+	BEGIN
+		IF diagnostics # NIL THEN
+			MakeMessage(pos, code, msg,message);
+			diagnostics.Error(source, pos.start, code, message);
+		END;
+	END ErrorC;
+
+	(* error message without code *)
+	PROCEDURE Error*(diagnostics: Diagnostics.Diagnostics; CONST source: ARRAY OF CHAR; pos: Position; CONST msg: ARRAY OF CHAR);
+	BEGIN
+		ErrorC(diagnostics, source, pos, InvalidCode, msg);
+	END Error;
+	
+	
+
+	PROCEDURE Warning*(diagnostics: Diagnostics.Diagnostics; CONST source: ARRAY OF CHAR; pos: Position; CONST msg: ARRAY OF CHAR);
+	VAR message: ARRAY 256 OF CHAR;
+	BEGIN
+		IF diagnostics # NIL THEN
+			MakeMessage(pos, InvalidCode, msg,message);
+			diagnostics.Warning(source, pos.start, InvalidCode, message);
+		END;
+	END Warning;
+
+	PROCEDURE Information*(diagnostics: Diagnostics.Diagnostics; CONST source: ARRAY OF CHAR; pos: Position;CONST msg: ARRAY OF CHAR);
+	VAR message: ARRAY 256 OF CHAR;
+	BEGIN
+		IF diagnostics # NIL THEN
+			MakeMessage(pos, InvalidCode, msg,message);
+			diagnostics.Information(source, pos.start, InvalidCode, message);
+		END;
+	END Information;
 
 
 	(** SetErrorMsg - Set message for error n *)
 	(** SetErrorMsg - Set message for error n *)
 
 

+ 2 - 2
source/FoxBinaryCode.Mod

@@ -183,7 +183,7 @@ TYPE
 	END FixupList;
 	END FixupList;
 
 
 	LabelList*= POINTER TO RECORD
 	LabelList*= POINTER TO RECORD
-		offset-: LONGINT; position-: LONGINT;
+		offset-: LONGINT; position-: Basic.Position;
 		prev-: LabelList;
 		prev-: LabelList;
 	END;
 	END;
 
 
@@ -242,7 +242,7 @@ TYPE
 		END Reset;
 		END Reset;
 
 
 
 
-		PROCEDURE AddLabel*(position: Unit);
+		PROCEDURE AddLabel*(position: Basic.Position);
 		VAR new: LabelList;
 		VAR new: LabelList;
 		BEGIN
 		BEGIN
 			NEW(new);
 			NEW(new);

+ 3 - 3
source/FoxBinaryObjectFile.Mod

@@ -130,7 +130,7 @@ TYPE
 			IF Trace THEN D.Str("FoxBinaryObjectFile.ObjectFileFormat.Export "); D.Str(moduleName); D.Ln; END;
 			IF Trace THEN D.Str("FoxBinaryObjectFile.ObjectFileFormat.Export "); D.Str(moduleName); D.Ln; END;
 
 
 			IF ~(module IS Sections.Module) THEN
 			IF ~(module IS Sections.Module) THEN
-				diagnostics.Error(module.module.sourceName,Diagnostics.Invalid,Diagnostics.Invalid,"generated module format does not match object file format");
+				Basic.Error(diagnostics, module.module.sourceName,Basic.invalidPosition, "generated module format does not match object file format");
 				RETURN FALSE;
 				RETURN FALSE;
 			ELSIF module.findPC # MAX(LONGINT) THEN
 			ELSIF module.findPC # MAX(LONGINT) THEN
 				MakeSectionOffsets(module(Sections.Module),constSize, varSize, codeSize, caseTableSize,const,code);
 				MakeSectionOffsets(module(Sections.Module),constSize, varSize, codeSize, caseTableSize,const,code);
@@ -385,12 +385,12 @@ TYPE
 					label := label.prev;
 					label := label.prev;
 				END;
 				END;
 				IF label # NIL THEN
 				IF label # NIL THEN
-					diagnostics.Information(module.module.sourceName,label.position,Diagnostics.Invalid," pc position");
+					Basic.Information(diagnostics, module.module.sourceName,label.position," pc position");
 					RETURN TRUE
 					RETURN TRUE
 				END;
 				END;
 			END
 			END
 		END;
 		END;
-		diagnostics.Error(module.module.sourceName,Diagnostics.Invalid,Diagnostics.Invalid," could not locate pc");
+		Basic.Error(diagnostics, module.module.sourceName,Basic.invalidPosition, " could not locate pc");
 		RETURN FALSE
 		RETURN FALSE
 	END FindPC;
 	END FindPC;
 
 

+ 2 - 2
source/FoxBinarySymbolFile.Mod

@@ -2333,13 +2333,13 @@ TYPE
 
 
 				IF noRedefinition OR noModification THEN
 				IF noRedefinition OR noModification THEN
 					IF (InterfaceComparison.Redefined IN flags) THEN
 					IF (InterfaceComparison.Redefined IN flags) THEN
-						diagnostics.Error(module.sourceName,Diagnostics.Invalid,Diagnostics.Invalid," no redefinition of symbol file allowed");
+						Basic.Error(diagnostics, module.sourceName, Basic.invalidPosition, " no redefinition of symbol file allowed");
 						RETURN FALSE;
 						RETURN FALSE;
 					END;
 					END;
 				END;
 				END;
 				IF noModification THEN
 				IF noModification THEN
 					IF (InterfaceComparison.Extended IN flags) THEN
 					IF (InterfaceComparison.Extended IN flags) THEN
-						diagnostics.Error(module.sourceName,Diagnostics.Invalid,Diagnostics.Invalid," no extension of symbol file allowed");
+						Basic.Error(diagnostics, module.sourceName,Basic.invalidPosition, " no extension of symbol file allowed");
 						RETURN FALSE;
 						RETURN FALSE;
 					END;
 					END;
 				END;
 				END;

+ 1 - 4
source/FoxCSharpParser.Mod

@@ -266,10 +266,7 @@ TYPE
         PROCEDURE Error(position: Position; code: LONGINT; CONST message: ARRAY OF CHAR);
         PROCEDURE Error(position: Position; code: LONGINT; CONST message: ARRAY OF CHAR);
             VAR errorMessage: ARRAY 256 OF CHAR;
             VAR errorMessage: ARRAY 256 OF CHAR;
         BEGIN
         BEGIN
-            IF diagnostics # NIL THEN
-                Basic.GetErrorMessage(code,message,errorMessage);
-                diagnostics.Error(scanner.source^, position.start, code, errorMessage);
-            END;
+            Basic.ErrorC(diagnostics, scanner.source^, position, code, errorMessage);
             error := TRUE;
             error := TRUE;
 (* @@@ *)
 (* @@@ *)
 HALT(100);
 HALT(100);

+ 2 - 8
source/FoxCSharpScanner.Mod

@@ -223,20 +223,14 @@ TYPE
         (** report an error occured during scanning **)
         (** report an error occured during scanning **)
         PROCEDURE ErrorS(CONST msg: ARRAY OF CHAR);
         PROCEDURE ErrorS(CONST msg: ARRAY OF CHAR);
         BEGIN
         BEGIN
-            IF diagnostics # NIL THEN
-                diagnostics.Error(source^, position.start, Diagnostics.Invalid, msg)
-            END;
+            Basic.Error(diagnostics, source^, position,  msg);
             error := TRUE;
             error := TRUE;
         END ErrorS;
         END ErrorS;
 
 
         (** report an error occured during scanning **)
         (** report an error occured during scanning **)
         PROCEDURE Error(code: INTEGER);
         PROCEDURE Error(code: INTEGER);
-            VAR errorMessage: ARRAY 256 OF CHAR;
         BEGIN
         BEGIN
-            IF diagnostics # NIL THEN
-                Basic.GetErrorMessage(code, "", errorMessage);
-                diagnostics.Error(source^, position.start, code, errorMessage)
-            END;
+            Basic.ErrorC(diagnostics, source^, position, code, "");
             error := TRUE;
             error := TRUE;
         END Error;
         END Error;
 
 

+ 4 - 6
source/FoxCodeGenerators.Mod

@@ -132,12 +132,12 @@ TYPE
 			SELF.module := module;
 			SELF.module := module;
 		END SetModule;
 		END SetModule;
 
 
-		PROCEDURE Error*(position: LONGINT; CONST message: ARRAY OF CHAR);
+		PROCEDURE Error*(position: Basic.Position; CONST message: ARRAY OF CHAR);
 		VAR string:Basic.MessageString;
 		VAR string:Basic.MessageString;
 		BEGIN
 		BEGIN
 			IF diagnostics # NIL THEN
 			IF diagnostics # NIL THEN
 				Basic.SegmentedNameToString(in.name, string);
 				Basic.SegmentedNameToString(in.name, string);
-				diagnostics.Error(string, position, Diagnostics.Invalid, message)
+				Basic.Error(diagnostics,string, position, message)
 			END;
 			END;
 			IF dump # NIL THEN (* to see error in trace output also *)
 			IF dump # NIL THEN (* to see error in trace output also *)
 				dump.String("Error: "); dump.String(message); dump.Ln; dump.Update;
 				dump.String("Error: "); dump.String(message); dump.Ln; dump.Update;
@@ -184,7 +184,7 @@ TYPE
 							Strings.Append(msg, ":");
 							Strings.Append(msg, ":");
 							Strings.IntToStr(fixup.offset, number);
 							Strings.IntToStr(fixup.offset, number);
 							Strings.Append(msg, number);
 							Strings.Append(msg, number);
-							Error(inPC,msg)
+							Error(Basic.invalidPosition,msg)
 						END
 						END
 					ELSE
 					ELSE
 						out.fixupList.AddFixup(fixup);
 						out.fixupList.AddFixup(fixup);
@@ -553,10 +553,8 @@ TYPE
 		END EmitReserve;
 		END EmitReserve;
 
 
 		PROCEDURE EmitLabel(CONST instruction: IntermediateCode.Instruction);
 		PROCEDURE EmitLabel(CONST instruction: IntermediateCode.Instruction);
-		VAR position: LONGINT;
 		BEGIN
 		BEGIN
-			position := SHORT(instruction.op1.intValue);
-			out.AddLabel(position);
+			out.AddLabel(instruction.textPosition);
 		END EmitLabel;
 		END EmitLabel;
 
 
 		PROCEDURE Prepare*;
 		PROCEDURE Prepare*;

+ 1 - 1
source/FoxDocumentationBackend.Mod

@@ -1421,7 +1421,7 @@ TYPE
 					MergeDocument(template, NIL, document);
 					MergeDocument(template, NIL, document);
 					document := template;
 					document := template;
 				ELSIF diagnostics # NIL THEN
 				ELSIF diagnostics # NIL THEN
-					diagnostics.Error("",Diagnostics.Invalid, Diagnostics.Invalid,"could not  open / parse documentation template");
+					Basic.Error(diagnostics, "",Basic.invalidPosition, "could not  open / parse documentation template");
 				END;
 				END;
 			END;
 			END;
 
 

+ 3 - 3
source/FoxGenericObjectFile.Mod

@@ -217,7 +217,7 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 									Strings.Append(msg, ", ");
 									Strings.Append(msg, ", ");
 									ObjectFile.SegmentedNameToString(test(IntermediateCode.Section).resolved.os.identifier.name,name);
 									ObjectFile.SegmentedNameToString(test(IntermediateCode.Section).resolved.os.identifier.name,name);
 									Strings.Append(msg, name);
 									Strings.Append(msg, name);
-									diagnostics.Warning(module.moduleName,Diagnostics.Invalid,Diagnostics.Invalid,msg);
+									Basic.Warning(diagnostics, module.moduleName,Basic.invalidPosition, msg);
 								END
 								END
 							END
 							END
 						END
 						END
@@ -276,7 +276,7 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 			IF Trace THEN D.String(">>> export generic object file"); D.Ln END;
 			IF Trace THEN D.String(">>> export generic object file"); D.Ln END;
 
 
 			IF ~(module IS Sections.Module) THEN
 			IF ~(module IS Sections.Module) THEN
-				diagnostics.Error (module.moduleName, Diagnostics.Invalid, Diagnostics.Invalid, "generated module format does not match object file format");
+				Basic.Error (diagnostics, module.moduleName, Basic.invalidPosition,  "generated module format does not match object file format");
 				RETURN FALSE;
 				RETURN FALSE;
 			END;
 			END;
 
 
@@ -287,7 +287,7 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 
 
 			file := Files.New (fileName);
 			file := Files.New (fileName);
 			IF file = NIL THEN
 			IF file = NIL THEN
-				diagnostics.Error(module.moduleName,Diagnostics.Invalid,Diagnostics.Invalid,"failed to open object file");
+				Basic.Error(diagnostics, module.moduleName,Basic.invalidPosition, "failed to open object file");
 				RETURN FALSE;
 				RETURN FALSE;
 			END;
 			END;
 
 

+ 2 - 2
source/FoxInterfaceComparison.Mod

@@ -65,8 +65,8 @@ CONST
 	BEGIN
 	BEGIN
 		COPY(s1,msg);
 		COPY(s1,msg);
 		Strings.Append(msg,s2);
 		Strings.Append(msg,s2);
-		IF (diagnostics # NIL) & (module # NIL) THEN
-			diagnostics.Information(module.sourceName,pos.start,Diagnostics.Invalid,msg);
+		IF (module # NIL) THEN
+			Basic.Information(diagnostics, module.sourceName,pos,msg);
 		END;
 		END;
 	END ErrorSS;
 	END ErrorSS;
 
 

+ 1 - 1
source/FoxIntermediateAssembler.Mod

@@ -84,7 +84,7 @@ TYPE
 				END;
 				END;
 
 
 				IF ~error THEN
 				IF ~error THEN
-					IntermediateCode.InitInstruction(instruction, 0, SHORTINT(mnem), operands[0], operands[1], operands[2]);
+					IntermediateCode.InitInstruction(instruction, pos, SHORTINT(mnem), operands[0], operands[1], operands[2]);
 					section.Emit(instruction);
 					section.Emit(instruction);
 					(*
 					(*
 
 

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


+ 5 - 5
source/FoxIntermediateCode.Mod

@@ -123,7 +123,7 @@ TYPE
 	Instruction* = POINTER TO RECORD
 	Instruction* = POINTER TO RECORD
 		opcode-: SHORTINT; (* instruction opcode *)
 		opcode-: SHORTINT; (* instruction opcode *)
 		subtype-: SHORTINT; (* for special backend instruction *)
 		subtype-: SHORTINT; (* for special backend instruction *)
-		textPosition-: LONGINT; (* for error handling and tracking (findPC) *)
+		textPosition-: Basic.Position; (* for error handling and tracking (findPC) *)
 		pc-: LONGINT; (* backend program counter (in bits) for debugging and for label fixups in backend *)
 		pc-: LONGINT; (* backend program counter (in bits) for debugging and for label fixups in backend *)
 		op1*,op2*,op3*: Operand; (* first operand typically provides the result, if any *)
 		op1*,op2*,op3*: Operand; (* first operand typically provides the result, if any *)
 	END;
 	END;
@@ -802,7 +802,7 @@ TYPE
 		AddFormat(special,"special",Any, Any, Any, {} );
 		AddFormat(special,"special",Any, Any, Any, {} );
 	END InitInstructions;
 	END InitInstructions;
 
 
-	PROCEDURE InitInstruction*(VAR instr: Instruction; textPosition: LONGINT; opcode: SHORTINT; op1,op2,op3: Operand);
+	PROCEDURE InitInstruction*(VAR instr: Instruction; textPosition: Basic.Position; opcode: SHORTINT; op1,op2,op3: Operand);
 	VAR format: InstructionFormat; mode1, mode2, mode3: LONGINT; (* debugging *)
 	VAR format: InstructionFormat; mode1, mode2, mode3: LONGINT; (* debugging *)
 	BEGIN
 	BEGIN
 		IF instr = NIL THEN NEW(instr) END;
 		IF instr = NIL THEN NEW(instr) END;
@@ -828,17 +828,17 @@ TYPE
 		instr.textPosition := textPosition;
 		instr.textPosition := textPosition;
 	END InitInstruction;
 	END InitInstruction;
 
 
-	PROCEDURE InitInstruction2*(VAR instr: Instruction; textPosition: LONGINT; opcode: SHORTINT; op1,op2: Operand);
+	PROCEDURE InitInstruction2*(VAR instr: Instruction; textPosition: Basic.Position; opcode: SHORTINT; op1,op2: Operand);
 	BEGIN
 	BEGIN
 		InitInstruction(instr, textPosition, opcode, op1, op2, empty);
 		InitInstruction(instr, textPosition, opcode, op1, op2, empty);
 	END InitInstruction2;
 	END InitInstruction2;
 
 
-	PROCEDURE InitInstruction1*(VAR instr: Instruction; textPosition: LONGINT; opcode: SHORTINT; op1: Operand);
+	PROCEDURE InitInstruction1*(VAR instr: Instruction; textPosition: Basic.Position; opcode: SHORTINT; op1: Operand);
 	BEGIN
 	BEGIN
 		InitInstruction(instr, textPosition, opcode, op1, empty, empty);
 		InitInstruction(instr, textPosition, opcode, op1, empty, empty);
 	END InitInstruction1;
 	END InitInstruction1;
 
 
-	PROCEDURE InitInstruction0*(VAR instr: Instruction; textPosition: LONGINT; opcode: SHORTINT);
+	PROCEDURE InitInstruction0*(VAR instr: Instruction; textPosition: Basic.Position; opcode: SHORTINT);
 	BEGIN
 	BEGIN
 		InitInstruction(instr, textPosition, opcode, empty, empty, empty);
 		InitInstruction(instr, textPosition, opcode, empty, empty, empty);
 	END InitInstruction0;
 	END InitInstruction0;

+ 36 - 36
source/FoxIntermediateLinker.Mod

@@ -75,7 +75,7 @@ TYPE
 				section.EmitAt(index, instruction)
 				section.EmitAt(index, instruction)
 			ELSE
 			ELSE
 				IntermediateCode.InitImmediate(op, instruction.op1.type, 1);
 				IntermediateCode.InitImmediate(op, instruction.op1.type, 1);
-				IntermediateCode.InitInstruction1(reserve,0, IntermediateCode.reserve, op);
+				IntermediateCode.InitInstruction1(reserve,Basic.invalidPosition, IntermediateCode.reserve, op);
 				WHILE (section.pc < index) DO
 				WHILE (section.pc < index) DO
 					section.Emit(reserve);
 					section.Emit(reserve);
 				END;
 				END;
@@ -96,7 +96,7 @@ TYPE
 			END; (* nothing to patch *)
 			END; (* nothing to patch *)
 			itype := IntermediateCode.GetType(backend.system, type);
 			itype := IntermediateCode.GetType(backend.system, type);
 			IntermediateCode.InitImmediate(op1,itype, value);
 			IntermediateCode.InitImmediate(op1,itype, value);
-			IntermediateCode.InitInstruction1(instruction, 0,  IntermediateCode.data, op1);
+			IntermediateCode.InitInstruction1(instruction, Basic.invalidPosition,  IntermediateCode.data, op1);
 			EmitAt(section(IntermediateCode.Section),index, instruction);
 			EmitAt(section(IntermediateCode.Section),index, instruction);
 			RETURN TRUE;
 			RETURN TRUE;
 		END PatchIntegerValue;
 		END PatchIntegerValue;
@@ -116,7 +116,7 @@ TYPE
 			ELSE
 			ELSE
 				IntermediateCode.InitImmediate(op1, type, 0);
 				IntermediateCode.InitImmediate(op1, type, 0);
 			END;
 			END;
-			IntermediateCode.InitInstruction1(instruction, 0,  IntermediateCode.data, op1);
+			IntermediateCode.InitInstruction1(instruction, Basic.invalidPosition,  IntermediateCode.data, op1);
 			EmitAt(section(IntermediateCode.Section), index, instruction);
 			EmitAt(section(IntermediateCode.Section), index, instruction);
 			RETURN TRUE;
 			RETURN TRUE;
 		END PatchBooleanValue;
 		END PatchBooleanValue;
@@ -135,7 +135,7 @@ TYPE
 			REPEAT
 			REPEAT
 				char := value[i];
 				char := value[i];
 				IntermediateCode.InitImmediate(op1, type, ORD(char));
 				IntermediateCode.InitImmediate(op1, type, ORD(char));
-				IntermediateCode.InitInstruction1(instruction, 0,  IntermediateCode.data, op1);
+				IntermediateCode.InitInstruction1(instruction, Basic.invalidPosition,  IntermediateCode.data, op1);
 				section(IntermediateCode.Section).Emit(instruction);
 				section(IntermediateCode.Section).Emit(instruction);
 				INC(i); 
 				INC(i); 
 			UNTIL char = 0X; 
 			UNTIL char = 0X; 
@@ -165,7 +165,7 @@ TYPE
 					IF module = NIL THEN
 					IF module = NIL THEN
 						msg := "failed to import IR file ";
 						msg := "failed to import IR file ";
 						Strings.Append(msg, moduleFileName);
 						Strings.Append(msg, moduleFileName);
-						diagnostics.Error(filename, Diagnostics.Invalid, Diagnostics.Invalid, msg);
+						Basic.Error(diagnostics, filename, Basic.invalidPosition, msg);
 						RETURN FALSE
 						RETURN FALSE
 					ELSE
 					ELSE
 						loadedModules.AddName(moduleName); (* to avoid recursive reloading this must be done before parsing *)
 						loadedModules.AddName(moduleName); (* to avoid recursive reloading this must be done before parsing *)
@@ -175,7 +175,7 @@ TYPE
 								IF  ~LoadModule(name, recursive) THEN
 								IF  ~LoadModule(name, recursive) THEN
 									msg := "failed to import ";
 									msg := "failed to import ";
 									Strings.Append(msg, name);
 									Strings.Append(msg, name);
-									diagnostics.Error(filename, Diagnostics.Invalid, Diagnostics.Invalid, msg);
+									Basic.Error(diagnostics, filename, Basic.invalidPosition, msg);
 									RETURN FALSE
 									RETURN FALSE
 								END;
 								END;
 							END;
 							END;
@@ -474,7 +474,7 @@ TYPE
 
 
 			IntermediateCode.InitImmediate(dataOperand, IntermediateCode.GetType(backend.GetSystem(), syntaxTreeValue.type.resolved), hugeintValue);
 			IntermediateCode.InitImmediate(dataOperand, IntermediateCode.GetType(backend.GetSystem(), syntaxTreeValue.type.resolved), hugeintValue);
 			IntermediateCode.InitOperand(emptyOperand);
 			IntermediateCode.InitOperand(emptyOperand);
-			IntermediateCode.InitInstruction(dataInstruction, -1, IntermediateCode.data, dataOperand, emptyOperand, emptyOperand);
+			IntermediateCode.InitInstruction(dataInstruction, Basic.invalidPosition, IntermediateCode.data, dataOperand, emptyOperand, emptyOperand);
 
 
 			ASSERT(section IS IntermediateCode.Section);
 			ASSERT(section IS IntermediateCode.Section);
 			section(IntermediateCode.Section).EmitAt(0, dataInstruction)
 			section(IntermediateCode.Section).EmitAt(0, dataInstruction)
@@ -661,15 +661,15 @@ TYPE
 
 
 
 
 			IF binaryModule = NIL THEN
 			IF binaryModule = NIL THEN
-				diagnostics.Error(desiredName, Diagnostics.Invalid, Diagnostics.Invalid, "the specified backend cannot process intermediate code");
+				Basic.Error(diagnostics, desiredName,Basic.invalidPosition, "the specified backend cannot process intermediate code");
 				result := FALSE
 				result := FALSE
 			ELSIF backend.error THEN
 			ELSIF backend.error THEN
-				diagnostics.Error(desiredName, Diagnostics.Invalid, Diagnostics.Invalid, "binary code could not be generated (backend error)");
+				Basic.Error(diagnostics, desiredName, Basic.invalidPosition, "binary code could not be generated (backend error)");
 				result := FALSE
 				result := FALSE
 			ELSE
 			ELSE
 				IF Trace THEN D.String(">>> binary code successfully generated"); D.Ln END;
 				IF Trace THEN D.String(">>> binary code successfully generated"); D.Ln END;
 				IF objectFileFormat = NIL THEN
 				IF objectFileFormat = NIL THEN
-					diagnostics.Error(desiredName, Diagnostics.Invalid, Diagnostics.Invalid, "no object file format specified");
+					Basic.Error(diagnostics, desiredName, Basic.invalidPosition, "no object file format specified");
 					result := FALSE
 					result := FALSE
 				ELSE
 				ELSE
 					(* write the generated code into an object file *)
 					(* write the generated code into an object file *)
@@ -683,7 +683,7 @@ TYPE
 						END;
 						END;
 						IF Trace THEN D.String(">>> object file successfully written"); D.Ln END;
 						IF Trace THEN D.String(">>> object file successfully written"); D.Ln END;
 					ELSE
 					ELSE
-						diagnostics.Error(desiredName, Diagnostics.Invalid, Diagnostics.Invalid, "object file could not be written");
+						Basic.Error(diagnostics, desiredName, Basic.invalidPosition, "object file could not be written");
 						result := FALSE
 						result := FALSE
 					END
 					END
 				END
 				END
@@ -719,7 +719,7 @@ TYPE
 			IF (inExtension # "") THEN irLinker.objectFile.SetExtension(inExtension) END;
 			IF (inExtension # "") THEN irLinker.objectFile.SetExtension(inExtension) END;
 			IF ~irLinker.LoadModule(backend(IntermediateCode.IntermediateBackend).runtimeModuleName, TRUE) THEN
 			IF ~irLinker.LoadModule(backend(IntermediateCode.IntermediateBackend).runtimeModuleName, TRUE) THEN
 				error := TRUE;
 				error := TRUE;
-				diagnostics.Error(backend(IntermediateCode.IntermediateBackend).runtimeModuleName,Diagnostics.Invalid, Diagnostics.Invalid, "could not load ir file");
+				Basic.Error(diagnostics, backend(IntermediateCode.IntermediateBackend).runtimeModuleName,Diagnostics.Invalid, Diagnostics.Invalid, "could not load ir file");
 			END;
 			END;
 			backend := irLinker.backend;
 			backend := irLinker.backend;
 			system := backend.system;
 			system := backend.system;
@@ -744,7 +744,7 @@ TYPE
 		BEGIN
 		BEGIN
 			irLinker.PrearrangeReachableDataSections;
 			irLinker.PrearrangeReachableDataSections;
 			IF irLinker.GenerateObjectFile(outputFormat, NIL, instanceName) THEN
 			IF irLinker.GenerateObjectFile(outputFormat, NIL, instanceName) THEN
-				diagnostics.Information(instanceName, Diagnostics.Invalid, Diagnostics.Invalid, "generated.");
+				Basic.Information(diagnostics, instanceName, Diagnostics.Invalid, Diagnostics.Invalid, "generated.");
 				RETURN TRUE
 				RETURN TRUE
 			ELSE
 			ELSE
 				RETURN FALSE
 				RETURN FALSE
@@ -810,7 +810,7 @@ TYPE
 						Strings.Append(msg, device.name);
 						Strings.Append(msg, device.name);
 						Strings.Append(msg," in cell ");
 						Strings.Append(msg," in cell ");
 						instance.AppendToMsg(msg);
 						instance.AppendToMsg(msg);
-						diagnostics.Error(specification.name,Diagnostics.Invalid, Diagnostics.Invalid, msg);
+						Basic.Error(diagnostics, specification.name,Diagnostics.Invalid, Diagnostics.Invalid, msg);
 						error := TRUE;
 						error := TRUE;
 					END;
 					END;
 				ELSE
 				ELSE
@@ -819,7 +819,7 @@ TYPE
 						Strings.Append(msg, device.name);
 						Strings.Append(msg, device.name);
 						Strings.Append(msg," in cell ");
 						Strings.Append(msg," in cell ");
 						instance.AppendToMsg(msg);
 						instance.AppendToMsg(msg);
-						diagnostics.Warning(specification.name,Diagnostics.Invalid,Diagnostics.Invalid,msg);
+						Basic.Warning(diagnostics, specification.name,Diagnostics.Invalid,Diagnostics.Invalid,msg);
 					END;
 					END;
 				END;
 				END;
 			END;
 			END;
@@ -829,7 +829,7 @@ TYPE
 			objectFileFormat.GetExtension(objectFileExtension);
 			objectFileFormat.GetExtension(objectFileExtension);
 			irLinker.PrearrangeReachableDataSections;
 			irLinker.PrearrangeReachableDataSections;
 			IF ~irLinker.GenerateObjectFile(objectFileFormat, specification.log, instanceName) THEN
 			IF ~irLinker.GenerateObjectFile(objectFileFormat, specification.log, instanceName) THEN
-				diagnostics.Error(specification.name,Diagnostics.Invalid, Diagnostics.Invalid, "could not generate object file");
+				Basic.Error(diagnostics, specification.name,Diagnostics.Invalid, Diagnostics.Invalid, "could not generate object file");
 				RETURN FALSE
 				RETURN FALSE
 			END;
 			END;
 
 
@@ -861,7 +861,7 @@ TYPE
 			END;
 			END;
 
 
 			IF (instructionMemorySize > 0) & (instructionMemorySize < code.SizeInBits() DIV system.codeUnit) THEN
 			IF (instructionMemorySize > 0) & (instructionMemorySize < code.SizeInBits() DIV system.codeUnit) THEN
-				diagnostics.Error(instanceName,Diagnostics.Invalid, Diagnostics.Invalid, "specified instruction memory size too small");
+				Basic.Error(diagnostics, instanceName,Diagnostics.Invalid, Diagnostics.Invalid, "specified instruction memory size too small");
 				error := TRUE;
 				error := TRUE;
 			ELSIF instructionMemorySize = 0 THEN
 			ELSIF instructionMemorySize = 0 THEN
 				instructionMemorySize := code.SizeInBits() DIV system.codeUnit;
 				instructionMemorySize := code.SizeInBits() DIV system.codeUnit;
@@ -872,7 +872,7 @@ TYPE
 			instance.SetDataMemorySize(dataMemorySize);
 			instance.SetDataMemorySize(dataMemorySize);
 
 
 			IF (dataMemorySize - data.SizeInBits() DIV system.dataUnit) < MinimalStackSize THEN
 			IF (dataMemorySize - data.SizeInBits() DIV system.dataUnit) < MinimalStackSize THEN
-				diagnostics.Error(specification.name,Diagnostics.Invalid, Diagnostics.Invalid, "specified data memory size too small");
+				Basic.Error(diagnostics, specification.name,Diagnostics.Invalid, Diagnostics.Invalid, "specified data memory size too small");
 				error := TRUE;
 				error := TRUE;
 			END;
 			END;
 
 
@@ -900,7 +900,7 @@ TYPE
 			ELSE
 			ELSE
 				msg := "could not link ";
 				msg := "could not link ";
 				Strings.Append(msg,linkRoot);
 				Strings.Append(msg,linkRoot);
-				diagnostics.Error("",Diagnostics.Invalid, Diagnostics.Invalid, msg);
+				Basic.Error(diagnostics, "",Diagnostics.Invalid, Diagnostics.Invalid, msg);
 			END;
 			END;
 			RETURN ~linker.error & ~error
 			RETURN ~linker.error & ~error
 		END LinkInstance;
 		END LinkInstance;
@@ -1018,11 +1018,11 @@ TYPE
 				NEW(irLinker, specification.diagnostics, backend, ""); (* TODO: pass an optional path as third parameter *)
 				NEW(irLinker, specification.diagnostics, backend, ""); (* TODO: pass an optional path as third parameter *)
 				IF ~irLinker.LoadModule(backend(IntermediateCode.IntermediateBackend).runtimeModuleName, TRUE) THEN
 				IF ~irLinker.LoadModule(backend(IntermediateCode.IntermediateBackend).runtimeModuleName, TRUE) THEN
 					error := TRUE;
 					error := TRUE;
-					diagnostics.Error(backend(IntermediateCode.IntermediateBackend).runtimeModuleName,Diagnostics.Invalid, Diagnostics.Invalid, "could not load ir file");
+					Basic.Error(diagnostics, backend(IntermediateCode.IntermediateBackend).runtimeModuleName,Diagnostics.Invalid, Diagnostics.Invalid, "could not load ir file");
 				END;
 				END;
 				IF ~irLinker.LoadModule(specification.name,TRUE) THEN
 				IF ~irLinker.LoadModule(specification.name,TRUE) THEN
 					error := TRUE;
 					error := TRUE;
-					diagnostics.Error(specification.name,Diagnostics.Invalid, Diagnostics.Invalid, "could not load ir file");
+					Basic.Error(diagnostics, specification.name,Diagnostics.Invalid, Diagnostics.Invalid, "could not load ir file");
 				END;
 				END;
 				backend := irLinker.backend;
 				backend := irLinker.backend;
 				system := backend.system;
 				system := backend.system;
@@ -1082,7 +1082,7 @@ TYPE
 				objectFileFormat.GetExtension(objectFileExtension);
 				objectFileFormat.GetExtension(objectFileExtension);
 				irLinker.PrearrangeReachableDataSections;
 				irLinker.PrearrangeReachableDataSections;
 				IF ~irLinker.GenerateObjectFile(objectFileFormat, specification.log, instanceName) THEN
 				IF ~irLinker.GenerateObjectFile(objectFileFormat, specification.log, instanceName) THEN
-					diagnostics.Error(specification.name,Diagnostics.Invalid, Diagnostics.Invalid, "could not generate object file");
+					Basic.Error(diagnostics, specification.name,Diagnostics.Invalid, Diagnostics.Invalid, "could not generate object file");
 					RETURN FALSE
 					RETURN FALSE
 				END;
 				END;
 
 
@@ -1114,7 +1114,7 @@ TYPE
 				END;
 				END;
 
 
 				IF (instructionMemorySize > 0) & (instructionMemorySize < code.SizeInBits() DIV system.codeUnit) THEN
 				IF (instructionMemorySize > 0) & (instructionMemorySize < code.SizeInBits() DIV system.codeUnit) THEN
-					diagnostics.Error(instanceName,Diagnostics.Invalid, Diagnostics.Invalid, "specified instruction memory size too small");
+					Basic.Error(diagnostics, instanceName,Diagnostics.Invalid, Diagnostics.Invalid, "specified instruction memory size too small");
 					error := TRUE;
 					error := TRUE;
 				ELSIF instructionMemorySize = 0 THEN
 				ELSIF instructionMemorySize = 0 THEN
 					instructionMemorySize := code.SizeInBits() DIV system.codeUnit;
 					instructionMemorySize := code.SizeInBits() DIV system.codeUnit;
@@ -1125,7 +1125,7 @@ TYPE
 				instance.SetDataMemorySize(dataMemorySize);
 				instance.SetDataMemorySize(dataMemorySize);
 
 
 				IF (dataMemorySize - data.SizeInBits() DIV system.dataUnit) < MinimalStackSize THEN
 				IF (dataMemorySize - data.SizeInBits() DIV system.dataUnit) < MinimalStackSize THEN
-					diagnostics.Error(specification.name,Diagnostics.Invalid, Diagnostics.Invalid, "specified data memory size too small");
+					Basic.Error(diagnostics, specification.name,Diagnostics.Invalid, Diagnostics.Invalid, "specified data memory size too small");
 					error := TRUE;
 					error := TRUE;
 				END;
 				END;
 
 
@@ -1153,7 +1153,7 @@ TYPE
 				ELSE
 				ELSE
 					msg := "could not link ";
 					msg := "could not link ";
 					Strings.Append(msg,linkRoot);
 					Strings.Append(msg,linkRoot);
-					diagnostics.Error("",Diagnostics.Invalid, Diagnostics.Invalid, msg);
+					Basic.Error(diagnostics, "",Diagnostics.Invalid, Diagnostics.Invalid, msg);
 				END;
 				END;
 				RETURN ~linker.error & ~error
 				RETURN ~linker.error & ~error
 			END LinkInstance;
 			END LinkInstance;
@@ -1186,7 +1186,7 @@ TYPE
 		PROCEDURE Error(CONST error: ARRAY OF CHAR);
 		PROCEDURE Error(CONST error: ARRAY OF CHAR);
 		BEGIN
 		BEGIN
 			IF diagnostics # NIL THEN
 			IF diagnostics # NIL THEN
-				diagnostics.Error("",Diagnostics.Invalid,Diagnostics.Invalid,error);
+				Basic.Error(diagnostics, "",Basic.invalidPosition, error);
 			END;
 			END;
 		END Error;
 		END Error;
 
 
@@ -1248,9 +1248,9 @@ TYPE
 				assemblinker.MarkReachabilityOfAll(TRUE);
 				assemblinker.MarkReachabilityOfAll(TRUE);
 				FileNameToModuleName(filename, moduleName);
 				FileNameToModuleName(filename, moduleName);
 				IF (targetFile = "") & assemblinker.GenerateObjectFile(objectFileFormat, context.out, moduleName) THEN
 				IF (targetFile = "") & assemblinker.GenerateObjectFile(objectFileFormat, context.out, moduleName) THEN
-					diagnostics.Information(filename, Diagnostics.Invalid, Diagnostics.Invalid, "done.")
+					Basic.Information(diagnostics, filename, Basic.invalidPosition, "done.")
 				ELSIF targetFile # "" THEN
 				ELSIF targetFile # "" THEN
-					diagnostics.Information(filename,  Diagnostics.Invalid, Diagnostics.Invalid, "loaded.")
+					Basic.Information(diagnostics, filename,  Basic.invalidPosition, "loaded.")
 				ELSE
 				ELSE
 					error := TRUE
 					error := TRUE
 				END
 				END
@@ -1262,7 +1262,7 @@ TYPE
 			assemblinker.PrearrangeReachableDataSections;
 			assemblinker.PrearrangeReachableDataSections;
 			IF 	assemblinker.GenerateObjectFile(objectFileFormat, context.out, targetFile)
 			IF 	assemblinker.GenerateObjectFile(objectFileFormat, context.out, targetFile)
 			THEN
 			THEN
-				diagnostics.Information(targetFile, Diagnostics.Invalid, Diagnostics.Invalid, "generated.")
+				Basic.Information(diagnostics, targetFile, Basic.invalidPosition, "generated.")
 			ELSE error := FALSE
 			ELSE error := FALSE
 			END;
 			END;
 		END;
 		END;
@@ -1293,7 +1293,7 @@ TYPE
 				
 				
 
 
 				IF (instructionMemorySize > 0) & (instructionMemorySize < code.SizeInBits() DIV system.codeUnit) THEN
 				IF (instructionMemorySize > 0) & (instructionMemorySize < code.SizeInBits() DIV system.codeUnit) THEN
-					diagnostics.Error(instanceName,Diagnostics.Invalid, Diagnostics.Invalid, "specified instruction memory size too small");
+					Basic.Error(diagnostics, instanceName, Basic.invalidPosition, "specified instruction memory size too small");
 					error := TRUE;
 					error := TRUE;
 				ELSIF instructionMemorySize = 0 THEN
 				ELSIF instructionMemorySize = 0 THEN
 					instructionMemorySize := code.SizeInBits() DIV system.codeUnit;
 					instructionMemorySize := code.SizeInBits() DIV system.codeUnit;
@@ -1302,7 +1302,7 @@ TYPE
 				dataMemorySize := MAX(data.SizeInBits() DIV system.dataUnit, dataMemorySize);
 				dataMemorySize := MAX(data.SizeInBits() DIV system.dataUnit, dataMemorySize);
 
 
 				IF (dataMemorySize - data.SizeInBits() DIV system.dataUnit) < MinimalStackSize THEN
 				IF (dataMemorySize - data.SizeInBits() DIV system.dataUnit) < MinimalStackSize THEN
-					diagnostics.Error(instanceName,Diagnostics.Invalid, Diagnostics.Invalid, "specified data memory size too small");
+					Basic.Error(diagnostics, instanceName,Basic.invalidPosition, "specified data memory size too small");
 					error := TRUE;
 					error := TRUE;
 				END;
 				END;
 
 
@@ -1333,7 +1333,7 @@ TYPE
 				ELSE
 				ELSE
 					msg := "could not link ";
 					msg := "could not link ";
 					Strings.Append(msg,instanceName);
 					Strings.Append(msg,instanceName);
-					diagnostics.Error("",Diagnostics.Invalid, Diagnostics.Invalid, msg);
+					Basic.Error(diagnostics, "",Basic.invalidPosition, msg);
 				END;
 				END;
 				RETURN ~linker.error & ~error
 				RETURN ~linker.error & ~error
 		
 		
@@ -1371,7 +1371,7 @@ TYPE
 		PROCEDURE Error(CONST error: ARRAY OF CHAR);
 		PROCEDURE Error(CONST error: ARRAY OF CHAR);
 		BEGIN
 		BEGIN
 			IF diagnostics # NIL THEN
 			IF diagnostics # NIL THEN
-				diagnostics.Error("",Diagnostics.Invalid,Diagnostics.Invalid,error);
+				Basic.Error(diagnostics, "",Basic.invalidPosition, error);
 			END;
 			END;
 		END Error;
 		END Error;
 
 
@@ -1460,9 +1460,9 @@ TYPE
 				assemblinker.MarkReachabilityOfAll(TRUE);
 				assemblinker.MarkReachabilityOfAll(TRUE);
 				FileNameToModuleName(filename, moduleName);
 				FileNameToModuleName(filename, moduleName);
 				IF (targetFile = "") & assemblinker.GenerateObjectFile(objectFileFormat, context.out, moduleName) THEN
 				IF (targetFile = "") & assemblinker.GenerateObjectFile(objectFileFormat, context.out, moduleName) THEN
-					diagnostics.Information(filename, Diagnostics.Invalid, Diagnostics.Invalid, "done.")
+					Basic.Information(diagnostics, filename, Diagnostics.Invalid, Diagnostics.Invalid, "done.")
 				ELSIF targetFile # "" THEN
 				ELSIF targetFile # "" THEN
-					diagnostics.Information(filename,  Diagnostics.Invalid, Diagnostics.Invalid, "loaded.")
+					Basic.Information(diagnostics, filename,  Diagnostics.Invalid, Diagnostics.Invalid, "loaded.")
 				ELSE
 				ELSE
 					error := TRUE
 					error := TRUE
 				END
 				END
@@ -1476,7 +1476,7 @@ TYPE
 			assemblinker.PrearrangeReachableDataSections;
 			assemblinker.PrearrangeReachableDataSections;
 			IF 	assemblinker.GenerateObjectFile(objectFileFormat, context.out, targetFile)
 			IF 	assemblinker.GenerateObjectFile(objectFileFormat, context.out, targetFile)
 			THEN
 			THEN
-				diagnostics.Information(targetFile, Diagnostics.Invalid, Diagnostics.Invalid, "generated.")
+				Basic.Information(diagnostics, targetFile, Diagnostics.Invalid, Diagnostics.Invalid, "generated.")
 			ELSE error := FALSE
 			ELSE error := FALSE
 			END;
 			END;
 		END;
 		END;

+ 3 - 3
source/FoxIntermediateObjectFile.Mod

@@ -177,7 +177,7 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 			IF Trace THEN D.String(">>> export intermediate object file"); D.Ln END;
 			IF Trace THEN D.String(">>> export intermediate object file"); D.Ln END;
 
 
 			IF ~(module IS Sections.Module) THEN
 			IF ~(module IS Sections.Module) THEN
-				diagnostics.Error(module.moduleName, Diagnostics.Invalid, Diagnostics.Invalid, "generated module format does not match object file format");
+				Basic.Error(diagnostics, module.moduleName, Basic.invalidPosition, "generated module format does not match object file format");
 				RETURN FALSE;
 				RETURN FALSE;
 			END;
 			END;
 
 
@@ -188,7 +188,7 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 
 
 			file := Files.New(filename);
 			file := Files.New(filename);
 			IF file = NIL THEN
 			IF file = NIL THEN
-				diagnostics.Error(module.moduleName, Diagnostics.Invalid,Diagnostics.Invalid, "failed to open object file for writting");
+				Basic.Error(diagnostics, module.moduleName, Basic.invalidPosition, "failed to open object file for writting");
 				RETURN FALSE
 				RETURN FALSE
 			END;
 			END;
 
 
@@ -316,7 +316,7 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 				ReadOperand(op1);
 				ReadOperand(op1);
 				ReadOperand(op2);
 				ReadOperand(op2);
 				ReadOperand(op3);
 				ReadOperand(op3);
-				IntermediateCode.InitInstruction(instruction, 0, SHORTINT(opcode), op1, op2, op3);
+				IntermediateCode.InitInstruction(instruction, Basic.invalidPosition, SHORTINT(opcode), op1, op2, op3);
 				IntermediateCode.SetSubType(instruction, SHORTINT(subtype));
 				IntermediateCode.SetSubType(instruction, SHORTINT(subtype));
 				section.Emit(instruction);
 				section.Emit(instruction);
 			END ReadInstruction;
 			END ReadInstruction;

+ 3 - 5
source/FoxIntermediateParser.Mod

@@ -35,9 +35,7 @@ TYPE
 		PROCEDURE Error(pos: Position; CONST msg: ARRAY OF CHAR);
 		PROCEDURE Error(pos: Position; CONST msg: ARRAY OF CHAR);
 		BEGIN
 		BEGIN
 			error := TRUE;
 			error := TRUE;
-			IF diagnostics # NIL THEN
-				diagnostics.Error(scanner.source^,pos.start,Diagnostics.Invalid,msg);
-			END;
+			Basic.Error(diagnostics, scanner.source^,pos,msg);
 
 
 			D.Update;
 			D.Update;
 			IF Trace THEN D.TraceBack END
 			IF Trace THEN D.TraceBack END
@@ -342,7 +340,7 @@ TYPE
 					END;
 					END;
 
 
 					IF ~error THEN
 					IF ~error THEN
-						IntermediateCode.InitInstruction(instruction, positionOfInstruction.start, opCode, operands[0], operands[1], operands[2]);
+						IntermediateCode.InitInstruction(instruction, positionOfInstruction, opCode, operands[0], operands[1], operands[2]);
 						IF Strict & ~IntermediateCode.CheckInstruction(instruction, message) THEN
 						IF Strict & ~IntermediateCode.CheckInstruction(instruction, message) THEN
 							Error(positionOfInstruction, message)
 							Error(positionOfInstruction, message)
 						END
 						END
@@ -617,7 +615,7 @@ TYPE
 		IF reader = NIL THEN
 		IF reader = NIL THEN
 			msg := "failed to open ";
 			msg := "failed to open ";
 			Strings.Append(msg, filename);
 			Strings.Append(msg, filename);
-			diagnostics.Error(filename, Diagnostics.Invalid, Diagnostics.Invalid, msg);
+			Basic.Error(diagnostics, filename, Basic.invalidPosition, msg);
 			RETURN NIL
 			RETURN NIL
 		ELSE
 		ELSE
 			NEW(module, NIL, system);
 			NEW(module, NIL, system);

+ 2 - 6
source/FoxInterpreter.Mod

@@ -136,9 +136,7 @@ TYPE
 			IF error THEN RETURN END;
 			IF error THEN RETURN END;
 			(*! use diagnostics *)
 			(*! use diagnostics *)
 			error := TRUE;
 			error := TRUE;
-			IF diagnostics # NIL THEN
-				diagnostics.Error("",Diagnostics.Invalid, Diagnostics.Invalid, msg);
-			END;
+			Basic.Error(diagnostics, "", Basic.invalidPosition, msg);
 			D.TraceBack;
 			D.TraceBack;
 		END Error;
 		END Error;
 
 
@@ -150,9 +148,7 @@ TYPE
 			error := TRUE;
 			error := TRUE;
 			COPY(msg, message);
 			COPY(msg, message);
 			IF id # 0 THEN Strings.Append(message," "); StringPool.GetString(id, name); Strings.Append(message, name); END;
 			IF id # 0 THEN Strings.Append(message," "); StringPool.GetString(id, name); Strings.Append(message, name); END;
-			IF diagnostics # NIL THEN
-				diagnostics.Error("",Diagnostics.Invalid, Diagnostics.Invalid, message);
-			END;
+			Basic.Error(diagnostics, "", Basic.invalidPosition, message);
 		END ErrorSS;
 		END ErrorSS;
 
 
 		(** syntax tree types omitted -- unused *)
 		(** syntax tree types omitted -- unused *)

+ 1 - 1
source/FoxInterpreterBackend.Mod

@@ -269,7 +269,7 @@ TYPE
 		END Stop;
 		END Stop;
 
 
 		PROCEDURE Error (CONST msg: ARRAY OF CHAR);
 		PROCEDURE Error (CONST msg: ARRAY OF CHAR);
-		BEGIN backend.Error ("", Diagnostics.Invalid, Diagnostics.Invalid, msg); Stop;
+		BEGIN backend.Error ("", Basic.invalidPosition, Diagnostics.Invalid, msg); Stop;
 		END Error;
 		END Error;
 
 
 		PROCEDURE Execute (VAR instr: Intermediate.Instruction; VAR pc: PC);
 		PROCEDURE Execute (VAR instr: Intermediate.Instruction; VAR pc: PC);

+ 6 - 6
source/FoxMinosObjectFile.Mod

@@ -35,7 +35,7 @@ TYPE
 			IF Trace THEN D.Str("FoxBinaryObjectFile.ObjectFileFormat.Export "); D.Str(moduleName); D.Ln; END;
 			IF Trace THEN D.Str("FoxBinaryObjectFile.ObjectFileFormat.Export "); D.Str(moduleName); D.Ln; END;
 
 
 			IF ~(module IS Sections.Module) THEN
 			IF ~(module IS Sections.Module) THEN
-				diagnostics.Error(module.module.sourceName,Diagnostics.Invalid,Diagnostics.Invalid,"generated module format does not match object file format");
+				Basic.Error(diagnostics, module.module.sourceName, Basic.invalidPosition, "generated module format does not match object file format");
 				RETURN FALSE;
 				RETURN FALSE;
 			ELSIF module.findPC # MAX(LONGINT) THEN
 			ELSIF module.findPC # MAX(LONGINT) THEN
 				MakeSectionOffsets(module(Sections.Module),varSize, codeSize, bodyOffset, code);
 				MakeSectionOffsets(module(Sections.Module),varSize, codeSize, bodyOffset, code);
@@ -103,7 +103,7 @@ TYPE
 							temp.fixupSection := section;
 							temp.fixupSection := section;
 							temp.nextFixup := first;
 							temp.nextFixup := first;
 							IF fixup.displacement # 0 THEN
 							IF fixup.displacement # 0 THEN
-								diagnostics.Error(module.moduleName,Diagnostics.Invalid, Diagnostics.Invalid,"Fixups with displacement # 0 not supported in Minos Object File.");
+								Basic.Error(diagnostics, module.moduleName, Basic.invalidPosition, "Fixups with displacement # 0 not supported in Minos Object File.");
 							END;
 							END;
 							first := temp;
 							first := temp;
 						END;
 						END;
@@ -135,12 +135,12 @@ TYPE
 					label := label.prev;
 					label := label.prev;
 				END;
 				END;
 				IF label # NIL THEN
 				IF label # NIL THEN
-					diagnostics.Information(module.module.sourceName,label.position,Diagnostics.Invalid," pc position");
+					Basic.Information(diagnostics, module.module.sourceName,label.position," pc position");
 					RETURN TRUE
 					RETURN TRUE
 				END;
 				END;
 			END
 			END
 		END;
 		END;
-		diagnostics.Error(module.module.sourceName,Diagnostics.Invalid,Diagnostics.Invalid," could not locate pc");
+		Basic.Error(diagnostics, module.module.sourceName,Basic.invalidPosition, " could not locate pc");
 		RETURN FALSE
 		RETURN FALSE
 	END FindPC;
 	END FindPC;
 
 
@@ -369,7 +369,7 @@ TYPE
 						fixup := binarySection.fixupList.firstFixup;
 						fixup := binarySection.fixupList.firstFixup;
 						WHILE fixup # NIL DO
 						WHILE fixup # NIL DO
 							IF (fixup.mode = BinaryCode.Relative)  & InModule(fixup.symbol.name) THEN
 							IF (fixup.mode = BinaryCode.Relative)  & InModule(fixup.symbol.name) THEN
-								diagnostics.Error(module.moduleName,Diagnostics.Invalid, Diagnostics.Invalid,"Relative self fixup not supported by Minos Object File.");
+								Basic.Error(diagnostics, module.moduleName, Basic.invalidPosition, "Relative self fixup not supported by Minos Object File.");
 							ELSIF (fixup.mode = BinaryCode.Absolute) & InModule(fixup.symbol.name) THEN
 							ELSIF (fixup.mode = BinaryCode.Absolute) & InModule(fixup.symbol.name) THEN
 								this := section.offset  + fixup.offset; (* location of the fixup *)
 								this := section.offset  + fixup.offset; (* location of the fixup *)
 								(*
 								(*
@@ -387,7 +387,7 @@ TYPE
 									Strings.Append(msg," : ");
 									Strings.Append(msg," : ");
 									Strings.AppendInt(msg, patchOffset);
 									Strings.AppendInt(msg, patchOffset);
 
 
-									diagnostics.Error(module.moduleName,Diagnostics.Invalid, Diagnostics.Invalid,msg);
+									Basic.Error(diagnostics, module.moduleName,Basic.invalidPosition, msg);
 
 
 									error := TRUE
 									error := TRUE
 								END;
 								END;

+ 2 - 7
source/FoxParser.Mod

@@ -214,7 +214,7 @@ TYPE
 			SELF.diagnostics := diagnostics;
 			SELF.diagnostics := diagnostics;
 			error := ~scanner.GetNextSymbol(symbol);
 			error := ~scanner.GetNextSymbol(symbol);
 			hasSymbol := TRUE;
 			hasSymbol := TRUE;
-			IF error THEN diagnostics.Error(scanner.source^, Diagnostics.Invalid, Diagnostics.Invalid, "no input stream") END;
+			IF error THEN Basic.Error(diagnostics, scanner.source^, Basic.invalidPosition, "no input stream") END;
 			recentCommentItem := NIL; recentComment := NIL;
 			recentCommentItem := NIL; recentComment := NIL;
 			(* debugging *)
 			(* debugging *)
 			indent := 0;
 			indent := 0;
@@ -235,13 +235,8 @@ TYPE
 
 
 		(** output error message and / or given code *)
 		(** output error message and / or given code *)
 		PROCEDURE Error(position: Position; 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
 		BEGIN
-			IF diagnostics # NIL THEN
-				Basic.GetErrorMessage(code,message,errorMessage);
-				Basic.AppendPosition(errorMessage, position);
-				diagnostics.Error(scanner.source^, position.start, code, errorMessage);
-			END;
+			Basic.ErrorC(diagnostics, scanner.source^, position, code, message);
 			error := TRUE
 			error := TRUE
 		END Error;
 		END Error;
 
 

+ 2 - 14
source/FoxScanner.Mod

@@ -339,27 +339,15 @@ TYPE
 
 
 		(** report an error occured during scanning **)
 		(** report an error occured during scanning **)
 		PROCEDURE ErrorS(CONST msg: ARRAY OF CHAR);
 		PROCEDURE ErrorS(CONST msg: ARRAY OF CHAR);
-		VAR errorMessage: ARRAY 256 OF CHAR;
 		BEGIN
 		BEGIN
-			IF diagnostics # NIL THEN
-				COPY(msg, errorMessage); 
-				IF useLineNumbers THEN
-					Basic.AppendPosition(errorMessage, position);
-				END;
-				diagnostics.Error(source^, position.start, Diagnostics.Invalid, errorMessage)
-			END;
+			Basic.Error(diagnostics, source^, position,  msg);
 			error := TRUE;
 			error := TRUE;
 		END ErrorS;
 		END ErrorS;
 
 
 		(** report an error occured during scanning **)
 		(** report an error occured during scanning **)
 		PROCEDURE Error( code: INTEGER );
 		PROCEDURE Error( code: INTEGER );
-		VAR errorMessage: ARRAY 256 OF CHAR;
 		BEGIN
 		BEGIN
-			IF diagnostics # NIL THEN
-				Basic.GetErrorMessage(code,"",errorMessage);
-				IF useLineNumbers THEN Basic.AppendPosition(errorMessage, position) END;
-				diagnostics.Error(source^, position.start, code, errorMessage)
-			END;
+			Basic.ErrorC(diagnostics, source^, position, code, "");
 			error := TRUE;
 			error := TRUE;
 		END Error;
 		END Error;
 
 

+ 14 - 25
source/FoxSemanticChecker.Mod

@@ -142,49 +142,38 @@ TYPE
 
 
 		(** report error **)
 		(** report error **)
 		PROCEDURE Error(position: Position; 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;
+		VAR errModule: SyntaxTree.Module;
 		BEGIN
 		BEGIN
-			IF diagnostics # NIL THEN
-				Basic.GetErrorMessage(code,message,errorMessage);
-				ASSERT(currentScope # NIL);
-				IF module # NIL THEN errModule := module ELSE errModule := currentScope.ownerModule END;
-				Basic.AppendPosition(errorMessage, position);
-				diagnostics.Error(errModule.sourceName, position.start, code, errorMessage);
-			END;
+			ASSERT(currentScope # NIL);
+			IF module # NIL THEN errModule := module ELSE errModule := currentScope.ownerModule END;
+			Basic.ErrorC(diagnostics, errModule.sourceName, position, code, message);
 			error := TRUE;
 			error := TRUE;
 		END Error;
 		END Error;
 
 
 		PROCEDURE Warning(position: Position; CONST message: ARRAY OF CHAR);
 		PROCEDURE Warning(position: Position; CONST message: ARRAY OF CHAR);
 		VAR errModule: SyntaxTree.Module;
 		VAR errModule: SyntaxTree.Module;
 		BEGIN
 		BEGIN
-			IF diagnostics # NIL THEN
-				IF module # NIL THEN errModule := module ELSE errModule := currentScope.ownerModule END;
-				diagnostics.Warning(errModule.sourceName, position.start, Diagnostics.Invalid, message);
-			END;
+			IF module # NIL THEN errModule := module ELSE errModule := currentScope.ownerModule END;
+			Basic.Warning(diagnostics, errModule.sourceName, position, message);
 		END Warning;
 		END Warning;
 
 
 
 
 		PROCEDURE ErrorSS(position: Position; CONST msg,msg2: ARRAY OF CHAR);
 		PROCEDURE ErrorSS(position: Position; CONST msg,msg2: ARRAY OF CHAR);
 		VAR errorMessage: ARRAY 256 OF CHAR;
 		VAR errorMessage: ARRAY 256 OF CHAR;
 		BEGIN
 		BEGIN
-			IF diagnostics # NIL THEN
-				Basic.Concat(errorMessage,msg," ", msg2);
-				Basic.AppendPosition(errorMessage, position);
-				diagnostics.Error(currentScope.ownerModule.sourceName, position.start, Diagnostics.Invalid, errorMessage);
-			END;
+			Basic.Concat(errorMessage,msg," ", msg2);
+			Basic.Error(diagnostics, currentScope.ownerModule.sourceName, position, errorMessage);
 			error := TRUE;
 			error := TRUE;
 		END ErrorSS;
 		END ErrorSS;
 
 
 		PROCEDURE InfoSS(position: Position; 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;
 		VAR msg, msg2: ARRAY 256 OF CHAR;
 		BEGIN
 		BEGIN
-			IF diagnostics # NIL THEN
-				COPY(msg1, msg);
-				Strings.Append(msg, " = ");
-				Basic.GetString(s, msg2);
-				Strings.Append(msg, msg2);
-				diagnostics.Information(currentScope.ownerModule.sourceName, position.start, Diagnostics.Invalid, msg);
-			END;
+			COPY(msg1, msg);
+			Strings.Append(msg, " = ");
+			Basic.GetString(s, msg2);
+			Strings.Append(msg, msg2);
+			Basic.Information(diagnostics, currentScope.ownerModule.sourceName, position, msg);
 		END InfoSS;
 		END InfoSS;
 
 
 
 
@@ -8659,7 +8648,7 @@ TYPE
 			Global.GetSymbolName(x,msg);
 			Global.GetSymbolName(x,msg);
 			Strings.Append(msg," ");
 			Strings.Append(msg," ");
 			Strings.Append(msg,text);
 			Strings.Append(msg,text);
-			diagnostics.Warning(module.sourceName,x.position.start,Diagnostics.Invalid,msg);
+			Basic.Warning(diagnostics, module.sourceName,x.position, msg);
 		END Warning;
 		END Warning;
 
 
 		(** symbols *)
 		(** symbols *)

+ 8 - 8
source/FoxTRMBackend.Mod

@@ -304,7 +304,7 @@ TYPE
 
 
 			PROCEDURE CheckEmptySpillStack(): BOOLEAN;
 			PROCEDURE CheckEmptySpillStack(): BOOLEAN;
 			BEGIN
 			BEGIN
-				IF spillStack.Size()#0 THEN Error(inPC,"implementation error, spill stack not cleared");
+				IF spillStack.Size()#0 THEN Error(Basic.invalidPosition,"implementation error, spill stack not cleared");
 					IF dump # NIL THEN
 					IF dump # NIL THEN
 						spillStack.Dump(dump);
 						spillStack.Dump(dump);
 						tickets.Dump(dump);
 						tickets.Dump(dump);
@@ -1460,7 +1460,7 @@ TYPE
 		BEGIN
 		BEGIN
 			IF IntermediateCode.IsConstantInteger(instruction.op3,value) & IntermediateBackend.PowerOf2(value,exp) THEN
 			IF IntermediateCode.IsConstantInteger(instruction.op3,value) & IntermediateBackend.PowerOf2(value,exp) THEN
 				IntermediateCode.InitImmediate(iop3, instruction.op3.type, exp);
 				IntermediateCode.InitImmediate(iop3, instruction.op3.type, exp);
-				IntermediateCode.InitInstruction(inst, -1, IntermediateCode.shl, instruction.op1, instruction.op2, iop3);
+				IntermediateCode.InitInstruction(inst, Basic.invalidPosition, IntermediateCode.shl, instruction.op1, instruction.op2, iop3);
 				EmitShift(inst);
 				EmitShift(inst);
 				RETURN;
 				RETURN;
 			END;
 			END;
@@ -1505,7 +1505,7 @@ TYPE
 			IF instruction.opcode = IntermediateCode.div THEN
 			IF instruction.opcode = IntermediateCode.div THEN
 				IF IntermediateCode.IsConstantInteger(instruction.op3,value) & IntermediateBackend.PowerOf2(value,exp) THEN
 				IF IntermediateCode.IsConstantInteger(instruction.op3,value) & IntermediateBackend.PowerOf2(value,exp) THEN
 					IntermediateCode.InitImmediate(iop3, instruction.op3.type, exp);
 					IntermediateCode.InitImmediate(iop3, instruction.op3.type, exp);
-					IntermediateCode.InitInstruction(inst, -1, IntermediateCode.shr, instruction.op1, instruction.op2, iop3);
+					IntermediateCode.InitInstruction(inst, Basic.invalidPosition, IntermediateCode.shr, instruction.op1, instruction.op2, iop3);
 					EmitShift(inst);
 					EmitShift(inst);
 					RETURN;
 					RETURN;
 				END;
 				END;
@@ -1520,7 +1520,7 @@ TYPE
 		BEGIN
 		BEGIN
 			IF IntermediateCode.IsConstantInteger(instruction.op3,value) & IntermediateBackend.PowerOf2(value,exp) THEN
 			IF IntermediateCode.IsConstantInteger(instruction.op3,value) & IntermediateBackend.PowerOf2(value,exp) THEN
 				IntermediateCode.InitImmediate(op3, instruction.op3.type, value-1);
 				IntermediateCode.InitImmediate(op3, instruction.op3.type, value-1);
-				IntermediateCode.InitInstruction(inst, -1, IntermediateCode.and, instruction.op1, instruction.op2, op3);
+				IntermediateCode.InitInstruction(inst, Basic.invalidPosition, IntermediateCode.and, instruction.op1, instruction.op2, op3);
 				EmitAnd(inst);
 				EmitAnd(inst);
 				RETURN;
 				RETURN;
 			END;
 			END;
@@ -2367,7 +2367,7 @@ TYPE
 		 		PatchFixups(in(IntermediateCode.Section).resolved)
 		 		PatchFixups(in(IntermediateCode.Section).resolved)
 		 	END;
 		 	END;
 
 
-			IF cg.error THEN Error("", Diagnostics.Invalid, Diagnostics.Invalid,  "") END;
+			IF cg.error THEN Error("", Basic.invalidPosition, Diagnostics.Invalid,  "") END;
 		END GenerateBinary;
 		END GenerateBinary;
 
 
 		(* genasm *)
 		(* genasm *)
@@ -2455,7 +2455,7 @@ TYPE
 			UNTIL (i = module(Sections.Module).allSections.Length()) OR (section.name = pooledName);
 			UNTIL (i = module(Sections.Module).allSections.Length()) OR (section.name = pooledName);
 
 
 			IF section.name # pooledName THEN
 			IF section.name # pooledName THEN
-				diagnostics.Error(module.module.sourceName,Diagnostics.Invalid,Diagnostics.Invalid," could not locate pc");
+				Basic.Error(diagnostics, module.module.sourceName,Basic.invalidPosition," could not locate pc");
 			ELSE
 			ELSE
 				binarySection := section(IntermediateCode.Section).resolved;
 				binarySection := section(IntermediateCode.Section).resolved;
 				label := binarySection.labels;
 				label := binarySection.labels;
@@ -2463,9 +2463,9 @@ TYPE
 					label := label.prev;
 					label := label.prev;
 				END;
 				END;
 				IF label # NIL THEN
 				IF label # NIL THEN
-					diagnostics.Information(module.module.sourceName,label.position,Diagnostics.Invalid," pc position");
+					Basic.Information(diagnostics, module.module.sourceName,label.position," pc position");
 				ELSE
 				ELSE
-					diagnostics.Error(module.module.sourceName,Diagnostics.Invalid,Diagnostics.Invalid," could not locate pc");
+					Basic.Error(diagnostics, module.module.sourceName, Basic.invalidPosition," could not locate pc");
 				END;
 				END;
 			END;
 			END;
 		END FindPC;
 		END FindPC;

+ 3 - 5
source/FoxTextualSymbolFile.Mod

@@ -44,9 +44,7 @@ TYPE
 
 
 			file := Files.New(fileName);
 			file := Files.New(fileName);
 			IF file = NIL THEN
 			IF file = NIL THEN
-				IF diagnostics # NIL THEN
-					diagnostics.Error(module.sourceName, -1, -1, "could not open export file for writing");
-				END;
+				Basic.Error(diagnostics, module.sourceName, Basic.invalidPosition,  "could not open export file for writing");
 				result := FALSE;
 				result := FALSE;
 			ELSE
 			ELSE
 
 
@@ -56,13 +54,13 @@ TYPE
 
 
 				IF noRedefinition OR noModification THEN
 				IF noRedefinition OR noModification THEN
 					IF (InterfaceComparison.Redefined IN flags) THEN
 					IF (InterfaceComparison.Redefined IN flags) THEN
-						diagnostics.Error(module.sourceName,Diagnostics.Invalid,Diagnostics.Invalid," no redefinition of symbol file allowed");
+						Basic.Error(diagnostics, module.sourceName, Basic.invalidPosition, " no redefinition of symbol file allowed");
 						RETURN FALSE;
 						RETURN FALSE;
 					END;
 					END;
 				END;
 				END;
 				IF noModification THEN
 				IF noModification THEN
 					IF (InterfaceComparison.Extended IN flags) THEN
 					IF (InterfaceComparison.Extended IN flags) THEN
-						diagnostics.Error(module.sourceName,Diagnostics.Invalid,Diagnostics.Invalid," no extension of symbol file allowed");
+						Basic.Error(diagnostics, module.sourceName,Basic.invalidPosition,  " no extension of symbol file allowed");
 						RETURN FALSE;
 						RETURN FALSE;
 					END;
 					END;
 				END;
 				END;

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