2
0
Эх сурвалжийг харах

removed unused symbols,
slightly improved some visitors

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

felixf 7 жил өмнө
parent
commit
1b22680b94

+ 1 - 1
source/BitSets.Mod

@@ -76,7 +76,7 @@ TYPE BitSet* = OBJECT
 	END SetBits;
 	END SetBits;
 	
 	
 	PROCEDURE SetBytes*(startPos: SIZE; bytes: LONGINT; CONST values: ARRAY OF CHAR);
 	PROCEDURE SetBytes*(startPos: SIZE; bytes: LONGINT; CONST values: ARRAY OF CHAR);
-	VAR adr: ADDRESS; i: SIZE;
+	VAR adr: ADDRESS;
 	BEGIN
 	BEGIN
 		ASSERT (startPos >= 0); ASSERT (startPos+8*bytes <= size); ASSERT(startPos MOD 8 = 0);
 		ASSERT (startPos >= 0); ASSERT (startPos+8*bytes <= size); ASSERT(startPos MOD 8 = 0);
 		adr := ADDRESS OF data[0] + startPos DIV 8;
 		adr := ADDRESS OF data[0] + startPos DIV 8;

+ 1 - 1
source/Compiler.Mod

@@ -102,7 +102,7 @@ TYPE
 		backendName: ARRAY 32 OF CHAR;
 		backendName: ARRAY 32 OF CHAR;
 
 
 		PROCEDURE FinalMessage(error: BOOLEAN; CONST msg: ARRAY OF CHAR);
 		PROCEDURE FinalMessage(error: BOOLEAN; CONST msg: ARRAY OF CHAR);
-		VAR message,name: ARRAY 256 OF CHAR;
+		VAR message: ARRAY 256 OF CHAR;
 		BEGIN
 		BEGIN
 			message := "";
 			message := "";
 			IF module # NIL THEN
 			IF module # NIL THEN

+ 3 - 2
source/FoxAMD64InstructionSet.Mod

@@ -57,13 +57,14 @@ CONST
 	cpuWillamette* = 8;
 	cpuWillamette* = 8;
 	cpuPrescott* = 9;
 	cpuPrescott* = 9;
 	cpuAMD64* = 10;
 	cpuAMD64* = 10;
-	(* unused options *)
+	(* unused options
 	cpuSW = 11;
 	cpuSW = 11;
 	cpuSB = 11;
 	cpuSB = 11;
 	cpuSMM = 11;
 	cpuSMM = 11;
 	cpuAR1 = 11;
 	cpuAR1 = 11;
 	cpuAR2 = 11;
 	cpuAR2 = 11;
 	cpuND = 11;
 	cpuND = 11;
+	*)
 
 
 	(** options selectable with CODE {SYSTEM.....} **)
 	(** options selectable with CODE {SYSTEM.....} **)
 	cpuPrivileged* = 20;
 	cpuPrivileged* = 20;
@@ -1896,7 +1897,7 @@ VAR
 		END EncodeV;
 		END EncodeV;
 		
 		
 		PROCEDURE AddInstructionV(mnemonic: LONGINT; CONST operands, code: ARRAY OF CHAR);
 		PROCEDURE AddInstructionV(mnemonic: LONGINT; CONST operands, code: ARRAY OF CHAR);
-		VAR i, at: LONGINT; name,operand: ARRAY 32 OF CHAR;
+		VAR i, at: LONGINT; name: ARRAY 32 OF CHAR;
 		BEGIN
 		BEGIN
 			i := 0; at := 0;
 			i := 0; at := 0;
 			WHILE (i<maxNumberOperands) DO
 			WHILE (i<maxNumberOperands) DO

+ 1 - 2
source/FoxBinaryCode.Mod

@@ -1,6 +1,6 @@
 MODULE FoxBinaryCode; (** AUTHOR ""; PURPOSE ""; *)
 MODULE FoxBinaryCode; (** AUTHOR ""; PURPOSE ""; *)
 
 
-IMPORT Basic := FoxBasic, Sections := FoxSections, SYSTEM, Streams, ObjectFile, BitSets, D := Debugging;
+IMPORT Basic := FoxBasic, Sections := FoxSections, Streams, ObjectFile, BitSets;
 
 
 CONST
 CONST
 	Absolute*=ObjectFile.Absolute;
 	Absolute*=ObjectFile.Absolute;
@@ -27,7 +27,6 @@ TYPE
 		END InitAlias;
 		END InitAlias;
 
 
 		PROCEDURE Dump*(w: Streams.Writer);
 		PROCEDURE Dump*(w: Streams.Writer);
-		VAR i: LONGINT;
 		BEGIN
 		BEGIN
 			Basic.WriteSegmentedName(w, identifier.name);
 			Basic.WriteSegmentedName(w, identifier.name);
 			IF identifier.fingerprint # 0 THEN w.String("["); w.Hex(identifier.fingerprint,-8); w.String("]") END;
 			IF identifier.fingerprint # 0 THEN w.String("["); w.Hex(identifier.fingerprint,-8); w.String("]") END;

+ 2 - 3
source/FoxCSharpScanner.Mod

@@ -1,8 +1,7 @@
 MODULE FoxCSharpScanner;
 MODULE FoxCSharpScanner;
 
 
 IMPORT Streams, Strings, Diagnostics, Commands, StringPool, 
 IMPORT Streams, Strings, Diagnostics, Commands, StringPool, 
-    D := Debugging, Basic := FoxBasic, FoxScanner,
-    KernelLog (* DEBUG *);
+    D := Debugging, Basic := FoxBasic, FoxScanner;
 
 
 CONST
 CONST
     Trace = FALSE;
     Trace = FALSE;
@@ -1059,7 +1058,7 @@ KernelLog.Ln();
             (diagnostics = NIL ==> no report) and reset the error state
             (diagnostics = NIL ==> no report) and reset the error state
             intended for silent symbol peeeking after the end of a module *)
             intended for silent symbol peeeking after the end of a module *)
         PROCEDURE ResetErrorDiagnostics*(VAR diagnostics: Diagnostics.Diagnostics);
         PROCEDURE ResetErrorDiagnostics*(VAR diagnostics: Diagnostics.Diagnostics);
-            VAR b: BOOLEAN; 
+        VAR 
                 d: Diagnostics.Diagnostics;
                 d: Diagnostics.Diagnostics;
         BEGIN
         BEGIN
             error := FALSE;
             error := FALSE;

+ 2 - 3
source/FoxFingerPrinter.Mod

@@ -171,7 +171,6 @@ TYPE
 		END SetTypeFingerprint;
 		END SetTypeFingerprint;
 
 
 		PROCEDURE VisitRangeType*(x: SyntaxTree.RangeType);
 		PROCEDURE VisitRangeType*(x: SyntaxTree.RangeType);
-		VAR fingerprint: FingerPrint;
 		BEGIN
 		BEGIN
 			SetTypeFingerprint(x,fpTypeRange);
 			SetTypeFingerprint(x,fpTypeRange);
 		END VisitRangeType;
 		END VisitRangeType;
@@ -483,7 +482,7 @@ TYPE
 		PrivateFP(PointerType)     = 0.
 		PrivateFP(PointerType)     = 0.
 		*)
 		*)
 		PROCEDURE VisitPointerType*(x: SyntaxTree.PointerType);
 		PROCEDURE VisitPointerType*(x: SyntaxTree.PointerType);
-		VAR fingerprint,typeFP: FingerPrint; fp: LONGINT; deep: BOOLEAN;
+		VAR fp: LONGINT; deep: BOOLEAN;
 		BEGIN
 		BEGIN
 			IF Trace THEN TraceEnter("PointerType");  END;
 			IF Trace THEN TraceEnter("PointerType");  END;
 			fingerprint := x.fingerprint;
 			fingerprint := x.fingerprint;
@@ -592,7 +591,7 @@ TYPE
 		END FPrintMethod;
 		END FPrintMethod;
 
 
 		PROCEDURE VisitCellType*(x: SyntaxTree.CellType);
 		PROCEDURE VisitCellType*(x: SyntaxTree.CellType);
-		VAR fingerprint: FingerPrint; fp:LONGINT; name: SyntaxTree.String;
+		VAR fingerprint: FingerPrint; fp:LONGINT;
 		BEGIN
 		BEGIN
 			fingerprint := x.fingerprint;
 			fingerprint := x.fingerprint;
 			deep := SELF.deep;
 			deep := SELF.deep;

+ 9 - 17
source/FoxGenericObjectFile.Mod

