瀏覽代碼

64 bit WinAPI adaptions
kernel boots and provides correct module loading (for one example)

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

felixf 7 年之前
父節點
當前提交
2a930f0ae0

+ 1 - 1
source/BitSets.Mod

@@ -121,7 +121,7 @@ BEGIN
 			dest.SetBit (destPos, source.GetBit (sourcePos));
 			dest.SetBit (destPos, source.GetBit (sourcePos));
 			INC (sourcePos); INC (destPos); DEC (count);
 			INC (sourcePos); INC (destPos); DEC (count);
 		END;
 		END;
-		WHILE (count > 31) DO
+		WHILE (count >= setSize) DO
 			dest.data[destPos DIV setSize] := source.data[sourcePos DIV setSize];
 			dest.data[destPos DIV setSize] := source.data[sourcePos DIV setSize];
 			INC(sourcePos,setSize); INC(destPos,setSize); DEC(count,setSize);
 			INC(sourcePos,setSize); INC(destPos,setSize); DEC(count,setSize);
 		END;
 		END;

+ 28 - 2
source/Builds.Tool

@@ -7,17 +7,39 @@ WIN32G -- 32-bit windows a2 using generic object files
 =================================
 =================================
 
 
 	## Compile all files ##
 	## Compile all files ##
-		Release.Build -b WinAosNewObjectFile ~
+		Release.Build WinAosNewObjectFile ~
 	
 	
 	## Link A2.exe (bootconsole for graphical OS) ##
 	## Link A2.exe (bootconsole for graphical OS) ##
 		StaticLinker.Link --fileFormat=PE32 --fileName=A2.exe --extension=GofW --displacement=401000H  
 		StaticLinker.Link --fileFormat=PE32 --fileName=A2.exe --extension=GofW --displacement=401000H  
 			Runtime Trace Kernel32 Machine Heaps Modules Objects Kernel KernelLog Streams Commands Files WinFS Clock Dates Reals Strings Diagnostics BitSets StringPool ObjectFile GenericLinker Reflection  GenericLoader  BootConsole ~		
 			Runtime Trace Kernel32 Machine Heaps Modules Objects Kernel KernelLog Streams Commands Files WinFS Clock Dates Reals Strings Diagnostics BitSets StringPool ObjectFile GenericLinker Reflection  GenericLoader  BootConsole ~		
 
 
+	## command line shell 
+	StaticLinker.Link  --fileFormat=PE32CUI --fileName=oberon.exe --extension=GofW --displacement=401000H 
+		Runtime Trace Kernel32 Machine Heaps Modules Objects Kernel KernelLog Streams Commands Files  WinFS Clock Dates Reals Strings 
+		Diagnostics BitSets StringPool ObjectFile GenericLinker Reflection GenericLoader WinTrace StdIO  
+		Traps RelativeFileSystem WMDefaultFont SystemTools StdIOShell ~
+
 	## Command line shell including compiler (and linker) ##
 	## Command line shell including compiler (and linker) ##
 		StaticLinker.Link  --fileFormat=PE32CUI --fileName=oberon.exe --extension=GofW --displacement=401000H 
 		StaticLinker.Link  --fileFormat=PE32CUI --fileName=oberon.exe --extension=GofW --displacement=401000H 
 			Runtime Trace Kernel32 Machine Heaps Modules Objects Kernel KernelLog Streams Commands Files  WinFS Clock Dates Reals Strings Diagnostics BitSets StringPool ObjectFile GenericLinker Reflection GenericLoader WinTrace 
 			Runtime Trace Kernel32 Machine Heaps Modules Objects Kernel KernelLog Streams Commands Files  WinFS Clock Dates Reals Strings Diagnostics BitSets StringPool ObjectFile GenericLinker Reflection GenericLoader WinTrace 
 			StdIO  Traps RelativeFileSystem SystemTools FSTools StdIOShell Shell StaticLinker Compiler FoxOberonFrontend FoxARMBackend FoxAMDBackend ~
 			StdIO  Traps RelativeFileSystem SystemTools FSTools StdIOShell Shell StaticLinker Compiler FoxOberonFrontend FoxARMBackend FoxAMDBackend ~
 
 
