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

Removed priority from generic sections (replaced by section types)
priority (actually: placement) rules should only occur at the level of the linker
This change implies a change of the object file format which is caught by handling the version number (new version 5)
To rebuild the release it is required to
- compile and link a new system with the old compiler and linker (use linker once first before compiling in order to keep old version). The new system will incorporate the new compiler and new version of the objectfile binary but compiled with old object file format
- compile and link a new system on top of the new system, it will then be compiled and linked using the new object file format.

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

felixf 7 жил өмнө
parent
commit
4e4e439576

+ 1 - 1
source/FoxAMD64Assembler.Mod

@@ -2746,7 +2746,7 @@ TYPE
 		InitOperand(op1); InitOperand(op2); InitOperand(op3);
 		NEW(diagnostics,context.error);
 		Basic.ToSegmentedName("test", pooledName);
-		NEW(code,Sections.CodeSection,8,0,pooledName,TRUE,TRUE);
+		NEW(code,Sections.CodeSection,8,pooledName,TRUE,TRUE);
 		NEW(assembly,diagnostics);
 		assembly.SetCode(code);
 		InitRegister(op1,InstructionSet.regEAX);

+ 1 - 1
source/FoxAMDBackend.Mod

@@ -3566,7 +3566,7 @@ TYPE
 	VAR section: BinaryCode.Section;
 	BEGIN
 		IF in.resolved = NIL THEN
