Bladeren bron

Finally: 64-bit A2 on Windows boots and works with the Garbage Collector

git-svn-id: https://svn.inf.ethz.ch/svn/lecturers/a2/trunk@7461 8c9fc860-2736-0410-a75d-ab315db34111
felixf 7 jaren geleden
bovenliggende
commit
9dc297a69d

+ 2 - 1
source/Builds.Tool

@@ -93,4 +93,5 @@ Win64G -- work in progress
 		StringPool ObjectFile GenericLinker Reflection  GenericLoader Shell  StdIOShell Traps ~
 
 	FSTools.CloseFiles A264.exe  ~
-	~
+	~
+	

+ 3 - 2
source/FoxAMDBackend.Mod

@@ -3364,10 +3364,11 @@ TYPE
 				 		IF out.os.type = Sections.VarSection THEN
 				 			IF out.pc = 1 THEN out.SetAlignment(FALSE,1)
 				 			ELSIF out.pc = 2 THEN out.SetAlignment(FALSE,2)
-				 			ELSIF out.pc > 2 THEN out.SetAlignment(FALSE,4)
+				 			ELSIF (out.pc > 4) & (bits > 32) THEN out.SetAlignment(FALSE,8)
+				 			ELSIF (out.pc > 2) THEN out.SetAlignment(FALSE,4)
 				 			END;
 				 		ELSIF out.os.type = Sections.ConstSection THEN
-				 			out.SetAlignment(FALSE,4);
+				 			out.SetAlignment(FALSE,bits DIV 8);
 				 		END;
 			 		END
 			 	END

+ 4 - 1
source/FoxIntermediateBackend.Mod

@@ -11343,7 +11343,7 @@ TYPE
 		PROCEDURE AddPointer(section: IntermediateCode.Section; offset: LONGINT);
 		BEGIN
 			IF ~implementationVisitor.backend.cooperative THEN
-				NamedSymbol(modulePointerSection, section.name, NIL, 0, offset);
+				NamedSymbol(modulePointerSection, section.name, NIL, offset, 0);
 				INC(modulePointers);
 				(* optimization hint: this can be done once at the end but for consistency of the first tests we keep it like this *)
 				PatchSize(modulePointerSection, modulePointerSizePC, modulePointers); 
@@ -12438,6 +12438,7 @@ TYPE
 						INCL(flags, flagConstructor);
 					END;
 					Set(section, flags);
+					IF module.system.addressType.sizeInBits = 64 THEN Longint(section, 0); END;
 					
 					IF RefInfo THEN Info(section, "Parameters") END;
 					parameter := procedureType.firstParameter;
@@ -12996,6 +12997,7 @@ TYPE
 					Info(source, "type flags");
 					flags := {};
 					Set( source, flags);
+					IF module.system.addressType.sizeInBits = 64 THEN Longint(source, 0); END;
 					
 					Info(source, "pointer to module");
 					moduleSection := ModuleSection();
@@ -13101,6 +13103,7 @@ TYPE
 			flags := {};
 			IF  implementationVisitor.backend.preciseGC THEN INCL(flags,0) END;
 			Set( moduleSection, flags);
+			IF module.system.addressType.sizeInBits = 64 THEN Longint(moduleSection, 0); END;
 
 			IF implementationVisitor.backend.cooperative THEN
 				PatchSymbol(moduleSection,MonitorOffset,moduleSection.name,NIL,moduleSection.pc,0);

+ 0 - 11
source/Generic.Win64.Kernel32.Mod

@@ -274,10 +274,6 @@ TYPE
 	*)
 	END; 
 				
-
-	Wow64Context*= RECORD (Context)
-		extension: ARRAY 512 (* MaxWOW64Extension *) OF CHAR;
-	END;
 	
 	ExceptionRecordPtr* = POINTER {UNSAFE} TO ExceptionRecord;
 	ExceptionRecord* = RECORD
@@ -635,9 +631,6 @@ VAR
 	GetThreadContext-: PROCEDURE {WINAPI} ( hThread: HANDLE;
 																			  VAR lpContext: Context ): BOOL;
 