+FSTools.CloseFiles oberon.exe ~
+
+Compiler.Compile -p=Win32G
+Runtime.Mod Trace.Mod Generic.Win32.Kernel32.Mod Win32.Machine.Mod Heaps.Mod 
+Generic.Modules.Mod Win32.Objects.Mod Win32.Kernel.Mod KernelLog.Mod Plugins.Mod Streams.Mod Pipes.Mod 
+Commands.Mod In.Mod Out.Mod I386.Reals.Mod Generic.Reflection.Mod TrapWriters.Mod CRC.Mod 
+SystemVersion.Mod Win32.Traps.Mod Win32.WinTrace.Mod Win32.StdIO.Mod Locks.Mod Win32.Clock.Mod 
+Disks.Mod Files.Mod Dates.Mod Strings.Mod UTF8Strings.Mod FileTrapWriter.Mod Caches.Mod 
+DiskVolumes.Mod OldDiskVolumes.Mod RAMVolumes.Mod DiskFS.Mod OldDiskFS.Mod OberonFS.Mod 
+FATVolumes.Mod FATFiles.Mod ISO9660Volumes.Mod ISO9660Files.Mod Win32.User32.Mod Win32.WinTrace.Mod 
+Win32.ODBC.Mod Win32.Shell32.Mod Win32.SQL.Mod Win32.WinFS.Mod RelativeFileSystem.Mod BitSets.Mod 
+Diagnostics.Mod StringPool.Mod ObjectFile.Mod GenericLinker.Mod GenericLoader.Mod BootConsole.Mod 
+Shell.Mod StdIOShell.Mod ~
+
+SystemTools.FreeDownTo FoxIntermediateBackend ~
+
 LINUX32G -- 32 bit linux a2 using generic object files
 LINUX32G -- 32 bit linux a2 using generic object files
 ================================
 ================================
 
 
@@ -73,6 +95,7 @@ Compiler.Compile -b=AMD --bits=64 --objectFile=Generic --newObjectFile  --symbol
 	StringPool.Mod ObjectFile.Mod GenericLinker.Mod GenericLoader.Mod BootConsole.Mod 
 	StringPool.Mod ObjectFile.Mod GenericLinker.Mod GenericLoader.Mod BootConsole.Mod 
 	Win32.WinTrace.Mod Pipes.Mod Win32.StdIO.Mod Shell.Mod StdIOShell.Mod 
 	Win32.WinTrace.Mod Pipes.Mod Win32.StdIO.Mod Shell.Mod StdIOShell.Mod 
 	Generic.Reflection.Mod CRC.Mod SystemVersion.Mod Win64.Traps.Mod TrapWriters.Mod
 	Generic.Reflection.Mod CRC.Mod SystemVersion.Mod Win64.Traps.Mod TrapWriters.Mod
+	ProducerConsumer.Mod 
 	~
 	~
 
 
 StaticLinker.Link --fileFormat=PE64CUI --fileName=A264.exe --extension=GofWw --displacement=401000H  
 StaticLinker.Link --fileFormat=PE64CUI --fileName=A264.exe --extension=GofWw --displacement=401000H  
@@ -89,4 +112,7 @@ FSTools.CloseFiles A264.exe  ~
 	 ConsumerProducer TestBoot ~
 	 ConsumerProducer TestBoot ~
 	ProducerConsumer.Mod TestBoot.Mod 	
 	ProducerConsumer.Mod TestBoot.Mod 	
 
 
-~ BootConsole ~			
+~ BootConsole ~		
+
+
+FoxGenericObjectFile.Show ConsumerProducer.GofWw ~	

+ 4 - 4
source/Generic.Win32.Kernel32.Mod

@@ -492,7 +492,7 @@ VAR
 	GetExitCodeProcess-: PROCEDURE {WINAPI} ( hProcess: HANDLE;
 	GetExitCodeProcess-: PROCEDURE {WINAPI} ( hProcess: HANDLE;
 																				  VAR lpExitCode: LONGINT ): BOOL;
 																				  VAR lpExitCode: LONGINT ): BOOL;
 	(** The GetFileAttributes function returns attributes for a specified file or directory. *)
 	(** The GetFileAttributes function returns attributes for a specified file or directory. *)
-	GetFileAttributes-: PROCEDURE {WINAPI} ( VAR lpFileName: ARRAY   OF CHAR ): SET;
+	GetFileAttributes-: PROCEDURE {WINAPI} ( VAR lpFileName: ARRAY   OF CHAR ): LONGINT;
 	(** The GetFileSize function retrieves the size, in bytes, of the specified file. *)
 	(** The GetFileSize function retrieves the size, in bytes, of the specified file. *)
 	GetFileSize-: PROCEDURE {WINAPI} ( hFile: HANDLE;  VAR lpFileSizeHigh: LONGINT ): LONGINT;
 	GetFileSize-: PROCEDURE {WINAPI} ( hFile: HANDLE;  VAR lpFileSizeHigh: LONGINT ): LONGINT;
 	GetFileSizeEx-: PROCEDURE {WINAPI} ( hFile: HANDLE;  VAR lpFileSize: HUGEINT ): BOOL;
 	GetFileSizeEx-: PROCEDURE {WINAPI} ( hFile: HANDLE;  VAR lpFileSize: HUGEINT ): BOOL;
