Parcourir la source

removed dependencies on module ActiveCells, Hardware and TRMTools

git-svn-id: https://svn.inf.ethz.ch/svn/lecturers/a2/trunk@6510 8c9fc860-2736-0410-a75d-ab315db34111
felixf il y a 9 ans
Parent
commit
e7ca9ce59f

BIN
source/Fox.Tool


+ 4 - 4
source/FoxAMDBackend.Mod

@@ -4,8 +4,8 @@ IMPORT
 	Basic := FoxBasic, Scanner := FoxScanner, SyntaxTree := FoxSyntaxTree, Global := FoxGlobal, Backend := FoxBackend, Sections := FoxSections,
 	Basic := FoxBasic, Scanner := FoxScanner, SyntaxTree := FoxSyntaxTree, Global := FoxGlobal, Backend := FoxBackend, Sections := FoxSections,
 	IntermediateCode := FoxIntermediateCode, IntermediateBackend := FoxIntermediateBackend, BinaryCode := FoxBinaryCode,
 	IntermediateCode := FoxIntermediateCode, IntermediateBackend := FoxIntermediateBackend, BinaryCode := FoxBinaryCode,
 	InstructionSet := FoxAMD64InstructionSet, Assembler := FoxAMD64Assembler, SemanticChecker := FoxSemanticChecker, Formats := FoxFormats,
 	InstructionSet := FoxAMD64InstructionSet, Assembler := FoxAMD64Assembler, SemanticChecker := FoxSemanticChecker, Formats := FoxFormats,
-	Diagnostics, Streams, Options, Strings, ObjectFileFormat := FoxBinaryObjectFile, ActiveCells := FoxActiveCells
-	, Machine, D := Debugging, CodeGenerators := FoxCodeGenerators, ObjectFile;
+	Diagnostics, Streams, Options, Strings, ObjectFileFormat := FoxBinaryObjectFile, 
+	Machine, D := Debugging, CodeGenerators := FoxCodeGenerators, ObjectFile;
 
 
 CONST
 CONST
 
 
@@ -3092,9 +3092,9 @@ TYPE
 			forceFPU := FALSE;
 			forceFPU := FALSE;
 		END InitBackendAMD64;
 		END InitBackendAMD64;
 
 
-		PROCEDURE Initialize(diagnostics: Diagnostics.Diagnostics; log: Streams.Writer; flags: SET; checker: SemanticChecker.Checker; system: Global.System; activeCells: ActiveCells.Specification);
+		PROCEDURE Initialize(diagnostics: Diagnostics.Diagnostics; log: Streams.Writer; flags: SET; checker: SemanticChecker.Checker; system: Global.System);
 		BEGIN
 		BEGIN
-			Initialize^(diagnostics,log, flags,checker,system,activeCells); NEW(cg, runtimeModuleName, diagnostics, SELF);
+			Initialize^(diagnostics,log, flags,checker,system); NEW(cg, runtimeModuleName, diagnostics, SELF);
 		END Initialize;
 		END Initialize;
 
 
 		PROCEDURE GetSystem(): Global.System;
 		PROCEDURE GetSystem(): Global.System;

+ 6 - 12
source/FoxARMBackend.Mod

@@ -5,11 +5,10 @@ IMPORT
 	IntermediateCode := FoxIntermediateCode, IntermediateBackend := FoxIntermediateBackend, CodeGenerators := FoxCodeGenerators, BinaryCode := FoxBinaryCode,
 	IntermediateCode := FoxIntermediateCode, IntermediateBackend := FoxIntermediateBackend, CodeGenerators := FoxCodeGenerators, BinaryCode := FoxBinaryCode,
 	SemanticChecker := FoxSemanticChecker, Formats := FoxFormats, Assembler := FoxARMAssembler, InstructionSet := FoxARMInstructionSet,
 	SemanticChecker := FoxSemanticChecker, Formats := FoxFormats, Assembler := FoxARMAssembler, InstructionSet := FoxARMInstructionSet,
 	SYSTEM, Diagnostics, Streams, Options, Strings, ObjectFile, Scanner := FoxScanner, ObjectFileFormat := FoxGenericObjectFile,
 	SYSTEM, Diagnostics, Streams, Options, Strings, ObjectFile, Scanner := FoxScanner, ObjectFileFormat := FoxGenericObjectFile,
-	ActiveCells := FoxActiveCells, D := Debugging;
+	D := Debugging;
 
 
 CONST
 CONST
 	Trace = FALSE; (* general trace *)
 	Trace = FALSE; (* general trace *)
-	TraceFixups = FALSE;
 	DefaultRuntimeModuleName = "ARMRuntime";
 	DefaultRuntimeModuleName = "ARMRuntime";
 
 
 	None = -1;
 	None = -1;
@@ -508,7 +507,7 @@ TYPE
 		if not, the location of a runtime is returned **)
 		if not, the location of a runtime is returned **)
 		PROCEDURE Supported(CONST irInstruction: IntermediateCode.Instruction; VAR moduleName, procedureName: ARRAY OF CHAR): BOOLEAN;
 		PROCEDURE Supported(CONST irInstruction: IntermediateCode.Instruction; VAR moduleName, procedureName: ARRAY OF CHAR): BOOLEAN;
 		VAR
 		VAR
-			result: BOOLEAN; value: HUGEINT; exp: LONGINT;
+			result: BOOLEAN;
 		BEGIN
 		BEGIN
 			CASE irInstruction.opcode OF
 			CASE irInstruction.opcode OF
 			| IntermediateCode.add, IntermediateCode.sub, IntermediateCode.mul, IntermediateCode.abs, IntermediateCode.neg:
 			| IntermediateCode.add, IntermediateCode.sub, IntermediateCode.mul, IntermediateCode.abs, IntermediateCode.neg:
@@ -591,7 +590,6 @@ TYPE
 		(** emit an ARM instruction with an arbitrary amount of operands **)
 		(** emit an ARM instruction with an arbitrary amount of operands **)
 		PROCEDURE Emit(opCode, condition: LONGINT; flags: SET; CONST operands: ARRAY InstructionSet.MaxOperands OF Operand);
 		PROCEDURE Emit(opCode, condition: LONGINT; flags: SET; CONST operands: ARRAY InstructionSet.MaxOperands OF Operand);
 		VAR
 		VAR
-			i: LONGINT;
 		BEGIN
 		BEGIN
 			(* check whether the instruction modifies the stack pointer *)
 			(* check whether the instruction modifies the stack pointer *)
 			CheckStackPointer(operands[0]);
 			CheckStackPointer(operands[0]);
@@ -1003,7 +1001,7 @@ TYPE
 		**)
 		**)
 		PROCEDURE RegisterFromIrRegister(CONST irRegisterOperand: IntermediateCode.Operand; part: LONGINT; registerHint: Operand): Operand;
 		PROCEDURE RegisterFromIrRegister(CONST irRegisterOperand: IntermediateCode.Operand; part: LONGINT; registerHint: Operand): Operand;
 		VAR
 		VAR