@@ -3,7 +3,7 @@ MODULE FoxGenericObjectFile; (** AUTHOR "negelef"; PURPOSE "Generic Object File
 IMPORT
 IMPORT
 	StringPool, Streams, Commands, Basic := FoxBasic, Formats := FoxFormats, Sections := FoxSections, IntermediateCode := FoxIntermediateCode,
 	StringPool, Streams, Commands, Basic := FoxBasic, Formats := FoxFormats, Sections := FoxSections, IntermediateCode := FoxIntermediateCode,
 	SyntaxTree := FoxSyntaxTree, BinaryCode := FoxBinaryCode,
 	SyntaxTree := FoxSyntaxTree, BinaryCode := FoxBinaryCode,
-	FingerPrinter := FoxFingerPrinter, Files, Options, ObjectFile, Diagnostics, SymbolFileFormat := FoxTextualSymbolFile, Strings, KernelLog, D := Debugging;
+	FingerPrinter := FoxFingerPrinter, Files, Options, ObjectFile, SymbolFileFormat := FoxTextualSymbolFile, Strings, KernelLog, D := Debugging;
 
 
 CONST
 CONST
 	Version = 5;
 	Version = 5;
@@ -66,11 +66,9 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 
 
 			PROCEDURE MergeSections (sections: Sections.SectionList): BOOLEAN;
 			PROCEDURE MergeSections (sections: Sections.SectionList): BOOLEAN;
 			VAR
 			VAR
-				section, test: Sections.Section;
-				i, j: LONGINT;
-				name: ObjectFile.SectionName;
+				section: Sections.Section;
+				i: LONGINT;
 				sname: Basic.SegmentedName;
 				sname: Basic.SegmentedName;
-				msg: ARRAY 256 OF CHAR;
 				codeAlign, dataAlign, constAlign: LONGINT;
 				codeAlign, dataAlign, constAlign: LONGINT;
 				codeUnit, dataUnit, constUnit: LONGINT;
 				codeUnit, dataUnit, constUnit: LONGINT;
 				resolved, codeSection, dataSection, constSection: BinaryCode.Section;
 				resolved, codeSection, dataSection, constSection: BinaryCode.Section;
@@ -193,13 +191,7 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 				section, test: Sections.Section;
 				section, test: Sections.Section;
 				i, j: LONGINT;
 				i, j: LONGINT;
 				name: ObjectFile.SectionName;
 				name: ObjectFile.SectionName;
-				sname: Basic.SegmentedName;
 				msg: ARRAY 256 OF CHAR;
 				msg: ARRAY 256 OF CHAR;
-				codeAlign, dataAlign, constAlign: LONGINT;
-				codeUnit, dataUnit, constUnit: LONGINT;
-				resolved, codeSection, dataSection, constSection: BinaryCode.Section;
-				alias: BinaryCode.Alias;
-				irSection: IntermediateCode.Section;
 			BEGIN
 			BEGIN
 
 
 				FOR i := 0 TO sections.Length() - 1 DO
 				FOR i := 0 TO sections.Length() - 1 DO
@@ -258,7 +250,7 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 			END MakeStatistics;
 			END MakeStatistics;
 
 
 			PROCEDURE ExportModule (module: Sections.Module): BOOLEAN;
 			PROCEDURE ExportModule (module: Sections.Module): BOOLEAN;
-			VAR result: BOOLEAN; pos,i: LONGINT;
+			VAR result: BOOLEAN; pos: LONGINT;
 				offers, requires: ObjectFile.NameList;
 				offers, requires: ObjectFile.NameList;
 				numImports: LONGINT; 
 				numImports: LONGINT; 
 				name: ObjectFile.SectionName;
 				name: ObjectFile.SectionName;
@@ -393,10 +385,10 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 
 
 	PROCEDURE CopyFixups(sections: Sections.SectionList; from, to: BinaryCode.Section; offset: LONGINT);
 	PROCEDURE CopyFixups(sections: Sections.SectionList; from, to: BinaryCode.Section; offset: LONGINT);
 	VAR fixup: BinaryCode.Fixup; i: INTEGER; index: LONGINT;	fixupList: ObjectFile.Fixups; fixups: LONGINT;
 	VAR fixup: BinaryCode.Fixup; i: INTEGER; index: LONGINT;	fixupList: ObjectFile.Fixups; fixups: LONGINT;
-		name: ObjectFile.SegmentedName; aliasSymbol: ObjectFile.Identifier; alias: Sections.Section; aliasOffset: LONGINT;
+		aliasSymbol: ObjectFile.Identifier; aliasOffset: LONGINT;
 
 
 		PROCEDURE PatchFixup (fixup: BinaryCode.Fixup; fixupOffset, targetOffset: LONGINT);
 		PROCEDURE PatchFixup (fixup: BinaryCode.Fixup; fixupOffset, targetOffset: LONGINT);
-		VAR target, address: ObjectFile.Unit; i,j: LONGINT;
+		VAR target, address: ObjectFile.Unit; j: LONGINT;
 
 
 			PROCEDURE PatchPattern (CONST pattern: ObjectFile.FixupPattern);
 			PROCEDURE PatchPattern (CONST pattern: ObjectFile.FixupPattern);
 			BEGIN
 			BEGIN
@@ -476,7 +468,7 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 	END Get;
 	END Get;
 
 
 	PROCEDURE ReadHeader(reader: Streams.Reader; VAR binary: BOOLEAN; VAR poolMap: ObjectFile.PoolMap; VAR offers, requires: ObjectFile.NameList): LONGINT;
 	PROCEDURE ReadHeader(reader: Streams.Reader; VAR binary: BOOLEAN; VAR poolMap: ObjectFile.PoolMap; VAR offers, requires: ObjectFile.NameList): LONGINT;
-	VAR ch: CHAR; string: ARRAY 32 OF CHAR; i,j,pos,size: LONGINT; name: ObjectFile.SectionName;
+	VAR ch: CHAR; string: ARRAY 32 OF CHAR;
 	VAR version: LONGINT;
 	VAR version: LONGINT;
 	BEGIN
 	BEGIN
 		reader.String(string);
 		reader.String(string);
@@ -509,10 +501,10 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 	END ReadHeader;
 	END ReadHeader;
 
 
 	PROCEDURE WriteHeader(writer: Streams.Writer; binary: BOOLEAN; sections: Sections.SectionList; VAR poolMap: ObjectFile.PoolMap; offers, requires: ObjectFile.NameList; fingerPrinter:FingerPrinter.FingerPrinter);
 	PROCEDURE WriteHeader(writer: Streams.Writer; binary: BOOLEAN; sections: Sections.SectionList; VAR poolMap: ObjectFile.PoolMap; offers, requires: ObjectFile.NameList; fingerPrinter:FingerPrinter.FingerPrinter);
-	VAR p1,p2, size,i: LONGINT; section: Sections.Section; fixups: LONGINT; fixupList: ObjectFile.Fixups;
+	VAR i: LONGINT; section: Sections.Section;
 
 
 		PROCEDURE ProcessSection(section: IntermediateCode.Section);
 		PROCEDURE ProcessSection(section: IntermediateCode.Section);
-		VAR i: LONGINT; fixup: BinaryCode.Fixup; index: LONGINT; alias: BinaryCode.Alias; name: ARRAY 256 OF CHAR;
+		VAR i: LONGINT; fixup: BinaryCode.Fixup; alias: BinaryCode.Alias;
 		BEGIN
 		BEGIN
 			IF (section.resolved # NIL)  & (section.alias = NIL)  THEN
 			IF (section.resolved # NIL)  & (section.alias = NIL)  THEN
 				poolMap.PutSegmentedName(section.resolved.os.identifier.name);
 				poolMap.PutSegmentedName(section.resolved.os.identifier.name);

+ 1 - 1
source/FoxGlobal.Mod

@@ -2,7 +2,7 @@ MODULE FoxGlobal; (** AUTHOR "fof & fn"; PURPOSE "Oberon Compiler Globally Defin
 (* (c) fof ETH Zürich, 2008 *)
 (* (c) fof ETH Zürich, 2008 *)
 
 
 IMPORT
 IMPORT
-	SyntaxTree := FoxSyntaxTree, Basic := FoxBasic, Scanner := FoxScanner, Strings, Dates, D:= Debugging;
+	SyntaxTree := FoxSyntaxTree, Basic := FoxBasic, Scanner := FoxScanner, Strings, Dates;
 
 
 CONST
 CONST
 	(* system flag names *)
 	(* system flag names *)

+ 66 - 182
source/FoxIntermediateBackend.Mod

@@ -125,6 +125,7 @@ TYPE
 		dimOffset: LONGINT;
 		dimOffset: LONGINT;
 	END;
 	END;
 
 
+	
 	Fixup= POINTER TO RECORD
 	Fixup= POINTER TO RECORD
 		pc: LONGINT;
 		pc: LONGINT;
 		nextFixup: Fixup;
 		nextFixup: Fixup;
@@ -169,7 +170,7 @@ TYPE
 
 
 	ConditionalBranch = PROCEDURE {DELEGATE}(label: Label; op1,op2: IntermediateCode.Operand);
 	ConditionalBranch = PROCEDURE {DELEGATE}(label: Label; op1,op2: IntermediateCode.Operand);
 
 
-	DeclarationVisitor =OBJECT(SyntaxTree.Visitor)
+	DeclarationVisitor =OBJECT
 	VAR
 	VAR
 		backend: IntermediateBackend;
 		backend: IntermediateBackend;
 		implementationVisitor: ImplementationVisitor;
 		implementationVisitor: ImplementationVisitor;
@@ -197,62 +198,40 @@ TYPE
 			backend.Error(module.module.sourceName, position, Streams.Invalid, s);
 			backend.Error(module.module.sourceName, position, Streams.Invalid, s);
 		END Error;
 		END Error;
 
 
+		(** types **)
+
 		PROCEDURE Type(x: SyntaxTree.Type);
 		PROCEDURE Type(x: SyntaxTree.Type);
 		BEGIN
 		BEGIN
-			VType(x);
+			WITH x: 
+			SyntaxTree.QualifiedType DO QualifiedType(x)
+			|SyntaxTree.MathArrayType DO meta.CheckTypeDeclaration(x)
+			|SyntaxTree.PointerType DO meta.CheckTypeDeclaration(x)			(* base type must not be visited => will be done via record type declaration, otherwise is done twice ! *)
+			|SyntaxTree.RecordType DO RecordType(x)
+			|SyntaxTree.CellType DO CellType(x)
+			ELSE
+			END;
 		END Type;
 		END Type;
 
 
-		(** types **)
-
-		PROCEDURE VisitBasicType*(x: SyntaxTree.BasicType);
-		BEGIN (* no code emission *) END VisitBasicType;
-
-		PROCEDURE VisitCharacterType*(x: SyntaxTree.CharacterType);
-		BEGIN (* no code emission *)  END VisitCharacterType;
-
-		PROCEDURE VisitIntegerType*(x: SyntaxTree.IntegerType);
-		BEGIN (* no code emission *)  END VisitIntegerType;
-
-		PROCEDURE VisitFloatType*(x: SyntaxTree.FloatType);
-		BEGIN (* no code emission *)  END VisitFloatType;
-
-		PROCEDURE VisitComplexType*(x: SyntaxTree.ComplexType);
-		BEGIN (* no code emission *)  END VisitComplexType;
-
-		PROCEDURE VisitQualifiedType*(x: SyntaxTree.QualifiedType);
+		PROCEDURE QualifiedType(x: SyntaxTree.QualifiedType);
 		VAR type: SyntaxTree.Type;
 		VAR type: SyntaxTree.Type;
 		BEGIN (* no further traversal to x.resolved necessary since type descriptor and code will be inserted at "original" position ? *)
 		BEGIN (* no further traversal to x.resolved necessary since type descriptor and code will be inserted at "original" position ? *)
 			type := x.resolved;
 			type := x.resolved;
 			IF (type.typeDeclaration # NIL) & (type.typeDeclaration.scope.ownerModule # module.module) THEN
 			IF (type.typeDeclaration # NIL) & (type.typeDeclaration.scope.ownerModule # module.module) THEN
 				meta.CheckTypeDeclaration(type);
 				meta.CheckTypeDeclaration(type);
 			END;
 			END;
-		END VisitQualifiedType;
-
-		PROCEDURE VisitStringType*(x: SyntaxTree.StringType);
-		BEGIN (* no code emission *)   END VisitStringType;
+		END QualifiedType;
 
 
-		PROCEDURE VisitArrayRangeType(x: SyntaxTree.RangeType);
-		BEGIN (* no code emission *)
-		END VisitArrayRangeType;
-
-		PROCEDURE VisitArrayType*(x: SyntaxTree.ArrayType);
-		BEGIN (* no code emission *)   END VisitArrayType;
-
-		PROCEDURE VisitPortType*(x: SyntaxTree.PortType);
-		BEGIN (* no code emission *)   END VisitPortType;
-
-		PROCEDURE VisitMathArrayType*(x: SyntaxTree.MathArrayType);
-		BEGIN
-			meta.CheckTypeDeclaration(x);
-		END VisitMathArrayType;
-
-		PROCEDURE VisitPointerType*(x: SyntaxTree.PointerType);
+		PROCEDURE HasFlag(modifiers: SyntaxTree.Modifier; CONST name: ARRAY OF CHAR): BOOLEAN;
+		VAR this: SyntaxTree.Modifier; id: SyntaxTree.Identifier;
 		BEGIN
 		BEGIN
-			meta.CheckTypeDeclaration(x);
-			(* base type must not be visited => will be done via record type declaration, otherwise is done twice ! *)
-		END VisitPointerType;
-
-		PROCEDURE VisitRecordType*(x: SyntaxTree.RecordType);
+			this := modifiers; id := SyntaxTree.NewIdentifier(name);
+			WHILE (this # NIL) & (this.identifier# id) DO
+				this := this.nextModifier;
+			END;
+			RETURN this # NIL
+		END HasFlag;
+		
+		PROCEDURE RecordType(x: SyntaxTree.RecordType);
 		VAR name: ARRAY 256 OF CHAR; td: SyntaxTree.TypeDeclaration;
 		VAR name: ARRAY 256 OF CHAR; td: SyntaxTree.TypeDeclaration;
 		BEGIN (* no code emission *)
 		BEGIN (* no code emission *)
 			meta.CheckTypeDeclaration(x);
 			meta.CheckTypeDeclaration(x);
@@ -267,19 +246,9 @@ TYPE
 				(* code section for object *)
 				(* code section for object *)
 			END;
 			END;
 			Scope(x.recordScope);
 			Scope(x.recordScope);
-		END VisitRecordType;
-
-		PROCEDURE HasFlag(modifiers: SyntaxTree.Modifier; CONST name: ARRAY OF CHAR): BOOLEAN;
-		VAR this: SyntaxTree.Modifier; id: SyntaxTree.Identifier;
-		BEGIN
-			this := modifiers; id := SyntaxTree.NewIdentifier(name);
-			WHILE (this # NIL) & (this.identifier# id) DO
-				this := this.nextModifier;
-			END;
-			RETURN this # NIL
-		END HasFlag;
-
-		PROCEDURE VisitCellType*(x: SyntaxTree.CellType);
+		END RecordType;
+		
+		PROCEDURE CellType(x: SyntaxTree.CellType);
 		VAR capabilities: SET;
 		VAR capabilities: SET;
 		BEGIN
 		BEGIN
 			IF backend.cellsAreObjects THEN meta.CheckTypeDeclaration(x) END;
 			IF backend.cellsAreObjects THEN meta.CheckTypeDeclaration(x) END;
@@ -291,28 +260,11 @@ TYPE
 			IF ~implementationVisitor.checker.SkipImplementation(x) THEN
 			IF ~implementationVisitor.checker.SkipImplementation(x) THEN
 				Scope(x.cellScope);
 				Scope(x.cellScope);
 			END;
 			END;
-		END VisitCellType;
-
-		PROCEDURE VisitProcedureType*(x: SyntaxTree.ProcedureType);
-		BEGIN (* no code emission *)   END VisitProcedureType;
-
-		PROCEDURE VisitEnumerationType*(x: SyntaxTree.EnumerationType);
-		BEGIN (* no code emission, exported enumeration type values should be included in symbol file *)
-		END VisitEnumerationType;
+		END CellType;
 
 
 		(* symbols *)
 		(* symbols *)
 
 
-		PROCEDURE VisitProcedure*(x: SyntaxTree.Procedure);
-		BEGIN
-			Procedure(x);
-		END VisitProcedure;
-
-		PROCEDURE VisitOperator*(x: SyntaxTree.Operator);
-		BEGIN
-			Procedure(x);
-		END VisitOperator;
-
-		PROCEDURE VisitVariable*(x: SyntaxTree.Variable);
+		PROCEDURE Variable(x: SyntaxTree.Variable);
 		VAR name: Basic.SegmentedName; irv: IntermediateCode.Section; align,  dim, i: LONGINT;
 		VAR name: Basic.SegmentedName; irv: IntermediateCode.Section; align,  dim, i: LONGINT;
 			size: LONGINT; lastUpdated: LONGINT; imm: IntermediateCode.Operand;
 			size: LONGINT; lastUpdated: LONGINT; imm: IntermediateCode.Operand;
 
 
@@ -455,14 +407,9 @@ TYPE
 			ELSIF currentScope IS SyntaxTree.ProcedureScope THEN
 			ELSIF currentScope IS SyntaxTree.ProcedureScope THEN
 			END;
 			END;
 			(* do not call Type(x.type) here as this must already performed in the type declaration section ! *)
 			(* do not call Type(x.type) here as this must already performed in the type declaration section ! *)
-		END VisitVariable;
-
-		PROCEDURE VisitProperty*(x: SyntaxTree.Property);
-		BEGIN
-			VisitVariable(x)
-		END VisitProperty; 
+		END Variable;
 
 
-		PROCEDURE VisitParameter*(x: SyntaxTree.Parameter);
+		PROCEDURE Parameter(x: SyntaxTree.Parameter);
 		VAR name: Basic.SegmentedName; irv: IntermediateCode.Section; align, i: LONGINT;
 		VAR name: Basic.SegmentedName; irv: IntermediateCode.Section; align, i: LONGINT;
 			size: LONGINT; lastUpdated: LONGINT;
 			size: LONGINT; lastUpdated: LONGINT;
 		BEGIN
 		BEGIN
@@ -492,24 +439,22 @@ TYPE
 				irv.SetPositionOrAlignment(x.fixed, align);
 				irv.SetPositionOrAlignment(x.fixed, align);
 				meta.CheckTypeDeclaration(x.type);
 				meta.CheckTypeDeclaration(x.type);
 			END;
 			END;
-		END VisitParameter;
-		
+		END Parameter;
 
 
-
-		PROCEDURE VisitTypeDeclaration*(x: SyntaxTree.TypeDeclaration);
+		PROCEDURE TypeDeclaration(x: SyntaxTree.TypeDeclaration);
 		BEGIN
 		BEGIN
 			Type(x.declaredType); (* => code in objects *)
 			Type(x.declaredType); (* => code in objects *)
 			IF ~(x.declaredType IS SyntaxTree.QualifiedType) & (x.declaredType.resolved IS SyntaxTree.PointerType) THEN
 			IF ~(x.declaredType IS SyntaxTree.QualifiedType) & (x.declaredType.resolved IS SyntaxTree.PointerType) THEN
 				Type(x.declaredType.resolved(SyntaxTree.PointerType).pointerBase);
 				Type(x.declaredType.resolved(SyntaxTree.PointerType).pointerBase);
 			END;
 			END;
-		END VisitTypeDeclaration;
+		END TypeDeclaration;
 
 
-		PROCEDURE VisitConstant*(x: SyntaxTree.Constant);
+		PROCEDURE Constant(x: SyntaxTree.Constant);
 		BEGIN
 		BEGIN
 			IF (SyntaxTree.Public * x.access # {}) THEN
 			IF (SyntaxTree.Public * x.access # {}) THEN
 				implementationVisitor.VisitConstant(x);
 				implementationVisitor.VisitConstant(x);
 			END;
 			END;
-		END VisitConstant;
+		END Constant;
 
 
 
 
 		PROCEDURE Scope(x: SyntaxTree.Scope);
 		PROCEDURE Scope(x: SyntaxTree.Scope);
@@ -530,12 +475,12 @@ TYPE
 				cell := x.ownerCell;
 				cell := x.ownerCell;
 				parameter := cell.firstParameter;
 				parameter := cell.firstParameter;
 				WHILE parameter # NIL DO
 				WHILE parameter # NIL DO
-					VisitParameter(parameter);
+					Parameter(parameter);
 					parameter := parameter.nextParameter;
 					parameter := parameter.nextParameter;
 				END;
 				END;
 				property := cell.firstProperty;
 				property := cell.firstProperty;
 				WHILE property # NIL DO
 				WHILE property # NIL DO
-					VisitProperty(property);
+					Variable(property);
 					property := property.nextProperty;
 					property := property.nextProperty;
 				END;
 				END;
 			ELSE
 			ELSE
@@ -543,25 +488,25 @@ TYPE
 
 
 			typeDeclaration := x.firstTypeDeclaration;
 			typeDeclaration := x.firstTypeDeclaration;
 			WHILE typeDeclaration # NIL DO
 			WHILE typeDeclaration # NIL DO
-				VisitTypeDeclaration(typeDeclaration);
+				TypeDeclaration(typeDeclaration);
 				typeDeclaration := typeDeclaration.nextTypeDeclaration;
 				typeDeclaration := typeDeclaration.nextTypeDeclaration;
 			END;
 			END;
 
 
 			variable := x.firstVariable;
 			variable := x.firstVariable;
 			WHILE variable # NIL DO
 			WHILE variable # NIL DO
-				VisitVariable(variable);
+				Variable(variable);
 				variable := variable.nextVariable;
 				variable := variable.nextVariable;
 			END;
 			END;
 
 
 			procedure := x.firstProcedure;
 			procedure := x.firstProcedure;
 			WHILE procedure # NIL DO
 			WHILE procedure # NIL DO
-				VisitProcedure(procedure);
+				Procedure(procedure);
 				procedure := procedure.nextProcedure;
 				procedure := procedure.nextProcedure;
 			END;
 			END;
 
 
 			constant := x.firstConstant;
 			constant := x.firstConstant;
 			WHILE constant # NIL DO
 			WHILE constant # NIL DO
-				VisitConstant(constant);
+				Constant(constant);
 				constant := constant.nextConstant;
 				constant := constant.nextConstant;
 			END;
 			END;
 			currentScope := prevScope;
 			currentScope := prevScope;
@@ -572,7 +517,7 @@ TYPE
 		BEGIN
 		BEGIN
 			parameter := first;
 			parameter := first;
 			WHILE parameter # NIL DO
 			WHILE parameter # NIL DO
-				VisitParameter(parameter);
+				Parameter(parameter);
 				parameter := parameter.nextParameter;
 				parameter := parameter.nextParameter;
 			END;
 			END;
 		END Parameters;
 		END Parameters;
@@ -1527,19 +1472,6 @@ TYPE
 		END GetCodeSectionNameForSymbol;
 		END GetCodeSectionNameForSymbol;
 
 
 
 
-		(** get the name for the code section that represens a certain symbol
-		(essentially the same as Global.GetSymbolName, apart from operators) **)
-		PROCEDURE GetCodeSectionNameForSymbolInScope(symbol: SyntaxTree.Symbol; scope: SyntaxTree.Scope; VAR name: ARRAY OF CHAR);
-		VAR string: ARRAY 32 OF CHAR;
-		BEGIN
-			Global.GetSymbolNameInScope(symbol, scope, name);
-			(* if the symbol is an operator, then append the fingerprint to the name *)
-			IF symbol IS SyntaxTree.Operator THEN
-				GetFingerprintString(symbol, string);
-				Strings.Append(name, string);
-			END
-		END GetCodeSectionNameForSymbolInScope;
-
 		PROCEDURE TraceEnter(CONST s: ARRAY OF CHAR);
 		PROCEDURE TraceEnter(CONST s: ARRAY OF CHAR);
 		BEGIN
 		BEGIN
 			IF dump # NIL THEN
 			IF dump # NIL THEN
@@ -1690,7 +1622,7 @@ TYPE
 		
 		
 		PROCEDURE EmitLeave(section: IntermediateCode.Section; position: Basic.Position; procedure: SyntaxTree.Procedure; callconv: LONGINT);
 		PROCEDURE EmitLeave(section: IntermediateCode.Section; position: Basic.Position; procedure: SyntaxTree.Procedure; callconv: LONGINT);
 		VAR prevSection: IntermediateCode.Section;
 		VAR prevSection: IntermediateCode.Section;
-		VAR op2, size: IntermediateCode.Operand;
+		VAR op2: IntermediateCode.Operand;
 		VAR body: SyntaxTree.Body;
 		VAR body: SyntaxTree.Body;
 		BEGIN
 		BEGIN
 			prevSection := SELF.section;
 			prevSection := SELF.section;
@@ -2158,7 +2090,9 @@ TYPE
 		END NewLabel;
 		END NewLabel;
 
 
 		PROCEDURE SetLabel(label: Label);
 		PROCEDURE SetLabel(label: Label);
-		BEGIN label.Resolve(section.pc);
+		BEGIN 
+			Emit(Nop(position));
+			label.Resolve(section.pc);
 		END SetLabel;
 		END SetLabel;
 
 
 		PROCEDURE LabelOperand(label: Label): IntermediateCode.Operand;
 		PROCEDURE LabelOperand(label: Label): IntermediateCode.Operand;
@@ -2172,6 +2106,7 @@ TYPE
 
 
 		PROCEDURE BrL(label: Label);
 		PROCEDURE BrL(label: Label);
 		BEGIN
 		BEGIN
+			Emit(Nop(position));
 			Emit(Br(position,LabelOperand(label)));
 			Emit(Br(position,LabelOperand(label)));
 		END BrL;
 		END BrL;
 
 
@@ -3548,7 +3483,7 @@ TYPE
 			leftType,rightType: SyntaxTree.Type;
 			leftType,rightType: SyntaxTree.Type;
 			leftExpression,rightExpression : SyntaxTree.Expression;
 			leftExpression,rightExpression : SyntaxTree.Expression;
 			componentType: IntermediateCode.Type;
 			componentType: IntermediateCode.Type;
-			value: HUGEINT; exp: LONGINT;next,exit: Label; recordType: SyntaxTree.RecordType; dest: IntermediateCode.Operand;
+			next,exit: Label; recordType: SyntaxTree.RecordType; dest: IntermediateCode.Operand;
 			size: LONGINT;
 			size: LONGINT;
 		BEGIN
 		BEGIN
 			IF Trace THEN TraceEnter("VisitBinaryExpression") END;
 			IF Trace THEN TraceEnter("VisitBinaryExpression") END;
@@ -5711,12 +5646,12 @@ TYPE
 			designator: SyntaxTree.Designator;
 			designator: SyntaxTree.Designator;
 			procedureType: SyntaxTree.ProcedureType;
 			procedureType: SyntaxTree.ProcedureType;
 			formalParameter: SyntaxTree.Parameter;
 			formalParameter: SyntaxTree.Parameter;
-			operand, returnValue: Operand;
+			operand: Operand;
 			reg, size, mask, dest: IntermediateCode.Operand;
 			reg, size, mask, dest: IntermediateCode.Operand;
 			saved,saved2: RegisterEntry;
 			saved,saved2: RegisterEntry;
 			symbol: SyntaxTree.Symbol;
 			symbol: SyntaxTree.Symbol;
 			variable: SyntaxTree.Variable;
 			variable: SyntaxTree.Variable;
-			i,  parametersSize, returnTypeSize : LONGINT;
+			i,  parametersSize : LONGINT;
 			structuredReturnType: BOOLEAN;
 			structuredReturnType: BOOLEAN;
 			firstWriteBackCall, currentWriteBackCall: WriteBackCall;
 			firstWriteBackCall, currentWriteBackCall: WriteBackCall;
 			tempVariableDesignator: SyntaxTree.Designator;
 			tempVariableDesignator: SyntaxTree.Designator;
@@ -6323,8 +6258,8 @@ TYPE
 				reason: type desciptors in Sections are then accessible via a type declaration symbol and for types
 				reason: type desciptors in Sections are then accessible via a type declaration symbol and for types
 				and variables, constants and procedures the same mechanism can be used for fixups etc.
 				and variables, constants and procedures the same mechanism can be used for fixups etc.
 			*)
 			*)
-			VAR  source: Sections.Section;null: HUGEINT; td: SyntaxTree.TypeDeclaration;
-				op: IntermediateCode.Operand; baseRecord: SyntaxTree.RecordType;
+			VAR  source: Sections.Section;td: SyntaxTree.TypeDeclaration;
+				baseRecord: SyntaxTree.RecordType;
 			BEGIN (* no code emission *)
 			BEGIN (* no code emission *)
 				source := NIL;
 				source := NIL;
 				x := x.resolved;
 				x := x.resolved;
@@ -7327,21 +7262,7 @@ TYPE
 			END;
 			END;
 			RETURN type
 			RETURN type
 		END GetMathArrayDescriptorType;
 		END GetMathArrayDescriptorType;
-
-		PROCEDURE NewMathArrayDescriptor(op: Operand; dimensions: LONGINT);
-		VAR reg: IntermediateCode.Operand; type: SyntaxTree.Type;
-		BEGIN
-			type := GetMathArrayDescriptorType(dimensions);
-			Emit(Push(position,op.op));
-			(* push type descriptor *)
-			reg := TypeDescriptorAdr(type);
-			Emit(Push(position,reg));
-			ReleaseIntermediateOperand(reg);
-			(* push realtime flag: false by default *)
-			Emit(Push(position,false));
-			CallThis(position,"Heaps","NewRec",3);
-		END NewMathArrayDescriptor;
-
+		
 		PROCEDURE PushConstString(CONST s: ARRAY OF CHAR);
 		PROCEDURE PushConstString(CONST s: ARRAY OF CHAR);
 		VAR res: Operand; string: SyntaxTree.String; sv: SyntaxTree.StringValue; type: SyntaxTree.Type;
 		VAR res: Operand; string: SyntaxTree.String; sv: SyntaxTree.StringValue; type: SyntaxTree.Type;
 		BEGIN
 		BEGIN
@@ -7750,7 +7671,6 @@ TYPE
 			required for generational garbage collector
 			required for generational garbage collector
 		*)
 		*)
 		PROCEDURE OnHeap(x: SyntaxTree.Expression): BOOLEAN;
 		PROCEDURE OnHeap(x: SyntaxTree.Expression): BOOLEAN;
-		VAR pos: LONGINT; y: SyntaxTree.Expression;
 		BEGIN
 		BEGIN
 			RETURN TRUE;
 			RETURN TRUE;
 			(*! find a conservative and simple algorithm. The following does, for example, not work for records on the stack
 			(*! find a conservative and simple algorithm. The following does, for example, not work for records on the stack
@@ -7769,7 +7689,7 @@ TYPE
 			constructor: SyntaxTree.Procedure; s0,s1,s2: Operand; hint: HUGEINT;
 			constructor: SyntaxTree.Procedure; s0,s1,s2: Operand; hint: HUGEINT;
 			i: LONGINT; formalParameter: SyntaxTree.Parameter;
 			i: LONGINT; formalParameter: SyntaxTree.Parameter;
 			tmp:IntermediateCode.Operand;
 			tmp:IntermediateCode.Operand;
-			size: LONGINT; dim,openDim: LONGINT; pointer: IntermediateCode.Operand; t,t0,t1,t2: SyntaxTree.Type; trueL,falseL,ignore: Label;
+			size: LONGINT; dim,openDim: LONGINT; pointer: IntermediateCode.Operand; t0,t1,t2: SyntaxTree.Type; trueL,falseL,ignore: Label;
 			exit,else,end: Label; procedureType: SyntaxTree.ProcedureType;
 			exit,else,end: Label; procedureType: SyntaxTree.ProcedureType;
 			name: Basic.SegmentedName; symbol: Sections.Section; operand: Operand;
 			name: Basic.SegmentedName; symbol: Sections.Section; operand: Operand;
 			dest: IntermediateCode.Operand;
 			dest: IntermediateCode.Operand;
@@ -7777,7 +7697,6 @@ TYPE
 			convert,isTensor: BOOLEAN;
 			convert,isTensor: BOOLEAN;
 			recordType: SyntaxTree.RecordType;
 			recordType: SyntaxTree.RecordType;
 			baseType: SyntaxTree.Type;
 			baseType: SyntaxTree.Type;
-			flags: SET;
 			left: SyntaxTree.Expression;
 			left: SyntaxTree.Expression;
 			call: SyntaxTree.Designator;
 			call: SyntaxTree.Designator;
 			procedure: SyntaxTree.Procedure;
 			procedure: SyntaxTree.Procedure;
@@ -9852,8 +9771,8 @@ TYPE
 		END VisitProperty;
 		END VisitProperty;
 
 
 		PROCEDURE VisitParameter*(x: SyntaxTree.Parameter);
 		PROCEDURE VisitParameter*(x: SyntaxTree.Parameter);
-		VAR type: SyntaxTree.Type; basereg, mem: IntermediateCode.Operand; parameter: SyntaxTree.Parameter;adr: LONGINT; symbol: Sections.Section;
-			name: Basic.SegmentedName; parameterType, ptype: SyntaxTree.Type; len,inc: LONGINT; temp: IntermediateCode.Operand;
+		VAR type: SyntaxTree.Type; basereg, mem: IntermediateCode.Operand; symbol: Sections.Section;
+			name: Basic.SegmentedName; ptype: SyntaxTree.Type; temp: IntermediateCode.Operand;
 		BEGIN
 		BEGIN
 			type := x.type.resolved;
 			type := x.type.resolved;
 			IF Trace THEN TraceEnter("VisitParameter") END;
 			IF Trace THEN TraceEnter("VisitParameter") END;
@@ -11749,15 +11668,7 @@ TYPE
 			IntermediateCode.InitImmediate(op,IntermediateCode.GetType(module.system, module.system.longintType),value);
 			IntermediateCode.InitImmediate(op,IntermediateCode.GetType(module.system, module.system.longintType),value);
 			section.Emit(Data(Basic.invalidPosition,op));
 			section.Emit(Data(Basic.invalidPosition,op));
 		END Longint;
 		END Longint;
-
-		PROCEDURE PatchAddress(section: IntermediateCode.Section; pc: LONGINT; value: LONGINT);
-		VAR op,noOperand: IntermediateCode.Operand;
-		BEGIN
-			IntermediateCode.InitOperand(noOperand);
-			IntermediateCode.InitImmediate(op,IntermediateCode.GetType(module.system, module.system.addressType),value);
-			section.PatchOperands(pc,op,noOperand,noOperand);
-		END PatchAddress;
-
+		
 		PROCEDURE PatchSize(section: IntermediateCode.Section; pc: LONGINT; value: LONGINT);
 		PROCEDURE PatchSize(section: IntermediateCode.Section; pc: LONGINT; value: LONGINT);
 		VAR op,noOperand: IntermediateCode.Operand;
 		VAR op,noOperand: IntermediateCode.Operand;
 		BEGIN
 		BEGIN
@@ -11797,13 +11708,6 @@ TYPE
 			section.Emit(Data(Basic.invalidPosition,op));
 			section.Emit(Data(Basic.invalidPosition,op));
 		END Char;
 		END Char;
 
 
-		PROCEDURE Integer(section: IntermediateCode.Section; int: LONGINT);
-		VAR op: IntermediateCode.Operand;
-		BEGIN
-			IntermediateCode.InitImmediate(op,IntermediateCode.GetType(module.system, module.system.integerType),int);
-			section.Emit(Data(Basic.invalidPosition,op));
-		END Integer;
-
 		PROCEDURE String(section: IntermediateCode.Section; CONST str: ARRAY OF CHAR);
 		PROCEDURE String(section: IntermediateCode.Section; CONST str: ARRAY OF CHAR);
 		VAR i: LONGINT;
 		VAR i: LONGINT;
 		BEGIN
 		BEGIN
@@ -12373,7 +12277,7 @@ TYPE
 				sfTypeProcedure = 29X;
 				sfTypeProcedure = 29X;
 				sfTypeDelegate = 2AX;
 				sfTypeDelegate = 2AX;
 				sfTypeENUM = 2BX; 
 				sfTypeENUM = 2BX; 
-				sfTypeCELL = 2CX;
+(*				sfTypeCELL = 2CX; *)
 				sfTypePORT = 2DX;
 				sfTypePORT = 2DX;
 				
 				
 				sfIN = 0X;
 				sfIN = 0X;
@@ -12397,7 +12301,7 @@ TYPE
 				RefInfo = TRUE;
 				RefInfo = TRUE;
 
 
 			VAR
 			VAR
-				s: Sections.Section; sizePC, i, startPC, lastOffset: LONGINT;
+				sizePC, startPC, lastOffset: LONGINT;
 				indirectTypes: Basic.HashTable;
 				indirectTypes: Basic.HashTable;
 
 
 
 
@@ -12704,7 +12608,7 @@ TYPE
 					Parameter = sfVariable prevSymbol:SIZE name:STRING (sfIndirec|sfRelative) offset:SIZE Type.
 					Parameter = sfVariable prevSymbol:SIZE name:STRING (sfIndirec|sfRelative) offset:SIZE Type.
 				*)
 				*)
 				PROCEDURE NParameter(parameter: SyntaxTree.Parameter; procOffset: LONGINT);
 				PROCEDURE NParameter(parameter: SyntaxTree.Parameter; procOffset: LONGINT);
-				VAR pos: LONGINT; type: SyntaxTree.Type;
+				VAR type: SyntaxTree.Type;
 				BEGIN
 				BEGIN
 					IF RefInfo THEN Info(section, "Parameter") END;
 					IF RefInfo THEN Info(section, "Parameter") END;
 					Char(section, sfVariable);
 					Char(section, sfVariable);
@@ -12857,7 +12761,7 @@ TYPE
 					Scope = sfScopeBegin {Variable} {Procedure} {TypeDeclaration} sfScopeEnd.
 					Scope = sfScopeBegin {Variable} {Procedure} {TypeDeclaration} sfScopeEnd.
 				*)
 				*)
 				PROCEDURE NScope(scope: SyntaxTree.Scope; prevSymbol: LONGINT);
 				PROCEDURE NScope(scope: SyntaxTree.Scope; prevSymbol: LONGINT);
-				VAR bodyProcedure, procedure: SyntaxTree.Procedure; variable: SyntaxTree.Variable; typeDeclaration: SyntaxTree.TypeDeclaration; pos: LONGINT;
+				VAR bodyProcedure, procedure: SyntaxTree.Procedure; variable: SyntaxTree.Variable; typeDeclaration: SyntaxTree.TypeDeclaration;
 				BEGIN
 				BEGIN
 					IF scope = NIL THEN RETURN END; 
 					IF scope = NIL THEN RETURN END; 
 					IF RefInfo THEN Info(section, "Scope") END;
 					IF RefInfo THEN Info(section, "Scope") END;
@@ -13091,7 +12995,7 @@ TYPE
 		
 		
 		(* only for tracing, the descriptor is otherwise not complete ! *)
 		(* only for tracing, the descriptor is otherwise not complete ! *)
 		PROCEDURE MakeProcedureDescriptorTag(procedureSection: IntermediateCode.Section): IntermediateCode.Section;
 		PROCEDURE MakeProcedureDescriptorTag(procedureSection: IntermediateCode.Section): IntermediateCode.Section;
-		VAR section: IntermediateCode.Section; infoName: Basic.SectionName;  offset: LONGINT; moduleSection: IntermediateCode.Section; name: Basic.SegmentedName;
+		VAR section: IntermediateCode.Section; infoName: Basic.SectionName;  moduleSection: IntermediateCode.Section; name: Basic.SegmentedName;
 		BEGIN
 		BEGIN
 			(* mini pseudo type tag that only refers to the information data for debugging purposes -- then the descriptor in the GC can be identified *)
 			(* mini pseudo type tag that only refers to the information data for debugging purposes -- then the descriptor in the GC can be identified *)
 			name := procedureSection.name;
 			name := procedureSection.name;
@@ -13334,7 +13238,7 @@ TYPE
 			moduleSection, pointerSection, importSection, emptyArraySection, exceptionSection, commandsSection,
 			moduleSection, pointerSection, importSection, emptyArraySection, exceptionSection, commandsSection,
 			typeInfoSection, procTableSection,  referenceSection : IntermediateCode.Section;
 			typeInfoSection, procTableSection,  referenceSection : IntermediateCode.Section;
 			emptyArraySectionOffset, pointerSectionOffset, importSectionOffset, numberPointers,
 			emptyArraySectionOffset, pointerSectionOffset, importSectionOffset, numberPointers,
-			exceptionSectionOffset, commandsSectionOffset, typeInfoSectionOffset, procTableSectionOffset, maxPointers, numberProcs,temp,
+			exceptionSectionOffset, commandsSectionOffset, typeInfoSectionOffset, procTableSectionOffset, numberProcs,temp,
 			referenceSectionOffset	: LONGINT;
 			referenceSectionOffset	: LONGINT;
 			name: Basic.SegmentedName; offset: LONGINT;
 			name: Basic.SegmentedName; offset: LONGINT;
 			flags: SET; 
 			flags: SET; 
@@ -13488,31 +13392,11 @@ TYPE
 			END;
 			END;
 			PatchArray(source,pc,numberPointers);
 			PatchArray(source,pc,numberPointers);
 		END PointerArray;
 		END PointerArray;
-
-			PROCEDURE SymbolSection(symbol: SyntaxTree.Symbol; CONST suffix: ARRAY OF CHAR; VAR pc: LONGINT): IntermediateCode.Section;
-			VAR
-				name: Basic.SegmentedName;
-				section: IntermediateCode.Section;
-			BEGIN
-					Global.GetSymbolSegmentedName(symbol,name);
-					Basic.AppendToSegmentedName(name,suffix);
-
-					section := implementationVisitor.NewSection(module.allSections, Sections.ConstSection, name, NIL,declarationVisitor.dump);
-					HeapBlock("Heaps","SystemBlockDesc", section, 2);
-					Info(section, "HeapBlock");
-					Address(section,0); (* empty such that GC does not go on traversing *)
-					Info(section, suffix);
-					Address(section,0);
-					pc := section.pc;
-					RETURN section;
-			END SymbolSection;
 			
 			
 		PROCEDURE CheckTypeDeclaration(x: SyntaxTree.Type);
 		PROCEDURE CheckTypeDeclaration(x: SyntaxTree.Type);
 		VAR recordType: SyntaxTree.RecordType;
 		VAR recordType: SyntaxTree.RecordType;
-			tir, tdInfo: IntermediateCode.Section; op: IntermediateCode.Operand; name: Basic.SegmentedName; td: SyntaxTree.TypeDeclaration;
+			tir, tdInfo: IntermediateCode.Section; td: SyntaxTree.TypeDeclaration;
 			section: Sections.Section; cellType: SyntaxTree.CellType;
 			section: Sections.Section; cellType: SyntaxTree.CellType;
-			tdInfoOffset: LONGINT;
-
 
 
 			PROCEDURE NewTypeDescriptorInfo(tag: Sections.Section; offset: LONGINT; isProtected: BOOLEAN): IntermediateCode.Section;
 			PROCEDURE NewTypeDescriptorInfo(tag: Sections.Section; offset: LONGINT; isProtected: BOOLEAN): IntermediateCode.Section;
 			VAR name: Basic.SegmentedName;source: IntermediateCode.Section;
 			VAR name: Basic.SegmentedName;source: IntermediateCode.Section;
@@ -13569,7 +13453,7 @@ TYPE
 			VAR name: Basic.SegmentedName; op: IntermediateCode.Operand; source, base: IntermediateCode.Section;
 			VAR name: Basic.SegmentedName; op: IntermediateCode.Operand; source, base: IntermediateCode.Section;
 				procedure: SyntaxTree.Procedure; baseRecord: SyntaxTree.RecordType;
 				procedure: SyntaxTree.Procedure; baseRecord: SyntaxTree.RecordType;
 				baseTD: SyntaxTree.TypeDeclaration; sym: SyntaxTree.Symbol;
 				baseTD: SyntaxTree.TypeDeclaration; sym: SyntaxTree.Symbol;
-				numberPointers: LONGINT;  padding, i, tdInfoOffset: LONGINT;
+				numberPointers: LONGINT;  padding, i: LONGINT;
 				
 				
 			CONST MPO=-40000000H;
 			CONST MPO=-40000000H;
 
 

+ 1 - 11
source/FoxIntermediateCode.Mod

@@ -2,7 +2,7 @@ MODULE FoxIntermediateCode; (** AUTHOR "fof"; PURPOSE "Oberon Compiler Abstract
 (* Active Oberon Compiler, (c) 2009 Felix Friedrich *)
 (* Active Oberon Compiler, (c) 2009 Felix Friedrich *)
 IMPORT
 IMPORT
 	Sections := FoxSections, Basic := FoxBasic, SyntaxTree := FoxSyntaxTree, BinaryCode := FoxBinaryCode, Backend := FoxBackend,
 	Sections := FoxSections, Basic := FoxBasic, SyntaxTree := FoxSyntaxTree, BinaryCode := FoxBinaryCode, Backend := FoxBackend,
-	SYSTEM, Streams, Global := FoxGlobal, D := Debugging, ObjectFile;
+	Streams, Global := FoxGlobal, D := Debugging, ObjectFile;
 
 
 CONST
 CONST
 	(* operand modes *)
 	(* operand modes *)
@@ -230,14 +230,6 @@ TYPE
 			RETURN sizeInUnits
 			RETURN sizeInUnits
 		END GetSize;
 		END GetSize;
 
 
-		PROCEDURE InitArray;
-		CONST MinInstructions = 8;
-		BEGIN
-			IF instructions = NIL THEN NEW(instructions, MinInstructions); END;
-			pc := 0;
-		END InitArray;
-
-
 		(* very useful for debugging:
 		(* very useful for debugging:
 		PROCEDURE Assert*(b: BOOLEAN; CONST s: ARRAY OF CHAR);
 		PROCEDURE Assert*(b: BOOLEAN; CONST s: ARRAY OF CHAR);
 		BEGIN
 		BEGIN
@@ -424,7 +416,6 @@ TYPE
 	**)
 	**)
 	PROCEDURE NewSection*(list: Sections.SectionList; type: SHORTINT; CONST name: Basic.SegmentedName; syntaxTreeSymbol: SyntaxTree.Symbol; dump: BOOLEAN): Section;
 	PROCEDURE NewSection*(list: Sections.SectionList; type: SHORTINT; CONST name: Basic.SegmentedName; syntaxTreeSymbol: SyntaxTree.Symbol; dump: BOOLEAN): Section;
 	VAR
 	VAR
-		t0: SHORTINT;
 		result: Sections.Section;
 		result: Sections.Section;
 		section: Section;
 		section: Section;
 	BEGIN
 	BEGIN
@@ -1211,7 +1202,6 @@ TYPE
 	- note that no conversion is done, but only the type is changed **)
 	- note that no conversion is done, but only the type is changed **)
 	PROCEDURE ToUnsigned*(operand: Operand): Operand;
 	PROCEDURE ToUnsigned*(operand: Operand): Operand;
 	VAR
 	VAR
-		type: Type;
 		result: Operand;
 		result: Operand;
 	BEGIN
 	BEGIN
 		ASSERT(operand.type.form IN Integer);
 		ASSERT(operand.type.form IN Integer);

+ 2 - 2
source/FoxProgTools.Mod

@@ -598,7 +598,7 @@ TYPE
 			END;
 			END;
 		END GetLine;
 		END GetLine;
 
 
-			PROCEDURE Operand(CONST op: ARRAY OF CHAR);
+			(*PROCEDURE Operand(CONST op: ARRAY OF CHAR);
 			VAR i: LONGINT;
 			VAR i: LONGINT;
 			BEGIN
 			BEGIN
 				IF op[0] = 0X THEN w.String("none")
 				IF op[0] = 0X THEN w.String("none")
@@ -613,7 +613,7 @@ TYPE
 					INC(i);
 					INC(i);
 				END;
 				END;
 				END;
 				END;
-			END Operand;
+			END Operand;*)
 
 
 			PROCEDURE AppendCh(VAR s: ARRAY OF CHAR; c: CHAR);
 			PROCEDURE AppendCh(VAR s: ARRAY OF CHAR; c: CHAR);
 			VAR i: LONGINT;
 			VAR i: LONGINT;

+ 18 - 95
source/FoxSemanticChecker.Mod

@@ -7885,7 +7885,7 @@ TYPE
 		**)
 		**)
 		PROCEDURE VisitCaseStatement*(caseStatement: SyntaxTree.CaseStatement);
 		PROCEDURE VisitCaseStatement*(caseStatement: SyntaxTree.CaseStatement);
 		VAR expression: SyntaxTree.Expression; i: LONGINT; type: SyntaxTree.Type; caseList: SyntaxTree.CaseConstant;
 		VAR expression: SyntaxTree.Expression; i: LONGINT; type: SyntaxTree.Type; caseList: SyntaxTree.CaseConstant;
-			ch: CHAR; l: Basic.Integer; min,max: Basic.Integer; msg: ARRAY 64 OF CHAR;
+			ch: CHAR; l: Basic.Integer; min,max: Basic.Integer;
 		BEGIN
 		BEGIN
 			expression := ResolveExpression(caseStatement.variable);
 			expression := ResolveExpression(caseStatement.variable);
 			type := RegularType(expression.position,expression.type);
 			type := RegularType(expression.position,expression.type);
@@ -8788,74 +8788,21 @@ TYPE
 			SELF.diagnostics := diagnostics
 			SELF.diagnostics := diagnostics
 		END InitWarnings;
 		END InitWarnings;
 
 
-		PROCEDURE VisitPortType*(x: SyntaxTree.PortType);
-		BEGIN	END VisitPortType;
-
 		(** types *)
 		(** types *)
-		PROCEDURE Type(x: SyntaxTree.Type);
-		BEGIN VType(x)
+		PROCEDURE Type(CONST x: SyntaxTree.Type);
+		BEGIN
+			IF SyntaxTree.Warned IN x.state THEN RETURN END;
+			x.SetState(SyntaxTree.Warned);
+			WITH x:
+			SyntaxTree.ArrayType DO  Type(x.arrayBase);
+			|SyntaxTree.MathArrayType DO Type(x.arrayBase);
+			|SyntaxTree.PointerType DO Type(x.pointerBase);
+			|SyntaxTree.RecordType DO Scope(x.recordScope);
+			|SyntaxTree.CellType DO Scope(x.cellScope)
+			ELSE
+			END;	
 		END Type;
 		END Type;
 
 
-		PROCEDURE VisitType*(x: SyntaxTree.Type);
-		BEGIN  END VisitType;
-
-		PROCEDURE VisitBasicType*(x: SyntaxTree.BasicType);
-		BEGIN  END VisitBasicType;
-
-		PROCEDURE VisitCharacterType*(x: SyntaxTree.CharacterType);
-		BEGIN END VisitCharacterType;
-
-		PROCEDURE VisitIntegerType*(x: SyntaxTree.IntegerType);
-		BEGIN END VisitIntegerType;
-
-		PROCEDURE VisitFloatType*(x: SyntaxTree.FloatType);
-		BEGIN END VisitFloatType;
-
-		PROCEDURE VisitQualifiedType*(x: SyntaxTree.QualifiedType);
-		BEGIN END VisitQualifiedType;
-
-		PROCEDURE VisitStringType*(x: SyntaxTree.StringType);
-		BEGIN END VisitStringType;
-
-		PROCEDURE VisitEnumerationType*(x: SyntaxTree.EnumerationType);
-		BEGIN END VisitEnumerationType;
-
-		PROCEDURE VisitRangeType*(x: SyntaxTree.RangeType);
-		BEGIN  END VisitRangeType;
-
-		PROCEDURE VisitArrayType*(x: SyntaxTree.ArrayType);
-		BEGIN
-			IF ~(SyntaxTree.Warned IN x.state) THEN
-				x.SetState(SyntaxTree.Warned);
-				Type(x.arrayBase);
-			END;
-		END VisitArrayType;
-
-		PROCEDURE VisitMathArrayType*(x: SyntaxTree.MathArrayType);
-		BEGIN
-			IF ~(SyntaxTree.Warned IN x.state) THEN
-				x.SetState(SyntaxTree.Warned);
-				Type(x.arrayBase);
-			END;
-		END VisitMathArrayType;
-
-		PROCEDURE VisitPointerType*(x: SyntaxTree.PointerType);
-		BEGIN
-			IF ~(SyntaxTree.Warned IN x.state) THEN
-				x.SetState(SyntaxTree.Warned);
-				Type(x.pointerBase);
-			END;
-		END VisitPointerType;
-
-		PROCEDURE VisitRecordType*(x: SyntaxTree.RecordType);
-		BEGIN Scope(x.recordScope) END VisitRecordType;
-
-		PROCEDURE VisitCellType*(x: SyntaxTree.CellType);
-		BEGIN  Scope(x.cellScope) END VisitCellType;
-
-		PROCEDURE VisitProcedureType*(x: SyntaxTree.ProcedureType);
-		BEGIN  END VisitProcedureType;
-
 		PROCEDURE Warning(x: SyntaxTree.Symbol; CONST text: ARRAY OF CHAR);
 		PROCEDURE Warning(x: SyntaxTree.Symbol; CONST text: ARRAY OF CHAR);
 		VAR msg: ARRAY 256 OF CHAR;
 		VAR msg: ARRAY 256 OF CHAR;
 		BEGIN
 		BEGIN
@@ -8873,38 +8820,14 @@ TYPE
 					Warning(x,"never used");
 					Warning(x,"never used");
 				END;
 				END;
 			END;
 			END;
+			WITH x: 
+			SyntaxTree.Procedure DO
+				Scope(x.procedureScope) 				
+			ELSE
+			END;				
 			x.Accept(SELF);
 			x.Accept(SELF);
 		END Symbol;
 		END Symbol;
 
 
-		PROCEDURE VisitSymbol*(x: SyntaxTree.Symbol);
-		BEGIN END VisitSymbol;
-
-		PROCEDURE VisitTypeDeclaration*(x: SyntaxTree.TypeDeclaration);
-		BEGIN Type(x.declaredType) END VisitTypeDeclaration;
-
-		PROCEDURE VisitConstant*(x: SyntaxTree.Constant);
-		BEGIN  END VisitConstant;
-
-		PROCEDURE VisitVariable*(x: SyntaxTree.Variable);
-		BEGIN  END VisitVariable;
-
-		PROCEDURE VisitProperty*(x: SyntaxTree.Property);
-		BEGIN  END VisitProperty;
-
-		PROCEDURE VisitParameter*(x: SyntaxTree.Parameter);
-		BEGIN	END VisitParameter;
-
-		PROCEDURE VisitProcedure*(x: SyntaxTree.Procedure);
-		BEGIN 
-			Scope(x.procedureScope) 
-		END VisitProcedure;
-
-		PROCEDURE VisitOperator*(x: SyntaxTree.Operator);
-		BEGIN END VisitOperator;
-
-		PROCEDURE VisitImport*(x: SyntaxTree.Import);
-		BEGIN END VisitImport;
-
 		PROCEDURE Scope(scope: SyntaxTree.Scope);
 		PROCEDURE Scope(scope: SyntaxTree.Scope);
 		VAR
 		VAR
 			symbol: SyntaxTree.Symbol;
 			symbol: SyntaxTree.Symbol;

+ 1 - 1
source/FoxTextualSymbolFile.Mod

@@ -3,7 +3,7 @@ MODULE FoxTextualSymbolFile; (** AUTHOR "fof & fn"; PURPOSE "Oberon Compiler: Sy
 
 
 IMPORT
 IMPORT
 	D := Debugging, Basic := FoxBasic,  Scanner := FoxScanner, SyntaxTree := FoxSyntaxTree, Global := FoxGlobal, Formats := FoxFormats, Files,Streams,
 	D := Debugging, Basic := FoxBasic,  Scanner := FoxScanner, SyntaxTree := FoxSyntaxTree, Global := FoxGlobal, Formats := FoxFormats, Files,Streams,
-	Printout := FoxPrintout,Parser:= FoxParser , SemanticChecker := FoxSemanticChecker, InterfaceComparison := FoxInterfaceComparison, Options, Diagnostics;
+	Printout := FoxPrintout,Parser:= FoxParser , SemanticChecker := FoxSemanticChecker, InterfaceComparison := FoxInterfaceComparison, Options;
 
 
 CONST Trace = FALSE;
 CONST Trace = FALSE;
 
 

+ 3 - 5
source/Linker.Mod

@@ -76,7 +76,6 @@ TYPE
 		PROCEDURE QuickSort(lo, hi: LONGINT);
 		PROCEDURE QuickSort(lo, hi: LONGINT);
 		VAR
 		VAR
 			i, j,m: LONGINT;
 			i, j,m: LONGINT;
-			x, t: ANY;
 		BEGIN
 		BEGIN
 			i := lo; j := hi; m := (lo + hi) DIV 2;
 			i := lo; j := hi; m := (lo + hi) DIV 2;
 
 
@@ -163,7 +162,6 @@ TYPE
 	END Patch;
 	END Patch;
 
 
 	PROCEDURE CheckReloc*(target: GenericLinker.Address; pattern: ObjectFile.Pattern; CONST patch: ObjectFile.Patch);
 	PROCEDURE CheckReloc*(target: GenericLinker.Address; pattern: ObjectFile.Pattern; CONST patch: ObjectFile.Patch);
-	VAR i: LONGINT;
 	BEGIN
 	BEGIN
 		IF (pattern.mode = ObjectFile.Absolute) & (relocInfo # NIL) THEN
 		IF (pattern.mode = ObjectFile.Absolute) & (relocInfo # NIL) THEN
 			relocInfo.AddReloc(LONGINT(target+patch.offset));
 			relocInfo.AddReloc(LONGINT(target+patch.offset));
@@ -295,7 +293,7 @@ BEGIN
 END WriteUnixBinaryFile;
 END WriteUnixBinaryFile;
 
 
 PROCEDURE WriteTRMFile (arrangement: Arrangement; writer: Files.Writer; bitsPerLine, lines:LONGINT);
 PROCEDURE WriteTRMFile (arrangement: Arrangement; writer: Files.Writer; bitsPerLine, lines:LONGINT);
-VAR i,j,size,end,nonZeroInLeadingNibble,leadingzeros: LONGINT;
+VAR i,j,size,end,nonZeroInLeadingNibble: LONGINT;
 	PROCEDURE GetBits(pos: LONGINT): LONGINT;
 	PROCEDURE GetBits(pos: LONGINT): LONGINT;
 	BEGIN
 	BEGIN
 		IF pos >= size THEN RETURN 0
 		IF pos >= size THEN RETURN 0
@@ -444,9 +442,9 @@ VAR OptionalHeaderSize, CodeSize, AlignedCodeSize, HeadersSize: LONGINT;  BaseCo
 	BEGIN RETURN Align(RelocTableSize(), SectionAlignment);
 	BEGIN RETURN Align(RelocTableSize(), SectionAlignment);
 	END AlignedRelocTableSize;
 	END AlignedRelocTableSize;
 
 
-	PROCEDURE SectionHeaderOffset(): LONGINT;
+	(*PROCEDURE SectionHeaderOffset(): LONGINT;
 	BEGIN RETURN DOSStubSize + HeaderSize + OptionalHeaderSize
 	BEGIN RETURN DOSStubSize + HeaderSize + OptionalHeaderSize
-	END SectionHeaderOffset;
+	END SectionHeaderOffset;*)
 
 
 	PROCEDURE WriteDOSStub;
 	PROCEDURE WriteDOSStub;
 	BEGIN
 	BEGIN

+ 10 - 21
source/ObjectFile.Mod

@@ -190,7 +190,7 @@ TYPE
 
 
 		(** read map and produce Local --> Global **)
 		(** read map and produce Local --> Global **)
 		PROCEDURE Read*(reader: Streams.Reader);
 		PROCEDURE Read*(reader: Streams.Reader);
-		VAR i,j,pos,size,value: LONGINT; ch: CHAR;name: SectionName;
+		VAR value,pos: LONGINT; name: SectionName;
 		BEGIN
 		BEGIN
 			pos := 1;
 			pos := 1;
 			reader.RawString(name);
 			reader.RawString(name);
@@ -298,7 +298,6 @@ VAR
 	END CopyPatches;
 	END CopyPatches;
 
 
 	PROCEDURE CopyFixup*(source: Fixup; VAR dest: Fixup);
 	PROCEDURE CopyFixup*(source: Fixup; VAR dest: Fixup);
-	VAR i: LONGINT;
 	BEGIN
 	BEGIN
 		CopyIdentifier(source.identifier, dest.identifier);
 		CopyIdentifier(source.identifier, dest.identifier);
 		CopyPattern(source.pattern, dest.pattern);
 		CopyPattern(source.pattern, dest.pattern);
@@ -306,7 +305,6 @@ VAR
 	END CopyFixup;
 	END CopyFixup;
 
 
 	PROCEDURE CopyAlias*(CONST source: Alias; VAR dest: Alias);
 	PROCEDURE CopyAlias*(CONST source: Alias; VAR dest: Alias);
-	VAR i: LONGINT;
 	BEGIN
 	BEGIN
 		CopyIdentifier(source.identifier, dest.identifier);
 		CopyIdentifier(source.identifier, dest.identifier);
 		dest.offset := source.offset;
 		dest.offset := source.offset;
@@ -372,7 +370,7 @@ VAR
 
 
 	PROCEDURE WriteSectionTextual (writer: Streams.Writer; CONST section: Section);
 	PROCEDURE WriteSectionTextual (writer: Streams.Writer; CONST section: Section);
 	CONST Separator = ' '; Tab = 09X;
 	CONST Separator = ' '; Tab = 09X;
-	VAR i,offset,start, len: LONGINT; size: Bits; bits: LONGINT;
+	VAR i,offset,start, len: LONGINT; size: Bits;
 
 
 		PROCEDURE WriteValueIdentifier (value: INTEGER; CONST identifiers: ARRAY OF ARRAY OF CHAR);
 		PROCEDURE WriteValueIdentifier (value: INTEGER; CONST identifiers: ARRAY OF ARRAY OF CHAR);
 		BEGIN
 		BEGIN
@@ -433,7 +431,6 @@ VAR
 		END WriteFixup;
 		END WriteFixup;
 
 
 		PROCEDURE WriteAlias (CONST alias: Alias);
 		PROCEDURE WriteAlias (CONST alias: Alias);
-		VAR i: LONGINT;
 		BEGIN
 		BEGIN
 			WriteIdentifier(alias.identifier);
 			WriteIdentifier(alias.identifier);
 			writer.Char (Separator);
 			writer.Char (Separator);
@@ -471,7 +468,7 @@ VAR
 		END GetSegment;
 		END GetSegment;
 
 
 		PROCEDURE WriteSegment(offset,len: LONGINT); (* offset in bits *)
 		PROCEDURE WriteSegment(offset,len: LONGINT); (* offset in bits *)
-		VAR bits: LONGINT; first: BOOLEAN;
+		VAR bits: LONGINT;
 		BEGIN
 		BEGIN
 			ASSERT(len MOD 4 = 0); ASSERT(offset MOD 4 = 0);
 			ASSERT(len MOD 4 = 0); ASSERT(offset MOD 4 = 0);
 			len := len DIV 4;
 			len := len DIV 4;
@@ -585,7 +582,6 @@ VAR
 		END ReadFixup;
 		END ReadFixup;
 
 
 		PROCEDURE ReadAlias (VAR alias: Alias);
 		PROCEDURE ReadAlias (VAR alias: Alias);
-		VAR i: LONGINT;
 		BEGIN
 		BEGIN
 			reader.SkipWhitespace; ReadIdentifier (alias.identifier);
 			reader.SkipWhitespace; ReadIdentifier (alias.identifier);
 			reader.SkipWhitespace; reader.Int(alias.offset,FALSE);
 			reader.SkipWhitespace; reader.Int(alias.offset,FALSE);
@@ -651,7 +647,7 @@ VAR
 	END ReadSectionTextual;
 	END ReadSectionTextual;
 
 
 	PROCEDURE ReadNameList*(reader: Streams.Reader; VAR nameList: NameList; binary: BOOLEAN; poolMap: PoolMap);
 	PROCEDURE ReadNameList*(reader: Streams.Reader; VAR nameList: NameList; binary: BOOLEAN; poolMap: PoolMap);
-	VAR i,len,num: LONGINT; name: ARRAY 256 OF CHAR;
+	VAR i,len: LONGINT; name: ARRAY 256 OF CHAR;
 
 
 		PROCEDURE ReadIdentifier(VAR name: SegmentedName);
 		PROCEDURE ReadIdentifier(VAR name: SegmentedName);
 		(*VAR name: SectionName;*)
 		(*VAR name: SectionName;*)
@@ -688,7 +684,7 @@ VAR
 	END ReadNameList;
 	END ReadNameList;
 
 
 	PROCEDURE WriteNameList*(writer: Streams.Writer; nameList: NameList; binary: BOOLEAN; poolMap: PoolMap);
 	PROCEDURE WriteNameList*(writer: Streams.Writer; nameList: NameList; binary: BOOLEAN; poolMap: PoolMap);
-	VAR i,len,num: LONGINT; name: ARRAY 256 OF CHAR;
+	VAR i,len: LONGINT; name: ARRAY 256 OF CHAR;
 	CONST Separator = ' ';
 	CONST Separator = ' ';
 
 
 		PROCEDURE WriteIdentifier(CONST name: SegmentedName);
 		PROCEDURE WriteIdentifier(CONST name: SegmentedName);
@@ -724,7 +720,7 @@ VAR
 	
 	
 
 
 	PROCEDURE WriteSectionBinary (writer: Streams.Writer; CONST section: Section; poolMap: PoolMap);
 	PROCEDURE WriteSectionBinary (writer: Streams.Writer; CONST section: Section; poolMap: PoolMap);
-	VAR pos, i, offset, start, len: LONGINT; size: Bits; bits: LONGINT; name: ARRAY 256 OF CHAR;
+	VAR pos, i, offset, start, len: LONGINT; size: Bits;
 	CONST ByteSize=8;
 	CONST ByteSize=8;
 
 
 		PROCEDURE WriteValueIdentifier (value: INTEGER; CONST identifiers: ARRAY OF ARRAY OF CHAR);
 		PROCEDURE WriteValueIdentifier (value: INTEGER; CONST identifiers: ARRAY OF ARRAY OF CHAR);
@@ -786,7 +782,6 @@ VAR
 		END WriteFixup;
 		END WriteFixup;
 
 
 		PROCEDURE WriteAlias (CONST alias: Alias);
 		PROCEDURE WriteAlias (CONST alias: Alias);
-		VAR i: LONGINT;
 		BEGIN
 		BEGIN
 			WriteIdentifier(alias.identifier);
 			WriteIdentifier(alias.identifier);
 			writer.RawNum(alias.offset);
 			writer.RawNum(alias.offset);
@@ -823,7 +818,7 @@ VAR
 		END GetSegment;
 		END GetSegment;
 
 
 		PROCEDURE WriteSegment(offset,len: LONGINT); (* offset in bits *)
 		PROCEDURE WriteSegment(offset,len: LONGINT); (* offset in bits *)
-		VAR bits: LONGINT; first: BOOLEAN; pos: LONGINT;
+		VAR bits: LONGINT; pos: LONGINT;
 		BEGIN
 		BEGIN
 			pos := writer.Pos();
 			pos := writer.Pos();
 			ASSERT(len > 0);
 			ASSERT(len > 0);
@@ -893,7 +888,7 @@ VAR
 	END WriteSectionBinary;
 	END WriteSectionBinary;
 
 
 	PROCEDURE ReadSectionBinary (reader: Streams.Reader; version: LONGINT; VAR section: Section; poolMap: PoolMap);
 	PROCEDURE ReadSectionBinary (reader: Streams.Reader; version: LONGINT; VAR section: Section; poolMap: PoolMap);
-	VAR i, size: LONGINT; char: CHAR; relocatibility: INTEGER; num: LONGINT; ch: CHAR; priority: LONGINT;
+	VAR i, size: LONGINT; relocatibility: INTEGER; ch: CHAR; priority: LONGINT;
 	CONST ByteSize=8;
 	CONST ByteSize=8;
 
 
 		PROCEDURE ReadValueIdentifier (VAR value: INTEGER; CONST identifiers: ARRAY OF ARRAY OF CHAR);
 		PROCEDURE ReadValueIdentifier (VAR value: INTEGER; CONST identifiers: ARRAY OF ARRAY OF CHAR);
@@ -970,14 +965,13 @@ VAR
 		END ReadFixup;
 		END ReadFixup;
 
 
 		PROCEDURE ReadAlias (VAR alias: Alias);
 		PROCEDURE ReadAlias (VAR alias: Alias);
-		VAR i: LONGINT;
 		BEGIN
 		BEGIN
 			ReadIdentifier (alias.identifier);
 			ReadIdentifier (alias.identifier);
 			reader.RawNum (alias.offset);
 			reader.RawNum (alias.offset);
 		END ReadAlias;
 		END ReadAlias;
 
 
 		PROCEDURE ReadSegment(): BOOLEAN;
 		PROCEDURE ReadSegment(): BOOLEAN;
-		VAR len,offset,bits: LONGINT; c: CHAR;
+		VAR len,offset: LONGINT; c: CHAR;
 			segment: ARRAY 128 OF CHAR;
 			segment: ARRAY 128 OF CHAR;
 			received: LONGINT;
 			received: LONGINT;
 		BEGIN
 		BEGIN
@@ -1119,12 +1113,7 @@ VAR
 		END;
 		END;
 		RETURN TRUE
 		RETURN TRUE
 	END SameFixupPattern;
 	END SameFixupPattern;
-
-	PROCEDURE SamePattern(left, right: Pattern): BOOLEAN;
-	BEGIN
-		RETURN (left.mode = right.mode) & (left.scale = right.scale) & (left.patterns = right.patterns) & SameFixupPattern(left.patterns, left.pattern, right.pattern);
-	END SamePattern;
-
+	
 	PROCEDURE HasPattern(pat: Pattern; mode, scale: LONGINT; patterns: LONGINT; pattern: FixupPatterns): BOOLEAN;
 	PROCEDURE HasPattern(pat: Pattern; mode, scale: LONGINT; patterns: LONGINT; pattern: FixupPatterns): BOOLEAN;
 	BEGIN
 	BEGIN
 		RETURN (pat.mode = mode) & (pat.scale = scale) & (pat.patterns = patterns) & SameFixupPattern(patterns, pat.pattern, pattern);
 		RETURN (pat.mode = mode) & (pat.scale = scale) & (pat.patterns = patterns) & SameFixupPattern(patterns, pat.pattern, pattern);