@@ -516,7 +516,7 @@ VAR
 	(* The GetLogicalDrives function retrieves a bitmask representing the currently available disk drives.
 	(* The GetLogicalDrives function retrieves a bitmask representing the currently available disk drives.
 *)
 *)
 
 
-	GetLogicalDrives-: PROCEDURE {WINAPI} ( ): SET;
+	GetLogicalDrives-: PROCEDURE {WINAPI} ( ): LONGINT;
 	GetModuleFileName-: PROCEDURE {WINAPI} ( hModule: HMODULE;
 	GetModuleFileName-: PROCEDURE {WINAPI} ( hModule: HMODULE;
 																				    VAR lpFileName: ARRAY   OF CHAR;
 																				    VAR lpFileName: ARRAY   OF CHAR;
 																				    nSize: LONGINT ): LONGINT;
 																				    nSize: LONGINT ): LONGINT;
@@ -717,7 +717,7 @@ VAR
 	SetCurrentDirectory-: PROCEDURE {WINAPI} ( VAR lpPathName: ARRAY   OF CHAR ): BOOL;
 	SetCurrentDirectory-: PROCEDURE {WINAPI} ( VAR lpPathName: ARRAY   OF CHAR ): BOOL;
 	(** The SetErrorMode function controls whether the system will handle the specified types of serious errors,
 	(** The SetErrorMode function controls whether the system will handle the specified types of serious errors,
 			or whether the process will handle them. *)
 			or whether the process will handle them. *)
-	SetErrorMode-: PROCEDURE {WINAPI} ( uMode: SET ): SET;
+	SetErrorMode-: PROCEDURE {WINAPI} ( uMode: SET ): LONGINT;
 	(** The SetEndOfFile function moves the end-of-file (EOF) position for the specified file to the current position of the file pointer. *)
 	(** The SetEndOfFile function moves the end-of-file (EOF) position for the specified file to the current position of the file pointer. *)
 	SetEndOfFile-: PROCEDURE {WINAPI} ( hFile: HANDLE ): BOOL;
 	SetEndOfFile-: PROCEDURE {WINAPI} ( hFile: HANDLE ): BOOL;
 	(** The SetEvent function sets the state of the specified event object to signaled. *)
 	(** The SetEvent function sets the state of the specified event object to signaled. *)
@@ -738,7 +738,7 @@ VAR
 	(** The SetLocalTime function sets the current local time and date. *)
 	(** The SetLocalTime function sets the current local time and date. *)
 	SetLocalTime-: PROCEDURE {WINAPI} ( VAR lpSystemTime: SystemTime ): BOOL;
 	SetLocalTime-: PROCEDURE {WINAPI} ( VAR lpSystemTime: SystemTime ): BOOL;
 	(** The SetThreadAffinityMask function sets a processor affinity mask for the specified thread. *)
 	(** The SetThreadAffinityMask function sets a processor affinity mask for the specified thread. *)
-	SetThreadAffinityMask-: PROCEDURE {WINAPI} ( hThread: HANDLE; dwThreadAffinityMask: SET): SET;
+	SetThreadAffinityMask-: PROCEDURE {WINAPI} ( hThread: HANDLE; dwThreadAffinityMask: SET): LONGINT;
 	(** The SetThreadContext function sets the context in the specified thread. *)
 	(** The SetThreadContext function sets the context in the specified thread. *)
 	SetThreadContext-: PROCEDURE {WINAPI} ( hThread: HANDLE;
 	SetThreadContext-: PROCEDURE {WINAPI} ( hThread: HANDLE;
 																			  VAR lpContext: Context ): BOOL;
 																			  VAR lpContext: Context ): BOOL;

+ 3 - 3
source/GenericLinker.Mod

@@ -3,10 +3,10 @@
 
 
 IMPORT ObjectFile, Streams, Diagnostics, Strings, SYSTEM;
 IMPORT ObjectFile, Streams, Diagnostics, Strings, SYSTEM;
 
 
-TYPE Address* = ObjectFile.Unit;
+TYPE Address* = ADDRESS;
 
 
 CONST
 CONST
-	InvalidAddress* = MAX (Address);
+	InvalidAddress* = -1 (* MAX (Address) *);
 
 
 CONST
 CONST
 	Fixed* = 0; InitCode*=1; BodyCode* = 2; Code* = 3; Data* = 4; Const* = 5; Empty* = 6;
 	Fixed* = 0; InitCode*=1; BodyCode* = 2; Code* = 3; Data* = 4; Const* = 5; Empty* = 6;
@@ -363,7 +363,7 @@ VAR
 				FOR i := 0 TO pattern.patterns-1 DO
 				FOR i := 0 TO pattern.patterns-1 DO
 					INC(nobits,pattern.pattern[i].bits);
 					INC(nobits,pattern.pattern[i].bits);
 				END;
 				END;