-			NEW(section,in.type, in.priority, 8, in.name,in.comments # NIL,FALSE);
+			NEW(section,in.type, 8, in.name,in.comments # NIL,FALSE);
 			section.SetAlignment(in.fixed, in.positionOrAlignment);
 			in.SetResolved(section);
 		ELSE

+ 1 - 1
source/FoxARMBackend.Mod

@@ -3806,7 +3806,7 @@ VAR
 		result: BinaryCode.Section;
 	BEGIN
 		IF irSection.resolved = NIL THEN
-			NEW(result, irSection.type, irSection.priority, 8, irSection.name, irSection.comments # NIL, FALSE);
+			NEW(result, irSection.type, 8, irSection.name, irSection.comments # NIL, FALSE);
 
 			(* set fixed position or alignment
 			(also make sure that any section has an alignment of at least 4 bytes) *)

+ 3 - 4
source/FoxBinaryCode.Mod

@@ -205,7 +205,7 @@ TYPE
 		END GetPC;
 
 
-		PROCEDURE & InitBinarySection*(type: SHORTINT; priority: LONGINT; unit: LONGINT; CONST name:Basic.SegmentedName; dump: BOOLEAN; bigEndian: BOOLEAN);
+		PROCEDURE & InitBinarySection*(type: SHORTINT; unit: LONGINT; CONST name:Basic.SegmentedName; dump: BOOLEAN; bigEndian: BOOLEAN);
 		BEGIN
 			ASSERT(unit > 0);
 			ASSERT(unit <= 32); (* implementation restriction *)
@@ -230,7 +230,6 @@ TYPE
 			NEW(aliasList);
 			pc := 0;
 			os.fixed := FALSE;
-			SELF.os.priority := priority;
 		END InitBinarySection;
 
 		PROCEDURE Reset*;
@@ -733,10 +732,10 @@ TYPE
 		NEW(fixup,mode,fixupOffset,symbol,symbolOffset,displacement,scale,fixupPattern); RETURN fixup
 	END NewFixup;
 
-	PROCEDURE NewBinarySection*(type: SHORTINT; priority: LONGINT; unit: LONGINT; CONST name: Basic.SegmentedName; dump: BOOLEAN; bigEndian: BOOLEAN): Section;
+	PROCEDURE NewBinarySection*(type: SHORTINT; unit: LONGINT; CONST name: Basic.SegmentedName; dump: BOOLEAN; bigEndian: BOOLEAN): Section;
 	VAR binarySection: Section;
 	BEGIN
-		NEW(binarySection,type,priority, unit,name,dump,bigEndian); RETURN binarySection
+		NEW(binarySection,type,unit,name,dump,bigEndian); RETURN binarySection
 	END NewBinarySection;
 
 

+ 15 - 13
source/FoxGenericObjectFile.Mod

@@ -6,7 +6,7 @@ IMPORT
 	FingerPrinter := FoxFingerPrinter, Files, Options, ObjectFile, Diagnostics, SymbolFileFormat := FoxTextualSymbolFile, Strings, KernelLog, D := Debugging;
 
 CONST
-	Version = 4;
+	Version = 5;
 	Trace = FALSE;
 	TraceAliases = FALSE;
 	WarnDuplicateFingerprints = FALSE;
@@ -84,7 +84,7 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 					resolved := section(IntermediateCode.Section).resolved;
 					IF resolved = NIL THEN RETURN FALSE END;
 
-					IF (resolved # NIL)  & (resolved.pc # 0) & (~resolved.os.fixed) & (resolved.os.priority = 0) THEN
+					IF (resolved # NIL)  & (resolved.pc # 0) & (~resolved.os.fixed) THEN
 						IF section.type = ObjectFile.Code THEN
 							codeAlign := CommonAlignment(codeAlign, resolved.os.alignment);
 							ASSERT((codeUnit=0) OR (codeUnit = resolved.os.unit));
@@ -103,19 +103,19 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 				IF codeUnit > 0 THEN
 					sname := module.moduleName;
 					Basic.AppendToSegmentedName(sname,".@CodeSections");
-					codeSection := BinaryCode.NewBinarySection(ObjectFile.Code, 0, codeUnit, sname, FALSE, FALSE);
+					codeSection := BinaryCode.NewBinarySection(ObjectFile.Code, codeUnit, sname, FALSE, FALSE);
 					codeSection.SetAlignment(FALSE,codeAlign);
 				END;
 				IF dataUnit > 0 THEN
 					sname := module.moduleName;
 					Basic.AppendToSegmentedName(sname,".@DataSections");
-					dataSection := BinaryCode.NewBinarySection(ObjectFile.Data, 0, dataUnit, sname, FALSE, FALSE);
+					dataSection := BinaryCode.NewBinarySection(ObjectFile.Data, dataUnit, sname, FALSE, FALSE);
 					dataSection.SetAlignment(FALSE,dataAlign);
 				END;
 				IF constUnit > 0 THEN
 					sname := module.moduleName;
 					Basic.AppendToSegmentedName(sname,".@ConstSections");
-					constSection := BinaryCode.NewBinarySection(ObjectFile.Const, 0, constUnit, sname, FALSE, FALSE);
+					constSection := BinaryCode.NewBinarySection(ObjectFile.Const, constUnit, sname, FALSE, FALSE);
 					constSection.SetAlignment(FALSE,constAlign);
 				END;
 				(*TRACE(codeAlign, dataAlign, constAlign);*)
@@ -124,7 +124,7 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 					section := sections.GetSection(i);
 					resolved := section(IntermediateCode.Section).resolved;
 					exported := section(IntermediateCode.Section).exported;
-					IF (resolved # NIL) & (resolved.pc # 0) & (~resolved.os.fixed) & (resolved.os.priority = 0)  THEN
+					IF (resolved # NIL) & (resolved.pc # 0) & (~resolved.os.fixed)  THEN
 						IF section.type = ObjectFile.Code THEN
 							IF resolved.os.alignment # 0 THEN
 							codeSection.Align(resolved.os.alignment);
@@ -475,7 +475,7 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 	BEGIN NEW(objectFileFormat); RETURN objectFileFormat
 	END Get;
 
-	PROCEDURE ReadHeader(reader: Streams.Reader; VAR binary: BOOLEAN; VAR poolMap: ObjectFile.PoolMap; VAR offers, requires: ObjectFile.NameList);
+	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 version: LONGINT;
 	BEGIN
@@ -505,6 +505,7 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 				ObjectFile.ReadNameList(reader, requires, binary, poolMap);
 			END
 		END;
+		RETURN version;
 	END ReadHeader;
 
 	PROCEDURE WriteHeader(writer: Streams.Writer; binary: BOOLEAN; sections: Sections.SectionList; VAR poolMap: ObjectFile.PoolMap; offers, requires: ObjectFile.NameList; fingerPrinter:FingerPrinter.FingerPrinter);
@@ -604,16 +605,17 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 		fileName: Files.FileName; file: Files.File; reader: Files.Reader; writer: Streams.Writer;
 		section: ObjectFile.Section; binary: BOOLEAN; poolMap, poolMapDummy: ObjectFile.PoolMap;
 		offers, requires: ObjectFile.NameList;
+		version: LONGINT;
 	BEGIN
 		IF context.arg.GetString(fileName) THEN
 			file := Files.Old(fileName);
 			IF file # NIL THEN
 				NEW(reader,file,0);
 				writer := Basic.GetWriter(Basic.GetDebugWriter(fileName));
-				ReadHeader(reader, binary, poolMap, offers, requires);
+				version := ReadHeader(reader, binary, poolMap, offers, requires);
 				WriteHeader(writer, FALSE, NIL, poolMapDummy, offers, requires, NIL);
 				WHILE reader.Peek () # 0X DO
-					ObjectFile.ReadSection (reader, section,binary, poolMap);
+					ObjectFile.ReadSection (reader, version, section,binary, poolMap);
 					ObjectFile.WriteSection(writer, section, FALSE, NIL); (* textual *)
 					reader.SkipWhitespace;
 				END;
@@ -648,13 +650,13 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 				file := Files.Old(fileName);
 				IF file # NIL THEN
 					NEW(reader,file,0);
-					ReadHeader(reader, binary, poolMap,offers, requires);
+					version := ReadHeader(reader, binary, poolMap,offers, requires);
 					WHILE reader.Peek () # 0X DO
 						ObjectFile.InitSection(section);
-						ObjectFile.ReadSection (reader, section, binary, poolMap);
-						NEW(bs, SHORTINT(section.type) ,section.priority,section.unit,name, FALSE, FALSE);
+						ObjectFile.ReadSection (reader, version, section, binary, poolMap);
+						NEW(bs, SHORTINT(section.type) ,section.unit,name, FALSE, FALSE);
 						bs.os := section;
-						NEW(is, SHORTINT(bs.os.type), SHORTINT(bs.os.priority), bs.os.identifier.name,NIL, FALSE);
+						NEW(is, SHORTINT(bs.os.type),  bs.os.identifier.name,NIL, FALSE);
 						is.SetResolved(bs);
 						sectionList.AddSection(is);		
 						reader.SkipWhitespace;

+ 7 - 6
source/FoxIntermediateBackend.Mod

@@ -698,9 +698,12 @@ TYPE
 			ELSE
 				inline := FALSE;
 				IF x.isEntry OR x.isExit THEN
-					ir := implementationVisitor.NewSection(module.allSections, Sections.InitCodeSection, name,x,dump);
+					IF x.isEntry THEN
+						ir := implementationVisitor.NewSection(module.allSections, Sections.EntryCodeSection, name,x,dump);
+					ELSE
+						ir := implementationVisitor.NewSection(module.allSections, Sections.ExitCodeSection, name,x,dump);
+					END;
 					ir.SetExported(TRUE);
-					IF x.isEntry THEN ir.SetPriority(EntryPriority) ELSE ir.SetPriority(ExitPriority) END;
 				ELSE
 					ir := implementationVisitor.NewSection(module.allSections, Sections.CodeSection, name,x,dump);
 					ir.SetExported(IsExported(x) OR SemanticChecker.InMethodTable(x));
@@ -920,7 +923,6 @@ TYPE
 			Global.GetSymbolSegmentedName (procedure,name);
 			ir := implementationVisitor.NewSection(module.allSections, Sections.InitCodeSection, name,procedure,dump);
 			ir.SetExported(TRUE);
-			ir.SetPriority(InitPriority);
 			Global.GetSymbolSegmentedName (bodyProcedure,name);
 			IF (backend.newObjectFile OR backend.cooperative) & ~meta.simple THEN
 				implementationVisitor.currentScope := module.module.moduleScope;
@@ -945,9 +947,8 @@ TYPE
 			Global.GetSymbolSegmentedName (symbol,name);
 			Basic.RemoveSuffix(name);
 			Basic.SuffixSegmentedName(name, Basic.MakeString("@StackAllocation"));
-			ir := implementationVisitor.NewSection(module.allSections,Sections.InitCodeSection,name,NIL,dump);
+			ir := implementationVisitor.NewSection(module.allSections,Sections.EntryCodeSection,name,NIL,dump);
 			ir.SetExported(TRUE);
-			ir.SetPriority(FirstPriority);
 			IntermediateCode.InitImmediate(op,addressType,initStack);
 			ir.Emit(Mov(Basic.invalidPosition,implementationVisitor.sp,op));
 		END AddStackAllocation;
@@ -9863,7 +9864,7 @@ TYPE
 				ELSIF (sectionType = Sections.InlineCodeSection) & (x.procedureScope.body.code.inlineCode # NIL) THEN
 					bits := x.procedureScope.body.code.inlineCode;
 					source := NewSection(module.allSections, sectionType, name, x, commentPrintout # NIL);
-					binary := BinaryCode.NewBinarySection(source.type, source.priority, system.codeUnit, name, FALSE, FALSE);
+					binary := BinaryCode.NewBinarySection(source.type, system.codeUnit, name, FALSE, FALSE);
 					binary.CopyBits(bits, 0, bits.GetSize());
 					source.SetResolved(binary);
 				ELSE

+ 3 - 3
source/FoxIntermediateCode.Mod

@@ -154,9 +154,9 @@ TYPE
 		BEGIN RETURN pc
 		END GetPC;
 
-		PROCEDURE & InitIntermediateSection*(type: SHORTINT; priority: INTEGER; CONST n: Basic.SegmentedName; symbol: SyntaxTree.Symbol; comment: BOOLEAN);
+		PROCEDURE & InitIntermediateSection*(type: SHORTINT; CONST n: Basic.SegmentedName; symbol: SyntaxTree.Symbol; comment: BOOLEAN);
 		BEGIN
-			InitSection(type,priority,n,symbol); (*InitArray;*) pc := 0; resolved := NIL;
+			InitSection(type,n,symbol); (*InitArray;*) pc := 0; resolved := NIL;
 			IF comment THEN NEW(comments,GetPC) ELSE comments := NIL END;
 			finally := -1;
 			sizeInUnits := NotYetCalculatedSize;
@@ -459,7 +459,7 @@ TYPE
 		ASSERT(name[0] > 0);
 
 		(* create a new section and enter it *)
-		NEW(section, type, 0 (* initial priority = 0 *), name, syntaxTreeSymbol, dump);
+		NEW(section, type, name, syntaxTreeSymbol, dump);
 		IF syntaxTreeSymbol # NIL THEN section.SetFingerprint(syntaxTreeSymbol.fingerprint.public) END;
 		list.AddSection(section);
 		RETURN section

+ 1 - 2
source/FoxIntermediateLinker.Mod

@@ -565,7 +565,7 @@ TYPE
 				IF GetPriority(leftSection) < GetPriority(rightSection) THEN
 					RETURN TRUE
 				ELSIF GetPriority(leftSection) = GetPriority(rightSection) THEN
-					RETURN (leftSection.priority < rightSection.priority) OR (leftSection.priority = rightSection.priority) & (leftSection.offset < rightSection.offset) (* must keep order as provided by loader *)
+					RETURN (leftSection.offset < rightSection.offset) (* must keep order as provided by loader *)
 				ELSE
 					RETURN FALSE
 				END
@@ -984,7 +984,6 @@ TYPE
 			copy.SetBitsPerUnit(section.bitsPerUnit);
 			copy.SetPositionOrAlignment(section.fixed, section.positionOrAlignment);
 			copy.SetFingerprint(section.fingerprint);
-			copy.SetPriority(section.priority);
 			FOR j := 0 TO section.pc-1 DO
 				instruction := section.instructions[j];
 				copy.Emit(instruction);

+ 1 - 4
source/FoxIntermediateObjectFile.Mod

@@ -128,7 +128,6 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 				SectionName(section.name);
 				w.RawBool(section.fixed);
 				w.RawNum(section.positionOrAlignment);
-				w.RawNum(section.priority);
 				w.RawNum(section.fingerprint);
 				w.RawNum(section.bitsPerUnit);
 
@@ -329,14 +328,13 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 				comment: BOOLEAN;
 				type: LONGINT;
 				fixed: BOOLEAN;
-				positionOrAlignment, priority, fingerprint, bitsPerUnit: LONGINT;
+				positionOrAlignment, fingerprint, bitsPerUnit: LONGINT;
 				pc,i: LONGINT;
 			BEGIN
 				r.RawLInt(type);
 				SectionName(name);
 				r.RawBool(fixed);
 				r.RawNum(positionOrAlignment);
-				r.RawNum(priority);
 				r.RawNum(fingerprint);
 				r.RawNum(bitsPerUnit);
 
@@ -351,7 +349,6 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 				END;
 				section.SetBitsPerUnit(bitsPerUnit);
 				section.SetFingerprint(fingerprint);
-				section.SetPriority(INTEGER(priority));
 				section.SetPositionOrAlignment(fixed, positionOrAlignment);
 
 				r.RawNum(pc);

+ 0 - 7
source/FoxIntermediateParser.Mod

@@ -400,13 +400,6 @@ TYPE
 					END
 
 				(* position *)
-				ELSIF ThisIdentifier("priority") & ExpectToken(Scanner.Equal) THEN
-					IF ExpectIntegerWithSign(integer) THEN
-						section.SetPriority(SHORT(integer));
-					ELSE
-						Error(positionOfProperty," invalid priority")
-					END;
-				(* alignment *)
 				ELSIF ThisIdentifier("aligned") & ExpectToken(Scanner.Equal) THEN
 					IF ExpectIntegerWithSign(integer) THEN
 						section.SetPositionOrAlignment(FALSE, integer)

+ 6 - 11
source/FoxSections.Mod

@@ -4,6 +4,8 @@ IMPORT SyntaxTree := FoxSyntaxTree,Streams,Global := FoxGlobal,Formats := FoxFor
 
 CONST
 	(* section categories *)
+	EntryCodeSection*=ObjectFile.EntryCode;
+	ExitCodeSection*=ObjectFile.ExitCode;
 	InitCodeSection*=ObjectFile.InitCode;
 	BodyCodeSection*=ObjectFile.BodyCode;
 	CodeSection*=ObjectFile.Code;
@@ -25,8 +27,7 @@ TYPE
 	Section*=OBJECT
 	VAR
 		name-: SectionName; (* name of this section (globally unique-name derived from symbol name) *)
-		type-: SHORTINT; (* CodeSection, InlineCodeSection, VarSection or ConstSection *)
-		priority-: INTEGER; (* priority of the section *)
+		type-: SHORTINT; (* CodeSection, InlineCodeSection, ...  *)
 
 		fixed-: BOOLEAN; (* whether the position of the section is fixed, as opposed to being restricted by an alignment *)
 		positionOrAlignment-: LONGINT; (* the alignment OR the position *)
@@ -42,12 +43,11 @@ TYPE
 		(* for linking *)
 		isReachable-: BOOLEAN;
 
-		PROCEDURE & InitSection*(type: SHORTINT; priority: INTEGER; CONST n: ObjectFile.SegmentedName; symbol: SyntaxTree.Symbol);
+		PROCEDURE & InitSection*(type: SHORTINT; CONST n: ObjectFile.SegmentedName; symbol: SyntaxTree.Symbol);
 		BEGIN
 			name := n;
 			SELF.symbol := symbol;
 			SELF.type := type;
-			SELF.priority := priority;
 			offset := 0;
 			referenced := TRUE;
 			fixed := FALSE;
@@ -101,14 +101,12 @@ TYPE
 		BEGIN SELF.type := type
 		END SetType;
 
-		PROCEDURE SetPriority*(priority: INTEGER);
-		BEGIN SELF.priority := priority
-		END SetPriority;
-
 		PROCEDURE Dump*(w: Streams.Writer);
 		BEGIN
 			w.String(".");
 			CASE type OF
+			| EntryCodeSection: w.String("entrycode")
+			| ExitCodeSection: w.String("exitcode")
 			| CodeSection: w.String("code")
 			| BodyCodeSection: w.String("bodycode")
 			| InlineCodeSection: w.String("inlinecode")
@@ -128,8 +126,6 @@ TYPE
 				w.String(" aligned="); w.Int(positionOrAlignment, 0)
 			END;
 
-			IF priority # 0 THEN w.String(" priority="); w.Int(priority,0) END;
-
 			IF fingerprint # 0 THEN w.String(" fingerprint="); w.Hex(fingerprint, -8) END;
 
 			IF bitsPerUnit # UnknownSize THEN w.String(" unit="); w.Int(bitsPerUnit, 0) END;
@@ -146,7 +142,6 @@ TYPE
 			Basic.WriteSegmentedName(w,name);
 			w.RawBool(fixed);
 			w.RawLInt(positionOrAlignment); 
-			w.RawLInt(priority);
 			w.RawLInt(fingerprint);
 			w.RawLInt(bitsPerUnit);
 		END WriteRaw;

+ 1 - 1
source/FoxTRMBackend.Mod

@@ -2502,7 +2502,7 @@ TYPE
 			END;
 
 			IF in.resolved = NIL THEN
-				NEW(section, in.type, in.priority, unit, in.name, in.comments # NIL, FALSE);
+				NEW(section, in.type, unit, in.name, in.comments # NIL, FALSE);
 				section.SetAlignment(in.fixed, in.positionOrAlignment);
 				in.SetResolved(section);
 			ELSE

+ 27 - 28
source/GenericLinker.Mod

@@ -9,9 +9,18 @@ CONST
 	InvalidAddress* = -1 (* MAX (Address) *);
 
 CONST
-	Fixed* = 0; InitCode*=1; BodyCode* = 2; Code* = 3; Data* = 4; Const* = 5; Empty* = 6;
+	Fixed* = 0; (* placed accroding to placement *)
+	EntryCode*= 1; (* must be placed before all other code *)
+	InitCode*=2; 
+	ExitCode*=3; (* must be placed after initcode but before code *)
+	BodyCode* = 4; 
+	Code* = 5; 
+	Data* = 6; 
+	Const* = 7; 
+	Empty* = 8; (* must be placed last *)
+	
 	UseAll *= {Fixed .. Empty};
-	UseInitCode*={Fixed, InitCode};
+	UseInitCode*={Fixed .. ExitCode};
 	UseAllButInitCode*={Fixed, BodyCode..Empty};
 
 TYPE
@@ -135,7 +144,7 @@ TYPE Block* = POINTER TO RECORD (ObjectFile.Section)
 	address*: Address;
 	aliasOf*: Block;
 	referenced, used: BOOLEAN;
-	prioType: LONGINT; (* priority cache *)
+	priority: LONGINT;
 END;
 
 TYPE Linker* = OBJECT
@@ -208,9 +217,9 @@ VAR
 	PROCEDURE Precedes* (this, that: Block): BOOLEAN;
 	VAR leftType, rightType: LONGINT;
 	BEGIN
-		leftType := this.prioType;
-		rightType := that.prioType;
-		RETURN (leftType < rightType) OR (leftType = rightType) & (this.priority < that.priority)
+		leftType := this.priority;
+		rightType := that.priority;
+		RETURN (leftType < rightType)
 	END Precedes;
 
 
@@ -220,7 +229,7 @@ VAR
 		IF FindBlock (section.identifier) # NIL THEN ObjectFile.SegmentedNameToString(section.identifier.name,name); Error (name, "duplicated section"); RETURN; END;
 		NEW (block); ObjectFile.CopySection (section, block^); block.address := InvalidAddress; block.referenced := FALSE; block.used := FALSE;
 		current := firstBlock; previous := NIL;
-		block.prioType := GetPriority(block);
+		block.priority := GetPriority(block);
 		WHILE (current # NIL) & ~Precedes(block,current) DO previous := current; current := current.next; END;
 		IF previous # NIL THEN previous.next := block; ELSE firstBlock := block; END; block.next := current;
 		hash.Put(block.identifier.name, block);
@@ -249,7 +258,7 @@ VAR
 		IF ~error THEN block := firstBlock;
 			WHILE (block # firstLinkedBlock) & ~error DO
 				ObjectFile.SegmentedNameToString(block.identifier.name, name);
-				used := (GetType (block) IN usedCategories) OR (linkRoot # "") & Strings.StartsWith(linkRoot,0,name) OR (block.aliases > 0);
+				used := (block.type IN usedCategories) OR (linkRoot # "") & Strings.StartsWith(linkRoot,0,name) OR (block.aliases > 0);
 				Reference (block, used); block := block.next;
 			END;
 		END;
@@ -450,23 +459,13 @@ VAR
 
 END Linker;
 
-PROCEDURE GetType*(block: Block): LONGINT;
-BEGIN
-	IF block.fixed THEN RETURN Fixed END;
-	IF block.type = ObjectFile.InitCode THEN RETURN InitCode END;
-	IF block.type = ObjectFile.BodyCode THEN RETURN BodyCode END;
-	IF block.bits.GetSize () = 0 THEN RETURN Empty END;
-	IF block.type = ObjectFile.Code THEN RETURN Code END;
-	IF block.type = ObjectFile.Data THEN RETURN Data END;
-	IF block.type = ObjectFile.Const THEN RETURN Const END;
-	HALT(100); (* undefined type *)
-END GetType;
-
 PROCEDURE GetPriority(block: Block): LONGINT;
 BEGIN
 	IF block.fixed THEN RETURN Fixed END;
 	IF block.type = ObjectFile.InitCode THEN RETURN InitCode END;
-	IF block.bits.GetSize () = 0 THEN RETURN Empty END;
+	IF block.type = ObjectFile.EntryCode THEN RETURN EntryCode END;
+	IF block.type = ObjectFile.ExitCode THEN RETURN ExitCode END;
+	IF (block.bits = NIL) OR (block.bits.GetSize () = 0) THEN RETURN Empty END;
 	IF block.type = ObjectFile.BodyCode THEN RETURN Code END;
 	IF block.type = ObjectFile.Code THEN RETURN Code END;
 	IF block.type = ObjectFile.Data THEN RETURN Code END;
@@ -474,7 +473,7 @@ BEGIN
 	HALT(100); (* undefined type *)
 END GetPriority;
 
-PROCEDURE Header(reader: Streams.Reader; linker: Linker; VAR binary: BOOLEAN; VAR poolMap: ObjectFile.PoolMap; VAR offers, requires: ObjectFile.NameList);
+PROCEDURE Header(reader: Streams.Reader; linker: Linker; VAR binary: BOOLEAN; VAR poolMap: ObjectFile.PoolMap; VAR offers, requires: ObjectFile.NameList): LONGINT;
 VAR ch: CHAR; version: LONGINT; string: ARRAY 32 OF CHAR;
 BEGIN
 	reader.String(string);
@@ -508,21 +507,21 @@ BEGIN
 			ObjectFile.ReadNameList(reader, requires, binary, poolMap);
 		END
 	END;
-
+	RETURN version;
 END Header;
 
 PROCEDURE OffersRequires*(reader: Streams.Reader; VAR offers, requires: ObjectFile.NameList);
-VAR section: ObjectFile.Section; binary: BOOLEAN; poolMap: ObjectFile.PoolMap; 
+VAR section: ObjectFile.Section; binary: BOOLEAN; poolMap: ObjectFile.PoolMap;  version: LONGINT;
 BEGIN
-	Header(reader, NIL, binary, poolMap, offers, requires);
+	version := Header(reader, NIL, binary, poolMap, offers, requires);
 END OffersRequires;
 
 PROCEDURE Process* (reader: Streams.Reader; linker: Linker);
-VAR section: ObjectFile.Section; binary: BOOLEAN; poolMap: ObjectFile.PoolMap; offers, requires: ObjectFile.NameList;
+VAR section: ObjectFile.Section; binary: BOOLEAN; poolMap: ObjectFile.PoolMap; offers, requires: ObjectFile.NameList; version: LONGINT;
 BEGIN
-	Header(reader, linker, binary, poolMap, offers, requires);
+	version := Header(reader, linker, binary, poolMap, offers, requires);
 	WHILE reader.Peek () # 0X DO
-		ObjectFile.ReadSection (reader, section,binary,poolMap);
+		ObjectFile.ReadSection (reader, version, section,binary,poolMap);
 		reader.SkipWhitespace;
 		IF reader.res = Streams.Ok THEN linker.AddSection (section); END;
 	END;

+ 45 - 21
source/ObjectFile.Mod

@@ -10,12 +10,14 @@ CONST
 
 	(* Section categories *)
 	(* code section categories, ordered by decreasing linking preference *)
-	InitCode*=0; (* initcode sections provide the entry point for static linking. A static linker includes this sections, a dynamic linker wants to omit them *)
-	BodyCode*=1; (* body code sections provide the entry point for dynamic linking. A dynamic linker needs to be able to distinguish them from normal code *)
-	Code*=2; (* normal executable code *)
+	EntryCode*= 0; (* entry code sections provide the entry point for static linking, enry code runs before module initializer callers *)
+	InitCode*=1; (* initcode sections provide the entry point for static linking. A static linker includes this sections, a dynamic linker wants to omit them *)
+	ExitCode*=2; (* exit code sections close a statically linked code, are executed after all init code callers *)
+	BodyCode*=3; (* body code sections provide the entry point for dynamic linking. A dynamic linker needs to be able to distinguish them from normal code *)
+	Code*=4; (* normal executable code *)
 	(* data section categories *)
-	Data* = 3; (* data sections provide space for (global) variables *)
-	Const* = 4; (* const sections are data sections that are immutable *)
+	Data* = 5; (* data sections provide space for (global) variables *)
+	Const* = 6; (* const sections are data sections that are immutable *)
 
 	(* alignment types *)
 	Aligned=0;
@@ -88,7 +90,6 @@ TYPE
 
 	Section* = RECORD
 		type*: SectionType;
-		priority*: LONGINT;
 		identifier*: Identifier;
 		unit*: Bits;
 		fixed*: BOOLEAN;
@@ -237,7 +238,7 @@ TYPE
 	NameList*= POINTER TO ARRAY OF SegmentedName;
 
 VAR
-	categories: ARRAY 6 OF ARRAY 10 OF CHAR;
+	categories: ARRAY 8 OF ARRAY 10 OF CHAR;
 	modes: ARRAY 2 OF ARRAY 4 OF CHAR;
 	relocatabilities: ARRAY 2 OF ARRAY 8 OF CHAR;
 
@@ -320,7 +321,7 @@ VAR
 		dest.unit := source.unit;
 		dest.fixed := source.fixed;
 		dest.alignment := source.alignment;
-		dest.priority := source.priority;
+
 		dest.fixups:= source.fixups;
 		dest.aliases := source.aliases;
 		NEW (dest.fixup, dest.fixups);
@@ -343,7 +344,7 @@ VAR
 		dest.unit := 0;
 		dest.fixed := FALSE;
 		dest.alignment := 0;
-		dest.priority := 0;
+
 		dest.fixups:= 0;
 		dest.aliases := 0;
 		dest.fixup := NIL;
@@ -496,8 +497,7 @@ VAR
 		writer.Char (Separator);
 		writer.Int (section.alignment, 0);
 		writer.Char (Separator);
-		writer.Int(section.priority, 0);
-		writer.Char (Separator);
+
 		writer.Int (section.aliases, 0);
 		writer.Char (Separator);
 		writer.Int (section.fixups, 0);
@@ -520,8 +520,8 @@ VAR
 		writer.Ln;
 	END WriteSectionTextual;
 
-	PROCEDURE ReadSectionTextual (reader: Streams.Reader; VAR section: Section);
-	VAR i, size: LONGINT; char: CHAR; relocatibility: INTEGER;
+	PROCEDURE ReadSectionTextual (reader: Streams.Reader; version: LONGINT; VAR section: Section);
+	VAR i, size: LONGINT; char: CHAR; relocatibility: INTEGER; priority: LONGINT;
 
 		PROCEDURE ReadValueIdentifier (VAR value: INTEGER; CONST identifiers: ARRAY OF ARRAY OF CHAR);
 		VAR identifier: ARRAY 10 OF CHAR;
@@ -615,7 +615,14 @@ VAR
 		ReadValueIdentifier(relocatibility, relocatabilities);
 		section.fixed := relocatibility = Fixed;
 		reader.SkipWhitespace; reader.Int (section.alignment, FALSE);
-		reader.SkipWhitespace; reader.Int (section.priority, FALSE);
+		IF version < 5 THEN
+			reader.SkipWhitespace; reader.Int (priority, FALSE);
+			IF section.type = InitCode THEN
+				IF priority = -4 THEN section.type := EntryCode;
+				ELSIF priority = -1  THEN section.type := ExitCode;
+				END;
+			END;
+		END;
 		reader.SkipWhitespace; reader.Int (section.aliases, FALSE);
 		reader.SkipWhitespace; reader.Int (section.fixups, FALSE);
 		reader.SkipWhitespace; reader.Int (size, FALSE); size := size * section.unit;
@@ -843,7 +850,7 @@ VAR
 		writer.RawNum (section.unit);
 		IF section.fixed THEN WriteValueIdentifier(Fixed,relocatabilities) ELSE WriteValueIdentifier(Aligned,relocatabilities) END;
 		writer.RawNum (section.alignment);
-		writer.RawNum (section.priority);
+
 		writer.RawNum (section.aliases);
 		writer.RawNum (section.fixups);
 		size := section.bits.GetSize ();
@@ -885,8 +892,8 @@ VAR
 		END;
 	END WriteSectionBinary;
 
-	PROCEDURE ReadSectionBinary (reader: Streams.Reader; VAR section: Section; poolMap: PoolMap);
-	VAR i, size: LONGINT; char: CHAR; relocatibility: INTEGER; num: LONGINT; ch: CHAR;
+	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;
 	CONST ByteSize=8;
 
 		PROCEDURE ReadValueIdentifier (VAR value: INTEGER; CONST identifiers: ARRAY OF ARRAY OF CHAR);
@@ -1009,7 +1016,22 @@ VAR
 		ReadValueIdentifier(relocatibility, relocatabilities);
 		section.fixed := relocatibility = Fixed;
 		reader.RawNum (section.alignment);
-		reader.RawNum (section.priority);
+		IF version < 5 THEN
+			reader.RawNum (priority);
+			CASE section.type OF
+			0: section.type := InitCode;
+			|1:section.type := BodyCode;
+			|2:section.type := Code;
+			|3:section.type := Data;
+			|4:section.type := Const;
+			END;
+
+			IF section.type = InitCode THEN
+				IF priority = -4 THEN section.type := EntryCode;
+				ELSIF priority = -1  THEN section.type := ExitCode;
+				END;
+			END;
+		END;
 		reader.RawNum (section.aliases);
 		reader.RawNum (section.fixups);
 		reader.RawNum (size); size := size * section.unit;
@@ -1036,12 +1058,12 @@ VAR
 		END;
 	END ReadSectionBinary;
 
-	PROCEDURE ReadSection*(reader: Streams.Reader; VAR section: Section; binary: BOOLEAN; poolMap: PoolMap);
+	PROCEDURE ReadSection*(reader: Streams.Reader; version: LONGINT; VAR section: Section; binary: BOOLEAN; poolMap: PoolMap);
 	BEGIN
 		IF binary THEN
-			ReadSectionBinary(reader,section,poolMap)
+			ReadSectionBinary(reader,version, section,poolMap)
 		ELSE
-			ReadSectionTextual(reader,section);
+			ReadSectionTextual(reader,version,section);
 		END
 	END ReadSection;
 
@@ -1361,7 +1383,9 @@ VAR
 
 BEGIN
 	categories[Code] := "code";
+	categories[EntryCode] := "entrycode";
 	categories[InitCode] := "initcode";
+	categories[ExitCode] := "exitcode";
 	categories[BodyCode] := "bodycode";
 	categories[Data] := "data";
 	categories[Const] := "const";