-	(** The GetThreadContext function retrieves the context of the specified thread. *)
-	Wow64GetThreadContext-: PROCEDURE {WINAPI} ( hThread: HANDLE;
-																			  VAR lpContext: Wow64Context ): BOOL;
 
 	(** The GetThreadPriority function returns the priority value for the specified thread. This value, together with
 			the priority class of the thread's process, determines the thread's base-priority level. *)
@@ -828,8 +821,6 @@ VAR
 	Sleep-: PROCEDURE {WINAPI} ( dwMilliseconds: LONGINT );
 	(** The SuspendThread function suspends the specified thread. *)
 	SuspendThread-: PROCEDURE {WINAPI} ( hThread: HANDLE ): LONGINT;
-	(** The SuspendThread function suspends the specified thread. *)
-	Wow64SuspendThread-: PROCEDURE {WINAPI} ( hThread: HANDLE ): LONGINT;
 	(** The SystemTimeToFileTime function converts a system time to a file time. *)
 	SystemTimeToFileTime-: PROCEDURE {WINAPI} ( VAR lpSystemTime: SystemTime;
 																					   VAR lpFileTime: FileTime ): BOOL;
@@ -1029,7 +1020,6 @@ VAR
 		GetProcAddress(mod, "GetTempFileNameA",SYSTEM.VAL(ADDRESS,GetTempFileName));
 		GetProcAddress(mod, "GetTempPathA",SYSTEM.VAL(ADDRESS,GetTempPath));
 		GetProcAddress(mod, "GetThreadContext",SYSTEM.VAL(ADDRESS,GetThreadContext));
-		GetProcAddress(mod, "Wow64GetThreadContext",SYSTEM.VAL(ADDRESS,Wow64GetThreadContext));
 		GetProcAddress(mod, "GetThreadPriority",SYSTEM.VAL(ADDRESS,GetThreadPriority));
 		GetProcAddress(mod, "GetThreadTimes",SYSTEM.VAL(ADDRESS,GetThreadTimes));
 		GetProcAddress(mod, "GetTickCount",SYSTEM.VAL(ADDRESS,GetTickCount));
@@ -1096,7 +1086,6 @@ VAR
 		GetProcAddress(mod, "SetupComm",SYSTEM.VAL(ADDRESS,SetupComm));
 		GetProcAddress(mod, "Sleep",SYSTEM.VAL(ADDRESS,Sleep));
 		GetProcAddress(mod, "SuspendThread",SYSTEM.VAL(ADDRESS,SuspendThread));
-		GetProcAddress(mod, "Wow64SuspendThread",SYSTEM.VAL(ADDRESS,Wow64SuspendThread));
 		GetProcAddress(mod, "SystemTimeToFileTime",SYSTEM.VAL(ADDRESS,SystemTimeToFileTime));
 		GetProcAddress(mod, "TerminateThread",SYSTEM.VAL(ADDRESS,TerminateThread));
 		GetProcAddress(mod, "TlsAlloc",SYSTEM.VAL(ADDRESS,TlsAlloc));

+ 2 - 1
source/Heaps.Mod

@@ -26,7 +26,8 @@ CONST
 
 	MaxTries = 16;				(* max number of times to try and allocate memory, before trapping *)
 	Unmarked = 0;				(* mark value of free blocks *)
-	BlockSize* = 32;			(* power of two, <= 32 for RegisterCandidates *)
+	BlockSize* = 8*SIZEOF(ADDRESS);			(* power of two, <= 32 for RegisterCandidates. Must be large enough to accomodate any basic block *)
+	
 	ArrayAlignment = 8;			(* first array element of ArrayBlock and first data element of SystemBlock must be aligned to 0 MOD ArrayAlignment *)
 	BlockHeaderSize* = 2 * AddressSize;
 	HeapBlockOffset* = - 2 * AddressSize;

+ 1 - 1
source/WMPerfMonPluginHeap.Mod