-				remainder := ASH(address,-nobits);
+				remainder := LONGINT(ASH(address,-nobits));
 
 
 				IF  (nobits <32) & ((remainder > 0) OR (remainder < -1)) THEN
 				IF  (nobits <32) & ((remainder > 0) OR (remainder < -1)) THEN
 					IF pattern.mode = ObjectFile.Relative THEN (* negative values allowed *)
 					IF pattern.mode = ObjectFile.Relative THEN (* negative values allowed *)

+ 26 - 26
source/GenericLoader.Mod

@@ -15,12 +15,12 @@ CONST
 TYPE
 TYPE
 
 
 	HashEntryIntInt = RECORD
 	HashEntryIntInt = RECORD
-		key,value: LONGINT;
+		key,value: SIZE;
 	END;
 	END;
 	HashIntArray = POINTER TO ARRAY OF HashEntryIntInt;
 	HashIntArray = POINTER TO ARRAY OF HashEntryIntInt;
 
 
 	HashEntryIntAny = RECORD
 	HashEntryIntAny = RECORD
-		key: LONGINT; value: ANY;
+		key: SIZE; value: ANY;
 	END;
 	END;
 
 
 	HashIntAnyArray = POINTER TO ARRAY OF HashEntryIntAny;
 	HashIntAnyArray = POINTER TO ARRAY OF HashEntryIntAny;
@@ -43,8 +43,8 @@ TYPE
 			maxLoadFactor := 0.75;
 			maxLoadFactor := 0.75;
 		END Init;
 		END Init;
 
 
