Browse Source

Also treated line numbers correctly in assembler code

git-svn-id: https://svn.inf.ethz.ch/svn/lecturers/a2/trunk@6955 8c9fc860-2736-0410-a75d-ab315db34111
felixf 8 years ago
parent
commit
e0864e2384

+ 4 - 7
source/Fox.Tool

@@ -10,19 +10,16 @@ Compiler.Compile --noInterfaceCheck
 	SystemTools.Timer start ~
 	SystemTools.Timer start ~
 
 
 	Compiler.Compile -p=Win32G *)
 	Compiler.Compile -p=Win32G *)
-(* 
-	SystemTools.DoCommands
-	SystemTools.Timer start ~
-
-	Compiler.Compile -p=Linux32G *)
 
 
 	BitSets.Mod ObjectFile.Mod GenericLinker.Mod StaticLinker.Mod
 	BitSets.Mod ObjectFile.Mod GenericLinker.Mod StaticLinker.Mod
 	FoxBasic.Mod  FoxProgTools.Mod  FoxScanner.Mod FoxCSharpScanner.Mod FoxSyntaxTree.Mod FoxGlobal.Mod
 	FoxBasic.Mod  FoxProgTools.Mod  FoxScanner.Mod FoxCSharpScanner.Mod FoxSyntaxTree.Mod FoxGlobal.Mod
 	FoxFormats.Mod FoxPrintout.Mod
 	FoxFormats.Mod FoxPrintout.Mod
 	FoxParser.Mod FoxCSharpParser.Mod  FoxSemanticChecker.Mod
 	FoxParser.Mod FoxCSharpParser.Mod  FoxSemanticChecker.Mod
 	FoxBackend.Mod FoxSections.Mod 
 	FoxBackend.Mod FoxSections.Mod 
-	FoxFrontend.Mod FoxOberonFrontend.Mod FoxCSharpFrontend.Mod
-	FoxCompiler.Mod FoxFingerPrinter.Mod  FoxInterfaceComparison.Mod FoxTextualSymbolFile.Mod FoxBinarySymbolFile.Mod
+	FoxFrontend.Mod 
+	FoxCompiler.Mod 
+	FoxOberonFrontend.Mod FoxCSharpFrontend.Mod
+	FoxFingerPrinter.Mod  FoxInterfaceComparison.Mod FoxTextualSymbolFile.Mod FoxBinarySymbolFile.Mod
 	FoxBinaryCode.Mod FoxIntermediateCode.Mod FoxIntermediateBackend.Mod FoxCodeGenerators.Mod
 	FoxBinaryCode.Mod FoxIntermediateCode.Mod FoxIntermediateBackend.Mod FoxCodeGenerators.Mod
 	FoxBinaryObjectFile.Mod FoxGenericObjectFile.Mod
 	FoxBinaryObjectFile.Mod FoxGenericObjectFile.Mod
 	FoxAMD64InstructionSet.Mod FoxAMD64Assembler.Mod FoxAMDBackend.Mod
 	FoxAMD64InstructionSet.Mod FoxAMD64Assembler.Mod FoxAMDBackend.Mod

+ 24 - 8
source/FoxAMD64Assembler.Mod

@@ -205,7 +205,8 @@ TYPE
 		code-: Code;
 		code-: Code;
 		error-: BOOLEAN;
 		error-: BOOLEAN;
 		diagnostics: Diagnostics.Diagnostics;
 		diagnostics: Diagnostics.Diagnostics;
-
+		assembly: Assembly; (* for error position *)
+		
 		(* overal state *)
 		(* overal state *)
 		cpuBits: Size; (* supported bit width for this cpu / target *)
 		cpuBits: Size; (* supported bit width for this cpu / target *)
 		cpuOptions: InstructionSet.CPUOptions;
 		cpuOptions: InstructionSet.CPUOptions;
@@ -237,14 +238,15 @@ TYPE
 		END SetBits;
 		END SetBits;
 
 
 		PROCEDURE Error(CONST message: ARRAY OF CHAR);
 		PROCEDURE Error(CONST message: ARRAY OF CHAR);
