Bladeren bron

Added proper constant for invalid stream positions

git-svn-id: https://svn.inf.ethz.ch/svn/lecturers/a2/trunk@8152 8c9fc860-2736-0410-a75d-ab315db34111
negelef 7 jaren geleden
bovenliggende
commit
7324dc8173

+ 6 - 6
source/Compiler.Mod

@@ -52,7 +52,7 @@ TYPE
 		replacement := NIL;
 		reader := Basic.GetFileReader(filename);
 		IF reader = NIL THEN
-			diagnostics.Error (filename, Diagnostics.Invalid, "failed to open");
+			diagnostics.Error (filename, Streams.Invalid, "failed to open");
 		ELSE
 
 			scanner := Scanner.NewScanner(filename, reader, 0, diagnostics);
@@ -111,7 +111,7 @@ TYPE
 			Strings.Append (message, msg);
 			IF error THEN
 				IF diagnostics # NIL THEN
-					diagnostics.Error (source, Diagnostics.Invalid, message);
+					diagnostics.Error (source, Streams.Invalid, message);
 				END;
 			ELSE
 				IF (log # NIL) & ~(Silent IN options.flags) & ~(FindPC IN options.flags) THEN
@@ -272,7 +272,7 @@ TYPE
 		PROCEDURE Error(CONST error: ARRAY OF CHAR);
 		BEGIN
 			IF diagnostics # NIL THEN
-				diagnostics.Error("",Diagnostics.Invalid,error);
+				diagnostics.Error("",Streams.Invalid,error);
 			END;
 		END Error;
 
@@ -467,7 +467,7 @@ TYPE
 				reader := Basic.GetFileReader(filename);
 
 				IF reader = NIL THEN
-					diagnostics.Error (filename, Diagnostics.Invalid, "failed to open"); error := TRUE;
+					diagnostics.Error (filename, Streams.Invalid, "failed to open"); error := TRUE;
 				ELSE
 					error := ~Modules(filename, reader, 0, diagnostics,context.out, options,  importCache);
 				END;
@@ -483,7 +483,7 @@ TYPE
 				WHILE replacement # NIL DO
 					IF ~replacement.used THEN
 						name := replacement.name;
-						diagnostics.Warning(name,  Diagnostics.Invalid, " unused replacement.");
+						diagnostics.Warning(name,  Streams.Invalid, " unused replacement.");
 					END;
 					replacement := replacement.next;
 				END;
@@ -506,7 +506,7 @@ TYPE
 		IF GetOptions(context.arg,context.error,diagnostics,options) THEN
 
 			IF reader = NIL THEN
-				diagnostics.Error (filename, Diagnostics.Invalid, "failed to open"); error := TRUE;
+				diagnostics.Error (filename, Streams.Invalid, "failed to open"); error := TRUE;
 			ELSE
 				error := ~Modules(filename, reader, 0, diagnostics, context.out, options, importCache);
 			END;

+ 2 - 2
source/CompilerInterface.Mod

@@ -41,12 +41,12 @@ TYPE
 			IF (compileText # NIL) THEN
 				compileText(t, source, pos, pc, opt, log, diagnostics, error);
 			ELSIF (diagnostics # NIL) THEN
-				diagnostics.Error(source, Diagnostics.Invalid, "Text compile procedure not set");
+				diagnostics.Error(source, Streams.Invalid, "Text compile procedure not set");
 			END;
 		FINALLY
 			IF trap THEN (* trap will be set in case a trap occurs in the block above *)
 				error := TRUE;
-				diagnostics.Error(source, Diagnostics.Invalid, "COMPILER TRAPPED");
+				diagnostics.Error(source, Streams.Invalid, "COMPILER TRAPPED");
 				log.String("COMPILER TRAPPED!!!"); log.Update;
 			END;
 		END CompileText;

+ 1 - 4
source/Diagnostics.Mod

@@ -3,9 +3,6 @@ MODULE Diagnostics; (** AUTHOR "staubesv"; PURPOSE "Generic diagnostics reportin
 IMPORT Streams;
 
 CONST
-	(** Indicate that a position is not valid *)
-	Invalid* = -1;
-
 	(** Entry types *)
 	TypeInformation* = 0;
 	TypeWarning* = 1;
@@ -176,7 +173,7 @@ PROCEDURE Print (w: Streams.Writer; CONST source : ARRAY OF CHAR; position: Stre
 BEGIN
 	w.Char(Tab);
 	IF (source # "") THEN w.String (source); END;
-	IF (position # Invalid) THEN w.Char ('@'); w.Int(position, 0); END;
+	IF (position # Streams.Invalid) THEN w.Char ('@'); w.Int(position, 0); END;
 	w.String(": ");
 	IF (type = TypeWarning) THEN
 		w.String("warning");

+ 1 - 1
source/FoxA2Interface.Mod

@@ -117,7 +117,7 @@ TYPE
 		END;
 		w.Char(Tab);
 		IF (source # "") THEN w.String (source); END;
-		IF (position # Diagnostics.Invalid) THEN w.Char ('@'); w.Int(position, 0); END;
+		IF (position # Streams.Invalid) THEN w.Char ('@'); w.Int(position, 0); END;
 		w.Char(Tab);
 		IF (type = Diagnostics.TypeWarning) THEN
 			w.String("warning");

+ 1 - 1
source/FoxAMD64Assembler.Mod

@@ -1154,7 +1154,7 @@ TYPE
 		BEGIN
 			pos := errPos;
 			COPY(message,msg);
-			IF (pos.start = Diagnostics.Invalid) OR (sourceName = "") THEN
+			IF (pos.start = Streams.Invalid) OR (sourceName = "") THEN
 				Strings.Append(msg," in ");
 				ObjectFile.SegmentedNameToString(emitter.code.os.identifier.name, name);
 				Strings.Append(msg, name);

+ 1 - 1
source/FoxAMDBackend.Mod

@@ -3480,7 +3480,7 @@ TYPE
 		 	END;
 			*)
 
-			IF cg.error THEN Error("",Basic.invalidPosition, Diagnostics.Invalid,"") END;
+			IF cg.error THEN Error("",Basic.invalidPosition, Streams.Invalid,"") END;
 		END GenerateBinary;
 
 		(* genasm *)

+ 1 - 1
source/FoxARMBackend.Mod

@@ -3752,7 +3752,7 @@ TYPE
 		 		PatchFixups(in(IntermediateCode.Section).resolved)
 		 	END;
 
-			IF cg.error THEN Error("", Basic.invalidPosition, Diagnostics.Invalid,  "") END
+			IF cg.error THEN Error("", Basic.invalidPosition, Streams.Invalid,  "") END
 		END GenerateBinary;
 
 		(** create an ARM code module from an intermediate code module **)

+ 2 - 2
source/FoxActiveCells.Mod

@@ -988,7 +988,7 @@ TYPE
 				 	module := modules.GetModule(i);
 				 	Strings.Append(msg," "); Strings.Append(msg,module.name);
 				 END;
-				 diagnostics.Error("",Diagnostics.Invalid, msg);
+				 diagnostics.Error("",Streams.Invalid, msg);
 			END;
 			RETURN ~linker.error
 		END LinkType;
@@ -1449,7 +1449,7 @@ TYPE
 				IF log # NIL THEN log.String(msg); log.Ln; END;
 				RETURN TRUE
 			ELSE
-				diagnostics.Error(fileName,Diagnostics.Invalid, "could not generate file");
+				diagnostics.Error(fileName,Streams.Invalid, "could not generate file");
 				IF TraceError THEN HALT(100) ELSE RETURN FALSE END
 			END;
 		END Emit;

+ 2 - 2
source/FoxBasic.Mod

@@ -29,7 +29,7 @@ CONST
 	InitErrMsgSize = 300;	(* initial size of array of error messages *)
 
 	invalidString* = -1;
-	InvalidCode* = Diagnostics.Invalid;
+	InvalidCode* = -1;
 TYPE
 	(*
 	String* = POINTER TO ARRAY OF CHAR;
@@ -1656,7 +1656,7 @@ TYPE
 			D.Ln;
 			D.String(" ---------------------- TRACE for COMPILER ERROR  < ");
 			D.String(source);
-			IF position # Diagnostics.Invalid THEN D.String("@"); D.Int(position,1) END;
+			IF position # Streams.Invalid THEN D.String("@"); D.Int(position,1) END;
 			D.String(" "); D.String(message);
 			D.String(" > ---------------------- ");
 			D.TraceBack

+ 15 - 15
source/FoxCSharpParser.Mod

@@ -938,7 +938,7 @@ KernelLog.Ln();
                     expression := SyntaxTree.NewParameterDesignator(position, designator, expressionList);
                 END;
              ELSE
-                Error(symbol.position, Diagnostics.Invalid, "Invalid primary expression");
+                Error(symbol.position, Basic.InvalidCode, "Invalid primary expression");
                 NextSymbol;
                 expression := SyntaxTree.invalidExpression;
             END;
@@ -1522,7 +1522,7 @@ KernelLog.Ln();
                 expression := PrimaryExpression();
             END;
             IF ~(expression IS SyntaxTree.Designator) THEN
-                Error(position, Diagnostics.Invalid, "Invalid expression statement");
+                Error(position, Basic.InvalidCode, "Invalid expression statement");
             ELSE
                 designator := expression(SyntaxTree.Designator);
                 position := symbol.position;
@@ -1610,7 +1610,7 @@ KernelLog.Ln();
                 ELSIF designator IS SyntaxTree.ParameterDesignator THEN
                     statement := SyntaxTree.NewProcedureCallStatement(designator.position, designator, outer);
                 ELSE
-                    Error(position, Diagnostics.Invalid, "Invalid expression statement");
+                    Error(position, Basic.InvalidCode, "Invalid expression statement");
                 END;
             END;
             IF statement # NIL THEN
@@ -1721,7 +1721,7 @@ KernelLog.Ln();
                     Check(Scanner.Default);
                     Check(Scanner.Colon);
                     IF haveDefault THEN
-                        Error(position, Diagnostics.Invalid, "Duplicate default label");
+                        Error(position, Basic.InvalidCode, "Duplicate default label");
                     ELSE
                         defaultSection := TRUE;
                         haveDefault := TRUE;
@@ -1731,13 +1731,13 @@ KernelLog.Ln();
             statements := StatementList(caseStatement);
             length := statements.Length();
             IF length = 0 THEN
-                Error(symbol.position, Diagnostics.Invalid, "Fall through in switch section");
+                Error(symbol.position, Basic.InvalidCode, "Fall through in switch section");
             ELSE
                 last := statements.GetStatement(length-1);
                 IF last IS SyntaxTree.ExitStatement THEN
                     statements.RemoveStatement(last);
                 ELSIF ~(last IS SyntaxTree.ReturnStatement) THEN
-                    Error(symbol.position, Diagnostics.Invalid, "Fall through in switch section");
+                    Error(symbol.position, Basic.InvalidCode, "Fall through in switch section");
                 END;
             END;
             IF ~defaultSection THEN
@@ -1925,7 +1925,7 @@ KernelLog.Ln();
                 ELSIF Optional(Scanner.Long) THEN
                     typename := lynxLong;
                 ELSE
-                    Error(position, Diagnostics.Invalid, "Missing integral type specifier");
+                    Error(position, Basic.InvalidCode, "Missing integral type specifier");
                     typename := lynxInt;
                 END;
                 type := 
@@ -1979,13 +1979,13 @@ KernelLog.Ln();
             caseBody := StatementList(caseStatement);
             length := caseBody.Length();
             IF length = 0 THEN
-                Error(symbol.position, Diagnostics.Invalid, "Fall through in switch section");
+                Error(symbol.position, Basic.InvalidCode, "Fall through in switch section");
             ELSE
                 last := caseBody.GetStatement(length-1);
                 IF last IS SyntaxTree.ExitStatement THEN
                     caseBody.RemoveStatement(last);
                 ELSIF ~(last IS SyntaxTree.ReturnStatement) THEN
-                    Error(symbol.position, Diagnostics.Invalid, "Fall through in switch section");
+                    Error(symbol.position, Basic.InvalidCode, "Fall through in switch section");
                 END;
             END;
 
@@ -2032,7 +2032,7 @@ KernelLog.Ln();
             position := symbol.position;
             Check(Scanner.RightBrace);
             IF index = 0 THEN
-                Error(position, Diagnostics.Invalid, "Empty select statement");
+                Error(position, Basic.InvalidCode, "Empty select statement");
             END;
             statements.AddStatement(caseStatement);
             IF Trace THEN 
@@ -2795,13 +2795,13 @@ KernelLog.Ln();
             VAR access: SET;
         BEGIN
             IF modifiers * {Public, Internal} = {Public, Internal} THEN
-                Error(symbol.position, Diagnostics.Invalid, "conflicting modifiers");
+                Error(symbol.position, Basic.InvalidCode, "conflicting modifiers");
             END;
             IF Public IN modifiers THEN
                 access := SyntaxTree.Public + SyntaxTree.Protected + SyntaxTree.Internal;
             ELSIF Internal IN modifiers THEN
                 IF ~allowedReadOnly THEN
-                    Error(symbol.position, Diagnostics.Invalid, "may not be defined internal")
+                    Error(symbol.position, Basic.InvalidCode, "may not be defined internal")
                 ELSE
                     access :=  SyntaxTree.ReadOnly + {SyntaxTree.InternalWrite};
                 END;
@@ -3155,9 +3155,9 @@ KernelLog.Ln();
             procedureType := SyntaxTree.NewProcedureType(position, parentScope);
             FormalParameterList(procedureType, procedureScope, type);
             IF procedureType.numberParameters # 0 THEN
-                Error(position, Diagnostics.Invalid, "constructor/main has parameters");
+                Error(position, Basic.InvalidCode, "constructor/main has parameters");
             ELSIF procedureType.returnType # NIL THEN
-                Error(position, Diagnostics.Invalid, "constructor/main returns value");
+                Error(position, Basic.InvalidCode, "constructor/main returns value");
             END;
             procedure.SetType(procedureType);
             procedure.SetBodyProcedure(TRUE);
@@ -3495,7 +3495,7 @@ KernelLog.Ln();
             ELSIF Optional(Scanner.Out) THEN
                 direction := SyntaxTree.OutPort;
             ELSE
-                Error(position, Diagnostics.Invalid, "invalid direction, expected in or out");
+                Error(position, Basic.InvalidCode, "invalid direction, expected in or out");
             END;
             type := SyntaxTree.NewPortType(position, direction, NIL, parentScope);
             IF Optional(Scanner.LeftBracket) THEN

+ 1 - 1
source/FoxInterfaceComparison.Mod

@@ -153,7 +153,7 @@ CONST
 			CompareScopes(module.moduleScope,importedModule.moduleScope);
 			IF importCache # NIL THEN SemanticChecker.RemoveModuleFromCache(importCache, importedModule) END;
 		ELSE
-			(* ErrorSS(Diagnostics.Invalid,fname," new module."); *)
+			(* ErrorSS(Streams.Invalid,fname," new module."); *)
 		END;
 	END CompareThis;
 

+ 3 - 3
source/FoxIntermediateBackend.Mod

@@ -2,7 +2,7 @@ MODULE FoxIntermediateBackend; (** AUTHOR ""; PURPOSE ""; *)
 
 IMPORT Basic := FoxBasic, SyntaxTree := FoxSyntaxTree, SemanticChecker := FoxSemanticChecker, Backend := FoxBackend, Global := FoxGlobal,
 	Scanner := FoxScanner, IntermediateCode := FoxIntermediateCode, Sections := FoxSections, BinaryCode := FoxBinaryCode,  Printout := FoxPrintout,
-	SYSTEM, Diagnostics, Strings, Options, Streams, Compiler, Formats := FoxFormats, SymbolFileFormat := FoxTextualSymbolFile, D := Debugging,
+	SYSTEM, Strings, Options, Streams, Compiler, Formats := FoxFormats, SymbolFileFormat := FoxTextualSymbolFile, D := Debugging,
 	FingerPrinter := FoxFingerPrinter, StringPool, CRC;
 
 CONST
@@ -198,7 +198,7 @@ TYPE
 
 		PROCEDURE Error(position: Position; CONST s: ARRAY OF CHAR);
 		BEGIN
-			backend.Error(module.module.sourceName, position, Diagnostics.Invalid, s);
+			backend.Error(module.module.sourceName, position, Streams.Invalid, s);
 		END Error;
 
 		PROCEDURE Type(x: SyntaxTree.Type);
@@ -2490,7 +2490,7 @@ TYPE
 
 		PROCEDURE Error(position: Position; CONST s: ARRAY OF CHAR);
 		BEGIN
-			backend.Error(module.module.sourceName,position,Diagnostics.Invalid,s);
+			backend.Error(module.module.sourceName,position,Streams.Invalid,s);
 			IF dump # NIL THEN
 				dump.String(s); dump.Ln;
 			END;

+ 17 - 17
source/FoxIntermediateLinker.Mod

@@ -719,7 +719,7 @@ TYPE
 			IF (inExtension # "") THEN irLinker.objectFile.SetExtension(inExtension) END;
 			IF ~irLinker.LoadModule(backend(IntermediateCode.IntermediateBackend).builtinsModuleName, TRUE) THEN
 				error := TRUE;
-				Basic.Error(diagnostics, backend(IntermediateCode.IntermediateBackend).builtinsModuleName,Diagnostics.Invalid, "could not load ir file");
+				Basic.Error(diagnostics, backend(IntermediateCode.IntermediateBackend).builtinsModuleName,Streams.Invalid, "could not load ir file");
 			END;
 			backend := irLinker.backend;
 			system := backend.system;
@@ -744,7 +744,7 @@ TYPE
 		BEGIN
 			irLinker.PrearrangeReachableDataSections;
 			IF irLinker.GenerateObjectFile(outputFormat, NIL, instanceName) THEN
-				Basic.Information(diagnostics, instanceName, Diagnostics.Invalid, "generated.");
+				Basic.Information(diagnostics, instanceName, Streams.Invalid, "generated.");
 				RETURN TRUE
 			ELSE
 				RETURN FALSE
@@ -810,7 +810,7 @@ TYPE
 						Strings.Append(msg, device.name);
 						Strings.Append(msg," in cell ");
 						instance.AppendToMsg(msg);
-						Basic.Error(diagnostics, specification.name,Diagnostics.Invalid, msg);
+						Basic.Error(diagnostics, specification.name,Streams.Invalid, msg);
 						error := TRUE;
 					END;
 				ELSE
@@ -819,7 +819,7 @@ TYPE
 						Strings.Append(msg, device.name);
 						Strings.Append(msg," in cell ");
 						instance.AppendToMsg(msg);
-						Basic.Warning(diagnostics, specification.name,Diagnostics.Invalid,msg);
+						Basic.Warning(diagnostics, specification.name,Streams.Invalid,msg);
 					END;
 				END;
 			END;
@@ -829,7 +829,7 @@ TYPE
 			objectFileFormat.GetExtension(objectFileExtension);
 			irLinker.PrearrangeReachableDataSections;
 			IF ~irLinker.GenerateObjectFile(objectFileFormat, specification.log, instanceName) THEN
-				Basic.Error(diagnostics, specification.name,Diagnostics.Invalid, "could not generate object file");
+				Basic.Error(diagnostics, specification.name,Streams.Invalid, "could not generate object file");
 				RETURN FALSE
 			END;
 
@@ -861,7 +861,7 @@ TYPE
 			END;
 
 			IF (instructionMemorySize > 0) & (instructionMemorySize < code.SizeInBits() DIV system.codeUnit) THEN
-				Basic.Error(diagnostics, instanceName,Diagnostics.Invalid, "specified instruction memory size too small");
+				Basic.Error(diagnostics, instanceName,Streams.Invalid, "specified instruction memory size too small");
 				error := TRUE;
 			ELSIF instructionMemorySize = 0 THEN
 				instructionMemorySize := code.SizeInBits() DIV system.codeUnit;
@@ -872,7 +872,7 @@ TYPE
 			instance.SetDataMemorySize(dataMemorySize);
 
 			IF (dataMemorySize - data.SizeInBits() DIV system.dataUnit) < MinimalStackSize THEN
-				Basic.Error(diagnostics, specification.name,Diagnostics.Invalid, "specified data memory size too small");
+				Basic.Error(diagnostics, specification.name,Streams.Invalid, "specified data memory size too small");
 				error := TRUE;
 			END;
 
@@ -900,7 +900,7 @@ TYPE
 			ELSE
 				msg := "could not link ";
 				Strings.Append(msg,linkRoot);
-				Basic.Error(diagnostics, "",Diagnostics.Invalid, msg);
+				Basic.Error(diagnostics, "",Streams.Invalid, msg);
 			END;
 			RETURN ~linker.error & ~error
 		END LinkInstance;
@@ -1019,11 +1019,11 @@ TYPE
 				NEW(irLinker, specification.diagnostics, backend, ""); (* TODO: pass an optional path as third parameter *)
 				IF ~irLinker.LoadModule(backend(IntermediateCode.IntermediateBackend).builtinsModuleName, TRUE) THEN
 					error := TRUE;
-					Basic.Error(diagnostics, backend(IntermediateCode.IntermediateBackend).builtinsModuleName,Diagnostics.Invalid, "could not load ir file");
+					Basic.Error(diagnostics, backend(IntermediateCode.IntermediateBackend).builtinsModuleName,Streams.Invalid, "could not load ir file");
 				END;
 				IF ~irLinker.LoadModule(specification.name,TRUE) THEN
 					error := TRUE;
-					Basic.Error(diagnostics, specification.name,Diagnostics.Invalid, "could not load ir file");
+					Basic.Error(diagnostics, specification.name,Streams.Invalid, "could not load ir file");
 				END;
 				backend := irLinker.backend;
 				system := backend.system;
@@ -1083,7 +1083,7 @@ TYPE
 				objectFileFormat.GetExtension(objectFileExtension);
 				irLinker.PrearrangeReachableDataSections;
 				IF ~irLinker.GenerateObjectFile(objectFileFormat, specification.log, instanceName) THEN
-					Basic.Error(diagnostics, specification.name,Diagnostics.Invalid, "could not generate object file");
+					Basic.Error(diagnostics, specification.name,Streams.Invalid, "could not generate object file");
 					RETURN FALSE
 				END;
 
@@ -1115,7 +1115,7 @@ TYPE
 				END;
 
 				IF (instructionMemorySize > 0) & (instructionMemorySize < code.SizeInBits() DIV system.codeUnit) THEN
-					Basic.Error(diagnostics, instanceName,Diagnostics.Invalid, "specified instruction memory size too small");
+					Basic.Error(diagnostics, instanceName,Streams.Invalid, "specified instruction memory size too small");
 					error := TRUE;
 				ELSIF instructionMemorySize = 0 THEN
 					instructionMemorySize := code.SizeInBits() DIV system.codeUnit;
@@ -1126,7 +1126,7 @@ TYPE
 				instance.SetDataMemorySize(dataMemorySize);
 
 				IF (dataMemorySize - data.SizeInBits() DIV system.dataUnit) < MinimalStackSize THEN
-					Basic.Error(diagnostics, specification.name,Diagnostics.Invalid, "specified data memory size too small");
+					Basic.Error(diagnostics, specification.name,Streams.Invalid, "specified data memory size too small");
 					error := TRUE;
 				END;
 
@@ -1154,7 +1154,7 @@ TYPE
 				ELSE
 					msg := "could not link ";
 					Strings.Append(msg,linkRoot);
-					Basic.Error(diagnostics, "",Diagnostics.Invalid, msg);
+					Basic.Error(diagnostics, "",Streams.Invalid, msg);
 				END;
 				RETURN ~linker.error & ~error
 			END LinkInstance;
@@ -1461,9 +1461,9 @@ TYPE
 				assemblinker.MarkReachabilityOfAll(TRUE);
 				FileNameToModuleName(filename, moduleName);
 				IF (targetFile = "") & assemblinker.GenerateObjectFile(objectFileFormat, context.out, moduleName) THEN
-					Basic.Information(diagnostics, filename, Diagnostics.Invalid, "done.")
+					Basic.Information(diagnostics, filename, Streams.Invalid, "done.")
 				ELSIF targetFile # "" THEN
-					Basic.Information(diagnostics, filename,  Diagnostics.Invalid, "loaded.")
+					Basic.Information(diagnostics, filename,  Streams.Invalid, "loaded.")
 				ELSE
 					error := TRUE
 				END
@@ -1477,7 +1477,7 @@ TYPE
 			assemblinker.PrearrangeReachableDataSections;
 			IF 	assemblinker.GenerateObjectFile(objectFileFormat, context.out, targetFile)
 			THEN
-				Basic.Information(diagnostics, targetFile, Diagnostics.Invalid, "generated.")
+				Basic.Information(diagnostics, targetFile, Streams.Invalid, "generated.")
 			ELSE error := FALSE
 			END;
 		END;

+ 2 - 2
source/FoxInterpreterBackend.Mod

@@ -1,6 +1,6 @@
 MODULE FoxInterpreterBackend; (** AUTHOR "fof"; PURPOSE "abstract code interpreter"; *)
 
-IMPORT Basic := FoxBasic, SYSTEM, Diagnostics, Intermediate := FoxIntermediateCode, Sections := FoxSections, SyntaxTree := FoxSyntaxTree, Options,
+IMPORT Basic := FoxBasic, SYSTEM, Intermediate := FoxIntermediateCode, Sections := FoxSections, SyntaxTree := FoxSyntaxTree, Options,
 	IntermediateBackend := FoxIntermediateBackend, Backend := FoxBackend, Global := FoxGlobal, Formats := FoxFormats,
 	Trace := KernelLog, Streams, SymbolFileFormat := FoxTextualSymbolFile;
 
@@ -269,7 +269,7 @@ TYPE
 		END Stop;
 
 		PROCEDURE Error (CONST msg: ARRAY OF CHAR);
-		BEGIN backend.Error ("", Basic.invalidPosition, Diagnostics.Invalid, msg); Stop;
+		BEGIN backend.Error ("", Basic.invalidPosition, Streams.Invalid, msg); Stop;
 		END Error;
 
 		PROCEDURE Execute (VAR instr: Intermediate.Instruction; VAR pc: PC);

+ 8 - 8
source/FoxParser.Mod

@@ -494,7 +494,7 @@ TYPE
 				access := SyntaxTree.Public + SyntaxTree.Protected + SyntaxTree.Internal;
 			ELSIF Optional( Scanner.Minus ) THEN
 				IF ~allowedReadOnly THEN
-					Error( symbol.position, Diagnostics.Invalid, "may not be defined read-only" )
+					Error( symbol.position, Basic.InvalidCode, "may not be defined read-only" )
 				ELSE
 					access :=  SyntaxTree.ReadOnly + {SyntaxTree.InternalWrite};
 				END;
@@ -1048,7 +1048,7 @@ TYPE
 					REPEAT
 						identifier := Identifier(position);
 						IF Optional(Scanner.Period) & Optional(Scanner.Identifier) THEN
-							Error(position,Diagnostics.Invalid,"forbidden qualified identifier in with statement");
+							Error(position,Basic.InvalidCode,"forbidden qualified identifier in with statement");
 						END;
 						withPart := SyntaxTree.NewWithPart();
 						withPart.SetPosition(symbol.position);
@@ -1123,7 +1123,7 @@ TYPE
 					CommentStatement(forStatement);
 					identifier := Identifier(position);
 					IF Optional(Scanner.Period) & Optional(Scanner.Identifier) THEN
-						Error(position,Diagnostics.Invalid,"forbidden non-local counter variable");
+						Error(position,Basic.InvalidCode,"forbidden non-local counter variable");
 					END;
 					designator := SyntaxTree.NewIdentifierDesignator(position,identifier);
 					forStatement.SetVariable( designator );
@@ -1400,7 +1400,7 @@ TYPE
 			*)
 
 			IF Optional( Scanner.Semicolon ) THEN
-				(*Warning(symbol.position,Diagnostics.Invalid,"no semicolon allowed here");*)
+				(*Warning(symbol.position,Basic.InvalidCode,"no semicolon allowed here");*)
 			END;
 
 			DeclarationSequence( recordScope);
@@ -1601,7 +1601,7 @@ TYPE
 				END;
 			END;
 			IF modifiers # NIL THEN
-				Error(modifiers.position, Diagnostics.Invalid, "forbidden modifiers");
+				Error(modifiers.position, Basic.InvalidCode, "forbidden modifiers");
 			END;
 			IF Trace THEN E( "ArrayType" ) END;
 			RETURN type
@@ -1649,7 +1649,7 @@ TYPE
 			ELSIF Optional(Scanner.Out) THEN
 				direction := SyntaxTree.OutPort
 			ELSE
-				Error(position,Diagnostics.Invalid,"invalid direction, expected IN or OUT");
+				Error(position,Basic.InvalidCode,"invalid direction, expected IN or OUT");
 			END;
 
 			IF Optional(Scanner.LeftParenthesis) THEN
@@ -1945,7 +1945,7 @@ TYPE
 			END;
 
 			IF Peek(Scanner.String) OR Peek(Scanner.Character)  THEN (* for compatibility with release *)
-				Error (position, Diagnostics.Invalid, "Invalid operator declaration: replace 'procedure' by 'operator' keyword!");
+				Error (position, Basic.InvalidCode, "Invalid operator declaration: replace 'procedure' by 'operator' keyword!");
 				OperatorDeclaration( parentScope );
 				RETURN
 			END;
@@ -2065,7 +2065,7 @@ TYPE
 			ELSIF parentScope IS SyntaxTree.RecordScope THEN
 				parentScope(SyntaxTree.RecordScope).AddOperator(operator);
 			ELSE
-				Error(position,Diagnostics.Invalid,"Operators only allowed in module or record scope"); (* nopov *)
+				Error(position,Basic.InvalidCode,"Operators only allowed in module or record scope"); (* nopov *)
 			END;
 			IF Trace THEN EE( "Operator", string^ ) END;
 		END OperatorDeclaration;

+ 1 - 1
source/FoxSemanticChecker.Mod

@@ -150,7 +150,7 @@ TYPE
 		BEGIN
 			ASSERT(currentScope # NIL);
 			IF module # NIL THEN errModule := module ELSE errModule := currentScope.ownerModule END;
-			Basic.ErrorC(diagnostics, errModule.sourceName, position, Diagnostics.Invalid, message);
+			Basic.ErrorC(diagnostics, errModule.sourceName, position, Basic.InvalidCode, message);
 			error := TRUE;
 		END Error;
 

+ 1 - 1
source/FoxTRMBackend.Mod

@@ -2365,7 +2365,7 @@ TYPE
 		 		PatchFixups(in(IntermediateCode.Section).resolved)
 		 	END;
 
-			IF cg.error THEN Error("", Basic.invalidPosition, Diagnostics.Invalid,  "") END;
+			IF cg.error THEN Error("", Basic.invalidPosition, Streams.Invalid,  "") END;
 		END GenerateBinary;
 
 		(* genasm *)

+ 7 - 7
source/FoxTRMTools.Mod

@@ -122,7 +122,7 @@ IMPORT Files,Commands,Options,Strings,Basic := FoxBasic, Diagnostics, BitSets,Ob
 		COPY(source, inputFileName);
 		inputFile := Files.Old(inputFileName);
 		IF inputFile= NIL THEN
-			diagnostics.Error(inputFileName,Diagnostics.Invalid,"could not open file");
+			diagnostics.Error(inputFileName,Streams.Invalid,"could not open file");
 			RETURN FALSE
 		END;
 		Files.OpenReader( reader,inputFile,0);
@@ -196,7 +196,7 @@ IMPORT Files,Commands,Options,Strings,Basic := FoxBasic, Diagnostics, BitSets,Ob
 		COPY(source, fileName);
 		oldFile := Files.Old(fileName);
 		IF oldFile = NIL THEN
-			diagnostics.Error(fileName,Diagnostics.Invalid,"could not open file");
+			diagnostics.Error(fileName,Streams.Invalid,"could not open file");
 			RETURN FALSE
 		END;
 		Files.OpenReader( reader,oldFile,0);
@@ -208,13 +208,13 @@ IMPORT Files,Commands,Options,Strings,Basic := FoxBasic, Diagnostics, BitSets,Ob
 			GetFileName(i,fileName);
 			newFiles[i] := Files.New(fileName);
 			IF newFiles[i]= NIL THEN
-				diagnostics.Error(fileName,Diagnostics.Invalid,"could not open file");
+				diagnostics.Error(fileName,Streams.Invalid,"could not open file");
 				RETURN FALSE
 			ELSE
 				Files.OpenWriter(writers[i],newFiles[i],0);
 			END;
 			IF verbose THEN
-				diagnostics.Information(fileName,Diagnostics.Invalid,"file generated");
+				diagnostics.Information(fileName,Streams.Invalid,"file generated");
 			END;
 		END;
 		(*If strided: read line by line, fill round robin into the output files*)
@@ -237,7 +237,7 @@ IMPORT Files,Commands,Options,Strings,Basic := FoxBasic, Diagnostics, BitSets,Ob
 			INC(line);
 		END;
 		IF reader.Available()>0 THEN
-			diagnostics.Warning(source,Diagnostics.Invalid,"source file truncated");
+			diagnostics.Warning(source,Streams.Invalid,"source file truncated");
 		END;
 		FOR i := 0 TO blocks-1 DO
 			writers[i].Update; Files.Register(newFiles[i])
@@ -296,11 +296,11 @@ IMPORT Files,Commands,Options,Strings,Basic := FoxBasic, Diagnostics, BitSets,Ob
 		IF ~options.GetString("target",targetName) THEN targetName:="default.mem" END;
 		NEW(diagnostics,context.out);
 		
-		diagnostics.Information("target name", Diagnostics.Invalid, targetName);
+		diagnostics.Information("target name", Streams.Invalid, targetName);
 		done:=TRUE;
 		WHILE done & context.arg.GetString (name) DO
 		
-			diagnostics.Information("source name", Diagnostics.Invalid, name);
+			diagnostics.Information("source name", Streams.Invalid, name);
 			done := SplitColumns(name,  targetName, insW, numB, baseD, diagnostics);
 		END;
 	END SplitColumnsCmd;

+ 2 - 2
source/GenericLinker.Mod

@@ -173,11 +173,11 @@ VAR
 	END SetLinkRoot;
 
 	PROCEDURE Error* (CONST source, message: ARRAY OF CHAR);
-	BEGIN diagnostics.Error (source, Diagnostics.Invalid, message); error := TRUE;
+	BEGIN diagnostics.Error (source, Streams.Invalid, message); error := TRUE;
 	END Error;
 
 	PROCEDURE Warning* (CONST source, message: ARRAY OF CHAR);
-	BEGIN diagnostics.Warning (source, Diagnostics.Invalid, message);
+	BEGIN diagnostics.Warning (source, Streams.Invalid, message);
 	END Warning;
 
 	PROCEDURE ErrorP*(CONST pooledName: ObjectFile.SegmentedName; CONST message: ARRAY OF CHAR);

+ 2 - 2
source/InterpreterShell.Mod

@@ -816,7 +816,7 @@ TYPE
 				NEW(scope, Interpreter.global, container);
 				NEW(interpreter, scope, diagnostics, context);
 				LOOP
-				(*diagnostics.Information("interpreter",Diagnostics.Invalid,"start statement");*)
+				(*diagnostics.Information("interpreter",Streams.Invalid,"start statement");*)
 				seq := SyntaxTree.NewStatementSequence();
 				IF parser.Optional(Scanner.Questionmark) THEN
 					first := TRUE;
@@ -846,7 +846,7 @@ TYPE
 					IF interpreter.error THEN interpreter.Reset END;
 				ELSE
 					IF ~parser.error & first THEN 
-						diagnostics.Error("",Diagnostics.Invalid, "no statement");
+						diagnostics.Error("",Streams.Invalid, "no statement");
 						first := FALSE;
 						context.out.Ln;
 						context.out.String(">");

+ 2 - 2
source/ModuleParser.Mod

@@ -5,7 +5,7 @@ MODULE ModuleParser;	(** AUTHOR "mb"; PURPOSE "Active Oberon parser for use with
  *)
 
 IMPORT
-	Strings, Files, Diagnostics, FoxScanner, KernelLog, Texts, TextUtilities;
+	Strings, Files, Streams, Diagnostics, FoxScanner, KernelLog, Texts, TextUtilities;
 
 CONST
 	(* visibilities *)
@@ -1599,7 +1599,7 @@ BEGIN
 		scanner := FoxScanner.NewScanner(filename, reader, 0, diagnostics);
 		Parse(scanner, module);
 	ELSIF (diagnostics # NIL) THEN
-		diagnostics.Error("ModuleParser", Diagnostics.Invalid, "File not found");
+		diagnostics.Error("ModuleParser", Streams.Invalid, "File not found");
 	END;
 	RETURN module
 END ParseFile;

+ 2 - 2
source/PCAAMD64.Mod

@@ -1930,7 +1930,7 @@ BEGIN
 	TextUtilities.LoadAuto (text, fileName, format, res);
 
 	IF res # 0 THEN
-		diagnostics.Error (fileName, Diagnostics.Invalid, "failed to open file"); RETURN;
+		diagnostics.Error (fileName, Streams.Invalid, "failed to open file"); RETURN;
 	END;
 
 	NEW (assembly, diagnostics, NIL);
@@ -1991,7 +1991,7 @@ BEGIN
 		writer.Update;
 		Files.Register(file);
 	ELSE
-		diagnostics.Error(filename, Diagnostics.Invalid, "Could not create output file");
+		diagnostics.Error(filename, Streams.Invalid, "Could not create output file");
 		error := TRUE;
 	END;
 END WriteBinary;

+ 2 - 2
source/PCARMRegisters.Mod

@@ -1,6 +1,6 @@
 MODULE PCARMRegisters;	(** be  **)
 
-IMPORT PCM, PCOARM, KernelLog, Diagnostics;
+IMPORT PCM, PCOARM, KernelLog;
 
 CONST
 	INTERNALERROR = 100;
@@ -307,7 +307,7 @@ TYPE
 				WHILE (r # lru.prevLRU) & (r.free > 0) DO r := r.nextLRU END;
 				IF (r.free = 0) THEN reg := r.id
 				ELSE (* not enough registers *)
-					PCM.Error(215, Diagnostics.Invalid, "Not enough registers.");
+					PCM.Error(215, PCM.InvalidPosition, "Not enough registers.");
 					HALT(MAX(INTEGER));
 					HALT(INTERNALERROR)
 				END;

+ 5 - 2
source/PCM.Mod

@@ -89,6 +89,9 @@ IMPORT
 		MaxErrors = 100;	(* maximum number of diagnostic messages *)
 		MaxWarnings = 100;
 
+		InvalidCode* = -1;
+		InvalidPosition* = Streams.Invalid;
+
 	TYPE
 		SymReader* = Files.Reader;
 
@@ -358,7 +361,7 @@ IMPORT
 			IF errors > MaxErrors THEN
 				RETURN
 			ELSIF errors = MaxErrors THEN
-				err := Diagnostics.Invalid; pos := Diagnostics.Invalid; str := "too many errors"
+				err := InvalidCode; pos := InvalidPosition; str := "too many errors"
 			END;
 			IF diagnostics # NIL THEN
 				diagnostics.Error (source, pos, str);
@@ -385,7 +388,7 @@ IMPORT
 		IF warnings > MaxWarnings THEN
 			RETURN
 		ELSIF warnings = MaxWarnings THEN
-			err := Diagnostics.Invalid; pos := Diagnostics.Invalid; str := "too many warnings"
+			err := InvalidCode; pos := InvalidPosition; str := "too many warnings"
 		ELSE
 			GetMessage (err, msg, str);
 		END;

+ 3 - 3
source/PCO.Mod

@@ -6,7 +6,7 @@ MODULE PCO; (** AUTHOR "prk / be"; PURPOSE "Parallel Compiler: Intel 386 code pa
 	Based on the OPO module for OP2 by N. Mannhart
 *)
 
-	IMPORT SYSTEM, PCM, PCLIR, Diagnostics;
+	IMPORT SYSTEM, PCM, PCLIR;
 
 
 	CONST
@@ -128,7 +128,7 @@ MODULE PCO; (** AUTHOR "prk / be"; PURPOSE "Parallel Compiler: Intel 386 code pa
                		code := c;
                		code[pos] := CHR(b); (*fof*)
            		ELSE
-               		IF ~CodeErr THEN  PCM.Error(210, Diagnostics.Invalid, ""); CodeErr:= TRUE  END;
+               		IF ~CodeErr THEN  PCM.Error(210, PCM.InvalidPosition, ""); CodeErr:= TRUE  END;
                		pc:= 0
            		END
        	ELSE
@@ -165,7 +165,7 @@ MODULE PCO; (** AUTHOR "prk / be"; PURPOSE "Parallel Compiler: Intel 386 code pa
                		code[pos]:= CHR (dw DIV 1000000H)
               		 (*fof<<*)
            		ELSE
-              		 IF ~CodeErr THEN  PCM.Error(210, Diagnostics.Invalid, ""); CodeErr:= TRUE  END;
+              		 IF ~CodeErr THEN  PCM.Error(210, PCM.InvalidPosition, ""); CodeErr:= TRUE  END;
                		pc:= 0
            		END
        	ELSE

+ 2 - 2
source/PCOARM.Mod

@@ -4,7 +4,7 @@ MODULE PCOARM;	(** be  **)
 
 (** Code Generator for ARM. Not concurrent ! *)
 
-IMPORT SYSTEM, Files, PCLIR, PCM(*Trace, PCARMDecoder *), Diagnostics;
+IMPORT SYSTEM, Files, PCLIR, PCM(*Trace, PCARMDecoder *);
 
 CONST
 	(*Trace = FALSE; *)
@@ -697,7 +697,7 @@ PROCEDURE Close*;
 VAR b: POINTER TO ARRAY OF CHAR;
 BEGIN
 	IF (codelen > MaxCodeLength) THEN (* code too long *)
-		PCM.Error(244, Diagnostics.Invalid, "Code too long.");
+		PCM.Error(244, PCM.InvalidPosition, "Code too long.");
 	ELSIF (codelen-start > 0) THEN
 		NEW(b, codelen-start);
 		SYSTEM.MOVE(ADDRESSOF(code[start]), ADDRESSOF(b[0]), codelen-start);

+ 3 - 3
source/PCOF.Mod

@@ -4,7 +4,7 @@ MODULE PCOF; (** AUTHOR "prk / be"; PURPOSE "Parallel Compiler: object file plug
 
 IMPORT
 	SYSTEM, KernelLog,
-	StringPool, PCDebug, PCBT, PCLIR, PCM, PCT, PCOM, Diagnostics;
+	StringPool, PCDebug, PCBT, PCLIR, PCM, PCT, PCOM;
 
 CONST
 	AddressSize = SIZEOF(ADDRESS);
@@ -900,7 +900,7 @@ VAR commands: ARRAY 128 OF PCT.Proc;
 
 			END;
 			FOR i := 0 TO exppos-1 DO
-				IF fp = explist[i] THEN  PCM.ErrorN(280, Diagnostics.Invalid, p.name) END
+				IF fp = explist[i] THEN  PCM.ErrorN(280, PCM.InvalidPosition, p.name) END
 			END;
 			IF exppos >= explen THEN
 				NEW(explist2, 2*explen);
@@ -1296,4 +1296,4 @@ END PCOF.
 	25.03.01	prk	limited HUGEINT implementation (as abstract type)
 	14.03.01	prk	OutRefs, don't list ARRAYs of user defined types
 	14.03.01	prk	OutRefs, don't list inlined procedures
-*)
+*)

+ 3 - 3
source/PCOFPE.Mod

@@ -3,7 +3,7 @@
 (* Paco, Copyright 2000 - 2002, Patrik Reali, ETH Zurich *)
 
 MODULE PCOFPE; (** AUTHOR "ejz"; PURPOSE "Parallel Compiler: PE object file plug-in"; *)
-	IMPORT SYSTEM, KernelLog, StringPool, PCDebug, PCBT, PCLIR, PCM, PCT, PCOM, Dates, Strings, Streams, Files, Clock, Diagnostics;
+	IMPORT SYSTEM, KernelLog, StringPool, PCDebug, PCBT, PCLIR, PCM, PCT, PCOM, Dates, Strings, Streams, Files, Clock;
 
 	CONST
 		Loader = "AosRuntime"; Heap = "AosRuntime"; Active = "Objects";
@@ -671,7 +671,7 @@ ASSERT(code.data[offset-1] # 0E8X);
 				StringPool.GetString(p.name, name);
 				fp := p.sym(PCOM.Symbol).fp;
 				FOR i := 0 TO exppos-1 DO
-					IF fp = explist[i] THEN PCM.ErrorN(280, Diagnostics.Invalid, p.name) END
+					IF fp = explist[i] THEN PCM.ErrorN(280, PCM.InvalidPosition, p.name) END
 				END;
 				IF exppos >= explen THEN
 					NEW(explist2, 2*explen);
@@ -1009,7 +1009,7 @@ ASSERT(code.data[offset-1] # 0E8X);
 				i := W.Pos();
 				PtrAdr(W, 0, rec, FALSE);
 				nofptrs := (W.Pos() - i) DIV 4;
-				IF nofptrs > MAX(INTEGER) THEN PCM.Error(221, Diagnostics.Invalid, "") END;
+				IF nofptrs > MAX(INTEGER) THEN PCM.Error(221, PCM.InvalidPosition, "") END;
 				IF nofptrs # 0 THEN
 					i := W.Pos(); W.SetPos(pos);
 					W.RawInt(SHORT(nofptrs));

+ 10 - 10
source/PCOM.Mod

@@ -60,7 +60,7 @@ MODULE PCOM; (** AUTHOR "prk"; PURPOSE "Parallel Compiler: symbol file plug-in";
 
 
 IMPORT
-		SYSTEM, Modules, StringPool, PCM, PCS, PCT, PCBT, PCLIR, Diagnostics;
+		SYSTEM, Modules, StringPool, PCM, PCS, PCT, PCBT, PCLIR;
 
 CONST
 		Trace = FALSE;
@@ -658,11 +658,11 @@ PROCEDURE Export*(VAR r: PCM.Rider; M: PCT.Module; new, extend, skipImport: BOOL
 			IF ~(PCT.Operator IN new.flags) THEN
 				IF  (old.sym(Symbol).fp # newsym.fp) OR
 					((new IS PCT.Type) OR (new.type IS PCT.Record) & (new.type.owner = NIL)) & TypeChanged(new.type, old.type) THEN
-					changed:=TRUE; PCM.ErrorN(402, Diagnostics.Invalid, new.name)
+					changed:=TRUE; PCM.ErrorN(402, PCM.InvalidPosition, new.name)
 				END
 			END
 		ELSIF new.vis # PCT.Internal THEN	(*new export*)
-			extended:=TRUE; PCM.ErrorN(403, Diagnostics.Invalid, new.name)
+			extended:=TRUE; PCM.ErrorN(403, PCM.InvalidPosition, new.name)
 		END
 	END CompareSymbol;
 
@@ -1076,9 +1076,9 @@ BEGIN
 	PCM.CloseSym(r);		(*commit file*)
 	IF changed OR extended  THEN
 		IF changed THEN
-			IF newsym OR new THEN COPY("  new symbol file", msg) ELSE PCM.Error(155, Diagnostics.Invalid, "") END
+			IF newsym OR new THEN COPY("  new symbol file", msg) ELSE PCM.Error(155, PCM.InvalidPosition, "") END
 		ELSIF extended THEN
-			IF extend OR new THEN COPY("  extended symbol file", msg) ELSE PCM.Error(155, Diagnostics.Invalid, "") END
+			IF extend OR new THEN COPY("  extended symbol file", msg) ELSE PCM.Error(155, PCM.InvalidPosition, "") END
 		END
 	END
 END Export;
@@ -1274,9 +1274,9 @@ PROCEDURE Import*(self: PCT.Module; VAR M: PCT.Module; modname: StringPool.Index
 			END;
 
 			IF  old=NIL  THEN
-				PCM.ErrorN(401, Diagnostics.Invalid, obj.name);  MAttr.changed:=TRUE
+				PCM.ErrorN(401, PCM.InvalidPosition, obj.name);  MAttr.changed:=TRUE
 			ELSIF  old.vis#obj.vis  THEN
-				PCM.ErrorN(401, Diagnostics.Invalid, obj.name);  MAttr.changed:=TRUE
+				PCM.ErrorN(401, PCM.InvalidPosition, obj.name);  MAttr.changed:=TRUE
 			ELSE
 				ASSERT(old.sym=NIL);
 				NEW(OAttr);  old.sym:=OAttr;  OAttr.sibling:=obj
@@ -1427,7 +1427,7 @@ PROCEDURE Import*(self: PCT.Module; VAR M: PCT.Module; modname: StringPool.Index
 						R.RawNum(tag)
 					END;
 
-					PCT.ChangeState(mscope, PCT.structdeclared, Diagnostics.Invalid);
+					PCT.ChangeState(mscope, PCT.structdeclared, PCM.InvalidPosition);
 				END
 			END;
 			IF ~selfimport THEN PCT.AddRecord(M.scope, rec) END;
@@ -1692,7 +1692,7 @@ BEGIN
 	IF (ver = PCM.FileVersion) OR (ver=PCM.FileVersionOC) THEN
 		R.RawSet(flags);
 	ELSE
-		PCM.Error(151, Diagnostics.Invalid, ""); M := NIL; RETURN
+		PCM.Error(151, PCM.InvalidPosition, ""); M := NIL; RETURN
 	END;
 
 	GetImports;
@@ -1909,4 +1909,4 @@ END PCOM.
 	25.03.01	prk	limited HUGEINT implementation (as abstract type)
 	22.02.01	prk	self reference for methods: use pointer-based self if possible (i.e. if object is dynamic and method
 								definitions in super-class is not record-based).
-*)
+*)

+ 3 - 3
source/PCP.Mod

@@ -3,7 +3,7 @@
 MODULE PCP; (** AUTHOR "prk"; PURPOSE "Parallel Compiler: parser"; *)
 
 IMPORT
-	Machine, Diagnostics, Modules, Objects, Kernel, Strings,
+	Machine, Modules, Objects, Kernel, Strings,
 	StringPool,
 	PCM, PCS, PCT, PCB, PCC, SYSTEM, PCArrays;
 
@@ -391,7 +391,7 @@ TYPE
 					Error(148, pos);	(* first parameter of ":=" must be VAR *)
 				END;
 				IF (scope.firstPar.nextPar # NIL) & (scope.firstPar.type = scope.firstPar.nextPar.type) THEN
-					PCM.Warning(Diagnostics.Invalid, pos, "Warning: both parameters of identical type");
+					PCM.Warning(PCM.InvalidCode, pos, "Warning: both parameters of identical type");
 				END
 			ELSIF opStr = "[]" THEN
 				IF (scope = NIL) OR (scope.parent = NIL) OR ~(scope.parent IS PCT.RecScope) THEN
@@ -2921,4 +2921,4 @@ END PCP.
 	08.05.01	prk	PCT interface cleanup. Use InitX instead of New*, allows type extension
 	26.04.01	prk	separation of RECORD and OBJECT in the parser
 	29.03.01	prk	Java imports
-*)
+*)

+ 3 - 3
source/PCT.Mod

@@ -3,7 +3,7 @@
 MODULE PCT; (** AUTHOR "prk"; PURPOSE "Parallel Compiler: symbol table"; *)
 
 IMPORT
-	SYSTEM, KernelLog, StringPool, Strings, PCM, PCS,Diagnostics;
+	SYSTEM, KernelLog, StringPool, Strings, PCM, PCS;
 
 CONST
 	MaxPlugins = 4;
@@ -2218,7 +2218,7 @@ VAR
 				IF (p.super.vis * Public # {}) & (vis*Public = {}) THEN
 					vis := vis + p.super.vis;
 					(*
-					PCM.Warning(Diagnostics.Invalid,pos,"auto-export of overwritten exported method");
+					PCM.Warning(Streams.Invalid,pos,"auto-export of overwritten exported method");
 					*)
 				END;
 			END;
@@ -2672,4 +2672,4 @@ Special errors:
 	22.02.01	prk	self reference for methods: use pointer-based self if possible (i.e. if object is dynamic and method
 								definitions in super-class is not record-based).
 	22.02.01	prk	delegates
-*)
+*)

+ 1 - 1
source/PET.Mod

@@ -774,7 +774,7 @@ TYPE
 			IF (diagnostics.nofEntries > 0) THEN
 				errorGrid.GetFirstPosition(positions, type);
 				IF (type = WMDiagnostics.TypeError) OR findPC & (type=WMDiagnostics.TypeInformation) THEN
-					IF (focus = EditorFocus) & (positions[0] # WMDiagnostics.Invalid) THEN
+					IF (focus = EditorFocus) & (positions[0] # Streams.Invalid) THEN
 						editor.tv.cursor.SetPosition(positions[0]);
 						editor.SetFocus;
 					ELSIF (focus = SplitEditorFocus) THEN

+ 7 - 7
source/Release.Mod

@@ -916,7 +916,7 @@ TYPE
 					END;
 				END;
 			ELSE
-				diagnostics.Error("", Diagnostics.Invalid, "No packages");
+				diagnostics.Error("", Streams.Invalid, "No packages");
 			END;
 		END GenerateZipFiles;
 
@@ -1483,7 +1483,7 @@ TYPE
 					INC(nofPrefixes);
 				ELSE
 					error := TRUE;
-					diagnostics.Warning("", Diagnostics.Invalid, "Maximum number of prefixes exceeded");
+					diagnostics.Warning("", Streams.Invalid, "Maximum number of prefixes exceeded");
 					FOR j := 0 TO LEN(prefixes)-1 DO
 						TRACE(prefixes[j]);
 					END;
@@ -1670,7 +1670,7 @@ TYPE
 				INC(nofBuilds);
 			ELSE
 				error := TRUE;
-				diagnostics.Error(source, Diagnostics.Invalid, "Maximum number of builds exceeded");
+				diagnostics.Error(source, Streams.Invalid, "Maximum number of builds exceeded");
 			END;
 			RETURN ~error;
 		END AddBuild;
@@ -1754,7 +1754,7 @@ TYPE
 								MakeMessage(message, "Excluded package '#' in build '#' does not exist",
 									builds[build].excludedPackages[package]^,
 									builds[build].name);
-								diagnostics.Error(source, Diagnostics.Invalid, message);
+								diagnostics.Error(source, Streams.Invalid, message);
 							END;
 						END;
 					END;
@@ -2007,7 +2007,7 @@ TYPE
 				ELSE
 					VersionToString(VersionMajor, VersionMinor, v1);
 					VersionToString(builds.version.major, builds.version.minor, v2);
-					Error(Diagnostics.Invalid, "Version mismatch, Release.Mod is version #, tool file is version #", v1, v2);
+					Error(Streams.Invalid, "Version mismatch, Release.Mod is version #, tool file is version #", v1, v2);
 				END;
 			END;
 			RETURN ~(error OR scanner.error OR (builds = NIL));
@@ -2550,7 +2550,7 @@ PROCEDURE GetModuleInfo(
 					ELSE
 						error := TRUE;
 						MakeMessage(message, "Maximum number of supported imports exceeded in module #", filename, "");
-						diagnostics.Error(source, Diagnostics.Invalid, message);
+						diagnostics.Error(source, Streams.Invalid, message);
 						EXIT;
 					END;
 
@@ -2752,7 +2752,7 @@ BEGIN
 	ELSE
 		builds := NIL;
 		MakeMessage(message, "Could not open file #", filename, "");
-		diagnostics.Error("", Diagnostics.Invalid, message);
+		diagnostics.Error("", Streams.Invalid, message);
 		RETURN FALSE;
 	END;
 END ParseBuildFile;

+ 2 - 0
source/Streams.Mod

@@ -16,6 +16,8 @@ CONST
 	DefaultWriterSize* = 4096;
 	DefaultReaderSize* = 4096;
 
+	Invalid* = -1;  (** invalid stream position *)
+
 CONST
 	CR = 0DX;  LF = 0AX;  TAB = 9X;  SP = 20X;
 

+ 1 - 1
source/SyntaxHighlighter.Mod

@@ -1931,7 +1931,7 @@ BEGIN
 		END;
 	ELSE
 		e := TRUE;
-		d.Error(filename, Diagnostics.Invalid, "File not found");
+		d.Error(filename, Streams.Invalid, "File not found");
 	END;
 	diagnostics := NIL; source := "";
 	ASSERT(error OR (document # NIL));

+ 1 - 1
source/TFPET.Mod

@@ -766,7 +766,7 @@ TYPE
 			diagnostics.EnableNotification;
 			IF (diagnostics.nofEntries > 0) THEN
 				errorGrid.GetFirstPosition(positions, type);
-				IF (focus = EditorFocus) & (positions[0] # WMDiagnostics.Invalid) THEN
+				IF (focus = EditorFocus) & (positions[0] # Streams.Invalid) THEN
 					editor.tv.cursor.SetPosition(positions[0]);
 					editor.SetFocus;
 				ELSIF (focus = SplitEditorFocus) THEN

+ 1 - 1
source/TestSuite.Mod

@@ -62,7 +62,7 @@ TYPE
 				diagnostics.Error (name, r.Pos(), "parse error"); RETURN FALSE;
 			END;
 			IF FindResult (tests, name) # NIL THEN
-				diagnostics.Error (name, Diagnostics.Invalid, "duplicated test"); RETURN FALSE;
+				diagnostics.Error (name, Streams.Invalid, "duplicated test"); RETURN FALSE;
 			END;
 			code.Clear; writer.Reset;
 			WHILE SkipLn (r) & Tabulator (r) & ReadText (r, line) DO writer.Char (09X); writer.String (line); writer.Char (0AX); END;

+ 3 - 3
source/TextConverter.Mod

@@ -13,12 +13,12 @@ BEGIN
 		IF res = 0 THEN
 			converter (text, filename, res);
 			IF res = 0 THEN
-				diagnostics.Information (filename, Diagnostics.Invalid, "successfully converted");
+				diagnostics.Information (filename, Streams.Invalid, "successfully converted");
 			ELSE
-				diagnostics.Information (filename, Diagnostics.Invalid, "failed to store");
+				diagnostics.Information (filename, Streams.Invalid, "failed to store");
 			END
 		ELSE
-			diagnostics.Error (filename, Diagnostics.Invalid, "failed to load");
+			diagnostics.Error (filename, Streams.Invalid, "failed to load");
 		END;
 	END;
 END Convert;

+ 3 - 5
source/WMDiagnostics.Mod

@@ -10,8 +10,6 @@ CONST
 	TypeWarning* = Diagnostics.TypeWarning;
 	TypeError* = Diagnostics.TypeError;
 
-	Invalid* = Diagnostics.Invalid;
-
 	(* Error grid colors *)
 	ColorError = LONGINT(0FF3030A0H);
 	ColorWarning = LONGINT(0D0D040C0H);
@@ -433,7 +431,7 @@ TYPE
 						picture := "";
 					END;
 
-					IF (entries[i].position # Invalid) & (textViews # NIL) THEN
+					IF (entries[i].position # Streams.Invalid) & (textViews # NIL) THEN
 						NEW(entries[i].pos, LEN(textViews));
 						FOR j := 0 TO LEN(textViews) - 1 DO
 							entries[i].pos[j] := textViews[j].CreatePositionMarker();
@@ -471,12 +469,12 @@ TYPE
 					IF (entries[0].pos # NIL) & (entries[0].pos[i] # NIL) THEN
 						positions[i] := entries[0].pos[i].GetPosition();
 					ELSE
-						positions[i] := Invalid;
+						positions[i] := Streams.Invalid;
 					END;
 					type := entries[0].type;
 				END;
 			ELSE
-				FOR i := 0 TO LEN(positions)-1 DO positions[i] := Invalid; END;
+				FOR i := 0 TO LEN(positions)-1 DO positions[i] := Streams.Invalid; END;
 			END;
 			Release;
 		END GetFirstPosition;

+ 1 - 1
tools/builds/a2/DependencyWalker.Mod

@@ -7,7 +7,7 @@ VAR reader: Streams.Reader; scanner: FoxScanner.Scanner; parser: FoxParser.Parse
 VAR module: FoxSyntaxTree.Module; import: FoxSyntaxTree.Import; string: ARRAY 64 OF CHAR;
 BEGIN
 	reader := FoxBasic.GetFileReader (moduleName);
-	IF reader = NIL THEN diagnostics.Error (moduleName, Diagnostics.Invalid, "Failed to open module"); RETURN FALSE END;
+	IF reader = NIL THEN diagnostics.Error (moduleName, Streams.Invalid, "Failed to open module"); RETURN FALSE END;
 	scanner := FoxScanner.NewScanner (moduleName, reader, 0, diagnostics);
 	NEW (parser, scanner, diagnostics);
 	module := parser.Module ();