@@ -6,7 +6,7 @@ IMPORT
 CONST
 	ModuleName = "WMPerfMonPluginHeap";
 
-	BlockSize = 32; (* {BlockSize = Heaps.BlockSize} *)
+	BlockSize = 8*SIZEOF(ADDRESS); (* {BlockSize = Heaps.BlockSize} *)
 
 TYPE
 	SizeArray = ARRAY 27 OF LONGINT;

+ 28 - 30
source/Win64.Machine.Mod

@@ -41,11 +41,9 @@ CONST
 
 	StrongChecks = FALSE;
 
-	HeaderSize = 40H; (* cf. Linker0 *)
-	EndBlockOfs = 38H;	(* cf. Linker0 *)
 	MemoryBlockOfs = BlockHeaderSize + RecordDescSize + BlockHeaderSize; (* memory block (including header) starts at offset HeaderSize *)
 
-	MemBlockSize = 128*1024*1024; (* must be multiple of StaticBlockSize *)
+	MemBlockSize = 32*1024*1024; (* must be multiple of StaticBlockSize *)
 	MinMemBlockSize = 4*1024*1024;
 
 	NilVal = 0;
@@ -1064,48 +1062,48 @@ CODE{SYSTEM.AMD64}
 	POP RDI
 END SetRDI;
 
-PROCEDURE Portin8*(port: LONGINT; VAR val: CHAR);
-CODE{SYSTEM.i386}
-	MOV EDX,[EBP+port]
+PROCEDURE  Portin8*(port: LONGINT; VAR val: CHAR);
+CODE{SYSTEM.AMD64}
+	MOV EDX,[RBP+port]
 	IN AL, DX
-	MOV ECX, [EBP+val]
-	MOV [ECX], AL
+	MOV RCX, [RBP+val]
+	MOV [RCX], AL
 END Portin8;
 
-PROCEDURE Portin16*(port: LONGINT; VAR val: INTEGER);
-CODE{SYSTEM.i386}
-	MOV EDX,[EBP+port]
+PROCEDURE  Portin16*(port: LONGINT; VAR val: INTEGER);
+CODE{SYSTEM.AMD64}
+	MOV EDX,[RBP+port]
 	IN AX, DX
-	MOV ECX, [EBP+val]
-	MOV [ECX], AX
+	MOV RCX, [RBP+val]
+	MOV [RCX], AX
 END Portin16;
 
-PROCEDURE Portin32*(port: LONGINT; VAR val: LONGINT);
-CODE{SYSTEM.i386}
-	MOV EDX,[EBP+port]
+PROCEDURE  Portin32*(port: LONGINT; VAR val: LONGINT);
+CODE{SYSTEM.AMD64}
+	MOV EDX,[RBP+port]
 	IN EAX, DX
-	MOV ECX, [EBP+val]
-	MOV [ECX], EAX
+	MOV RCX, [RBP+val]
+	MOV [RCX], EAX
 END Portin32;
 
-PROCEDURE Portout8*(port: LONGINT; val: CHAR);
-CODE{SYSTEM.i386}
-	MOV AL,[EBP+val]
-	MOV EDX,[EBP+port]
+PROCEDURE  Portout8*(port: LONGINT; val: CHAR);
+CODE{SYSTEM.AMD64}
+	MOV AL,[RBP+val]
+	MOV EDX,[RBP+port]
 	OUT DX,AL
 END Portout8;
 
-PROCEDURE Portout16*(port: LONGINT; val: INTEGER);
-CODE{SYSTEM.i386}
-	MOV AX,[EBP+val]
-	MOV EDX,[EBP+port]
+PROCEDURE  Portout16*(port: LONGINT; val: INTEGER);
+CODE{SYSTEM.AMD64}
+	MOV AX,[RBP+val]
+	MOV EDX,[RBP+port]
 	OUT DX,AX
 END Portout16;
 