-		VAR msg,name: ARRAY 256 OF CHAR;
+		VAR msg,name: ARRAY 256 OF CHAR; errPos: LONGINT;
 		BEGIN
 		BEGIN
 			COPY(message,msg);
 			COPY(message,msg);
 			Strings.Append(msg," in ");
 			Strings.Append(msg," in ");
 			ObjectFile.SegmentedNameToString(code.os.identifier.name,name);
 			ObjectFile.SegmentedNameToString(code.os.identifier.name,name);
 			Strings.Append(msg, name);
 			Strings.Append(msg, name);
 			IF diagnostics # NIL THEN
 			IF diagnostics # NIL THEN
-				diagnostics.Error("",Diagnostics.Invalid,Diagnostics.Invalid,msg);
+				IF assembly # NIL THEN errPos := assembly.errPos ELSE errPos := Diagnostics.Invalid END;
+				diagnostics.Error("",Diagnostics.Invalid,errPos,msg);
 			END;
 			END;
 			error := TRUE;
 			error := TRUE;
 			IF dump # NIL THEN dump.Update; END;
 			IF dump # NIL THEN dump.Update; END;
@@ -1067,6 +1069,7 @@ TYPE
 		(* output *)
 		(* output *)
 		errPos: LONGINT;
 		errPos: LONGINT;
 		error-: BOOLEAN;
 		error-: BOOLEAN;
+		useLineNumbers*: BOOLEAN;
 		emitter: Emitter;
 		emitter: Emitter;
 
 
 		(* overal state *)
 		(* overal state *)
@@ -1139,9 +1142,10 @@ TYPE
 			orgCodePos: LONGINT;
 			orgCodePos: LONGINT;
 			prevSourceName: Basic.FileName;
 			prevSourceName: Basic.FileName;
 			position: LONGINT;
 			position: LONGINT;
+			line: LONGINT;
 			prevCpuBits: Size;
 			prevCpuBits: Size;
 			prevCpuOptions: InstructionSet.CPUOptions;
 			prevCpuOptions: InstructionSet.CPUOptions;
