Browse Source

Added basic support for conditional compilation

The compiler accepts a new optional called --define which contains a comma-separated list of identifiers which can be used to conditionally compile blocks of arbitrary code according to the following syntax:

    Block = '#' 'if' Expression 'then' Block { '#' 'elsif' Expression 'then' Block } ['#' 'else' Block] '#' 'end' | any other token until next new line.
    Expression = Term {'or' Term}.
    Term = Factor {'&' Factor}.
    Factor = Identifier | '~' Factor | '(' Expression ')'.

Identifiers in conditional if and elsif statements yield a Boolean value indicating whether they have been defined when invoking the compiler, but they are not available in normal Oberon code. Conditional statements begin with a # sign on separate lines and are designed to combine code blocks for different platforms and architectures; They are not meant to provide a generic macro replacement mechanism as preprocessors do.

git-svn-id: https://svn.inf.ethz.ch/svn/lecturers/a2/trunk@8167 8c9fc860-2736-0410-a75d-ab315db34111
negelef 7 years ago
parent
commit
2b14a3f3f3

+ 5 - 2
source/Compiler.Mod

@@ -42,6 +42,7 @@ TYPE
 		srcPath, destPath: Files.FileName;
 		replacements: SemanticChecker.Replacement;
 		platformCallingConvention: SyntaxTree.CallingConvention;
+		definitions: Options.Parameter;
 	END;
 
 	PROCEDURE ParseReplacements(CONST filename: ARRAY OF CHAR; VAR replacement: SemanticChecker.Replacement; diagnostics: Diagnostics.Diagnostics): BOOLEAN;
@@ -56,7 +57,7 @@ TYPE
 		ELSE
 
 			scanner := Scanner.NewScanner(filename, reader, 0, diagnostics);
-			NEW(parser, scanner, diagnostics);
+			NEW(parser, scanner, diagnostics, "");
 
 			REPEAT (* WHILE parser.Peek(Scanner.Identifier) DO*)
 				identifier := parser.QualifiedIdentifier();