-		PROCEDURE Put*(key: LONGINT; value: LONGINT);
-		VAR hash: LONGINT;
+		PROCEDURE Put*(key: SIZE; value: SIZE);
+		VAR hash: SIZE;
 		BEGIN
 		BEGIN
 			ASSERT(key # 0);
 			ASSERT(key # 0);
 			ASSERT(used < size);
 			ASSERT(used < size);
@@ -57,12 +57,12 @@ TYPE
 			IF (used / size) > maxLoadFactor THEN Grow END;
 			IF (used / size) > maxLoadFactor THEN Grow END;
 		END Put;
 		END Put;
 
 
-		PROCEDURE Get*(key: LONGINT):LONGINT;
+		PROCEDURE Get*(key: SIZE):SIZE;
 		BEGIN
 		BEGIN
 			RETURN table[HashValue(key)].value;
 			RETURN table[HashValue(key)].value;
 		END Get;
 		END Get;
 
 
-		PROCEDURE Has*(key: LONGINT):BOOLEAN;
+		PROCEDURE Has*(key: SIZE):BOOLEAN;
 		BEGIN
 		BEGIN
 			RETURN table[HashValue(key)].key = key;
 			RETURN table[HashValue(key)].key = key;
 		END Has;
 		END Has;
@@ -76,8 +76,8 @@ TYPE
 
 
 		(* Internals *)
 		(* Internals *)
 
 
-		PROCEDURE HashValue(key: LONGINT):LONGINT;
-		VAR value, h1, h2, i: LONGINT;
+		PROCEDURE HashValue(key: SIZE):SIZE;
+		VAR value, h1, h2, i: SIZE;
 		BEGIN
 		BEGIN
 			i := 0;
 			i := 0;
 			value := key;
 			value := key;
@@ -92,7 +92,7 @@ TYPE
 		END HashValue;
 		END HashValue;
 
 
 		PROCEDURE Grow;
 		PROCEDURE Grow;
-		VAR oldTable: HashIntArray; oldSize, i, key: LONGINT;
+		VAR oldTable: HashIntArray; oldSize, i, key: SIZE;
 		BEGIN
 		BEGIN
 			oldSize := size;
 			oldSize := size;
 			oldTable := table;
 			oldTable := table;
@@ -125,8 +125,8 @@ TYPE
 			maxLoadFactor := 0.75;
 			maxLoadFactor := 0.75;
 		END Init;
 		END Init;
 
 
-		PROCEDURE Put*(key: LONGINT; value: ANY);
-		VAR hash: LONGINT;
+		PROCEDURE Put*(key: SIZE; value: ANY);
+		VAR hash: SIZE;
 		BEGIN
 		BEGIN
 			ASSERT(key # 0);
 			ASSERT(key # 0);
 			ASSERT(used < size);
 			ASSERT(used < size);
@@ -160,8 +160,8 @@ TYPE
 
 
 		(* Internals *)
 		(* Internals *)
 
 
-		PROCEDURE HashValue(key: LONGINT):LONGINT;
-		VAR value, h1, h2, i: LONGINT;
+		PROCEDURE HashValue(key: SIZE):SIZE;
+		VAR value, h1, h2, i:SIZE;
 		BEGIN
 		BEGIN
 			i := 0;
 			i := 0;
 			value := key;
 			value := key;
@@ -176,7 +176,7 @@ TYPE
 		END HashValue;
 		END HashValue;
 
 
 		PROCEDURE Grow;
 		PROCEDURE Grow;
-		VAR oldTable: HashIntAnyArray; oldSize, i, key: LONGINT;
+		VAR oldTable: HashIntAnyArray; oldSize, i, key: SIZE;
 		BEGIN
 		BEGIN
 			oldSize := size;
 			oldSize := size;
 			oldTable := table;
 			oldTable := table;
@@ -191,14 +191,14 @@ TYPE
 
 
 	END HashTableIntAny;
 	END HashTableIntAny;
 
 
-	Data=RECORD size, pos: LONGINT; bytes: Modules.Bytes; firstAddress: LONGINT; END;
+	Data=RECORD size, pos: LONGINT; bytes: Modules.Bytes; firstAddress: ADDRESS; END;
 
 
 	Arrangement* = OBJECT (GenericLinker.Arrangement);
 	Arrangement* = OBJECT (GenericLinker.Arrangement);
 	VAR
 	VAR
 		code, data: Data;
 		code, data: Data;
 		(*moduleAdr: LONGINT;*)
 		(*moduleAdr: LONGINT;*)
 		hasBody: BOOLEAN;
 		hasBody: BOOLEAN;
-		bodyAddress : LONGINT;
+		bodyAddress : ADDRESS;
 
 
 		PROCEDURE & InitArrangement;
 		PROCEDURE & InitArrangement;
 		BEGIN InitData(code); InitData(data); hasBody := FALSE;
 		BEGIN InitData(code); InitData(data); hasBody := FALSE;
@@ -271,7 +271,7 @@ TYPE
 			any: ANY;
 			any: ANY;
 
 
 			PROCEDURE TraverseScopes(CONST scope: Modules.ExportDesc; level: LONGINT);
 			PROCEDURE TraverseScopes(CONST scope: Modules.ExportDesc; level: LONGINT);
-			VAR adr,i: LONGINT;
+			VAR adr: ADDRESS; i: LONGINT;
 			BEGIN
 			BEGIN
 				IF (level > 2) THEN RETURN END;
 				IF (level > 2) THEN RETURN END;
 				IF (scope.fp # 0) THEN
 				IF (scope.fp # 0) THEN
@@ -356,9 +356,9 @@ TYPE
 
 
 		PROCEDURE ImportBlock(CONST fixup: ObjectFile.Fixup): GenericLinker.Block;
 		PROCEDURE ImportBlock(CONST fixup: ObjectFile.Fixup): GenericLinker.Block;
 		VAR name: Modules.Name; res: LONGINT;
 		VAR name: Modules.Name; res: LONGINT;
-			msg: ARRAY 128 OF CHAR; module: Modules.Module; adr: LONGINT; m: HashTableInt;
+			msg: ARRAY 128 OF CHAR; module: Modules.Module; adr: ADDRESS; m: HashTableInt;
 			s: ObjectFile.SectionName; isModule: BOOLEAN; identifier: ObjectFile.Identifier;
 			s: ObjectFile.SectionName; isModule: BOOLEAN; identifier: ObjectFile.Identifier;
-			fp: LONGINT;
+			fp: SIZE;
 
 
 			PROCEDURE CheckName(n: StringPool.Index;  name {UNTRACED}: Modules.DynamicName): LONGINT;
 			PROCEDURE CheckName(n: StringPool.Index;  name {UNTRACED}: Modules.DynamicName): LONGINT;
 			VAR s: ObjectFile.SectionName; i: LONGINT;
 			VAR s: ObjectFile.SectionName; i: LONGINT;
@@ -381,8 +381,8 @@ TYPE
 			
 			
 		
 		
 			(* stupid implementation: just search for fp in all exports *)
 			(* stupid implementation: just search for fp in all exports *)
-			PROCEDURE CheckScope(CONST scope: Modules.ExportDesc; level: LONGINT): LONGINT;
-			VAR adr,lo,hi,m,res: LONGINT;
+			PROCEDURE CheckScope(CONST scope: Modules.ExportDesc; level: LONGINT): ADDRESS;
+			VAR adr,lo,hi,m,res: SIZE;
 			BEGIN
 			BEGIN
 				adr := 0;
 				adr := 0;
 				(* export names are sorted, binary search: *)
 				(* export names are sorted, binary search: *)
@@ -457,7 +457,7 @@ TYPE
 				(*D.String("GenericLoader Fatal error: did not find block "); s := identifier.name; D.String(s); D.Ln;*)
 				(*D.String("GenericLoader Fatal error: did not find block "); s := identifier.name; D.String(s); D.Ln;*)
 				RETURN NIL;
 				RETURN NIL;
 			ELSE (* found *)
 			ELSE (* found *)
-				importBlock.identifier.fingerprint := fp; importBlock.address := adr
+				importBlock.identifier.fingerprint := LONGINT(fp); importBlock.address := adr
 			END;
 			END;
 			RETURN importBlock
 			RETURN importBlock
 		END ImportBlock;
 		END ImportBlock;
@@ -503,8 +503,8 @@ VAR
 		INC(data.size, section.bits.GetSize() DIV 8);
 		INC(data.size, section.bits.GetSize() DIV 8);
 	END DoPreallocate;
 	END DoPreallocate;
 
 
-	PROCEDURE DoAllocate(CONST section: ObjectFile.Section; VAR data: Data): GenericLinker.Address;
-	VAR address: ObjectFile.Bits; size: SIZE;
+	PROCEDURE DoAllocate(CONST section: ObjectFile.Section; VAR data: Data): ADDRESS;
+	VAR address: ADDRESS; size: SIZE;
 	BEGIN
 	BEGIN
 		IF (data.bytes = NIL) OR (LEN(data.bytes) # data.size) THEN NEW(data.bytes, data.size) END;
 		IF (data.bytes = NIL) OR (LEN(data.bytes) # data.size) THEN NEW(data.bytes, data.size) END;
 
 
@@ -514,7 +514,7 @@ VAR
 		address := ADDRESSOF(data.bytes[0])+data.pos; (*  to account for potentially empty variable at end of data ... *)
 		address := ADDRESSOF(data.bytes[0])+data.pos; (*  to account for potentially empty variable at end of data ... *)
 		size := section.bits.GetSize();
 		size := section.bits.GetSize();
 		section.bits.CopyTo(address, size);
 		section.bits.CopyTo(address, size);
-		INC(data.pos, size DIV 8);
+		INC(data.pos, LONGINT(size DIV 8));
 		(*
 		(*
 		bitPos:= 0;
 		bitPos:= 0;
 		WHILE size > 0 DO
 		WHILE size > 0 DO
@@ -532,7 +532,7 @@ VAR
 	VAR
 	VAR
 		file: Files.File; reader: Files.Reader; linker: Linker;
 		file: Files.File; reader: Files.Reader; linker: Linker;
 		arrangement: Arrangement; diagnostics: Diagnostics.StreamDiagnostics; stringWriter: Streams.StringWriter;
 		arrangement: Arrangement; diagnostics: Diagnostics.StreamDiagnostics; stringWriter: Streams.StringWriter;
-		module: Modules.Module; heapBlockAdr,moduleAdr: LONGINT;
+		module: Modules.Module; heapBlockAdr,moduleAdr: ADDRESS;
 		Log: Streams.Writer;
 		Log: Streams.Writer;
 	BEGIN
 	BEGIN
 		file := Files.Old(fileName);
 		file := Files.Old(fileName);

+ 2 - 2
source/StaticLinker.Mod

@@ -157,7 +157,7 @@ TYPE
 	BEGIN SELF.bits.SetBits ((pos - displacement) * unit + offset, bits, value);
 	BEGIN SELF.bits.SetBits ((pos - displacement) * unit + offset, bits, value);
 	END Patch;
 	END Patch;
 
 
-	PROCEDURE CheckReloc(target: LONGINT; pattern: ObjectFile.Pattern; CONST patch: ObjectFile.Patch);
+	PROCEDURE CheckReloc(target: GenericLinker.Address; pattern: ObjectFile.Pattern; CONST patch: ObjectFile.Patch);
 	VAR i: LONGINT;
 	VAR i: LONGINT;
 	BEGIN
 	BEGIN
 		IF (pattern.mode = ObjectFile.Absolute) & (relocInfo # NIL) THEN
 		IF (pattern.mode = ObjectFile.Absolute) & (relocInfo # NIL) THEN
@@ -959,7 +959,7 @@ PROCEDURE Link* (context: Commands.Context);
 VAR options: Options.Options;
 VAR options: Options.Options;
 	silent, useAll, strict: BOOLEAN;
 	silent, useAll, strict: BOOLEAN;
 	codeFileFormat, dataFileFormat: FileFormat;
 	codeFileFormat, dataFileFormat: FileFormat;
-	codeDisplacement, dataDisplacement: GenericLinker.Address;
+	codeDisplacement, dataDisplacement: LONGINT;
 	path, extension, codeFileName, dataFileName, moduleName, logFileName, tempName: Files.FileName;
 	path, extension, codeFileName, dataFileName, moduleName, logFileName, tempName: Files.FileName;
 	diagnostics: Diagnostics.StreamDiagnostics; code, data: Arrangement; linker: GenericLinker.Linker;
 	diagnostics: Diagnostics.StreamDiagnostics; code, data: Arrangement; linker: GenericLinker.Linker;
 	linkRoot: ARRAY 256 OF CHAR; logFile: Files.File; log: Files.Writer;
 	linkRoot: ARRAY 256 OF CHAR; logFile: Files.File; log: Files.Writer;

+ 2 - 2
source/Streams.Mod

@@ -750,8 +750,8 @@ TYPE
 		VAR ch: CHAR;  n, y: LONGINT;
 		VAR ch: CHAR;  n, y: LONGINT;
 		BEGIN
 		BEGIN
 			n := 0;  y := 0;  ch := Get();
 			n := 0;  y := 0;  ch := Get();
-			WHILE ch >= 80X DO INC( y, LSH( LONG( ORD( ch ) ) - 128, n ) );  INC( n, 7 );  ch := Get() END;
-			x := ASH( LSH( LONG( ORD( ch ) ), 25 ), n - 25 ) + y
+			WHILE ch >= 80X DO INC( y, LSH( LONGINT( ORD( ch ) ) - 128, n ) );  INC( n, 7 );  ch := Get() END;
+			x := ASH( LSH( LONGINT( ORD( ch ) ), 25 ), n - 25 ) + y
 		END RawNum;
 		END RawNum;
 
 
 		(** -- Read formatted data (uses Peek for one character lookahead) -- *)
 		(** -- Read formatted data (uses Peek for one character lookahead) -- *)

+ 13 - 7
source/Win32.WinFS.Mod

@@ -317,7 +317,7 @@ TYPE
 			END EnumeratePath;
 			END EnumeratePath;
 
 
 		BEGIN {EXCLUSIVE}
 		BEGIN {EXCLUSIVE}
-			COPY( mask, path );  ConvertChar( path, Files.PathDelimiter, PathDelimiter );  attr := Kernel32.GetFileAttributes( path );  path := "";
+			COPY( mask, path );  ConvertChar( path, Files.PathDelimiter, PathDelimiter );  attr := ToSet(Kernel32.GetFileAttributes( path ));  path := "";
 			IF (Kernel32.FileAttributeDirectory IN attr) & (~(Kernel32.FileAttributeTemporary IN attr)) THEN COPY( mask, path );  COPY( "*", pattern );  ELSE Files.SplitPath( mask, path, pattern );  END;
 			IF (Kernel32.FileAttributeDirectory IN attr) & (~(Kernel32.FileAttributeTemporary IN attr)) THEN COPY( mask, path );  COPY( "*", pattern );  ELSE Files.SplitPath( mask, path, pattern );  END;
 			IF TraceFileSystem IN Trace THEN
 			IF TraceFileSystem IN Trace THEN
 				KernelLog.String( "Enumerate0: " );   KernelLog.String( mask );  KernelLog.String( " :: " );  KernelLog.String( path );  KernelLog.String( " :: " );  KernelLog.String( pattern );  KernelLog.Ln;
 				KernelLog.String( "Enumerate0: " );   KernelLog.String( mask );  KernelLog.String( " :: " );  KernelLog.String( path );  KernelLog.String( " :: " );  KernelLog.String( pattern );  KernelLog.Ln;
@@ -419,7 +419,7 @@ TYPE
 			COPY(fileName, name);
 			COPY(fileName, name);
 			ConvertChar(name, Files.PathDelimiter, PathDelimiter );  
 			ConvertChar(name, Files.PathDelimiter, PathDelimiter );  
 			IF FindFile(fileName, fullName) THEN 
 			IF FindFile(fileName, fullName) THEN 
-				flags := FileFlags(Kernel32.GetFileAttributes(fullName));
+				flags := FileFlags(ToSet(Kernel32.GetFileAttributes(fullName)));
 				ConvertChar(fullName, PathDelimiter,Files.PathDelimiter);  
 				ConvertChar(fullName, PathDelimiter,Files.PathDelimiter);  
 				RETURN TRUE
 				RETURN TRUE
 			ELSE
 			ELSE
@@ -444,7 +444,7 @@ TYPE
 		fileSystem: WinFileSystem;
 		fileSystem: WinFileSystem;
 
 
 		PROCEDURE & Init*( VAR name: ARRAY OF CHAR;  hfile: Kernel32.HANDLE;  key: LONGINT ; fs: WinFileSystem);
 		PROCEDURE & Init*( VAR name: ARRAY OF CHAR;  hfile: Kernel32.HANDLE;  key: LONGINT ; fs: WinFileSystem);
-		VAR s: SET;  res: Kernel32.BOOL;
+		VAR s: SET;  res: Kernel32.BOOL; 
 		BEGIN
 		BEGIN
 			IF TraceFile IN Trace THEN KernelLog.String( "Init: " );  KernelLog.String( name );  KernelLog.String( " (" );  KernelLog.Int( key, 1 );  KernelLog.String( ")" );  KernelLog.Ln;  END;
 			IF TraceFile IN Trace THEN KernelLog.String( "Init: " );  KernelLog.String( name );  KernelLog.String( " (" );  KernelLog.Int( key, 1 );  KernelLog.String( ")" );  KernelLog.Ln;  END;
 			SELF.key := key;  fpos := 0;  SELF.hfile := hfile;  COPY( name, SELF.fname );  tfname := NIL;
 			SELF.key := key;  fpos := 0;  SELF.hfile := hfile;  COPY( name, SELF.fname );  tfname := NIL;
@@ -606,7 +606,7 @@ TYPE
 		PROCEDURE GetAttributes(): SET;
 		PROCEDURE GetAttributes(): SET;
 		VAR s: SET;
 		VAR s: SET;
 		BEGIN
 		BEGIN
-			s := Kernel32.GetFileAttributes( fname );
+			s := ToSet(Kernel32.GetFileAttributes( fname ));
 			RETURN FileFlags(s);
 			RETURN FileFlags(s);
 		END GetAttributes;
 		END GetAttributes;
 
 
@@ -722,6 +722,12 @@ VAR
 	winFS: WinFileSystem;   (* must be unique *)
 	winFS: WinFileSystem;   (* must be unique *)
 
 
 
 
+	PROCEDURE ToSet(d: UNSIGNED32): SET;
+	BEGIN
+		RETURN SYSTEM.VAL(SET, ADDRESS(d)); 
+	END ToSet;
+	
+
 	PROCEDURE DebugFile(f: File);
 	PROCEDURE DebugFile(f: File);
 	BEGIN
 	BEGIN
 		KernelLog.String("fname = "); KernelLog.String(f.fname); KernelLog.Ln;
 		KernelLog.String("fname = "); KernelLog.String(f.fname); KernelLog.Ln;
@@ -1063,7 +1069,7 @@ VAR
 	END CheckPath;
 	END CheckPath;
 
 
 	PROCEDURE CheckName*( name: ARRAY OF CHAR ): BOOLEAN;
 	PROCEDURE CheckName*( name: ARRAY OF CHAR ): BOOLEAN;
-	VAR fullName: FileName;  fileNamePart: Kernel32.LPSTR;  ret, i: LONGINT;  ch: CHAR;  stream, ok: BOOLEAN;
+	VAR fullName: FileName;  fileNamePart: Kernel32.LPSTR;  ret, i: SIZE;  ch: CHAR;  stream, ok: BOOLEAN;
 	BEGIN
 	BEGIN
 		ConvertChar( name, Files.PathDelimiter, PathDelimiter );  ret := Kernel32.GetFullPathName( name, Kernel32.MaxPath, fullName, fileNamePart );
 		ConvertChar( name, Files.PathDelimiter, PathDelimiter );  ret := Kernel32.GetFullPathName( name, Kernel32.MaxPath, fullName, fileNamePart );
 		IF (ret > 0) & CheckPath( fullName ) & (fileNamePart # Kernel32.NULL) THEN
 		IF (ret > 0) & CheckPath( fullName ) & (fileNamePart # Kernel32.NULL) THEN
@@ -1085,7 +1091,7 @@ VAR
 	PROCEDURE GetAttributes*( file: ARRAY OF CHAR ): SET;   (** non-portable *)
 	PROCEDURE GetAttributes*( file: ARRAY OF CHAR ): SET;   (** non-portable *)
 	VAR attrs: SET;
 	VAR attrs: SET;
 	BEGIN
 	BEGIN
-		ConvertChar( file, Files.PathDelimiter, PathDelimiter );  attrs := Kernel32.GetFileAttributes( file );
+		ConvertChar( file, Files.PathDelimiter, PathDelimiter );  attrs := ToSet(Kernel32.GetFileAttributes( file ));
 		IF attrs = {0..31} THEN RETURN {} ELSE RETURN attrs END
 		IF attrs = {0..31} THEN RETURN {} ELSE RETURN attrs END
 	END GetAttributes;
 	END GetAttributes;
 
 
@@ -1196,7 +1202,7 @@ VAR
 
 
 		(* now the file system is installed *)
 		(* now the file system is installed *)
 
 
-		drives := Kernel32.GetLogicalDrives();
+		drives := ToSet(Kernel32.GetLogicalDrives());
 		drives := drives - {0,1}; (* do not scan for diskettes *)
 		drives := drives - {0,1}; (* do not scan for diskettes *)
 		AutoMountWindowsLogicalDrives( drives );
 		AutoMountWindowsLogicalDrives( drives );