-
+			prevAssembly: Assembly;
 			PROCEDURE NextChar;
 			PROCEDURE NextChar;
 			BEGIN
 			BEGIN
 				(*
 				(*
@@ -1215,7 +1219,11 @@ TYPE
 			PROCEDURE NextSymbol;
 			PROCEDURE NextSymbol;
 			BEGIN
 			BEGIN
 				SkipBlanks;
 				SkipBlanks;
-				errPos := position- 1;
+				IF useLineNumbers THEN
+					errPos := line
+				ELSE
+					errPos := position- 1;
+				END;
 
 
 				CASE char OF
 				CASE char OF
 				'A' .. 'Z', 'a' .. 'z', '_' :
 				'A' .. 'Z', 'a' .. 'z', '_' :
@@ -1237,8 +1245,12 @@ TYPE
 					NextChar;
 					NextChar;
 				| ':': symbol := symColon;
 				| ':': symbol := symColon;
 					NextChar;
 					NextChar;
-				| CR, LF: symbol := symLn;
-					NextChar;
+				| CR: symbol := symLn;
+					NextChar; INC(line);
+					IF char = LF THEN NextChar END;
+				| LF: symbol := symLn;
+					NextChar;INC(line);
+					IF char = CR THEN NextChar END;
 				| ',': symbol := symComma;
 				| ',': symbol := symComma;
 					NextChar;
 					NextChar;
 				| '+': symbol := symPlus;
 				| '+': symbol := symPlus;
@@ -1908,6 +1920,7 @@ TYPE
 			PROCEDURE Reset;
 			PROCEDURE Reset;
 			BEGIN
 			BEGIN
 				position := orgPos;
 				position := orgPos;
+				IF useLineNumbers THEN line := orgPos END;
 				reader.SetPos(orgReaderPos);
 				reader.SetPos(orgReaderPos);
 				emitter.code.SetPC(orgCodePos);
 				emitter.code.SetPC(orgCodePos);
 				NextChar;
 				NextChar;
@@ -1964,9 +1977,11 @@ TYPE
 			END FixupLabels;
 			END FixupLabels;
 
 
 		BEGIN
 		BEGIN
+			prevAssembly := emitter.assembly;
 			prevSourceName := sourceName;
 			prevSourceName := sourceName;
 			prevCpuBits := emitter.cpuBits;
 			prevCpuBits := emitter.cpuBits;
 			prevCpuOptions := emitter.cpuOptions;
 			prevCpuOptions := emitter.cpuOptions;
+			emitter.assembly := SELF;
 
 
 			IF scope # NIL THEN
 			IF scope # NIL THEN
 				sourceName := scope.ownerModule.sourceName;
 				sourceName := scope.ownerModule.sourceName;
@@ -2002,7 +2017,7 @@ TYPE
 								RETURN
 								RETURN
 							END;
 							END;
 							IF ident # "SYSTEM" THEN
 							IF ident # "SYSTEM" THEN
-								Error("unsupported target identifier");
+								Error("unsupportorted target identifier");
 								RETURN
 								RETURN
 							END;
 							END;
 							IF symbol # symPeriod THEN
 							IF symbol # symPeriod THEN
@@ -2144,6 +2159,7 @@ TYPE
 			sourceName := prevSourceName;
 			sourceName := prevSourceName;
 			emitter.cpuBits := prevCpuBits;
 			emitter.cpuBits := prevCpuBits;
 			emitter.cpuOptions := prevCpuOptions;
 			emitter.cpuOptions := prevCpuOptions;
+			emitter.assembly := prevAssembly;
 		END Assemble;
 		END Assemble;
 
 
 	END Assembly;
 	END Assembly;

+ 2 - 1
source/FoxAMDBackend.Mod

@@ -4,7 +4,7 @@ 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, 
+	Diagnostics, Streams, Options, Strings, ObjectFileFormat := FoxBinaryObjectFile, Compiler,
 	Machine, D := Debugging, CodeGenerators := FoxCodeGenerators, ObjectFile;
 	Machine, D := Debugging, CodeGenerators := FoxCodeGenerators, ObjectFile;
 
 
 CONST
 CONST
@@ -3114,6 +3114,7 @@ TYPE
 			procedure := symbol(SyntaxTree.Procedure);
 			procedure := symbol(SyntaxTree.Procedure);
 			scope := procedure.procedureScope;
 			scope := procedure.procedureScope;
 			NEW(assembler,diagnostics,emitter);
 			NEW(assembler,diagnostics,emitter);
+			assembler.useLineNumbers := Compiler.UseLineNumbers IN backend.flags;
 			assembler.Assemble(reader,SHORT(instruction.op1.intValue),scope,in,in,module,procedure.access * SyntaxTree.Public # {}, procedure.isInline, map)	;
 			assembler.Assemble(reader,SHORT(instruction.op1.intValue),scope,in,in,module,procedure.access * SyntaxTree.Public # {}, procedure.isInline, map)	;
 			error := error OR assembler.error;
 			error := error OR assembler.error;
 
 

+ 2 - 1
source/FoxARMBackend.Mod

@@ -4,7 +4,7 @@ IMPORT
 	Basic := FoxBasic, SyntaxTree := FoxSyntaxTree, Global := FoxGlobal, Backend := FoxBackend, Sections := FoxSections,
 	Basic := FoxBasic, SyntaxTree := FoxSyntaxTree, Global := FoxGlobal, Backend := FoxBackend, Sections := FoxSections,
 	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, Compiler,
 	D := Debugging;
 	D := Debugging;
 
 
 CONST
 CONST
@@ -2645,6 +2645,7 @@ TYPE
 
 
 			NEW(assembler, diagnostics);
 			NEW(assembler, diagnostics);
 			scanner := Scanner.NewAssemblerScanner(module.moduleName(*module.module.sourceName*), reader, LONGINT(irInstruction.op1.intValue) (* ? *), diagnostics);
 			scanner := Scanner.NewAssemblerScanner(module.moduleName(*module.module.sourceName*), reader, LONGINT(irInstruction.op1.intValue) (* ? *), diagnostics);
+			scanner.useLineNumbers := Compiler.UseLineNumbers IN backend.flags;
 			assembler.InlineAssemble(scanner, in, scope, module);
 			assembler.InlineAssemble(scanner, in, scope, module);
 			error := error OR assembler.error
 			error := error OR assembler.error
 		END EmitAsm;
 		END EmitAsm;

+ 2 - 2
source/FoxCSharpFrontend.Mod

@@ -10,9 +10,9 @@ TYPE
 		scanner: Scanner.Scanner;
 		scanner: Scanner.Scanner;
 		parser: Parser.Parser;
 		parser: Parser.Parser;
 		
 		
-		PROCEDURE Initialize*(diagnostics: Diagnostics.Diagnostics; reader: Streams.Reader; CONST fileName: ARRAY OF CHAR; pos: LONGINT);
+		PROCEDURE Initialize*(diagnostics: Diagnostics.Diagnostics; flags: SET; reader: Streams.Reader; CONST fileName: ARRAY OF CHAR; pos: LONGINT);
 		BEGIN
 		BEGIN
-			Initialize^(diagnostics, reader, fileName, pos);
+			Initialize^(diagnostics, flags, reader, fileName, pos);
 			scanner := Scanner.NewScanner(fileName, reader, pos, diagnostics);
 			scanner := Scanner.NewScanner(fileName, reader, pos, diagnostics);
 			parser := Parser.NewParser( scanner, diagnostics );
 			parser := Parser.NewParser( scanner, diagnostics );
 		END Initialize;
 		END Initialize;

+ 3 - 5
source/FoxCompiler.Mod

@@ -23,6 +23,7 @@ CONST
 	ChangeCase*=12;
 	ChangeCase*=12;
 	Cooperative*=13;
 	Cooperative*=13;
 	CellsAreObjects*=14;
 	CellsAreObjects*=14;
+	UseLineNumbers*=15;
 
 
 	DefaultBackend = "AMD";
 	DefaultBackend = "AMD";
 	DefaultFrontend = "Oberon";
 	DefaultFrontend = "Oberon";
@@ -160,7 +161,7 @@ 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;
 
 
-		options.frontend.Initialize(diagnostics, reader, source, position);
+		options.frontend.Initialize(diagnostics, flags, reader, source, position);
 		REPEAT
 		REPEAT
 			(** first phase: scan and parse **)
 			(** first phase: scan and parse **)
 			module := options.frontend.Parse();
 			module := options.frontend.Parse();
@@ -428,12 +429,9 @@ 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 options.GetFlag("lineNumbers") THEN INCL(compilerOptions.flags, UseLineNumbers) END;
 		END;
 		END;
 
 
-		IF (compilerOptions.frontend # NIL) THEN
-			compilerOptions.frontend.lineNumbers := options.GetFlag("lineNumbers");
-		END;
-		
 		IF options.GetFlag("showOptions") THEN options.Show(error) END;
 		IF options.GetFlag("showOptions") THEN options.Show(error) END;
 		RETURN result
 		RETURN result
 	END GetOptions;
 	END GetOptions;

+ 5 - 4
source/FoxFrontend.Mod

@@ -6,17 +6,18 @@ IMPORT
 TYPE
 TYPE
 
 
 	Frontend* = OBJECT
 	Frontend* = OBJECT
-	VAR		
-		lineNumbers*: BOOLEAN;
+	VAR
+		flags-: SET;
 		
 		
 		PROCEDURE & InitFrontEnd*;
 		PROCEDURE & InitFrontEnd*;
 		BEGIN
 		BEGIN
-			Initialize(NIL, NIL, "", 0);
+			Initialize(NIL, {}, NIL, "", 0);
 		END InitFrontEnd;
 		END InitFrontEnd;
 		
 		
 		(* initialize frontend for usage *)
 		(* initialize frontend for usage *)
-		PROCEDURE Initialize*(diagnostics: Diagnostics.Diagnostics; reader: Streams.Reader;CONST fileName: ARRAY OF CHAR; pos: LONGINT);
+		PROCEDURE Initialize*(diagnostics: Diagnostics.Diagnostics; flags: SET; reader: Streams.Reader;CONST fileName: ARRAY OF CHAR; pos: LONGINT);
 		BEGIN
 		BEGIN
+			SELF.flags := flags;
 		END Initialize;
 		END Initialize;
 
 
 		PROCEDURE Parse*(): SyntaxTree.Module;
 		PROCEDURE Parse*(): SyntaxTree.Module;

+ 4 - 4
source/FoxOberonFrontend.Mod

@@ -1,7 +1,7 @@
 MODULE FoxOberonFrontend; (**  AUTHOR "fof"; PURPOSE "Oberon Compiler: Oberon frontend module";  **)
 MODULE FoxOberonFrontend; (**  AUTHOR "fof"; PURPOSE "Oberon Compiler: Oberon frontend module";  **)
 
 
 IMPORT
 IMPORT
-	Streams, Diagnostics,  SyntaxTree := FoxSyntaxTree, Parser := FoxParser, Scanner := FoxScanner,FoxFrontend;
+	Streams, Diagnostics,  SyntaxTree := FoxSyntaxTree, Parser := FoxParser, Scanner := FoxScanner,FoxFrontend, Compiler;
 
 
 TYPE
 TYPE
 
 
@@ -10,11 +10,11 @@ TYPE
 		scanner: Scanner.Scanner;
 		scanner: Scanner.Scanner;
 		parser: Parser.Parser;
 		parser: Parser.Parser;
 		
 		
-		PROCEDURE Initialize*(diagnostics: Diagnostics.Diagnostics; reader: Streams.Reader; CONST fileName: ARRAY OF CHAR; pos: LONGINT);
+		PROCEDURE Initialize*(diagnostics: Diagnostics.Diagnostics; flags: SET; reader: Streams.Reader; CONST fileName: ARRAY OF CHAR; pos: LONGINT);
 		BEGIN
 		BEGIN
-			Initialize^(diagnostics, reader, fileName, pos);
+			Initialize^(diagnostics, flags, reader, fileName, pos);
 			scanner := Scanner.NewScanner(fileName, reader, pos, diagnostics);
 			scanner := Scanner.NewScanner(fileName, reader, pos, diagnostics);
-			scanner.useLineNumbers := lineNumbers;
+			scanner.useLineNumbers := Compiler.UseLineNumbers IN flags;
 			parser := Parser.NewParser( scanner, diagnostics );
 			parser := Parser.NewParser( scanner, diagnostics );
 		END Initialize;
 		END Initialize;
 		
 		

+ 6 - 3
source/FoxScanner.Mod

@@ -318,7 +318,7 @@ TYPE
 			IF reader = NIL THEN ch := EOT ELSE 	GetNextCharacter END;
 			IF reader = NIL THEN ch := EOT ELSE 	GetNextCharacter END;
 			IF Trace THEN D.Str( "New scanner  " );   D.Ln;  END;
 			IF Trace THEN D.Str( "New scanner  " );   D.Ln;  END;
 			SELF.position := position;
 			SELF.position := position;
-			line := 0;
+			SELF.line := position;
 			useLineNumbers := FALSE;
 			useLineNumbers := FALSE;
 		END InitializeScanner;
 		END InitializeScanner;
 
 
@@ -814,6 +814,7 @@ TYPE
 			ASSERT(case # Unknown);
 			ASSERT(case # Unknown);
 			stringMaker.Clear;
 			stringMaker.Clear;
 			startPos := symbol.end;
 			startPos := symbol.end;
+			IF useLineNumbers THEN startPos := line END;
 			s := symbol.token;
 			s := symbol.token;
 			WHILE (s # EndOfText) & (s # End) & (s # With) DO
 			WHILE (s # EndOfText) & (s # End) & (s # With) DO
 				symbol.start := position;
 				symbol.start := position;
@@ -990,7 +991,7 @@ TYPE
 	END Scanner;
 	END Scanner;
 
 
 	Context*=RECORD
 	Context*=RECORD
-		position, readerPosition : LONGINT;
+		position, readerPosition, line : LONGINT;
 		ch: CHAR;
 		ch: CHAR;
 	END;
 	END;
 
 
@@ -1023,6 +1024,7 @@ TYPE
 		BEGIN
 		BEGIN
 			context.ch := ch;
 			context.ch := ch;
 			context.position := position;
 			context.position := position;
+			context.line := line;
 			context.readerPosition := reader.Pos();
 			context.readerPosition := reader.Pos();
 		END GetContext;
 		END GetContext;
 
 
@@ -1030,6 +1032,7 @@ TYPE
 		BEGIN
 		BEGIN
 			reader.SetPos(context.readerPosition);
 			reader.SetPos(context.readerPosition);
 			ch := context.ch;
 			ch := context.ch;
+			line := context.line;
 			position := context.position;
 			position := context.position;
 		END SetContext;
 		END SetContext;
 
 
@@ -1160,7 +1163,7 @@ TYPE
 						IF ch = '*' THEN GetNextCharacter; ReadComment(symbol);  s := Comment; ELSE s := LeftParenthesis END
 						IF ch = '*' THEN GetNextCharacter; ReadComment(symbol);  s := Comment; ELSE s := LeftParenthesis END
 				| ')':     s := RightParenthesis;  GetNextCharacter
 				| ')':     s := RightParenthesis;  GetNextCharacter
 				| CR: GetNextCharacter; s := Ln;IF ch = LF THEN GetNextCharacter END;
 				| CR: GetNextCharacter; s := Ln;IF ch = LF THEN GetNextCharacter END;
-				| LF: GetNextCharacter; s := Ln;
+				| LF: GetNextCharacter; s := Ln; IF ch = CR THEN GetNextCharacter END;
 				| '*':    s := Times; GetNextCharacter;
 				| '*':    s := Times; GetNextCharacter;
 				| '+':    s := Plus ; GetNextCharacter;
 				| '+':    s := Plus ; GetNextCharacter;
 				| ',':     s := Comma;  GetNextCharacter
 				| ',':     s := Comma;  GetNextCharacter

+ 2 - 1
source/FoxTRMBackend.Mod

@@ -5,7 +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,
-	CodeGenerators := FoxCodeGenerators, D := Debugging;
+	CodeGenerators := FoxCodeGenerators, D := Debugging, Compiler;
 
 
 CONST
 CONST
 	TraceFixups = FALSE;
 	TraceFixups = FALSE;
@@ -2183,6 +2183,7 @@ TYPE
 
 
 			NEW(assembler, diagnostics, backend.capabilities,instructionSet );
 			NEW(assembler, diagnostics, backend.capabilities,instructionSet );
 			scanner := Scanner.NewAssemblerScanner(module.moduleName(*module.module.sourceName*), reader, SHORT(instr.op1.intValue), diagnostics);
 			scanner := Scanner.NewAssemblerScanner(module.moduleName(*module.module.sourceName*), reader, SHORT(instr.op1.intValue), diagnostics);
+			scanner.useLineNumbers := Compiler.UseLineNumbers IN backend.flags;
 			assembler.InlineAssemble(scanner, in, scope, module);
 			assembler.InlineAssemble(scanner, in, scope, module);
 			error := error OR assembler.error
 			error := error OR assembler.error
 		END EmitAsm;
 		END EmitAsm;

+ 15 - 8
source/StdIOShell.Mod

@@ -56,8 +56,10 @@ SystemTools.DoCommands
 		FoxActiveCells.Mod FoxHardware.Mod FoxFormats.Mod FoxPrintout.Mod
 		FoxActiveCells.Mod FoxHardware.Mod FoxFormats.Mod FoxPrintout.Mod
 		FoxParser.Mod FoxCSharpParser.Mod  FoxSemanticChecker.Mod
 		FoxParser.Mod FoxCSharpParser.Mod  FoxSemanticChecker.Mod
 		FoxBackend.Mod FoxSections.Mod 
 		FoxBackend.Mod FoxSections.Mod 
-		FoxFrontend.Mod FoxOberonFrontend.Mod FoxCSharpFrontend.Mod
-		FoxCompiler.Mod FoxFingerPrinter.Mod  FoxInterfaceComparison.Mod FoxTextualSymbolFile.Mod FoxBinarySymbolFile.Mod
+		FoxFrontend.Mod 
+		FoxCompiler.Mod 
+		FoxOberonFrontend.Mod FoxCSharpFrontend.Mod
+		FoxFingerPrinter.Mod  FoxInterfaceComparison.Mod FoxTextualSymbolFile.Mod FoxBinarySymbolFile.Mod
 		FoxBinaryCode.Mod FoxIntermediateCode.Mod FoxIntermediateBackend.Mod FoxCodeGenerators.Mod
 		FoxBinaryCode.Mod FoxIntermediateCode.Mod FoxIntermediateBackend.Mod FoxCodeGenerators.Mod
 		FoxBinaryObjectFile.Mod FoxGenericObjectFile.Mod
 		FoxBinaryObjectFile.Mod FoxGenericObjectFile.Mod
 		FoxAMD64InstructionSet.Mod FoxAMD64Assembler.Mod FoxAMDBackend.Mod
 		FoxAMD64InstructionSet.Mod FoxAMD64Assembler.Mod FoxAMDBackend.Mod
@@ -92,8 +94,9 @@ SystemTools.DoCommands
 		FoxParser  FoxSemanticChecker
 		FoxParser  FoxSemanticChecker
 		FoxBackend FoxSections 
 		FoxBackend FoxSections 
 		
 		
-		FoxFrontend FoxOberonFrontend 
-		Compiler FoxFingerPrinter FoxInterfaceComparison FoxTextualSymbolFile FoxBinarySymbolFile
+		FoxFrontend
+		Compiler  FoxOberonFrontend 
+		FoxFingerPrinter FoxInterfaceComparison FoxTextualSymbolFile FoxBinarySymbolFile
 		
 		
 		FoxBinaryCode FoxIntermediateCode FoxIntermediateBackend FoxCodeGenerators
 		FoxBinaryCode FoxIntermediateCode FoxIntermediateBackend FoxCodeGenerators
 		FoxBinaryObjectFile FoxGenericObjectFile
 		FoxBinaryObjectFile FoxGenericObjectFile
@@ -143,8 +146,10 @@ SystemTools.DoCommands
 		FoxActiveCells.Mod FoxHardware.Mod FoxFormats.Mod FoxPrintout.Mod
 		FoxActiveCells.Mod FoxHardware.Mod FoxFormats.Mod FoxPrintout.Mod
 		FoxParser.Mod FoxCSharpParser.Mod  FoxSemanticChecker.Mod
 		FoxParser.Mod FoxCSharpParser.Mod  FoxSemanticChecker.Mod
 		FoxBackend.Mod FoxSections.Mod 
 		FoxBackend.Mod FoxSections.Mod 
-		FoxFrontend.Mod FoxOberonFrontend.Mod FoxCSharpFrontend.Mod
-		FoxCompiler.Mod FoxFingerPrinter.Mod  FoxInterfaceComparison.Mod FoxTextualSymbolFile.Mod FoxBinarySymbolFile.Mod
+		FoxFrontend.Mod
+		FoxCompiler.Mod 
+		FoxOberonFrontend.Mod FoxCSharpFrontend.Mod
+		FoxFingerPrinter.Mod  FoxInterfaceComparison.Mod FoxTextualSymbolFile.Mod FoxBinarySymbolFile.Mod
 		FoxBinaryCode.Mod FoxIntermediateCode.Mod FoxIntermediateBackend.Mod FoxCodeGenerators.Mod
 		FoxBinaryCode.Mod FoxIntermediateCode.Mod FoxIntermediateBackend.Mod FoxCodeGenerators.Mod
 		FoxBinaryObjectFile.Mod FoxGenericObjectFile.Mod
 		FoxBinaryObjectFile.Mod FoxGenericObjectFile.Mod
 		FoxAMD64InstructionSet.Mod FoxAMD64Assembler.Mod FoxAMDBackend.Mod
 		FoxAMD64InstructionSet.Mod FoxAMD64Assembler.Mod FoxAMDBackend.Mod
@@ -181,8 +186,10 @@ SystemTools.DoCommands
 		FoxParser  FoxSemanticChecker
 		FoxParser  FoxSemanticChecker
 		FoxBackend FoxSections 
 		FoxBackend FoxSections 
 		
 		
-		FoxFrontend FoxOberonFrontend 
-		Compiler FoxFingerPrinter FoxInterfaceComparison FoxTextualSymbolFile FoxBinarySymbolFile
+		FoxFrontend
+		Compiler 
+		FoxOberonFrontend 
+		FoxFingerPrinter FoxInterfaceComparison FoxTextualSymbolFile FoxBinarySymbolFile
 		FoxBinaryCode FoxIntermediateCode FoxIntermediateBackend FoxCodeGenerators
 		FoxBinaryCode FoxIntermediateCode FoxIntermediateBackend FoxCodeGenerators
 		FoxBinaryObjectFile FoxGenericObjectFile
 		FoxBinaryObjectFile FoxGenericObjectFile
 		FoxAMD64InstructionSet FoxAMD64Assembler FoxAMDBackend
 		FoxAMD64InstructionSet FoxAMD64Assembler FoxAMDBackend