-			result, offsetOperand, tempReg: Operand;
+			result: Operand;
 		BEGIN
 		BEGIN
 			ASSERT(irRegisterOperand.mode = IntermediateCode.ModeRegister);
 			ASSERT(irRegisterOperand.mode = IntermediateCode.ModeRegister);
 
 
@@ -1169,7 +1167,6 @@ TYPE
 		**)
 		**)
 		PROCEDURE RegisterFromIrOperand(VAR irOperand: IntermediateCode.Operand; part: LONGINT; registerHint: Operand): Operand;
 		PROCEDURE RegisterFromIrOperand(VAR irOperand: IntermediateCode.Operand; part: LONGINT; registerHint: Operand): Operand;
 		VAR
 		VAR
-			value: LONGINT;
 			result: Operand;
 			result: Operand;
 		BEGIN
 		BEGIN
 			CASE irOperand.mode OF
 			CASE irOperand.mode OF
@@ -1331,9 +1328,6 @@ TYPE
 
 
 		(** generate code for a certain IR instruction **)
 		(** generate code for a certain IR instruction **)
 		PROCEDURE Generate(VAR irInstruction: IntermediateCode.Instruction);
 		PROCEDURE Generate(VAR irInstruction: IntermediateCode.Instruction);
-		VAR
-			ticket: Ticket;
-			(* hwreg, lastUse: LONGINT; *)
 		BEGIN
 		BEGIN
 			(* CheckFixups; *)
 			(* CheckFixups; *)
 			EmitFixupBlockIfNeeded;
 			EmitFixupBlockIfNeeded;
@@ -2556,7 +2550,7 @@ TYPE
 			fixup,failFixup: BinaryCode.Fixup;
 			fixup,failFixup: BinaryCode.Fixup;
 			fixupPatternList: ObjectFile.FixupPatterns;
 			fixupPatternList: ObjectFile.FixupPatterns;
 			identifier: ObjectFile.Identifier;
 			identifier: ObjectFile.Identifier;
-			hiHit, hiFail, lowHit, lowFail: LONGINT;
+			hiHit, hiFail, lowHit: LONGINT;
 
 
 			PROCEDURE JmpDest(branchConditionCode: LONGINT);
 			PROCEDURE JmpDest(branchConditionCode: LONGINT);
 			BEGIN
 			BEGIN
@@ -3089,9 +3083,9 @@ TYPE
 			SetHasLinkRegister;
 			SetHasLinkRegister;
 		END InitBackendARM;
 		END InitBackendARM;
 
 
-		PROCEDURE Initialize(diagnostics: Diagnostics.Diagnostics; log: Streams.Writer; flags: SET; checker: SemanticChecker.Checker; system: Global.System; activeCellsSpecification: ActiveCells.Specification);
+		PROCEDURE Initialize(diagnostics: Diagnostics.Diagnostics; log: Streams.Writer; flags: SET; checker: SemanticChecker.Checker; system: Global.System);
 		BEGIN
 		BEGIN
-			Initialize^(diagnostics, log, flags, checker, system, activeCellsSpecification);
+			Initialize^(diagnostics, log, flags, checker, system);
 			NEW(cg, runtimeModuleName, diagnostics, SELF)
 			NEW(cg, runtimeModuleName, diagnostics, SELF)
 		END Initialize;
 		END Initialize;
 
 

+ 1 - 1
source/FoxActiveCells.Mod

@@ -1,5 +1,5 @@
 MODULE FoxActiveCells; (** AUTHOR "fof"; PURPOSE "hardware library for the ActiveCells compiler"; *)
 MODULE FoxActiveCells; (** AUTHOR "fof"; PURPOSE "hardware library for the ActiveCells compiler"; *)
-
+(*! deprecated -- not used any more in Active Cells 3 *)
 IMPORT SyntaxTree := FoxSyntaxTree, Basic := FoxBasic, Global := FoxGlobal, Files, Streams,  D := Debugging, Diagnostics, Strings, Commands, GenericLinker, StaticLinker, SYSTEM, Modules;
 IMPORT SyntaxTree := FoxSyntaxTree, Basic := FoxBasic, Global := FoxGlobal, Files, Streams,  D := Debugging, Diagnostics, Strings, Commands, GenericLinker, StaticLinker, SYSTEM, Modules;
 
 
 CONST
 CONST

+ 2 - 4
source/FoxBackend.Mod

@@ -1,7 +1,7 @@
 MODULE FoxBackend; (**  AUTHOR "kaeserm,fof"; PURPOSE "Oberon Compiler: Common backend module";  **)
 MODULE FoxBackend; (**  AUTHOR "kaeserm,fof"; PURPOSE "Oberon Compiler: Common backend module";  **)
 
 
 IMPORT
 IMPORT
-	Streams, Diagnostics, Global := FoxGlobal, Formats := FoxFormats, SyntaxTree := FoxSyntaxTree, SemanticChecker := FoxSemanticChecker, ActiveCells := FoxActiveCells, Options, Strings;
+	Streams, Diagnostics, Global := FoxGlobal, Formats := FoxFormats, SyntaxTree := FoxSyntaxTree, SemanticChecker := FoxSemanticChecker, Options, Strings;
 
 
 
 
 TYPE
 TYPE
@@ -16,7 +16,6 @@ TYPE
 		error-: BOOLEAN;
 		error-: BOOLEAN;
 		checker-: SemanticChecker.Checker;
 		checker-: SemanticChecker.Checker;
 		source-: SyntaxTree.String;
 		source-: SyntaxTree.String;
-		activeCellsSpecification-: ActiveCells.Specification;
 		findSectionName-: SectionName;
 		findSectionName-: SectionName;
 		findSectionOffset-: LONGINT;
 		findSectionOffset-: LONGINT;
 		capabilities-: SET;
 		capabilities-: SET;
@@ -69,7 +68,7 @@ TYPE
 		END ResetError;
 		END ResetError;
 
 
 		(* initialize backend for usage *)
 		(* initialize backend for usage *)
-		PROCEDURE Initialize*(diagnostics: Diagnostics.Diagnostics; log: Streams.Writer; flags: SET; checker: SemanticChecker.Checker; system: Global.System; activeCellsSpecification: ActiveCells.Specification);
+		PROCEDURE Initialize*(diagnostics: Diagnostics.Diagnostics; log: Streams.Writer; flags: SET; checker: SemanticChecker.Checker; system: Global.System);
 		BEGIN
 		BEGIN
 			error := FALSE;
 			error := FALSE;
 			SELF.diagnostics := diagnostics;
 			SELF.diagnostics := diagnostics;
@@ -77,7 +76,6 @@ TYPE
 			SELF.flags := flags;
 			SELF.flags := flags;
 			SELF.checker := checker;
 			SELF.checker := checker;
 			SELF.system := system;
 			SELF.system := system;
-			SELF.activeCellsSpecification := activeCellsSpecification;
 		END Initialize;
 		END Initialize;
 
 
 		(* Get the system used by this backend (singleton) *)
 		(* Get the system used by this backend (singleton) *)

+ 1 - 1
source/FoxBinarySymbolFile.Mod