-PROCEDURE Portout32*(port: LONGINT; val: LONGINT);
-CODE{SYSTEM.i386}
-	MOV EAX,[EBP+val]
-	MOV EDX,[EBP+port]
+PROCEDURE  Portout32*(port: LONGINT; val: LONGINT);
+CODE{SYSTEM.AMD64}
+	MOV EAX,[RBP+val]
+	MOV EDX,[RBP+port]
 	OUT DX,EAX
 END Portout32;
 

+ 3 - 23
source/Win64.Objects.Mod

@@ -6,7 +6,7 @@ IMPORT SYSTEM, Trace, Kernel32, Machine, Modules, Heaps;
 
 CONST
 	HandleExcp = TRUE;   (* FALSE -> we asume that it is done correctly by Traps *)
-	TraceVerbose = TRUE;
+	TraceVerbose = FALSE;
 	StrongChecks = FALSE;  defaultStackSize = 0;
 	TraceOpenClose = FALSE;
 
@@ -217,7 +217,6 @@ TYPE
 						SYSTEM.GET(bp, n);
 						IF ODD(n) THEN (* procedure descriptor at bp *)
 							desc := SYSTEM.VAL(Modules.ProcedureDescPointer, n-1);
-							WriteType(desc); Trace.Ln;
 							IF desc # NIL THEN
 								a0 := ADDRESSOF(desc.offsets);
 								a1 :=  SYSTEM.VAL(ADDRESS, desc.offsets);
@@ -276,11 +275,7 @@ TYPE
 				WHILE p # NIL DO
 					cur := p(Process);
 					IF ((cur.mode = Ready) OR (cur.mode = Running)) & (cur.priority <= High) & (cur # r) THEN
-						IF isWow64 THEN 
-							res := Kernel32.Wow64SuspendThread(cur.handle);
-						ELSE
-							res := Kernel32.SuspendThread(cur.handle);
-						END;
+						res := Kernel32.SuspendThread(cur.handle);
 						ASSERT(res >= 0);
 						cur.mode := Suspended
 					ELSE INC(num);
@@ -382,8 +377,6 @@ VAR
 
 	excplock: Kernel32.CriticalSection;  exceptionhandler: ExceptionHandler;
 	
-	isWow64: BOOLEAN; (* TRUE for WOW64 environment *)
-
 (* Set the current process' priority. *)
 PROCEDURE SetPriority*( priority: LONGINT );
 VAR r: Process; prio: LONGINT; res: Kernel32.BOOL;
@@ -1089,11 +1082,7 @@ END Await;
 		IF CurrentProcess() # t THEN
 			Machine.Acquire( Machine.Objects );
 			LOOP
-				IF isWow64 THEN 
-					retBOOL := Kernel32.Wow64SuspendThread(t.handle);
-				ELSE
-					retBOOL := Kernel32.SuspendThread( t.handle );
-				END;
+				retBOOL := Kernel32.SuspendThread( t.handle );
 				t.state.ContextFlags := SYSTEM.VAL(LONGINT, Kernel32.ContextControl);
 				retBOOL := Kernel32.GetThreadContext( t.handle, t.state );
 				mod := Modules.ThisModuleByAdr( t.state.PC );  Trace.String( "Objects Break at adr: " );
@@ -1343,7 +1332,6 @@ BEGIN
 END ReenterA2;
 
 VAR
-	lpContext: Kernel32.Wow64Context;
 	TraceProcessHook*: PROCEDURE (prcoess: Process; pc, bp: ADDRESS; stacklow, stackhigh: ADDRESS);
 	
 BEGIN
@@ -1356,14 +1344,6 @@ BEGIN
 	Kernel32.SendToDebugger("Modules.root", ADDRESSOF(Modules.root));
 	
 	
-	(* determine whether it is WOW64 environment *)
-	(*
-	isWow64 := (Kernel32.Wow64GetThreadContext # NIL) & (Kernel32.Wow64GetThreadContext(Kernel32.GetCurrentThread(),lpContext) # 0); 
-	TRACE("Objects 5"); 
-	IF isWow64 THEN
-		Trace.String("Use Wow64"); Trace.Ln;
-	END;
-	*)
 	Init;
 END Objects.