@@ -156,7 +157,7 @@ TYPE
 
 		IF (options.objectFile # NIL) & (options.objectFile.ForceModuleBodies()) THEN INCL(flags, ForceModuleBodies) END;
 
-		options.frontend.Initialize(diagnostics, flags, reader, source, position);
+		options.frontend.Initialize(diagnostics, flags, reader, source, options.definitions, position);
 		REPEAT
 			(** first phase: scan and parse **)
 			module := options.frontend.Parse();
@@ -307,6 +308,7 @@ TYPE
 		options.Add(0X,"replacements", Options.String);
 		options.Add(0X,"cooperative", Options.Flag);
 		options.Add(0X,"platformCC",Options.String);
+		options.Add("d","define",Options.String);
 
 		position := input.Pos();
 		parsed := options.ParseStaged(input, error);
@@ -426,6 +428,7 @@ TYPE
 			IF compilerOptions.objectFile # NIL THEN compilerOptions.objectFile.GetOptions(options) END;
 			IF compilerOptions.documentation # NIL THEN compilerOptions.documentation.GetOptions(options) END;
 			IF options.GetFlag("lineNumbers") THEN INCL(compilerOptions.flags, UseLineNumbers) END;
+			IF ~options.GetString("define", compilerOptions.definitions) THEN compilerOptions.definitions := "" END;
 			IF options.GetString("platformCC", name) THEN
 				IF name = Global.StringC THEN compilerOptions.platformCallingConvention := SyntaxTree.CCallingConvention
 				ELSIF name = Global.StringWinAPI THEN compilerOptions.platformCallingConvention := SyntaxTree.WinAPICallingConvention

+ 1 - 0
source/Fox.Tool

@@ -66,6 +66,7 @@ compiler options:
 	-S	--sourcePath	string	specification of a source path
 	-D --destPath		string	specification of a destination path
 	-p 	--platform		string	compiler options for platforms such as ARMA2, Win32, defined in Compiler.Mod
+	-d	--define	string	define comma-separated identifiers for conditional compilation
 
 backend options (intermediate and AMD)
 		--trace			string	display trace information for sections (--trace=* : all sections)

+ 3 - 3
source/FoxCSharpFrontend.Mod

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

+ 3 - 3
source/FoxFrontend.Mod

@@ -11,11 +11,11 @@ TYPE
 		
 		PROCEDURE & InitFrontEnd*;
 		BEGIN
-			Initialize(NIL, {}, NIL, "", 0);
+			Initialize(NIL, {}, NIL, "", "", 0);
 		END InitFrontEnd;
 		
 		(* initialize frontend for usage *)
-		PROCEDURE Initialize*(diagnostics: Diagnostics.Diagnostics; flags: SET; reader: Streams.Reader;CONST fileName: ARRAY OF CHAR; pos: LONGINT);
+		PROCEDURE Initialize*(diagnostics: Diagnostics.Diagnostics; flags: SET; reader: Streams.Reader;CONST fileName, definitions: ARRAY OF CHAR; pos: LONGINT);
 		BEGIN
 			SELF.flags := flags;
 		END Initialize;
@@ -71,4 +71,4 @@ TYPE
 		ASSERT(b);
 	END Assert;
 
-END FoxFrontend.
+END FoxFrontend.

+ 4 - 4
source/FoxOberonFrontend.Mod

@@ -10,12 +10,12 @@ TYPE
 		scanner: Scanner.Scanner;
 		parser: Parser.Parser;
 		
-		PROCEDURE Initialize*(diagnostics: Diagnostics.Diagnostics; flags: SET; reader: Streams.Reader; CONST fileName: ARRAY OF CHAR; pos: LONGINT);
+		PROCEDURE Initialize*(diagnostics: Diagnostics.Diagnostics; flags: SET; reader: Streams.Reader; CONST fileName, definitions: ARRAY OF CHAR; pos: LONGINT);
 		BEGIN
-			Initialize^(diagnostics, flags, reader, fileName, pos);
+			Initialize^(diagnostics, flags, reader, fileName, definitions, pos);
 			scanner := Scanner.NewScanner(fileName, reader, pos, diagnostics);
 			scanner.useLineNumbers := Compiler.UseLineNumbers IN flags;
-			parser := Parser.NewParser( scanner, diagnostics );
+			parser := Parser.NewParser( scanner, diagnostics, definitions );
 		END Initialize;
 		
 		PROCEDURE Parse*(): SyntaxTree.Module;
@@ -44,4 +44,4 @@ TYPE
 	END Get;
 
 
-END FoxOberonFrontend.
+END FoxOberonFrontend.

+ 129 - 10
source/FoxParser.Mod

@@ -1,7 +1,7 @@
 MODULE FoxParser;   (**  AUTHOR "fof & fn"; PURPOSE "Oberon Compiler: Parser";  **)
 (* (c) fof ETH Zurich, 2009 *)
 
-IMPORT Basic := FoxBasic, Scanner := FoxScanner, D := Debugging, SyntaxTree := FoxSyntaxTree, Global := FoxGlobal,  Diagnostics;
+IMPORT Basic := FoxBasic, Scanner := FoxScanner, D := Debugging, SyntaxTree := FoxSyntaxTree, Global := FoxGlobal, Diagnostics, Streams, Strings, StringPool;
 
 CONST
 	Trace = FALSE;	
@@ -182,6 +182,14 @@ TYPE
 		hasSymbol: BOOLEAN;
 		prevPosition-: Position;
 
+		(* conditional compilation *)
+		CONST Processing = 0; ProcessingElse = 1; Skipping = 2; Ignoring = 3; IgnoringElse = 4;
+
+		VAR conditional: WORD;
+		VAR conditionals: ARRAY 10 OF WORD;
+		VAR definitions: ARRAY 10 OF Scanner.IdentifierType;
+		VAR conditionalCount, definitionCount: SIZE;
+
 		PROCEDURE S( CONST s: ARRAY OF CHAR );   (* for debugging purposes only *)
 		VAR i: LONGINT;
 		BEGIN
@@ -209,11 +217,30 @@ TYPE
 		END EE;
 
 		(** constructor, init parser with scanner providing input and with diagnostics for error output *)
-		PROCEDURE & Init*( scanner: Scanner.Scanner; diagnostics: Diagnostics.Diagnostics );
+		PROCEDURE & Init*( scanner: Scanner.Scanner; diagnostics: Diagnostics.Diagnostics; CONST definitions: ARRAY OF CHAR );
+		VAR begin, end: LONGINT (* SIZE! *); definition: ARRAY 32 OF CHAR;
 		BEGIN
+			conditional := Processing;
+			conditionalCount := 0;
+			definitionCount := 0;
+			begin := 0;
+			REPEAT
+				end := Strings.Find (definitions, begin, ',');
+				IF end # -1 THEN
+					Strings.Copy (definitions, begin, end - begin, definition);
+					begin := end + 1;
+				ELSE
+					Strings.Copy (definitions, begin, Strings.Length (definitions) - begin, definition);
+				END;
+				IF definition # "" THEN
+					StringPool.GetIndex (definition, SELF.definitions[definitionCount]);
+					INC (definitionCount);
+				END;
+			UNTIL end = -1;
+
 			SELF.scanner := scanner;
 			SELF.diagnostics := diagnostics;
-			error := ~scanner.GetNextSymbol(symbol);
+			error := ~GetNextSymbol(symbol);
 			hasSymbol := TRUE;
 			IF error THEN Basic.Error(diagnostics, scanner.source^, Basic.invalidPosition, "no input stream") END;
 			recentCommentItem := NIL; recentComment := NIL;
@@ -241,6 +268,97 @@ TYPE
 			error := TRUE
 		END Error;
 
+		(* conditional compilation according to the following syntax *)
+		(* Block = '#' 'if' Expression 'then' Block { '#' 'elsif' Expression 'then' Block } ['#' 'else' Block] '#' 'end' | any token until next new line. *)
+		PROCEDURE GetNextSymbol(VAR symbol: Scanner.Symbol): BOOLEAN;
+		VAR line: Streams.Position; value: BOOLEAN;
+
+			(* Factor = Identifier | '~' Factor | '(' Expression ')'. *)
+			PROCEDURE Factor (VAR value: BOOLEAN): BOOLEAN;
+			VAR i: SIZE;
+			BEGIN
+				IF symbol.token = Scanner.Identifier THEN
+					value := FALSE; i := 0;
+					WHILE (i # definitionCount) & ~value DO value := symbol.identifier = definitions[i]; INC (i) END;
+					IF ~scanner.GetNextSymbol (symbol) THEN RETURN FALSE END;
+				ELSIF symbol.token = Scanner.Not THEN
+					IF ~scanner.GetNextSymbol (symbol) THEN RETURN FALSE END;
+					IF ~Factor (value) THEN RETURN FALSE END;
+					value := ~value;
+				ELSIF symbol.token = Scanner.LeftParenthesis THEN
+					IF ~scanner.GetNextSymbol (symbol) THEN RETURN FALSE END;
+					IF ~Expression (value) THEN RETURN FALSE END;
+					IF symbol.token # Scanner.RightParenthesis THEN Error (symbol.position, Scanner.RightParenthesis, ""); RETURN FALSE END;
+					IF ~scanner.GetNextSymbol (symbol) THEN RETURN FALSE END;
+				ELSE
+					Error (symbol.position, Scanner.Identifier, ""); RETURN FALSE;
+				END;
+				RETURN TRUE;
+			END Factor;
+
+			(* Term = Factor {'&' Factor}. *)
+			PROCEDURE Term (VAR value: BOOLEAN): BOOLEAN;
+			VAR next: BOOLEAN;
+			BEGIN
+				IF ~Factor (value) THEN RETURN FALSE END;
+				WHILE symbol.token = Scanner.And DO
+					IF ~scanner.GetNextSymbol (symbol) THEN RETURN FALSE END;
+					IF ~Factor (next) THEN RETURN FALSE END;
+					IF ~next THEN value := FALSE END;
+				END;
+				RETURN TRUE;
+			END Term;
+
+			(* Expression = Term {'or' Term}. *)
+			PROCEDURE Expression (VAR value: BOOLEAN): BOOLEAN;
+			VAR next: BOOLEAN;
+			BEGIN
+				IF ~Term (value) THEN RETURN FALSE END;
+				WHILE symbol.token = Scanner.Or DO
+					IF ~scanner.GetNextSymbol (symbol) THEN RETURN FALSE END;
+					IF ~Term (next) THEN RETURN FALSE END;
+					IF next THEN value := TRUE END;
+				END;
+				RETURN TRUE;
+			END Expression;
+
+		BEGIN
+			LOOP
+				line := symbol.position.line;
+				IF ~scanner.GetNextSymbol (symbol) THEN RETURN FALSE END;
+				IF (symbol.token = Scanner.Unequal) & (symbol.position.line # line) THEN
+					IF ~scanner.GetNextSymbol (symbol) THEN RETURN FALSE END;
+					IF symbol.token = Scanner.If THEN
+						IF ~scanner.GetNextSymbol (symbol) THEN RETURN FALSE END;
+						IF ~Expression (value) THEN RETURN FALSE END;
+						IF symbol.token # Scanner.Then THEN Error (symbol.position, Scanner.Then, ""); RETURN FALSE END;
+						conditionals[conditionalCount] := conditional; INC (conditionalCount);
+						IF (conditional # Processing) & (conditional # ProcessingElse) THEN conditional := Ignoring;
+						ELSIF value THEN conditional := Processing ELSE conditional := Skipping;
+						END;
+					ELSIF symbol.token = Scanner.Elsif THEN
+						IF ~scanner.GetNextSymbol (symbol) THEN RETURN FALSE END;
+						IF ~Expression (value) THEN RETURN FALSE END;
+						IF symbol.token # Scanner.Then THEN Error (symbol.position, Scanner.Then, ""); RETURN FALSE END;
+						IF (conditional = Processing) & (conditionalCount # 0) OR (conditional = Ignoring) THEN conditional := Ignoring;
+						ELSIF conditional = Skipping THEN IF value THEN conditional := Processing ELSE conditional := Skipping END;
+						ELSE Error(symbol.position,Basic.InvalidCode,"invalid conditional elsif"); RETURN FALSE END;
+					ELSIF symbol.token = Scanner.Else THEN
+						IF (conditional = Processing) & (conditionalCount # 0) OR (conditional = Ignoring) THEN conditional := IgnoringElse;
+						ELSIF conditional = Skipping THEN conditional := ProcessingElse;
+						ELSE Error(symbol.position,Basic.InvalidCode,"invalid conditional else"); RETURN FALSE END;
+					ELSIF symbol.token = Scanner.End THEN
+						IF conditionalCount # 0 THEN DEC (conditionalCount); conditional := conditionals[conditionalCount];
+						ELSE Error(symbol.position,Basic.InvalidCode,"invalid conditional end"); RETURN FALSE END;
+					ELSE
+						Error(symbol.position,Basic.InvalidCode,"invalid conditional statement"); RETURN FALSE;
+					END;
+				ELSIF (conditional = Processing) OR (conditional = ProcessingElse) THEN
+					RETURN TRUE;
+				END;
+			END;
+		END GetNextSymbol;
+
 		(** helper procedures interfacing to the scanner **)
 
 		PROCEDURE SkipComments(b: BOOLEAN);
@@ -283,7 +401,7 @@ TYPE
 					END;
 				END;
 				NextSymbol;
-				(*error := ~scanner.GetNextSymbol(symbol);*)
+				(*error := ~GetNextSymbol(symbol);*)
 			END;
 		END SkipComments;
 
@@ -291,7 +409,7 @@ TYPE
 		PROCEDURE NextSymbol*;
 		BEGIN
 			(*
-				error := ~scanner.GetNextSymbol(symbol) OR error;
+				error := ~GetNextSymbol(symbol) OR error;
 				hasSymbol := TRUE;
 				SkipComments();
 			*)
@@ -302,9 +420,9 @@ TYPE
 		BEGIN
 			IF ~hasSymbol OR (symbol.token = Scanner.Escape) THEN
 				prevPosition := symbol.position;
-				error := ~scanner.GetNextSymbol(symbol) OR error;
+				error := ~GetNextSymbol(symbol) OR error;
 				IF symbol.token = Scanner.Escape THEN 
-					error := ~scanner.GetNextSymbol(symbol) OR error;
+					error := ~GetNextSymbol(symbol) OR error;
 				END;
 				hasSymbol := TRUE;
 				SkipComments(FALSE);
@@ -317,7 +435,7 @@ TYPE
 		BEGIN
 			IF ~hasSymbol THEN
 				prevPosition := symbol.position;
-				error := ~scanner.GetNextSymbol(symbol) OR error;
+				error := ~GetNextSymbol(symbol) OR error;
 				hasSymbol := TRUE;
 				SkipComments(TRUE);
 			END;
@@ -2306,6 +2424,7 @@ TYPE
 					*)
 				END;
 			END;
+			IF conditionalCount # 0 THEN Error (symbol.position, Basic.InvalidCode, "missing conditional end"); error := TRUE END;
 			IF Trace THEN E( "Module" ) END;
 			RETURN module
 		END Module;
@@ -2335,10 +2454,10 @@ TYPE
 	END AppendModifier;
 
 	(** parser retrieval **)
-	PROCEDURE NewParser*( scanner: Scanner.Scanner;  diagnostics: Diagnostics.Diagnostics): Parser;
+	PROCEDURE NewParser*( scanner: Scanner.Scanner;  diagnostics: Diagnostics.Diagnostics; CONST definitions: ARRAY OF CHAR): Parser;
 	VAR parser: Parser;
 	BEGIN
-		NEW( parser, scanner, diagnostics );  RETURN parser;
+		NEW( parser, scanner, diagnostics, definitions );  RETURN parser;
 	END NewParser;
 
 END FoxParser.

+ 1 - 1
source/FoxTextualSymbolFile.Mod

@@ -20,7 +20,7 @@ TYPE
 			reader := Basic.GetFileReader(fileName);
 			scanner := Scanner.NewScanner(moduleFileName, reader, 0, diagnostics);
 			IF ~scanner.error THEN
-				parser := Parser.NewParser(scanner,NIL);
+				parser := Parser.NewParser(scanner,NIL, "");
 				module := parser.Module();
 				IF parser.error THEN module := NIL END;
 			END;

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

@@ -9,7 +9,7 @@ BEGIN
 	reader := FoxBasic.GetFileReader (moduleName);
 	IF reader = NIL THEN diagnostics.Error (moduleName, Streams.Invalid, "Failed to open module"); RETURN FALSE END;
 	scanner := FoxScanner.NewScanner (moduleName, reader, 0, diagnostics);
-	NEW (parser, scanner, diagnostics);
+	NEW (parser, scanner, diagnostics, "");
 	module := parser.Module ();
 	IF parser.error THEN RETURN FALSE END;
 	FoxGlobal.ModuleFileName (module.name, module.context, string);