@@ -245,7 +245,7 @@ TYPE
 		BEGIN
 		BEGIN
 			typeList := NIL; SELF.system := system; NEW(typeFixes);
 			typeList := NIL; SELF.system := system; NEW(typeFixes);
 			NEW(streamDiagnostics, D.Log);
 			NEW(streamDiagnostics, D.Log);
-			checker := SemanticChecker.NewChecker(streamDiagnostics,FALSE,FALSE,TRUE,system,symbolFile,NIL,importCache);
+			checker := SemanticChecker.NewChecker(streamDiagnostics,FALSE,FALSE,TRUE,system,symbolFile,importCache);
 		END Init;
 		END Init;
 
 
 		(* types that do not refer to other types *)
 		(* types that do not refer to other types *)

+ 4 - 56
source/FoxCompiler.Mod

@@ -5,8 +5,7 @@ IMPORT
 	Basic := FoxBasic, Scanner := FoxScanner, Parser := FoxParser,
 	Basic := FoxBasic, Scanner := FoxScanner, Parser := FoxParser,
 	SemanticChecker := FoxSemanticChecker, SyntaxTree := FoxSyntaxTree, Formats := FoxFormats,
 	SemanticChecker := FoxSemanticChecker, SyntaxTree := FoxSyntaxTree, Formats := FoxFormats,
 	Streams, Commands,Diagnostics, Options, Kernel, Printout := FoxPrintout, Backend := FoxBackend,Strings, Global := FoxGlobal,
 	Streams, Commands,Diagnostics, Options, Kernel, Printout := FoxPrintout, Backend := FoxBackend,Strings, Global := FoxGlobal,
-	ActiveCells := FoxActiveCells, Hardware := FoxHardware, Frontend := FoxFrontend,
-	Files;
+	Frontend := FoxFrontend,	Files;
 
 
 CONST
 CONST
 	(* flags *)
 	(* flags *)
@@ -38,10 +37,8 @@ TYPE
 		backend*: Backend.Backend;
 		backend*: Backend.Backend;
 		symbolFile*: Formats.SymbolFileFormat;
 		symbolFile*: Formats.SymbolFileFormat;
 		objectFile*: Formats.ObjectFileFormat;
 		objectFile*: Formats.ObjectFileFormat;
-		hardware*: Hardware.Description;
 		findPC*: SectionName;
 		findPC*: SectionName;
 		documentation*: Backend.Backend;
 		documentation*: Backend.Backend;
-		activeCellsBackend, activeCellsAssembler: Backend.Backend;
 		srcPath, destPath: Files.FileName;
 		srcPath, destPath: Files.FileName;
 		replacements: SemanticChecker.Replacement;
 		replacements: SemanticChecker.Replacement;
 	END;
 	END;
@@ -101,7 +98,6 @@ TYPE
 		name: SyntaxTree.IdentifierString;
 		name: SyntaxTree.IdentifierString;
 		split: Strings.StringArray;
 		split: Strings.StringArray;
 		sectionOffset: LONGINT;
 		sectionOffset: LONGINT;
-		activeCellsSpecification: ActiveCells.Specification;
 		flags: SET;
 		flags: SET;
 
 
 		PROCEDURE FinalMessage(error: BOOLEAN; CONST msg: ARRAY OF CHAR);
 		PROCEDURE FinalMessage(error: BOOLEAN; CONST msg: ARRAY OF CHAR);
@@ -165,14 +161,6 @@ TYPE
 
 
 		IF (options.objectFile # NIL) & (options.objectFile.ForceModuleBodies()) THEN INCL(flags, ForceModuleBodies) END;
 		IF (options.objectFile # NIL) & (options.objectFile.ForceModuleBodies()) THEN INCL(flags, ForceModuleBodies) END;
 
 
-		IF (ActiveCellsFlag IN flags) & ~(CellsAreObjects IN flags) THEN
-			NEW(activeCellsSpecification, "", diagnostics, log);
-			IF (system # NIL) THEN
-				activeCellsSpecification.DefineDevices(system);
-				Global.OperatorDefined(system, Scanner.Questionmarks, TRUE);
-			END;
-			IF options.activeCellsBackend = NIL THEN FinalMessage(TRUE,"could not install activeCells backend"); RETURN FALSE END;
-		END;
 		options.frontend.Initialize(diagnostics, reader, source, position, ActiveCellsFlag IN flags);
 		options.frontend.Initialize(diagnostics, reader, source, position, ActiveCellsFlag IN flags);
 		REPEAT
 		REPEAT
 			(** first phase: scan and parse **)
 			(** first phase: scan and parse **)
@@ -188,7 +176,7 @@ TYPE
 				IF (options.symbolFile # NIL) THEN
 				IF (options.symbolFile # NIL) THEN
 					options.symbolFile.Initialize(diagnostics,system,options.destPath);
 					options.symbolFile.Initialize(diagnostics,system,options.destPath);
 				END;
 				END;
-				checker := SemanticChecker.NewChecker(diagnostics,Info IN flags,UseDarwinCCalls IN flags,Cooperative IN flags,system,options.symbolFile,activeCellsSpecification,importCache);
+				checker := SemanticChecker.NewChecker(diagnostics,Info IN flags,UseDarwinCCalls IN flags,Cooperative IN flags,system,options.symbolFile,importCache);
 				checker.replacements := options.replacements;
 				checker.replacements := options.replacements;
 				checker.Module(module);
 				checker.Module(module);
 				IF checker.error THEN
 				IF checker.error THEN
@@ -207,12 +195,11 @@ TYPE
 
 
 				IF (ActiveCellsFlag IN flags) & ~(CellsAreObjects IN flags) THEN
 				IF (ActiveCellsFlag IN flags) & ~(CellsAreObjects IN flags) THEN
 					Global.GetSymbolName(module,name);
 					Global.GetSymbolName(module,name);
-					activeCellsSpecification.Init(name,diagnostics,log)
 				END;
 				END;
 
 
 				(** third phase: generate code, can consist of sub-phases (such as intermediate backend / hardware backend) **)
 				(** third phase: generate code, can consist of sub-phases (such as intermediate backend / hardware backend) **)
 				IF options.backend # NIL THEN
 				IF options.backend # NIL THEN
-					options.backend.Initialize(diagnostics, log, flags, checker, system, activeCellsSpecification);
+					options.backend.Initialize(diagnostics, log, flags, checker, system);
 					IF options.findPC # "" THEN
 					IF options.findPC # "" THEN
 						split := Strings.Split(options.findPC,":");
 						split := Strings.Split(options.findPC,":");
 						IF LEN(split)>1 THEN
 						IF LEN(split)>1 THEN
@@ -259,34 +246,10 @@ TYPE
 					END;
 					END;
 				END;
 				END;
 
 
-				IF activeCellsSpecification # NIL THEN
-					options.activeCellsBackend.Initialize(diagnostics,log, flags,checker,system,activeCellsSpecification);
-					generatedModule := options.activeCellsBackend.ProcessSyntaxTreeModule(module);
-					IF options.activeCellsBackend.error THEN
-						FinalMessage(TRUE, " could not be compiled (activeCells backend errors)");
-						RETURN FALSE
-					END;
-				END;
 
 
-				IF activeCellsSpecification = NIL THEN (* no activeCells *)
-				ELSIF (activeCellsSpecification.types.Length() = 0) & (activeCellsSpecification.instances.Length()=0) THEN (* nothing defined *)
-				ELSE
-					IF options.activeCellsAssembler= NIL THEN FinalMessage(TRUE,"could not install activeCells assembler"); RETURN FALSE END;
-					options.activeCellsAssembler.Initialize(diagnostics, log, flags, checker, system, activeCellsSpecification);
-					IF options.hardware # NIL THEN options.hardware.Init(diagnostics, log) END;
-
-					IF ~options.activeCellsAssembler.Emit(options.backend) THEN
-						(*activeCellsSpecification.Link(diagnostics,system.codeUnit, system.dataUnit) *)
-						FinalMessage(TRUE, " could not assemble"); RETURN FALSE
-					ELSIF ~activeCellsSpecification.Emit() THEN
-						FinalMessage(TRUE, " could not emit backend specification"); RETURN FALSE;
-					ELSIF (options.hardware # NIL) & ~options.hardware.Emit(activeCellsSpecification) THEN
-						FinalMessage(TRUE, " could not emit hardware"); RETURN FALSE;
-					END;
-				END;
 
 
 				IF options.documentation # NIL THEN
 				IF options.documentation # NIL THEN
-					options.documentation.Initialize(diagnostics,log, flags,checker,system,activeCellsSpecification);
+					options.documentation.Initialize(diagnostics,log, flags,checker,system);
 					generatedModule := options.documentation.ProcessSyntaxTreeModule(module);
 					generatedModule := options.documentation.ProcessSyntaxTreeModule(module);
 				END;
 				END;
 
 
@@ -427,12 +390,6 @@ TYPE
 			compilerOptions.symbolFile := compilerOptions.objectFile.DefaultSymbolFileFormat();
 			compilerOptions.symbolFile := compilerOptions.objectFile.DefaultSymbolFileFormat();
 		END;
 		END;
 
 
-		IF options.GetString("hardware",name) THEN
-			compilerOptions.hardware := Hardware.GetDescription(name);
-			IF compilerOptions.hardware = NIL THEN
-				Error("hardware description could not be installed"); result := FALSE;
-			END;
-		END;
 
 
 		IF options.GetString("d", name) THEN
 		IF options.GetString("d", name) THEN
 			compilerOptions.documentation := Backend.GetBackendByName("Documentation");
 			compilerOptions.documentation := Backend.GetBackendByName("Documentation");
@@ -443,11 +400,6 @@ TYPE
 			compilerOptions.documentation := NIL
 			compilerOptions.documentation := NIL
 		END;
 		END;
 
 
-		IF options.GetFlag("activeCells") THEN
-			compilerOptions.activeCellsBackend := Backend.GetBackendByName("FoxActiveCellsBackend");
-			compilerOptions.activeCellsAssembler := Backend.GetBackendByName("FoxIntermediateLinker");
-		END;
-
 		IF options.GetString("replacements", name) THEN
 		IF options.GetString("replacements", name) THEN
 			IF ~ParseReplacements(name, compilerOptions.replacements, diagnostics) THEN
 			IF ~ParseReplacements(name, compilerOptions.replacements, diagnostics) THEN
 				Error("replacement file could not be opened or is empty"); result := FALSE;
 				Error("replacement file could not be opened or is empty"); result := FALSE;
@@ -460,8 +412,6 @@ TYPE
 		IF compilerOptions.symbolFile # NIL THEN compilerOptions.symbolFile.DefineOptions(options); INCL(compilerOptions.flags,Check) END;
 		IF compilerOptions.symbolFile # NIL THEN compilerOptions.symbolFile.DefineOptions(options); INCL(compilerOptions.flags,Check) END;
 		IF compilerOptions.objectFile # NIL THEN compilerOptions.objectFile.DefineOptions(options); INCL(compilerOptions.flags,Check) END;
 		IF compilerOptions.objectFile # NIL THEN compilerOptions.objectFile.DefineOptions(options); INCL(compilerOptions.flags,Check) END;
 		IF compilerOptions.documentation # NIL THEN compilerOptions.documentation.DefineOptions(options) END;
 		IF compilerOptions.documentation # NIL THEN compilerOptions.documentation.DefineOptions(options) END;
-		IF compilerOptions.activeCellsBackend # NIL THEN compilerOptions.activeCellsBackend.DefineOptions(options) END;
-		IF compilerOptions.activeCellsAssembler # NIL THEN compilerOptions.activeCellsAssembler.DefineOptions(options) END;
 
 
 		IF result & ~parsed THEN
 		IF result & ~parsed THEN
 			options.Clear;
 			options.Clear;
@@ -494,8 +444,6 @@ TYPE
 			IF compilerOptions.symbolFile # NIL THEN compilerOptions.symbolFile.GetOptions(options) END;
 			IF compilerOptions.symbolFile # NIL THEN compilerOptions.symbolFile.GetOptions(options) END;
 			IF compilerOptions.objectFile # NIL THEN compilerOptions.objectFile.GetOptions(options) END;
 			IF compilerOptions.objectFile # NIL THEN compilerOptions.objectFile.GetOptions(options) END;
 			IF compilerOptions.documentation # NIL THEN compilerOptions.documentation.GetOptions(options) END;
 			IF compilerOptions.documentation # NIL THEN compilerOptions.documentation.GetOptions(options) END;
-			IF compilerOptions.activeCellsBackend # NIL THEN compilerOptions.activeCellsBackend.GetOptions(options) END;
-			IF compilerOptions.activeCellsAssembler # NIL THEN compilerOptions.activeCellsAssembler.GetOptions(options) END;
 		END;
 		END;
 		
 		
 		IF options.GetFlag("showOptions") THEN options.Show(error) END;
 		IF options.GetFlag("showOptions") THEN options.Show(error) END;

+ 3 - 2
source/FoxHardware.Mod

@@ -2,6 +2,8 @@
 	@author Felix Friedrich
 	@author Felix Friedrich
 	@purpose Hardware Module containing base class of hardware description object for emission of hardware on FPGAs
 	@purpose Hardware Module containing base class of hardware description object for emission of hardware on FPGAs
 **)
 **)
+
+(*! deprecated -- not used any more in ActiveCells 3 *)
 MODULE FoxHardware;
 MODULE FoxHardware;
 
 
 IMPORT ActiveCells := FoxActiveCells, Streams, Diagnostics, Strings, Commands, Files;
 IMPORT ActiveCells := FoxActiveCells, Streams, Diagnostics, Strings, Commands, Files;
@@ -76,8 +78,7 @@ TYPE
 	BEGIN
 	BEGIN
 		RETURN (sizeInUnits-1) DIV blockSize +1
 		RETURN (sizeInUnits-1) DIV blockSize +1
 	END SizeInBlocks;
 	END SizeInBlocks;
-
-
+	
 END FoxHardware.
 END FoxHardware.
 
 
 FoxHardware.Emit ML505 TL.spec ~
 FoxHardware.Emit ML505 TL.spec ~

+ 14 - 47
source/FoxIntermediateBackend.Mod

@@ -3,7 +3,7 @@ MODULE FoxIntermediateBackend; (** AUTHOR ""; PURPOSE ""; *)
 IMPORT Basic := FoxBasic, SyntaxTree := FoxSyntaxTree, SemanticChecker := FoxSemanticChecker, Backend := FoxBackend, Global := FoxGlobal,
 IMPORT Basic := FoxBasic, SyntaxTree := FoxSyntaxTree, SemanticChecker := FoxSemanticChecker, Backend := FoxBackend, Global := FoxGlobal,
 	Scanner := FoxScanner, IntermediateCode := FoxIntermediateCode, Sections := FoxSections, BinaryCode := FoxBinaryCode,  Printout := FoxPrintout,
 	Scanner := FoxScanner, IntermediateCode := FoxIntermediateCode, Sections := FoxSections, BinaryCode := FoxBinaryCode,  Printout := FoxPrintout,
 	SYSTEM, Diagnostics, Strings, Options, Streams, Compiler, Formats := FoxFormats, SymbolFileFormat := FoxTextualSymbolFile, D := Debugging,
 	SYSTEM, Diagnostics, Strings, Options, Streams, Compiler, Formats := FoxFormats, SymbolFileFormat := FoxTextualSymbolFile, D := Debugging,
-	FingerPrinter := FoxFingerPrinter, StringPool, ActiveCells := FoxActiveCells;
+	FingerPrinter := FoxFingerPrinter, StringPool;
 
 
 CONST
 CONST
 		(* operand modes *)
 		(* operand modes *)
@@ -50,7 +50,6 @@ CONST
 		TraceRegisterUsageCount=TRUE;
 		TraceRegisterUsageCount=TRUE;
 
 
 		ArrayAlignment = 8*8;			(* first array element of ArrayBlock and first data element of SystemBlock must be aligned to 0 MOD ArrayAlignment *)
 		ArrayAlignment = 8*8;			(* first array element of ArrayBlock and first data element of SystemBlock must be aligned to 0 MOD ArrayAlignment *)
-		LongNameLength = 64;
 
 
 		(** system call numbers  *)
 		(** system call numbers  *)
 		NumberSystemCalls* = 12;
 		NumberSystemCalls* = 12;
@@ -271,8 +270,7 @@ TYPE
 		END HasFlag;
 		END HasFlag;
 
 
 		PROCEDURE VisitCellType(x: SyntaxTree.CellType);
 		PROCEDURE VisitCellType(x: SyntaxTree.CellType);
-		VAR name:Basic.SegmentedName; td: SyntaxTree.TypeDeclaration; type: SyntaxTree.Type; len,port,adr: LONGINT;
-			parameter: SyntaxTree.Parameter; symbol: IntermediateCode.Section; op: IntermediateCode.Operand; capabilities: SET;
+		VAR port,adr: LONGINT; symbol: IntermediateCode.Section; op: IntermediateCode.Operand; capabilities: SET;
 
 
 			PROCEDURE CreatePorts(type: SyntaxTree.Type; len: LONGINT);
 			PROCEDURE CreatePorts(type: SyntaxTree.Type; len: LONGINT);
 			VAR i,len2: LONGINT; baseType: SyntaxTree.Type;
 			VAR i,len2: LONGINT; baseType: SyntaxTree.Type;
@@ -520,6 +518,8 @@ TYPE
 				ELSE RETURN FALSE
 				ELSE RETURN FALSE
 				END;
 				END;
 			END HasValue;
 			END HasValue;
+		
+			CONST DefaultDataMemorySize=512;
 
 
 		BEGIN
 		BEGIN
 			IF x.externalName # NIL THEN RETURN END;
 			IF x.externalName # NIL THEN RETURN END;
@@ -558,7 +558,7 @@ TYPE
 			ELSIF (scope.outerScope IS SyntaxTree.CellScope) & (x = scope.outerScope(SyntaxTree.CellScope).bodyProcedure) THEN
 			ELSIF (scope.outerScope IS SyntaxTree.CellScope) & (x = scope.outerScope(SyntaxTree.CellScope).bodyProcedure) THEN
 				inline := FALSE;
 				inline := FALSE;
 				cellType := scope.outerScope(SyntaxTree.CellScope).ownerCell;
 				cellType := scope.outerScope(SyntaxTree.CellScope).ownerCell;
-				IF ~HasValue(cellType.modifiers,Global.StringDataMemorySize,stackSize) THEN stackSize := ActiveCells.defaultDataMemorySize END;
+				IF ~HasValue(cellType.modifiers,Global.StringDataMemorySize,stackSize) THEN stackSize := DefaultDataMemorySize END;
 				AddBodyCallStub(x);
 				AddBodyCallStub(x);
 				AddStackAllocation(x,stackSize);
 				AddStackAllocation(x,stackSize);
 				ir := implementationVisitor.NewSection(module.allSections,Sections.BodyCodeSection, name,x,dump);
 				ir := implementationVisitor.NewSection(module.allSections,Sections.BodyCodeSection, name,x,dump);
@@ -987,13 +987,6 @@ TYPE
 			RETURN register
 			RETURN register
 		END Map;
 		END Map;
 
 
-		PROCEDURE Remap(register: LONGINT; to: LONGINT);
-		BEGIN
-			used[register].map:= to;
-			used[to].count := used[register].count;
-			used[register].count := 0;
-		END Remap;
-
 		PROCEDURE Use(register: LONGINT): LONGINT;
 		PROCEDURE Use(register: LONGINT): LONGINT;
 		BEGIN
 		BEGIN
 			IF register< LEN(used) THEN
 			IF register< LEN(used) THEN
@@ -9114,7 +9107,6 @@ TYPE
 						INC(adr, inc);
 						INC(adr, inc);
 						parameter := parameter.nextParameter
 						parameter := parameter.nextParameter
 					END;
 					END;
-					adr := backend.activeCellsSpecification.GetPortAddress(adr);
 					IntermediateCode.InitImmediate(result.op,addressType,adr);
 					IntermediateCode.InitImmediate(result.op,addressType,adr);
 					RETURN
 					RETURN
 				END;
 				END;
@@ -10918,7 +10910,7 @@ TYPE
 		END EnterDynamicName;
 		END EnterDynamicName;
 
 
 		PROCEDURE DynamicName(source: IntermediateCode.Section; index: StringPool.Index; pool: Basic.HashTableInt): LONGINT;
 		PROCEDURE DynamicName(source: IntermediateCode.Section; index: StringPool.Index; pool: Basic.HashTableInt): LONGINT;
-		VAR name: Basic.SectionName; i: LONGINT; ch: CHAR; position: LONGINT;
+		VAR name: Basic.SectionName; position: LONGINT;
 		BEGIN
 		BEGIN
 			IF pool.Has(index) THEN
 			IF pool.Has(index) THEN
 				RETURN pool.GetInt(index)
 				RETURN pool.GetInt(index)
@@ -10928,12 +10920,7 @@ TYPE
 			END;
 			END;
 			RETURN position;
 			RETURN position;
 		END DynamicName;
 		END DynamicName;
-		
-		PROCEDURE DynamicNameS(source: IntermediateCode.Section; CONST name: ARRAY OF CHAR; pool: Basic.HashTableInt): LONGINT;
-		BEGIN
-			RETURN EnterDynamicName(source, name, StringPool.GetIndex1(name), pool)
-		END DynamicNameS;
-		
+				
 		PROCEDURE Block(CONST mName, typeName, suffix: ARRAY OF CHAR; VAR offset: LONGINT): IntermediateCode.Section;
 		PROCEDURE Block(CONST mName, typeName, suffix: ARRAY OF CHAR; VAR offset: LONGINT): IntermediateCode.Section;
 		VAR name: ARRAY 128 OF CHAR; section: IntermediateCode.Section; pooledName: Basic.SegmentedName;
 		VAR name: ARRAY 128 OF CHAR; section: IntermediateCode.Section; pooledName: Basic.SegmentedName;
 		BEGIN
 		BEGIN
@@ -11239,19 +11226,6 @@ TYPE
 			END Name;
 			END Name;
 
 
 
 
-			PROCEDURE LongName(section: IntermediateCode.Section; CONST name: ARRAY OF CHAR);
-			VAR i: LONGINT; ch: CHAR;
-			BEGIN
-				i := 0;
-				REPEAT
-					ch := name[i]; INC(i);
-					Char( section, ch);
-				UNTIL ch = 0X;
-				ASSERT(i < LongNameLength);
-				WHILE i < 64 DO
-					Char( section, 0X); INC(i);
-				END;
-			END LongName;
 
 
 			PROCEDURE References(section: IntermediateCode.Section);
 			PROCEDURE References(section: IntermediateCode.Section);
 			CONST
 			CONST
@@ -11304,7 +11278,7 @@ TYPE
 				END BaseType;
 				END BaseType;
 
 
 				PROCEDURE RecordType(type: SyntaxTree.RecordType);
 				PROCEDURE RecordType(type: SyntaxTree.RecordType);
-				VAR destination: Sections.Section; name: SyntaxTree.IdentifierString; sname: Basic.SegmentedName;
+				VAR destination: Sections.Section; 
 				BEGIN
 				BEGIN
 					destination := module.allSections.FindBySymbol(type.typeDeclaration); (*TODO*)
 					destination := module.allSections.FindBySymbol(type.typeDeclaration); (*TODO*)
 					IF type.pointerType # NIL THEN
 					IF type.pointerType # NIL THEN
@@ -12108,7 +12082,7 @@ TYPE
 			END ReflectProcedures;
 			END ReflectProcedures;
 			
 			
 			PROCEDURE VariableArray(source: IntermediateCode.Section; variable: SyntaxTree.Variable);
 			PROCEDURE VariableArray(source: IntermediateCode.Section; variable: SyntaxTree.Variable);
-			VAR pc, offset: LONGINT; tir: Sections.Section; size: LONGINT; name: ARRAY 128 OF CHAR;
+			VAR pc, offset: LONGINT; tir: Sections.Section; size: LONGINT;
 				segmentedName: Basic.SegmentedName;
 				segmentedName: Basic.SegmentedName;
 				td: SyntaxTree.TypeDeclaration;
 				td: SyntaxTree.TypeDeclaration;
 				type: SyntaxTree.Type;
 				type: SyntaxTree.Type;
@@ -12155,9 +12129,8 @@ TYPE
 			END VariableArray;
 			END VariableArray;
 			
 			
 			PROCEDURE ProcedureArray(source: IntermediateCode.Section; procedure: SyntaxTree.Procedure);
 			PROCEDURE ProcedureArray(source: IntermediateCode.Section; procedure: SyntaxTree.Procedure);
-			VAR pc, offset: LONGINT; tir: Sections.Section; size: LONGINT; name: ARRAY 128 OF CHAR;
+			VAR pc: LONGINT; size: LONGINT; 
 				segmentedName: Basic.SegmentedName;
 				segmentedName: Basic.SegmentedName;
-				td: SyntaxTree.TypeDeclaration;
 			BEGIN
 			BEGIN
 				Array(source,pc,"Modules.ProcedureEntry");
 				Array(source,pc,"Modules.ProcedureEntry");
 
 
@@ -12192,11 +12165,11 @@ TYPE
 		PROCEDURE CheckTypeDeclaration(x: SyntaxTree.Type);
 		PROCEDURE CheckTypeDeclaration(x: SyntaxTree.Type);
 		VAR recordType: SyntaxTree.RecordType;
 		VAR recordType: SyntaxTree.RecordType;
 			tir: IntermediateCode.Section; op: IntermediateCode.Operand; name: Basic.SegmentedName; td: SyntaxTree.TypeDeclaration;
 			tir: IntermediateCode.Section; op: IntermediateCode.Operand; name: Basic.SegmentedName; td: SyntaxTree.TypeDeclaration;
-			section: Sections.Section; type: SyntaxTree.Type; cellType: SyntaxTree.CellType;
+			section: Sections.Section; cellType: SyntaxTree.CellType;
 
 
 
 
 			PROCEDURE NewTypeDescriptorInfo(tag: Sections.Section; offset: LONGINT; isProtected: BOOLEAN): Sections.Section;
 			PROCEDURE NewTypeDescriptorInfo(tag: Sections.Section; offset: LONGINT; isProtected: BOOLEAN): Sections.Section;
-			VAR name: Basic.SegmentedName;source, fieldSection: IntermediateCode.Section;
+			VAR name: Basic.SegmentedName;source: IntermediateCode.Section;
 				moduleSection: IntermediateCode.Section; i: LONGINT; flags: SET;
 				moduleSection: IntermediateCode.Section; i: LONGINT; flags: SET;
 				sectionName: Basic.SectionName;
 				sectionName: Basic.SectionName;
 			CONST MPO=-40000000H;
 			CONST MPO=-40000000H;
@@ -12279,7 +12252,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,offset, i: LONGINT;
+				numberPointers: LONGINT;  padding, i: LONGINT;
 			CONST MPO=-40000000H;
 			CONST MPO=-40000000H;
 
 
 				PROCEDURE TdTable(size: LONGINT; reverse: BOOLEAN);
 				PROCEDURE TdTable(size: LONGINT; reverse: BOOLEAN);
@@ -12642,17 +12615,12 @@ TYPE
 			declarationVisitor: DeclarationVisitor;
 			declarationVisitor: DeclarationVisitor;
 			implementationVisitor: ImplementationVisitor;
 			implementationVisitor: ImplementationVisitor;
 			module: Sections.Module;
 			module: Sections.Module;
-			name, instructionSet, platformName: SyntaxTree.IdentifierString;
+			name, platformName: SyntaxTree.IdentifierString;
 			meta: MetaDataGenerator; 
 			meta: MetaDataGenerator; 
 		BEGIN
 		BEGIN
 			ResetError;
 			ResetError;
 			Global.GetSymbolName(x,name);
 			Global.GetSymbolName(x,name);
 
 
-			IF activeCellsSpecification # NIL THEN
-				GetDescription(instructionSet);
-				activeCellsSpecification.SetInstructionSet(instructionSet)
-			END;
-
 			NEW(module,x,system); (* backend structures *)
 			NEW(module,x,system); (* backend structures *)
 
 
 			Global.GetModuleName(x, name);
 			Global.GetModuleName(x, name);
@@ -12916,7 +12884,6 @@ TYPE
 
 
 	PROCEDURE GetSymbol*(scope: SyntaxTree.ModuleScope; CONST moduleName, symbolName: ARRAY OF CHAR): SyntaxTree.Symbol;
 	PROCEDURE GetSymbol*(scope: SyntaxTree.ModuleScope; CONST moduleName, symbolName: ARRAY OF CHAR): SyntaxTree.Symbol;
 	VAR import: SyntaxTree.Import;
 	VAR import: SyntaxTree.Import;
-		s: Basic.MessageString;
 		selfName: SyntaxTree.IdentifierString;
 		selfName: SyntaxTree.IdentifierString;
 		module: SyntaxTree.Module;
 		module: SyntaxTree.Module;
 	BEGIN
 	BEGIN

+ 2 - 6
source/FoxIntermediateLinker.Mod

@@ -42,7 +42,7 @@ TYPE
 			backend := defaultBackend;
 			backend := defaultBackend;
 			defaultBackend.GetDescription(platformName);
 			defaultBackend.GetDescription(platformName);
 			
 			
-			backend.Initialize(diagnostics, NIL, {}, NIL, backend.GetSystem(), NIL);
+			backend.Initialize(diagnostics, NIL, {}, NIL, backend.GetSystem());
 			NEW(allSections);
 			NEW(allSections);
 			NEW(importList, 128);
 			NEW(importList, 128);
 			NEW(loadedModules, 128);
 			NEW(loadedModules, 128);
@@ -645,7 +645,7 @@ TYPE
 			result := TRUE;
 			result := TRUE;
 
 
 			(* generate binary code *)
 			(* generate binary code *)
-			backend.Initialize(diagnostics, log, {}, NIL, backend.GetSystem(), NIL);
+			backend.Initialize(diagnostics, log, {}, NIL, backend.GetSystem());
 			binaryModule := backend.ProcessIntermediateCodeModule(intermediateCodeModule); count := 0;
 			binaryModule := backend.ProcessIntermediateCodeModule(intermediateCodeModule); count := 0;
 
 
 			(* iterative compilation until all sections remain fixed at their position *)
 			(* iterative compilation until all sections remain fixed at their position *)
@@ -1272,12 +1272,8 @@ TYPE
 	
 	
 	PROCEDURE WriteCodeAndDataFiles*(CONST instanceName: ARRAY OF CHAR; VAR instructionMemorySize, dataMemorySize: LONGINT; backend: Backend.Backend;  diagnostics: Diagnostics.Diagnostics; log:Streams.Writer): BOOLEAN;
 	PROCEDURE WriteCodeAndDataFiles*(CONST instanceName: ARRAY OF CHAR; VAR instructionMemorySize, dataMemorySize: LONGINT; backend: Backend.Backend;  diagnostics: Diagnostics.Diagnostics; log:Streams.Writer): BOOLEAN;
 	VAR code, data: StaticLinker.Arrangement; linker: GenericLinker.Linker; linkerLog: Files.Writer;
 	VAR code, data: StaticLinker.Arrangement; linker: GenericLinker.Linker; linkerLog: Files.Writer;
-			inker: GenericLinker.Linker;
-			i: LONGINT;
 			logFile: Files.File; 
 			logFile: Files.File; 
 			objectFileExtension: ARRAY 32 OF CHAR;
 			objectFileExtension: ARRAY 32 OF CHAR;
-			value: SyntaxTree.Value;
-			pooledName: Basic.SegmentedName;
 			error : BOOLEAN;
 			error : BOOLEAN;
 			fileName, codeFileName, dataFileName: Files.FileName;
 			fileName, codeFileName, dataFileName: Files.FileName;
 			system: Global.System;
 			system: Global.System;

+ 4 - 6
source/FoxSemanticChecker.Mod

@@ -3,7 +3,7 @@ MODULE FoxSemanticChecker; (* AUTHOR "fof & fn"; PURPOSE "Oberon Compiler: Seman
 (* (c) fof ETHZ 2009 *)
 (* (c) fof ETHZ 2009 *)
 
 
 IMPORT D := Debugging, Basic := FoxBasic, Scanner := FoxScanner, SyntaxTree := FoxSyntaxTree, Parser := FoxParser,
 IMPORT D := Debugging, Basic := FoxBasic, Scanner := FoxScanner, SyntaxTree := FoxSyntaxTree, Parser := FoxParser,
-Diagnostics, Global := FoxGlobal, Printout:= FoxPrintout, Formats := FoxFormats, ActiveCells := FoxActiveCells, SYSTEM, Streams, Strings;
+Diagnostics, Global := FoxGlobal, Printout:= FoxPrintout, Formats := FoxFormats, SYSTEM, Streams, Strings;
 
 
 CONST
 CONST
 	Trace = FALSE;
 	Trace = FALSE;
@@ -104,19 +104,17 @@ TYPE
 		global: SyntaxTree.ModuleScope;
 		global: SyntaxTree.ModuleScope;
 		withEntries: WithEntry;
 		withEntries: WithEntry;
 		activeCellsStatement: BOOLEAN;
 		activeCellsStatement: BOOLEAN;
-		activeCellsSpecification: ActiveCells.Specification;
 		replacements*: Replacement;
 		replacements*: Replacement;
 		cellsAreObjects: BOOLEAN;
 		cellsAreObjects: BOOLEAN;
 		variableAccessed: BOOLEAN;
 		variableAccessed: BOOLEAN;
 
 
-		PROCEDURE &InitChecker*(diagnostics: Diagnostics.Diagnostics; verboseErrorMessage,useDarwinCCalls,cooperative: BOOLEAN; system: Global.System; symbolFileFormat: Formats.SymbolFileFormat; activeCellsSpecification: ActiveCells.Specification; VAR importCache: SyntaxTree.ModuleScope);
+		PROCEDURE &InitChecker*(diagnostics: Diagnostics.Diagnostics; verboseErrorMessage,useDarwinCCalls,cooperative: BOOLEAN; system: Global.System; symbolFileFormat: Formats.SymbolFileFormat; VAR importCache: SyntaxTree.ModuleScope);
 		BEGIN
 		BEGIN
 			SELF.diagnostics := diagnostics;
 			SELF.diagnostics := diagnostics;
 			SELF.useDarwinCCalls := useDarwinCCalls;
 			SELF.useDarwinCCalls := useDarwinCCalls;
 			SELF.cooperative := cooperative;
 			SELF.cooperative := cooperative;
 			SELF.system := system;
 			SELF.system := system;
 			SELF.symbolFileFormat := symbolFileFormat;
 			SELF.symbolFileFormat := symbolFileFormat;
-			SELF.activeCellsSpecification := activeCellsSpecification;
 			error := FALSE;
 			error := FALSE;
 			NEW(typeFixes);
 			NEW(typeFixes);
 			NEW(pointerFixes);
 			NEW(pointerFixes);
@@ -9591,10 +9589,10 @@ TYPE
 	END EnterCase;
 	END EnterCase;
 
 
 	(** generate and return a new checker object, errors are entered into diagnostics **)
 	(** generate and return a new checker object, errors are entered into diagnostics **)
-	PROCEDURE NewChecker*(diagnostics: Diagnostics.Diagnostics; verboseErrorMessage,useDarwinCCalls,cooperative: BOOLEAN; system: Global.System; symbolFileFormat: Formats.SymbolFileFormat; activeCellsSpecification: ActiveCells.Specification; VAR importCache: SyntaxTree.ModuleScope): Checker;
+	PROCEDURE NewChecker*(diagnostics: Diagnostics.Diagnostics; verboseErrorMessage,useDarwinCCalls,cooperative: BOOLEAN; system: Global.System; symbolFileFormat: Formats.SymbolFileFormat; VAR importCache: SyntaxTree.ModuleScope): Checker;
 	VAR checker: Checker;
 	VAR checker: Checker;
 	BEGIN
 	BEGIN
-		NEW(checker, diagnostics,verboseErrorMessage,useDarwinCCalls,cooperative,system,symbolFileFormat,activeCellsSpecification, importCache);
+		NEW(checker, diagnostics,verboseErrorMessage,useDarwinCCalls,cooperative,system,symbolFileFormat,importCache);
 		RETURN checker
 		RETURN checker
 	END NewChecker;
 	END NewChecker;
 
 

+ 3 - 5
source/FoxTRMBackend.Mod

@@ -5,8 +5,7 @@ IMPORT
 	IntermediateCode := FoxIntermediateCode, IntermediateBackend := FoxIntermediateBackend, BinaryCode := FoxBinaryCode,
 	IntermediateCode := FoxIntermediateCode, IntermediateBackend := FoxIntermediateBackend, BinaryCode := FoxBinaryCode,
 	SemanticChecker := FoxSemanticChecker, Formats := FoxFormats, Assembler := FoxTRMAssembler, InstructionSet := FoxTRMInstructionSet,
 	SemanticChecker := FoxSemanticChecker, Formats := FoxFormats, Assembler := FoxTRMAssembler, InstructionSet := FoxTRMInstructionSet,
 	SYSTEM, Diagnostics, Streams, Options, Strings, ObjectFile, Scanner := FoxScanner, ObjectFileFormat := FoxIntermediateObjectFile,
 	SYSTEM, Diagnostics, Streams, Options, Strings, ObjectFile, Scanner := FoxScanner, ObjectFileFormat := FoxIntermediateObjectFile,
-	ActiveCells := FoxActiveCells, CodeGenerators := FoxCodeGenerators, D := Debugging,
-	KernelLog;
+	CodeGenerators := FoxCodeGenerators, D := Debugging;
 
 
 CONST
 CONST
 	TraceFixups = FALSE;
 	TraceFixups = FALSE;
@@ -2182,11 +2181,10 @@ TYPE
 			SetHasLinkRegister;
 			SetHasLinkRegister;
 		END InitBackendTRM;
 		END InitBackendTRM;
 
 
-		PROCEDURE Initialize(diagnostics: Diagnostics.Diagnostics; log: Streams.Writer; flags: SET; checker: SemanticChecker.Checker; system: Global.System;
-			activeCellsSpecification: ActiveCells.Specification);
+		PROCEDURE Initialize(diagnostics: Diagnostics.Diagnostics; log: Streams.Writer; flags: SET; checker: SemanticChecker.Checker; system: Global.System);
 		VAR
 		VAR
 		BEGIN
 		BEGIN
-			Initialize^(diagnostics, log, flags, checker, system, activeCellsSpecification); (*goes up the inheritance hierarchy all the way to Backend.Mod*)
+			Initialize^(diagnostics, log, flags, checker, system); (*goes up the inheritance hierarchy all the way to Backend.Mod*)
 			
 			
 			
 			
 			NEW(cg, runtimeModuleName, diagnostics, SELF,myInstructionSet);
 			NEW(cg, runtimeModuleName, diagnostics, SELF,myInstructionSet);

+ 1 - 1
source/FoxTRMTools.Mod

@@ -1,5 +1,5 @@
 MODULE FoxTRMTools; (** AUTHOR ""; PURPOSE ""; *)
 MODULE FoxTRMTools; (** AUTHOR ""; PURPOSE ""; *)
-
+(*! deprecated -- not used any more in Active Cells3 *)
 IMPORT Files,Commands,Options,Strings,Basic := FoxBasic, Diagnostics, Random, Machine, ActiveCells := FoxActiveCells, Streams, WinApplications, Hardware := FoxHardware,
 IMPORT Files,Commands,Options,Strings,Basic := FoxBasic, Diagnostics, Random, Machine, ActiveCells := FoxActiveCells, Streams, WinApplications, Hardware := FoxHardware,
 		BitSets,ObjectFile;
 		BitSets,ObjectFile;
 
 

+ 1 - 1
source/FoxTextCompiler.Mod

@@ -1,7 +1,7 @@
 MODULE TextCompiler; (** AUTHOR ""; PURPOSE ""; *)
 MODULE TextCompiler; (** AUTHOR ""; PURPOSE ""; *)
 
 
 IMPORT Streams, Modules, Basic := FoxBasic, Compiler, TextUtilities, Diagnostics, Texts, Backend := FoxBackend, SyntaxTree := FoxSyntaxTree,
 IMPORT Streams, Modules, Basic := FoxBasic, Compiler, TextUtilities, Diagnostics, Texts, Backend := FoxBackend, SyntaxTree := FoxSyntaxTree,
-	CompilerInterface, Hardware := FoxHardware, Formats := FoxFormats, ActiveCells := FoxActiveCells, Strings, UTF8Strings, Commands;
+	CompilerInterface, Formats := FoxFormats, Strings, UTF8Strings, Commands;
 
 
 CONST
 CONST
 
 

+ 1 - 1
source/FoxTextualSymbolFile.Mod

@@ -27,7 +27,7 @@ TYPE
 
 
 			IF (module # NIL) & ~(SyntaxTree.Resolved IN module.state) THEN
 			IF (module # NIL) & ~(SyntaxTree.Resolved IN module.state) THEN
 				(*! should rather be done by importer *)
 				(*! should rather be done by importer *)
-				checker := SemanticChecker.NewChecker(NIL,FALSE,FALSE,TRUE,system,SELF,NIL,importCache);
+				checker := SemanticChecker.NewChecker(NIL,FALSE,FALSE,TRUE,system,SELF,importCache);
 				checker.Module(module); (* semantic check *)
 				checker.Module(module); (* semantic check *)
 				IF checker.error THEN module := NIL END;
 				IF checker.error THEN module := NIL END;
 			END;
 			END;