Forráskód Böngészése

Replaced unnecessary hugeint functions with proper operators

git-svn-id: https://svn.inf.ethz.ch/svn/lecturers/a2/trunk@6401 8c9fc860-2736-0410-a75d-ab315db34111
eth.negelef 10 éve
szülő
commit
34afa206ac

+ 2 - 2
source/AMD64.ATADisks.Mod

@@ -1236,7 +1236,7 @@ TYPE
 			command := cmdLBA48;
 			command := cmdLBA48;
 			ResetCommand(command, SIZEOF(CommandLBA48Desc));
 			ResetCommand(command, SIZEOF(CommandLBA48Desc));
 			command.dev := dev; command.cmd := cmd;
 			command.dev := dev; command.cmd := cmd;
-			command.lbaHigh := SHORT(Machine.ASHH(lba, -32));command.lbaLow := SHORT(lba); command.count := count;
+			command.lbaHigh := SHORT(ASH(lba, -32));command.lbaLow := SHORT(lba); command.count := count;
 			RETURN command;
 			RETURN command;
 		END NewCommandLBA48;
 		END NewCommandLBA48;
 
 
@@ -1763,7 +1763,7 @@ TYPE
 			END;
 			END;
 
 
 			lbaLow := SHORT(lba);
 			lbaLow := SHORT(lba);
-			lbaHigh := SHORT(Machine.ASHH(lba, -32));
+			lbaHigh := SHORT(ASH(lba, -32));
 			ASSERT((lbaHigh = 0) OR (lbaHigh = -1)); (* negative value possible for raw writing *)
 			ASSERT((lbaHigh = 0) OR (lbaHigh = -1)); (* negative value possible for raw writing *)
 			command.packet[2] := CHR(ASH(lbaLow, -24) MOD 100H);
 			command.packet[2] := CHR(ASH(lbaLow, -24) MOD 100H);
 			command.packet[3] := CHR(ASH(lbaLow, -16) MOD 100H);
 			command.packet[3] := CHR(ASH(lbaLow, -16) MOD 100H);

+ 2 - 2
source/AMD64.BenchInterrupts.Mod

@@ -68,7 +68,7 @@ END Bench;
 
 
 PROCEDURE CyclesToMs(cycles : HUGEINT; mhz : LONGINT) : LONGREAL;
 PROCEDURE CyclesToMs(cycles : HUGEINT; mhz : LONGINT) : LONGREAL;
 BEGIN
 BEGIN
-	RETURN Machine.HIntToLReal(cycles) / (1000*mhz);
+	RETURN LONGREAL(cycles) / (1000*mhz);
 END CyclesToMs;
 END CyclesToMs;
 
 
 PROCEDURE ShowMs(cycles : HUGEINT; out : Streams.Writer);
 PROCEDURE ShowMs(cycles : HUGEINT; out : Streams.Writer);
@@ -95,7 +95,7 @@ BEGIN {EXCLUSIVE}
 			END;
 			END;
 			sum := sum + data[i];
 			sum := sum + data[i];
 		END;
 		END;
-		avg := SHORT(Machine.DivH(sum, nofSamples));
+		avg := SHORT(sum DIV nofSamples);
 		(* calculate standard deviation *)
 		(* calculate standard deviation *)
 		diffSum := 0;
 		diffSum := 0;
 		FOR i := 0 TO LEN(data)-1 DO
 		FOR i := 0 TO LEN(data)-1 DO

+ 3 - 34
source/AMD64.Machine.Mod

@@ -489,37 +489,6 @@ CODE {SYSTEM.AMD64}
 	AND AL, 1
 	AND AL, 1
 END InterruptsEnabled;
 END InterruptsEnabled;
 
 
-(** -- HUGEINT operations -- *)
-
-(** Return h*g. *)
-PROCEDURE MulH* (h, g: HUGEINT): HUGEINT;
-BEGIN RETURN h * g;
-END MulH;
-
-(** Return h DIV g. Rounding and division by zero behaviour is currently undefined. *)
-PROCEDURE DivH* (x, y: HUGEINT): HUGEINT;
-BEGIN RETURN x DIV y
-END DivH;
-
-(** Return ASH(h, n). *)
-PROCEDURE ASHH* (h: HUGEINT; n: LONGINT): HUGEINT;
-BEGIN RETURN ASH (h, n);
-END ASHH;
-
-(** Return a HUGEINT composed of high and low. *)
-PROCEDURE -LInt2ToHInt* (high, low: LONGINT): HUGEINT;
-CODE {SYSTEM.AMD64}
-	POP RAX
-END LInt2ToHInt;
-
-(** Return h as a LONGREAL, with possible loss of precision. *)
-PROCEDURE -HIntToLReal* (h: HUGEINT): LONGREAL;
-CODE {SYSTEM.AMD64, SYSTEM.FPU}
-	FILD QWORD [ESP]
-	PAUSE
-	ADD RSP, 8
-END HIntToLReal;
-
 (** -- Processor initialization -- *)
 (** -- Processor initialization -- *)
 PROCEDURE -SetFCR (s: SET);
 PROCEDURE -SetFCR (s: SET);
 CODE {SYSTEM.AMD64, SYSTEM.FPU}
 CODE {SYSTEM.AMD64, SYSTEM.FPU}
@@ -3377,13 +3346,13 @@ BEGIN
 		FOR i := 0 TO numProcessors-1 DO
 		FOR i := 0 TO numProcessors-1 DO
 			INC (mean, t[i])
 			INC (mean, t[i])
 		END;
 		END;
-		mean := DivH(mean, n);
+		mean := mean DIV n;
 		var := 0;
 		var := 0;
 		FOR i := 0 TO numProcessors-1 DO
 		FOR i := 0 TO numProcessors-1 DO
 			n := t[i] - mean;
 			n := t[i] - mean;
-			INC (var, MulH(n, n))
+			INC (var, n * n)
 		END;
 		END;
-		var := DivH(var, numProcessors - 1);
+		var := var DIV (numProcessors - 1);
 		Trace.String(" mean="); Trace.HIntHex(mean, 16);
 		Trace.String(" mean="); Trace.HIntHex(mean, 16);
 		Trace.String(" var="); Trace.HIntHex(var, 16);
 		Trace.String(" var="); Trace.HIntHex(var, 16);
 		Trace.String(" var="); Trace.Int(SHORT (var), 1);
 		Trace.String(" var="); Trace.Int(SHORT (var), 1);

+ 0 - 161
source/Coop.I386.Machine.Mod

@@ -226,168 +226,7 @@ END GetInit;
 		REP	STOSD
 		REP	STOSD
 		POP	ECX
 		POP	ECX
 	END Fill32;
 	END Fill32;
-	(** -- HUGEINT operations -- *)
 
 
-(** Return h*g. *)
-
-	(** Return h*g. based on code from "AMD Athlon Processor x86 code optimization guide" *)
-	PROCEDURE MulH* (h, g: HUGEINT): HUGEINT;
-	CODE {SYSTEM.i386}
-		PUSH	ECX
-		MOV EDX, [EBP+12]	; y_hi
-		MOV ECX, [EBP+20]	; x_hi
-		OR EDX, ECX		; are x_hi and y_hi both zeros?
-		MOV EDX, [EBP+16]	; x_lo
-		MOV EAX, [EBP+8]	; y_lo
-		JNZ fullMul			; yes, requires full multiplication
-		MUL EDX			; EDX:EAX := y_lo * x_lo
-		JMP exit			; done, return to caller
-
-	fullMul:					; full multiplication is required
-
-		MUL ECX			; EAX := LO(y_lo*x_hi)
-		MOV EBX, EAX		; keep the result
-
-		MOV EAX, [EBP+12] 	; y_hi
-		MUL DWORD [EBP+16]	; EAX := LO(y_hi*x_lo)
-		ADD EBX, EAX 		; EBX := LO(y_lo*x_hi) + LO(y_hi*x_lo)
-
-		MOV EAX, [EBP+8]	; y_lo
-		MUL DWORD [EBP+16]	; EDX := HI(y_lo*x_lo), EAX := LO(y_lo*x_lo)
-		ADD EDX, EBX		; EDX := y_lo*x_hi + y_hi*x_lo + HI(y_lo*x_lo)
-	exit:
-		POP	ECX
-	END MulH;
-
-	(** Return h DIV g. Rounding and division by zero behaviour is currently undefined. *)
-	PROCEDURE DivH* (x, y: HUGEINT): HUGEINT;
-	CODE {SYSTEM.i386}
-		PUSH	ECX
-		MOV ECX, [EBP+12]	; y-hi
-		MOV EBX, [EBP+8]	; y-lo
-		MOV EDX, [EBP+20]	; x-hi
-		MOV EAX, [EBP+16]	; x-lo
-
-		MOV ESI, ECX		; y-hi
-		XOR ESI, EDX		; y-hi ^ x-hi
-		SAR ESI, 31			; (quotient < 0) ? -1 : 0
-		MOV EDI, EDX		; x-hi
-		SAR EDI, 31			; (x < 0) ? -1 : 0
-		XOR EAX, EDI		; if (x < 0)
-		XOR EDX, EDI		; compute 1s complement of x
-		SUB EAX, EDI		; if (x < 0)
-		SBB EDX, EDI		; compute 2s complement of x
-		MOV EDI, ECX		; y-hi
-		SAR EDI, 31			; (y < 0) ? -1 : 0
-		XOR EBX, EDI		; if (y < 0)
-		XOR ECX, EDI		; compute 1s complement of y
-		SUB EBX, EDI		; if (y < 0)
-		SBB ECX, EDI		; compute 2s complement of y
-		JNZ bigDivisor		; y > 2^32-1
-		CMP EDX, EBX		; only one division needed ? (ECX = 0)
-		JAE twoDivs			; need two divisions
-		DIV EBX			; EAX = quotient-lo
-		MOV EDX, ECX		; EDX = quotient-hi = 0
-		; quotient in EDX:EAX
-		XOR EAX, ESI		; if (quotient < 0)
-		XOR EDX, ESI		; compute 1s complement of result
-		SUB EAX, ESI		; if (quotient < 0)
-		SBB EDX, ESI		; compute 2s complement of result
-		JMP exit			; done, return to caller
-
-	twoDivs:
-		MOV ECX, EAX		; save x-lo in ECX
-		MOV EAX, EDX		; get x-hi
-		XOR EDX, EDX		; zero extend it into EDX:EAX
-		DIV EBX			; quotient-hi in EAX
-		XCHG EAX, ECX		; ECX = quotient-hi, EAX = x-lo
-		DIV EBX			; EAX = quotient-lo
-		MOV EDX, ECX		; EDX = quotient-hi
-		; quotient in EDX:EAX
-		JMP makeSign		; make quotient signed
-
-	bigDivisor:
-		SUB ESP, 12			; create three local variables
-		MOV [ESP], EAX		; x-lo
-		MOV [ESP+4], EBX	; y-lo
-		MOV [ESP+8], EDX	; x-hi
-		MOV EDI, ECX		; save y-hi
-		SHR EDX, 1			; shift both
-		RCR EAX, 1			; y and
-		ROR EDI, 1			; and x
-		RCR EBX, 1			; right by 1 bit
-		BSR ECX, ECX		; ECX = number of remaining shifts
-		SHRD EBX, EDI, CL	; scale down y and
-		SHRD EAX, EDX, CL	; x such that y
-		SHR EDX, CL		; less than 2^32 (i.e. fits in EBX)
-		ROL EDI, 1			; restore original y-hi
-		DIV EBX			; compute quotient
-		MOV EBX, [ESP]		; x-lo
-		MOV ECX, EAX		; save quotient
-		IMUL EDI, EAX		; quotient * y hi-word (low only)
-		MUL DWORD [ESP+4]	; quotient * y lo-word
-		ADD EDX, EDI		; EDX:EAX = quotient * y
-		SUB EBX, EAX		; x-lo - (quot.*y)-lo
-		MOV EAX, ECX		; get quotient
-		MOV ECX, [ESP+8]	; x-hi
-		SBB ECX, EDX		; subtract y * quot. from x
-		SBB EAX, 0			; adjust quotient if remainder negative
-		XOR EDX, EDX		; clear hi-word of quotient
-		ADD ESP, 12		; remove local variables
-
-	makeSign:
-		XOR EAX, ESI		; if (quotient < 0)
-		XOR EDX, ESI		; compute 1s complement of result
-		SUB EAX, ESI		; if (quotient < 0)
-		SBB EDX, ESI		; compute 2s complement of result
-	exit:
-		POP	ECX
-	END DivH;
-
-(** Return ASH(h, n). *)
-	PROCEDURE -ASHH*( h: HUGEINT;  n: LONGINT ): HUGEINT;
-	CODE {SYSTEM.i386}
-		POP	EBX
-		POP	EAX
-		POP	EDX
-		CMP	EBX, 0
-		JL	right
-		AND	EBX, 63	;  limit count, like ASH
-		JZ	exit
-		ll:
-		SHL	EAX, 1
-		RCL	EDX, 1
-		DEC	EBX
-		JNZ	ll
-		JMP	exit
-		right:
-		NEG EBX
-		AND	EBX, 63	;  limit count, like ASH
-		JZ	exit
-		lr:
-		SAR	EDX, 1
-		RCR	EAX, 1
-		DEC	EBX
-		JNZ	lr
-		exit:
-	END ASHH;
-
-(** Return a HUGEINT composed of high and low. *)
-
-	PROCEDURE -LInt2ToHInt*( high, low: LONGINT ): HUGEINT;
-	CODE {SYSTEM.i386}
-		POP	EAX
-		POP	EDX
-	END LInt2ToHInt;
-
-(** Return h as a LONGREAL, with possible loss of precision. *)
-
-	PROCEDURE -HIntToLReal*( h: HUGEINT ): LONGREAL;
-	CODE {SYSTEM.i386, SYSTEM.FPU}
-		FILD	QWORD[ESP]
-		FWAIT
-		ADD	ESP, 8
-	END HIntToLReal;
 (** -- Processor initialization -- *)
 (** -- Processor initialization -- *)
 
 
 	PROCEDURE -SetFCR( s: SET );
 	PROCEDURE -SetFCR( s: SET );

+ 1 - 1
source/CryptoBigNumbers.Mod

@@ -370,7 +370,7 @@ VAR
 	BEGIN
 	BEGIN
 		tb.lo := b;  tb.hi := 0;
 		tb.lo := b;  tb.hi := 0;
 		tc.lo := c;  tc.hi := 0;
 		tc.lo := c;  tc.hi := 0;
-		res := M.MulH( S.VAL( HUGEINT, tb ), S.VAL( HUGEINT, tc ) );
+		res := S.VAL( HUGEINT, tb ) * S.VAL( HUGEINT, tc );
 		INC( res, d );
 		INC( res, d );
 		low := SHORT( res );
 		low := SHORT( res );
 		high := SHORT( LSH( res, -32 ) );
 		high := SHORT( LSH( res, -32 ) );

+ 1 - 1
source/DebugLog.Mod

@@ -324,7 +324,7 @@ VAR
 BEGIN {EXCLUSIVE}
 BEGIN {EXCLUSIVE}
 	TraceIdString();
 	TraceIdString();
 	out := logwindow.tw;
 	out := logwindow.tw;
-	out.Hex(SHORT (Machine.ASHH(x, -32)), w-8);
+	out.Hex(SHORT (ASH(x, -32)), w-8);
 	out.Hex(SHORT (x), 8);
 	out.Hex(SHORT (x), 8);
 	out.Ln(); out.Update();
 	out.Ln(); out.Update();
 END HIntHex;
 END HIntHex;

+ 5 - 5
source/DiskTests.Mod

@@ -16,7 +16,7 @@ MODULE DiskTests; (** AUTHOR "staubesv"; PURPOSE "Simple block device tests"; *)
  *)
  *)
 
 
 IMPORT
 IMPORT
-	Machine, Streams, Random, Kernel, Commands, Disks, Partitions, Lib := PartitionsLib, Strings;
+	Streams, Random, Kernel, Commands, Disks, Partitions, Lib := PartitionsLib, Strings;
 
 
 TYPE
 TYPE
 
 
@@ -197,9 +197,9 @@ TYPE
 			PROCEDURE WriteB(b: HUGEINT; w : Streams.Writer);
 			PROCEDURE WriteB(b: HUGEINT; w : Streams.Writer);
 			VAR suffix: ARRAY 3 OF CHAR;
 			VAR suffix: ARRAY 3 OF CHAR;
 			BEGIN
 			BEGIN
-				IF b > 1024*1024*1024 THEN suffix := "GB"; b := Machine.DivH(b, 1024*1024*1024);
-				ELSIF b > 1024*1024 THEN suffix := "MB"; b := Machine.DivH(b, 1024*1024);
-				ELSIF b > 1024 THEN suffix := "KB"; b := Machine.DivH(b, 1024);
+				IF b > 1024*1024*1024 THEN suffix := "GB"; b := b DIV (1024*1024*1024);
+				ELSIF b > 1024*1024 THEN suffix := "MB"; b := b DIV (1024*1024);
+				ELSIF b > 1024 THEN suffix := "KB"; b := b DIV 1024;
 				ELSE suffix := "B";
 				ELSE suffix := "B";
 				END;
 				END;
 				w.Int(SHORT(b), 0); w.String(suffix);
 				w.Int(SHORT(b), 0); w.String(suffix);
@@ -216,7 +216,7 @@ TYPE
 				val := 0; FOR i := 0 TO LEN(testedSectors)-1 DO IF testedSectors[i] THEN INC(val); END; END;
 				val := 0; FOR i := 0 TO LEN(testedSectors)-1 DO IF testedSectors[i] THEN INC(val); END; END;
 				info.String("   Transfer Sizes Coverage: "); info.FloatFix(100.0 * val / LEN(testedSectors), 5, 2, 0); info.Char("%"); info.Ln;
 				info.String("   Transfer Sizes Coverage: "); info.FloatFix(100.0 * val / LEN(testedSectors), 5, 2, 0); info.Char("%"); info.Ln;
 			END;
 			END;
-			info.String("   Total amount of data read: "); WriteB(Machine.MulH(blocksRead, disk.device.blockSize), info); info.Ln;
+			info.String("   Total amount of data read: "); WriteB(blocksRead * disk.device.blockSize, info); info.Ln;
 		END WriteSummary;
 		END WriteSummary;
 
 
 		PROCEDURE PerformStep;
 		PROCEDURE PerformStep;

+ 3 - 34
source/EFI.AMD64.Machine.Mod

@@ -490,37 +490,6 @@ CODE {SYSTEM.AMD64}
 	AND AL, 1
 	AND AL, 1
 END InterruptsEnabled;
 END InterruptsEnabled;
 
 
-(** -- HUGEINT operations -- *)
-
-(** Return h*g. *)
-PROCEDURE MulH* (h, g: HUGEINT): HUGEINT;
-BEGIN RETURN h * g;
-END MulH;
-
-(** Return h DIV g. Rounding and division by zero behaviour is currently undefined. *)
-PROCEDURE DivH* (x, y: HUGEINT): HUGEINT;
-BEGIN RETURN x DIV y
-END DivH;
-
-(** Return ASH(h, n). *)
-PROCEDURE ASHH* (h: HUGEINT; n: LONGINT): HUGEINT;
-BEGIN RETURN ASH (h, n);
-END ASHH;
-
-(** Return a HUGEINT composed of high and low. *)
-PROCEDURE -LInt2ToHInt* (high, low: LONGINT): HUGEINT;
-CODE {SYSTEM.AMD64}
-	POP RAX
-END LInt2ToHInt;
-
-(** Return h as a LONGREAL, with possible loss of precision. *)
-PROCEDURE -HIntToLReal* (h: HUGEINT): LONGREAL;
-CODE {SYSTEM.AMD64, SYSTEM.FPU}
-	FILD QWORD [ESP]
-	PAUSE
-	ADD RSP, 8
-END HIntToLReal;
-
 (** -- Processor initialization -- *)
 (** -- Processor initialization -- *)
 PROCEDURE -SetFCR (s: SET);
 PROCEDURE -SetFCR (s: SET);
 CODE {SYSTEM.AMD64, SYSTEM.FPU}
 CODE {SYSTEM.AMD64, SYSTEM.FPU}
@@ -3378,13 +3347,13 @@ BEGIN
 		FOR i := 0 TO numProcessors-1 DO
 		FOR i := 0 TO numProcessors-1 DO
 			INC (mean, t[i])
 			INC (mean, t[i])
 		END;
 		END;
-		mean := DivH(mean, n);
+		mean := mean DIV n;
 		var := 0;
 		var := 0;
 		FOR i := 0 TO numProcessors-1 DO
 		FOR i := 0 TO numProcessors-1 DO
 			n := t[i] - mean;
 			n := t[i] - mean;
-			INC (var, MulH(n, n))
+			INC (var, n * n)
 		END;
 		END;
-		var := DivH(var, numProcessors - 1);
+		var := var DIV (numProcessors - 1);
 		Trace.String(" mean="); Trace.HIntHex(mean, 16);
 		Trace.String(" mean="); Trace.HIntHex(mean, 16);
 		Trace.String(" var="); Trace.HIntHex(var, 16);
 		Trace.String(" var="); Trace.HIntHex(var, 16);
 		Trace.String(" var="); Trace.Int(SHORT (var), 1);
 		Trace.String(" var="); Trace.Int(SHORT (var), 1);

+ 3 - 3
source/FoxInterpreterBackend.Mod

@@ -1,6 +1,6 @@
 MODULE FoxInterpreterBackend; (** AUTHOR "fof"; PURPOSE "abstract code interpreter"; *)
 MODULE FoxInterpreterBackend; (** AUTHOR "fof"; PURPOSE "abstract code interpreter"; *)
 
 
-IMPORT Basic := FoxBasic, SYSTEM, Diagnostics, Intermediate := FoxIntermediateCode, Sections := FoxSections, SyntaxTree := FoxSyntaxTree, Options, Machine,
+IMPORT Basic := FoxBasic, SYSTEM, Diagnostics, Intermediate := FoxIntermediateCode, Sections := FoxSections, SyntaxTree := FoxSyntaxTree, Options,
 	IntermediateBackend := FoxIntermediateBackend, Backend := FoxBackend, Global := FoxGlobal, Formats := FoxFormats,
 	IntermediateBackend := FoxIntermediateBackend, Backend := FoxBackend, Global := FoxGlobal, Formats := FoxFormats,
 	Trace := KernelLog, Streams, SymbolFileFormat := FoxTextualSymbolFile;
 	Trace := KernelLog, Streams, SymbolFileFormat := FoxTextualSymbolFile;
 
 
@@ -516,7 +516,7 @@ TYPE
 		ELSE
 		ELSE
 			IF type.sizeInBits= 1 THEN dest.int1 := dest.int1 * source.int1;
 			IF type.sizeInBits= 1 THEN dest.int1 := dest.int1 * source.int1;
 			ELSIF type.sizeInBits= 2 THEN dest.int2 := dest.int2 * source.int2;
 			ELSIF type.sizeInBits= 2 THEN dest.int2 := dest.int2 * source.int2;
-			ELSIF type.sizeInBits= 8 THEN dest.int8 := Machine.MulH (dest.int8, source.int8);
+			ELSIF type.sizeInBits= 8 THEN dest.int8 := dest.int8 * source.int8;
 			ELSE dest.int4 := dest.int4 * source.int4; END;
 			ELSE dest.int4 := dest.int4 * source.int4; END;
 		END;
 		END;
 	END Multiply;
 	END Multiply;
@@ -529,7 +529,7 @@ TYPE
 		ELSE
 		ELSE
 			IF type.sizeInBits= 1 THEN dest.int1 := dest.int1 DIV source.int1;
 			IF type.sizeInBits= 1 THEN dest.int1 := dest.int1 DIV source.int1;
 			ELSIF type.sizeInBits= 2 THEN dest.int2 := dest.int2 DIV source.int2;
 			ELSIF type.sizeInBits= 2 THEN dest.int2 := dest.int2 DIV source.int2;
-			ELSIF type.sizeInBits= 8 THEN dest.int8 := Machine.DivH (dest.int8, source.int8);
+			ELSIF type.sizeInBits= 8 THEN dest.int8 := dest.int8 * source.int8;
 			ELSE dest.int4 := dest.int4 DIV source.int4; END;
 			ELSE dest.int4 := dest.int4 DIV source.int4; END;
 		END;
 		END;
 	END Divide;
 	END Divide;

+ 3 - 158
source/Generic.I386.Machine.Mod

@@ -497,161 +497,6 @@ CODE {SYSTEM.i386}
 	AND AL, 1
 	AND AL, 1
 END InterruptsEnabled;
 END InterruptsEnabled;
 
 
-(** -- HUGEINT operations -- *)
-
-(** Return h*g. based on code from "AMD Athlon Processor x86 code optimization guide" *)
-PROCEDURE  MulH* (h, g: HUGEINT): HUGEINT;
-CODE {SYSTEM.i386}
-	MOV EDX, [EBP+12]	; y_hi
-	MOV ECX, [EBP+20]	; x_hi
-	OR EDX, ECX		; are x_hi and y_hi both zeros?
-	MOV EDX, [EBP+16]	; x_lo
-	MOV EAX, [EBP+8]	; y_lo
-	JNZ fullMul			; yes, requires full multiplication
-	MUL EDX			; EDX:EAX := y_lo * x_lo
-	JMP exit			; done, return to caller
-
-fullMul:					; full multiplication is required
-
-	MUL ECX			; EAX := LO(y_lo*x_hi)
-	MOV EBX, EAX		; keep the result
-
-	MOV EAX, [EBP+12] 	; y_hi
-	MUL DWORD  [EBP+16]	; EAX := LO(y_hi*x_lo)
-	ADD EBX, EAX 		; EBX := LO(y_lo*x_hi) + LO(y_hi*x_lo)
-
-	MOV EAX, [EBP+8]	; y_lo
-	MUL DWORD   [EBP+16]	; EDX := HI(y_lo*x_lo), EAX := LO(y_lo*x_lo)
-	ADD EDX, EBX		; EDX := y_lo*x_hi + y_hi*x_lo + HI(y_lo*x_lo)
-exit:
-END MulH;
-
-(** Return h DIV g. Rounding and division by zero behaviour is currently undefined. *)
-PROCEDURE DivH* (x, y: HUGEINT): HUGEINT;
-CODE {SYSTEM.i386}
-	MOV ECX, [EBP+12]	; y-hi
-	MOV EBX, [EBP+8]	; y-lo
-	MOV EDX, [EBP+20]	; x-hi
-	MOV EAX, [EBP+16]	; x-lo
-
-	MOV ESI, ECX		; y-hi
-	XOR ESI, EDX		; y-hi ^ x-hi
-	SAR ESI, 31			; (quotient < 0) ? -1 : 0
-	MOV EDI, EDX		; x-hi
-	SAR EDI, 31			; (x < 0) ? -1 : 0
-	XOR EAX, EDI		; if (x < 0)
-	XOR EDX, EDI		; compute 1s complement of x
-	SUB EAX, EDI		; if (x < 0)
-	SBB EDX, EDI		; compute 2s complement of x
-	MOV EDI, ECX		; y-hi
-	SAR EDI, 31			; (y < 0) ? -1 : 0
-	XOR EBX, EDI		; if (y < 0)
-	XOR ECX, EDI		; compute 1s complement of y
-	SUB EBX, EDI		; if (y < 0)
-	SBB ECX, EDI		; compute 2s complement of y
-	JNZ bigDivisor		; y > 2^32-1
-	CMP EDX, EBX		; only one division needed ? (ECX = 0)
-	JAE twoDivs			; need two divisions
-	DIV EBX			; EAX = quotient-lo
-	MOV EDX, ECX		; EDX = quotient-hi = 0
-	; quotient in EDX:EAX
-	XOR EAX, ESI		; if (quotient < 0)
-	XOR EDX, ESI		; compute 1s complement of result
-	SUB EAX, ESI		; if (quotient < 0)
-	SBB EDX, ESI		; compute 2s complement of result
-	JMP exit			; done, return to caller
-
-twoDivs:
-	MOV ECX, EAX		; save x-lo in ECX
-	MOV EAX, EDX		; get x-hi
-	XOR EDX, EDX		; zero extend it into EDX:EAX
-	DIV EBX			; quotient-hi in EAX
-	XCHG EAX, ECX		; ECX = quotient-hi, EAX = x-lo
-	DIV EBX			; EAX = quotient-lo
-	MOV EDX, ECX		; EDX = quotient-hi
-	; quotient in EDX:EAX
-	JMP makeSign		; make quotient signed
-
-bigDivisor:
-	SUB ESP, 12			; create three local variables
-	MOV [ESP], EAX		; x-lo
-	MOV [ESP+4], EBX	; y-lo
-	MOV [ESP+8], EDX	; x-hi
-	MOV EDI, ECX		; save y-hi
-	SHR EDX, 1			; shift both
-	RCR EAX, 1			; y and
-	ROR EDI, 1			; and x
-	RCR EBX, 1			; right by 1 bit
-	BSR ECX, ECX		; ECX = number of remaining shifts
-	SHRD EBX, EDI, CL	; scale down y and
-	SHRD EAX, EDX, CL	; x such that y
-	SHR EDX, CL		; less than 2^32 (i.e. fits in EBX)
-	ROL EDI, 1			; restore original y-hi
-	DIV EBX			; compute quotient
-	MOV EBX, [ESP]		; x-lo
-	MOV ECX, EAX		; save quotient
-	IMUL EDI, EAX		; quotient * y hi-word (low only)
-	MUL DWORD [ESP+4]	; quotient * y lo-word
-	ADD EDX, EDI		; EDX:EAX = quotient * y
-	SUB EBX, EAX		; x-lo - (quot.*y)-lo
-	MOV EAX, ECX		; get quotient
-	MOV ECX, [ESP+8]	; x-hi
-	SBB ECX, EDX		; subtract y * quot. from x
-	SBB EAX, 0			; adjust quotient if remainder negative
-	XOR EDX, EDX		; clear hi-word of quotient
-	ADD ESP, 12		; remove local variables
-
-makeSign:
-	XOR EAX, ESI		; if (quotient < 0)
-	XOR EDX, ESI		; compute 1s complement of result
-	SUB EAX, ESI		; if (quotient < 0)
-	SBB EDX, ESI		; compute 2s complement of result
-exit:
-END DivH;
-
-(** Return ASH(h, n). *)
-PROCEDURE  -ASHH* (h: HUGEINT; n: LONGINT): HUGEINT;
-CODE {SYSTEM.i386}
-	POP ECX
-	POP EAX
-	POP EDX
-	CMP ECX, 0
-	JL right
-	AND ECX, 63	; limit count, like ASH
-	JZ exit
-ll:
-	SHL EAX, 1
-	RCL EDX, 1
-	DEC ECX
-	JNZ ll
-	JMP exit
-right:
-	NEG ECX
-	AND ECX, 63	; limit count, like ASH
-	JZ exit
-lr:
-	SAR EDX, 1
-	RCR EAX, 1
-	DEC ECX
-	JNZ lr
-exit:
-END ASHH;
-
-(** Return a HUGEINT composed of high and low. *)
-PROCEDURE  -LInt2ToHInt* (high, low: LONGINT): HUGEINT;
-CODE {SYSTEM.i386}
-	POP EAX
-	POP EDX
-END LInt2ToHInt;
-
-(** Return h as a LONGREAL, with possible loss of precision. *)
-PROCEDURE -HIntToLReal* (h: HUGEINT): LONGREAL;
-CODE {SYSTEM.i386, SYSTEM.FPU}
-	FILD QWORD [ESP]
-	FWAIT
-	ADD ESP, 8
-END HIntToLReal;
-
 (** -- Processor initialization -- *)
 (** -- Processor initialization -- *)
 PROCEDURE -SetFCR (s: SET);
 PROCEDURE -SetFCR (s: SET);
 CODE {SYSTEM.i386, SYSTEM.FPU}
 CODE {SYSTEM.i386, SYSTEM.FPU}
@@ -3279,13 +3124,13 @@ BEGIN
 		FOR i := 0 TO numProcessors-1 DO
 		FOR i := 0 TO numProcessors-1 DO
 			INC (mean, t[i])
 			INC (mean, t[i])
 		END;
 		END;
-		mean := DivH(mean, n);
+		mean := mean DIV n;
 		var := 0;
 		var := 0;
 		FOR i := 0 TO numProcessors-1 DO
 		FOR i := 0 TO numProcessors-1 DO
 			n := t[i] - mean;
 			n := t[i] - mean;
-			INC (var, MulH(n, n))
+			INC (var, n * n)
 		END;
 		END;
-		var := DivH(var, numProcessors - 1);
+		var := var DIV (numProcessors - 1);
 		Trace.String(" mean="); Trace.HIntHex(mean, 16);
 		Trace.String(" mean="); Trace.HIntHex(mean, 16);
 		Trace.String(" var="); Trace.HIntHex(var, 16);
 		Trace.String(" var="); Trace.HIntHex(var, 16);
 		Trace.String(" var="); Trace.Int(SHORT (var), 1);
 		Trace.String(" var="); Trace.Int(SHORT (var), 1);

+ 2 - 2
source/I386.ATADisks.Mod

@@ -1235,7 +1235,7 @@ TYPE
 			command := cmdLBA48;
 			command := cmdLBA48;
 			ResetCommand(command, SIZEOF(CommandLBA48Desc));
 			ResetCommand(command, SIZEOF(CommandLBA48Desc));
 			command.dev := dev; command.cmd := cmd;
 			command.dev := dev; command.cmd := cmd;
-			command.lbaHigh := SHORT(Machine.ASHH(lba, -32));command.lbaLow := SHORT(lba); command.count := count;
+			command.lbaHigh := SHORT(ASH(lba, -32));command.lbaLow := SHORT(lba); command.count := count;
 			RETURN command;
 			RETURN command;
 		END NewCommandLBA48;
 		END NewCommandLBA48;
 
 
@@ -1761,7 +1761,7 @@ TYPE
 			END;
 			END;
 
 
 			lbaLow := SHORT(lba);
 			lbaLow := SHORT(lba);
-			lbaHigh := SHORT(Machine.ASHH(lba, -32));
+			lbaHigh := SHORT(ASH(lba, -32));
 			ASSERT((lbaHigh = 0) OR (lbaHigh = -1)); (* negative value possible for raw writing *)
 			ASSERT((lbaHigh = 0) OR (lbaHigh = -1)); (* negative value possible for raw writing *)
 			command.packet[2] := CHR(ASH(lbaLow, -24) MOD 100H);
 			command.packet[2] := CHR(ASH(lbaLow, -24) MOD 100H);
 			command.packet[3] := CHR(ASH(lbaLow, -16) MOD 100H);
 			command.packet[3] := CHR(ASH(lbaLow, -16) MOD 100H);

+ 2 - 2
source/I386.BenchInterrupts.Mod

@@ -68,7 +68,7 @@ END Bench;
 
 
 PROCEDURE CyclesToMs(cycles : HUGEINT; mhz : LONGINT) : LONGREAL;
 PROCEDURE CyclesToMs(cycles : HUGEINT; mhz : LONGINT) : LONGREAL;
 BEGIN
 BEGIN
-	RETURN Machine.HIntToLReal(cycles) / (1000*mhz);
+	RETURN LONGREAL(cycles) / (1000*mhz);
 END CyclesToMs;
 END CyclesToMs;
 
 
 PROCEDURE ShowMs(cycles : HUGEINT; out : Streams.Writer);
 PROCEDURE ShowMs(cycles : HUGEINT; out : Streams.Writer);
@@ -95,7 +95,7 @@ BEGIN {EXCLUSIVE}
 			END;
 			END;
 			sum := sum + data[i];
 			sum := sum + data[i];
 		END;
 		END;
-		avg := SHORT(Machine.DivH(sum, nofSamples));
+		avg := SHORT(sum DIV nofSamples);
 		(* calculate standard deviation *)
 		(* calculate standard deviation *)
 		diffSum := 0;
 		diffSum := 0;
 		FOR i := 0 TO LEN(data)-1 DO
 		FOR i := 0 TO LEN(data)-1 DO

+ 3 - 158
source/I386.Machine.Mod

@@ -492,161 +492,6 @@ CODE {SYSTEM.i386}
 	AND AL, 1
 	AND AL, 1
 END InterruptsEnabled;
 END InterruptsEnabled;
 
 
-(** -- HUGEINT operations -- *)
-
-(** Return h*g. based on code from "AMD Athlon Processor x86 code optimization guide" *)
-PROCEDURE  MulH* (h, g: HUGEINT): HUGEINT;
-CODE {SYSTEM.i386}
-	MOV EDX, [EBP+12]	; y_hi
-	MOV ECX, [EBP+20]	; x_hi
-	OR EDX, ECX		; are x_hi and y_hi both zeros?
-	MOV EDX, [EBP+16]	; x_lo
-	MOV EAX, [EBP+8]	; y_lo
-	JNZ fullMul			; yes, requires full multiplication
-	MUL EDX			; EDX:EAX := y_lo * x_lo
-	JMP exit			; done, return to caller
-
-fullMul:					; full multiplication is required
-
-	MUL ECX			; EAX := LO(y_lo*x_hi)
-	MOV EBX, EAX		; keep the result
-
-	MOV EAX, [EBP+12] 	; y_hi
-	MUL DWORD  [EBP+16]	; EAX := LO(y_hi*x_lo)
-	ADD EBX, EAX 		; EBX := LO(y_lo*x_hi) + LO(y_hi*x_lo)
-
-	MOV EAX, [EBP+8]	; y_lo
-	MUL DWORD   [EBP+16]	; EDX := HI(y_lo*x_lo), EAX := LO(y_lo*x_lo)
-	ADD EDX, EBX		; EDX := y_lo*x_hi + y_hi*x_lo + HI(y_lo*x_lo)
-exit:
-END MulH;
-
-(** Return h DIV g. Rounding and division by zero behaviour is currently undefined. *)
-PROCEDURE DivH* (x, y: HUGEINT): HUGEINT;
-CODE {SYSTEM.i386}
-	MOV ECX, [EBP+12]	; y-hi
-	MOV EBX, [EBP+8]	; y-lo
-	MOV EDX, [EBP+20]	; x-hi
-	MOV EAX, [EBP+16]	; x-lo
-
-	MOV ESI, ECX		; y-hi
-	XOR ESI, EDX		; y-hi ^ x-hi
-	SAR ESI, 31			; (quotient < 0) ? -1 : 0
-	MOV EDI, EDX		; x-hi
-	SAR EDI, 31			; (x < 0) ? -1 : 0
-	XOR EAX, EDI		; if (x < 0)
-	XOR EDX, EDI		; compute 1s complement of x
-	SUB EAX, EDI		; if (x < 0)
-	SBB EDX, EDI		; compute 2s complement of x
-	MOV EDI, ECX		; y-hi
-	SAR EDI, 31			; (y < 0) ? -1 : 0
-	XOR EBX, EDI		; if (y < 0)
-	XOR ECX, EDI		; compute 1s complement of y
-	SUB EBX, EDI		; if (y < 0)
-	SBB ECX, EDI		; compute 2s complement of y
-	JNZ bigDivisor		; y > 2^32-1
-	CMP EDX, EBX		; only one division needed ? (ECX = 0)
-	JAE twoDivs			; need two divisions
-	DIV EBX			; EAX = quotient-lo
-	MOV EDX, ECX		; EDX = quotient-hi = 0
-	; quotient in EDX:EAX
-	XOR EAX, ESI		; if (quotient < 0)
-	XOR EDX, ESI		; compute 1s complement of result
-	SUB EAX, ESI		; if (quotient < 0)
-	SBB EDX, ESI		; compute 2s complement of result
-	JMP exit			; done, return to caller
-
-twoDivs:
-	MOV ECX, EAX		; save x-lo in ECX
-	MOV EAX, EDX		; get x-hi
-	XOR EDX, EDX		; zero extend it into EDX:EAX
-	DIV EBX			; quotient-hi in EAX
-	XCHG EAX, ECX		; ECX = quotient-hi, EAX = x-lo
-	DIV EBX			; EAX = quotient-lo
-	MOV EDX, ECX		; EDX = quotient-hi
-	; quotient in EDX:EAX
-	JMP makeSign		; make quotient signed
-
-bigDivisor:
-	SUB ESP, 12			; create three local variables
-	MOV [ESP], EAX		; x-lo
-	MOV [ESP+4], EBX	; y-lo
-	MOV [ESP+8], EDX	; x-hi
-	MOV EDI, ECX		; save y-hi
-	SHR EDX, 1			; shift both
-	RCR EAX, 1			; y and
-	ROR EDI, 1			; and x
-	RCR EBX, 1			; right by 1 bit
-	BSR ECX, ECX		; ECX = number of remaining shifts
-	SHRD EBX, EDI, CL	; scale down y and
-	SHRD EAX, EDX, CL	; x such that y
-	SHR EDX, CL		; less than 2^32 (i.e. fits in EBX)
-	ROL EDI, 1			; restore original y-hi
-	DIV EBX			; compute quotient
-	MOV EBX, [ESP]		; x-lo
-	MOV ECX, EAX		; save quotient
-	IMUL EDI, EAX		; quotient * y hi-word (low only)
-	MUL DWORD [ESP+4]	; quotient * y lo-word
-	ADD EDX, EDI		; EDX:EAX = quotient * y
-	SUB EBX, EAX		; x-lo - (quot.*y)-lo
-	MOV EAX, ECX		; get quotient
-	MOV ECX, [ESP+8]	; x-hi
-	SBB ECX, EDX		; subtract y * quot. from x
-	SBB EAX, 0			; adjust quotient if remainder negative
-	XOR EDX, EDX		; clear hi-word of quotient
-	ADD ESP, 12		; remove local variables
-
-makeSign:
-	XOR EAX, ESI		; if (quotient < 0)
-	XOR EDX, ESI		; compute 1s complement of result
-	SUB EAX, ESI		; if (quotient < 0)
-	SBB EDX, ESI		; compute 2s complement of result
-exit:
-END DivH;
-
-(** Return ASH(h, n). *)
-PROCEDURE  -ASHH* (h: HUGEINT; n: LONGINT): HUGEINT;
-CODE {SYSTEM.i386}
-	POP ECX
-	POP EAX
-	POP EDX
-	CMP ECX, 0
-	JL right
-	AND ECX, 63	; limit count, like ASH
-	JZ exit
-ll:
-	SHL EAX, 1
-	RCL EDX, 1
-	DEC ECX
-	JNZ ll
-	JMP exit
-right:
-	NEG ECX
-	AND ECX, 63	; limit count, like ASH
-	JZ exit
-lr:
-	SAR EDX, 1
-	RCR EAX, 1
-	DEC ECX
-	JNZ lr
-exit:
-END ASHH;
-
-(** Return a HUGEINT composed of high and low. *)
-PROCEDURE  -LInt2ToHInt* (high, low: LONGINT): HUGEINT;
-CODE {SYSTEM.i386}
-	POP EAX
-	POP EDX
-END LInt2ToHInt;
-
-(** Return h as a LONGREAL, with possible loss of precision. *)
-PROCEDURE -HIntToLReal* (h: HUGEINT): LONGREAL;
-CODE {SYSTEM.i386, SYSTEM.FPU}
-	FILD QWORD [ESP]
-	FWAIT
-	ADD ESP, 8
-END HIntToLReal;
-
 (** -- Processor initialization -- *)
 (** -- Processor initialization -- *)
 PROCEDURE -SetFCR (s: SET);
 PROCEDURE -SetFCR (s: SET);
 CODE {SYSTEM.i386, SYSTEM.FPU}
 CODE {SYSTEM.i386, SYSTEM.FPU}
@@ -3279,13 +3124,13 @@ BEGIN
 		FOR i := 0 TO numProcessors-1 DO
 		FOR i := 0 TO numProcessors-1 DO
 			INC (mean, t[i])
 			INC (mean, t[i])
 		END;
 		END;
-		mean := DivH(mean, n);
+		mean := mean DIV n;
 		var := 0;
 		var := 0;
 		FOR i := 0 TO numProcessors-1 DO
 		FOR i := 0 TO numProcessors-1 DO
 			n := t[i] - mean;
 			n := t[i] - mean;
-			INC (var, MulH(n, n))
+			INC (var, n * n)
 		END;
 		END;
-		var := DivH(var, numProcessors - 1);
+		var := var DIV (numProcessors - 1);
 		Trace.String(" mean="); Trace.HIntHex(mean, 16);
 		Trace.String(" mean="); Trace.HIntHex(mean, 16);
 		Trace.String(" var="); Trace.HIntHex(var, 16);
 		Trace.String(" var="); Trace.HIntHex(var, 16);
 		Trace.String(" var="); Trace.Int(SHORT (var), 1);
 		Trace.String(" var="); Trace.Int(SHORT (var), 1);

+ 8 - 8
source/OGGUtilities.Mod

@@ -4,7 +4,7 @@
 MODULE OGGUtilities;
 MODULE OGGUtilities;
 
 
 IMPORT
 IMPORT
-	SYSTEM, Strings, Files,  KernelLog, Machine, SoundDevices, BIT;
+	SYSTEM, Strings, Files,  KernelLog, SoundDevices, BIT;
 
 
 CONST
 CONST
 	(* debugging set *)
 	(* debugging set *)
@@ -673,7 +673,7 @@ TYPE
 		IF h < 0 THEN h := -1 * h END;
 		IF h < 0 THEN h := -1 * h END;
 		res := 0;
 		res := 0;
 		FOR i := 0 TO 63 DO
 		FOR i := 0 TO 63 DO
-			IF Machine.HIntToLInt(h) MOD 2 = 1 THEN
+			IF LONGINT(h) MOD 2 = 1 THEN
 				res := i
 				res := i
 			END;
 			END;
 			h := LSH(h, -1)
 			h := LSH(h, -1)
@@ -737,8 +737,8 @@ TYPE
 		ELSE
 		ELSE
 			n := Ny DIV 2;
 			n := Ny DIV 2;
 			divident := LSH(LONG(LONG(1)), n);
 			divident := LSH(LONG(LONG(1)), n);
-			a := Machine.DivH(a, divident);
-			b := Machine.DivH(b, divident);
+			a := a DIV divident;
+			b := b DIV, divident;
 			RETURN a * b
 			RETURN a * b
 		END
 		END
 	END MultFP;
 	END MultFP;
@@ -794,13 +794,13 @@ TYPE
 	(** scales a hugeint down for fix-point representation (rounded) with constant fraction Ny*)
 	(** scales a hugeint down for fix-point representation (rounded) with constant fraction Ny*)
 	PROCEDURE ScaleDownRoundedHuge*(i: HUGEINT): LONGINT;
 	PROCEDURE ScaleDownRoundedHuge*(i: HUGEINT): LONGINT;
 	BEGIN
 	BEGIN
-		RETURN SHORT(Machine.DivH(i + Machine.DivH(ScaleFactor , 2), ScaleFactor))
+		RETURN SHORT((i + ScaleFactor DIV 2) DIV ScaleFactor)
 	END ScaleDownRoundedHuge;
 	END ScaleDownRoundedHuge;
 
 
 	(** scales a hugeint down for fix-point representation  with constant fraction Ny*)
 	(** scales a hugeint down for fix-point representation  with constant fraction Ny*)
 	PROCEDURE ScaleDownHuge(i: HUGEINT): HUGEINT;
 	PROCEDURE ScaleDownHuge(i: HUGEINT): HUGEINT;
 	BEGIN
 	BEGIN
-		RETURN Machine.DivH(i, ScaleFactor)
+		RETURN i DIV ScaleFactor
 	END ScaleDownHuge;
 	END ScaleDownHuge;
 
 
 
 
@@ -945,7 +945,7 @@ TYPE
 	BEGIN
 	BEGIN
 		IF (value < 0) THEN sign := -1; value := -1 * value ELSE sign := 1 END;
 		IF (value < 0) THEN sign := -1; value := -1 * value ELSE sign := 1 END;
 		IF (sign = -1) THEN w.String("-") ELSE w.String(" ") END;
 		IF (sign = -1) THEN w.String("-") ELSE w.String(" ") END;
-		PrintHex(SHORT (Machine.ASHH(value, -32)));
+		PrintHex(SHORT (ASH(value, -32));
 		PrintHex(SHORT (value));
 		PrintHex(SHORT (value));
 		w.Update
 		w.Update
 	END VarH2;
 	END VarH2;
@@ -986,4 +986,4 @@ BEGIN
 	Ny := Nx; (* necessary for some reason *)
 	Ny := Nx; (* necessary for some reason *)
 	ScaleFactor := LSH(LONG(LONG(1)), Ny DIV 2);
 	ScaleFactor := LSH(LONG(LONG(1)), Ny DIV 2);
 	ScaleFactor := ScaleFactor * ScaleFactor;
 	ScaleFactor := ScaleFactor * ScaleFactor;
-END OGGUtilities.
+END OGGUtilities.

+ 6 - 6
source/OGGVorbisPlayer.Mod

@@ -4,7 +4,7 @@
 MODULE OGGVorbisPlayer;
 MODULE OGGVorbisPlayer;
 
 
 IMPORT
 IMPORT
-	SYSTEM, Strings, KernelLog, Streams, Files, Machine, Commands, SoundDevices, BIT, Math,
+	SYSTEM, Strings, KernelLog, Streams, Files, Commands, SoundDevices, BIT, Math,
 	OGGUtilities, Modules, Kernel,
 	OGGUtilities, Modules, Kernel,
 	TCP, WebHTTP, WebHTTPClient;
 	TCP, WebHTTP, WebHTTPClient;
 
 
@@ -2153,13 +2153,13 @@ TYPE
 				waco := OGGUtilities.MultHugeFP(wa, trig[c]);
 				waco := OGGUtilities.MultHugeFP(wa, trig[c]);
 				wbco := OGGUtilities.MultHugeFP(wb, trig[c]);
 				wbco := OGGUtilities.MultHugeFP(wb, trig[c]);
 				INC(c);
 				INC(c);
-				x[x1] := Machine.DivH(wc + waco + wbce, 2);
+				x[x1] := (wc + waco + wbce) DIV 2;
 				INC(x1);
 				INC(x1);
-				x[x2] := Machine.DivH(-wd + wbco - wace, 2);
+				x[x2] := (-wd + wbco - wace) DIV 2;
 				DEC(x2);
 				DEC(x2);
-				x[x1] := Machine.DivH(wd + wbco - wace, 2);
+				x[x1] := (wd + wbco - wace) DIV 2;
 				INC(x1);
 				INC(x1);
-				x[x2] := Machine.DivH(wc - waco - wbce, 2);
+				x[x2] := (wc - waco - wbce) DIV 2;
 				DEC(x2)
 				DEC(x2)
 			END;
 			END;
 		END KernelStep3;
 		END KernelStep3;
@@ -3584,4 +3584,4 @@ OGGVorbisPlayer.Stop ~
 OGGVorbisPlayer.Play epoq.ogg ~
 OGGVorbisPlayer.Play epoq.ogg ~
 OGGVorbisPlayer.Play hydrate.ogg ~
 OGGVorbisPlayer.Play hydrate.ogg ~
 OGGVorbisPlayer.Play mistoftime.ogg ~
 OGGVorbisPlayer.Play mistoftime.ogg ~
-OGGVorbisPlayer.Play lumme.ogg ~
+OGGVorbisPlayer.Play lumme.ogg ~

+ 3 - 3
source/PCS.Mod

@@ -3,7 +3,7 @@
 MODULE PCS; (** AUTHOR "prk"; PURPOSE "Parallel Compiler: scanner"; *)
 MODULE PCS; (** AUTHOR "prk"; PURPOSE "Parallel Compiler: scanner"; *)
 
 
 	IMPORT
 	IMPORT
-		Streams, Texts, UTF8Strings, StringPool, PCM, Machine;
+		Streams, Texts, UTF8Strings, StringPool, PCM;
 
 
 	CONST
 	CONST
 		Trace = FALSE;
 		Trace = FALSE;
@@ -244,7 +244,7 @@ TYPE
 						IF intval = longintval THEN numtyp := integer END;
 						IF intval = longintval THEN numtyp := integer END;
 					ELSE (* decimal *) numtyp := longinteger;
 					ELSE (* decimal *) numtyp := longinteger;
 						WHILE i < n DO d := Ord(dig[i], FALSE); INC(i);
 						WHILE i < n DO d := Ord(dig[i], FALSE); INC(i);
-							longintval := Machine.MulH (longintval, 10) + d;
+							longintval := longintval * 10 + d;
 							IF longintval < 0 THEN err(203) END;
 							IF longintval < 0 THEN err(203) END;
 						END;
 						END;
 						intval := SHORT (longintval);
 						intval := SHORT (longintval);
@@ -760,4 +760,4 @@ END PCS.
 	21.06.01	prk	using stringpool index instead of array of char
 	21.06.01	prk	using stringpool index instead of array of char
 	12.06.01	prk	Interfaces
 	12.06.01	prk	Interfaces
 	26.04.01	prk	separation of RECORD and OBJECT in the parser
 	26.04.01	prk	separation of RECORD and OBJECT in the parser
-*)
+*)

+ 3 - 3
source/SambaClient.Mod

@@ -1,7 +1,7 @@
 MODULE SambaClient; (** AUTHOR "mancos"; PURPOSE "SMB Client"; *)
 MODULE SambaClient; (** AUTHOR "mancos"; PURPOSE "SMB Client"; *)
 
 
 IMPORT
 IMPORT
-	SYSTEM, Machine, Streams, KernelLog, Dates, Strings, Locks, Files, DNS, IP, TCP;
+	SYSTEM, Streams, KernelLog, Dates, Strings, Locks, Files, DNS, IP, TCP;
 
 
 CONST
 CONST
 	PID = 9876;
 	PID = 9876;
@@ -1173,8 +1173,8 @@ VAR
 	ts: LONGINT;
 	ts: LONGINT;
 	continue: BOOLEAN;
 	continue: BOOLEAN;
 BEGIN
 BEGIN
-	tsh := Machine.MulH(t[1], 100000000H) + t[0];
-	tsh := Machine.DivH(tsh, 10000000);
+	tsh := t[1] * 100000000H + t[0];
+	tsh := tsh DIV 10000000;
 	tsh := tsh - 11644473600;
 	tsh := tsh - 11644473600;
 	ts := SHORT(tsh);
 	ts := SHORT(tsh);
 	second := ts MOD 60;
 	second := ts MOD 60;

+ 4 - 4
source/SambaServer.Mod

@@ -1,6 +1,6 @@
 MODULE SambaServer; (** AUTHOR "mancos"; PURPOSE "SMB Server"; *)
 MODULE SambaServer; (** AUTHOR "mancos"; PURPOSE "SMB Server"; *)
 
 
-IMPORT SYSTEM, Machine, Modules, Streams, KernelLog, Commands, Dates, Strings, Files, TCP, TCPServices;
+IMPORT SYSTEM, Modules, Streams, KernelLog, Commands, Dates, Strings, Files, TCP, TCPServices;
 
 
 CONST
 CONST
 	PrimaryDomain = "BLUEBOTTLE";
 	PrimaryDomain = "BLUEBOTTLE";
@@ -2010,10 +2010,10 @@ BEGIN
 	dtOld.minute := 0;
 	dtOld.minute := 0;
 	dtOld.second := 0;
 	dtOld.second := 0;
 	Dates.TimeDifference(dtOld, dtNow, diffDay, diffHour, diffMinute, diffSecond);
 	Dates.TimeDifference(dtOld, dtNow, diffDay, diffHour, diffMinute, diffSecond);
-	tsNow := Machine.MulH(diffDay, 86400) + diffHour * 3600 + diffMinute * 60 + diffSecond;
-	tsNow := Machine.MulH(tsNow,10000000);
+	tsNow := diffDay * 86400 + diffHour * 3600 + diffMinute * 60 + diffSecond;
+	tsNow := tsNow * 10000000;
 	t[0] := SHORT(tsNow);
 	t[0] := SHORT(tsNow);
-	t[1] := SHORT(Machine.DivH(tsNow, 100000000H));
+	t[1] := SHORT(tsNow DIV 100000000H);
 END GetSMBTimeStamp;
 END GetSMBTimeStamp;
 
 
 PROCEDURE GetUnixTimeStamp(dtNow: Dates.DateTime; VAR t: LONGINT);
 PROCEDURE GetUnixTimeStamp(dtNow: Dates.DateTime; VAR t: LONGINT);

+ 0 - 36
source/Unix.AMD64.Machine.Mod

@@ -283,40 +283,6 @@ VAR
 		OR RAX, RDX
 		OR RAX, RDX
 	END GetTimer;
 	END GetTimer;
 
 
-	
-	(** -- HUGEINT operations -- *)
-
-	(** Return h*g. *)
-	PROCEDURE MulH* (h, g: HUGEINT): HUGEINT;
-	BEGIN RETURN h * g;
-	END MulH;
-
-	(** Return h DIV g. Rounding and division by zero behaviour is currently undefined. *)
-	PROCEDURE DivH* (x, y: HUGEINT): HUGEINT;
-	BEGIN RETURN x DIV y
-	END DivH;
-
-	(** Return ASH(h, n). *)
-	PROCEDURE ASHH* (h: HUGEINT; n: LONGINT): HUGEINT;
-	BEGIN RETURN ASH (h, n);
-	END ASHH;
-
-	(** Return a HUGEINT composed of high and low. *)
-	PROCEDURE -LInt2ToHInt* (high, low: LONGINT): HUGEINT;
-	CODE {SYSTEM.AMD64}
-		POP RAX
-	END LInt2ToHInt;
-
-	(** Return h as a LONGREAL, with possible loss of precision. *)
-	PROCEDURE -HIntToLReal* (h: HUGEINT): LONGREAL;
-	CODE {SYSTEM.AMD64, SYSTEM.FPU}
-		FILD QWORD [ESP]
-		PAUSE
-		ADD RSP, 8
-	END HIntToLReal;
-
-
-
 
 
 	PROCEDURE  Portin8*(port: LONGINT; VAR val: CHAR);
 	PROCEDURE  Portin8*(port: LONGINT; VAR val: CHAR);
 	END Portin8;
 	END Portin8;
@@ -337,8 +303,6 @@ VAR
 	END Portout32;
 	END Portout32;
 
 
 
 
-
-
 	PROCEDURE Is32BitAddress*( adr: ADDRESS ): BOOLEAN;
 	PROCEDURE Is32BitAddress*( adr: ADDRESS ): BOOLEAN;
 	BEGIN  RETURN S.VAL( LONGINT, adr ) = adr;
 	BEGIN  RETURN S.VAL( LONGINT, adr ) = adr;
 	END Is32BitAddress;
 	END Is32BitAddress;

+ 0 - 157
source/Unix.I386.Machine.Mod

@@ -259,163 +259,6 @@ ok:
 END Fill32;
 END Fill32;
 
 
 
 
-
-(** Return h*g. based on code from "AMD Athlon Processor x86 code optimization guide" *)
-PROCEDURE {REALTIME} MulH* (h, g: HUGEINT): HUGEINT;
-CODE {SYSTEM.i386}
-	MOV EDX, [EBP+12]	; y_hi
-	MOV ECX, [EBP+20]	; x_hi
-	OR	 EDX, ECX		; are x_hi and y_hi both zeros?
-	MOV EDX, [EBP+16]	; x_lo
-	MOV EAX, [EBP+8]	; y_lo
-	JNZ fullMul			; yes, requires full multiplication
-	MUL EDX			; EDX:EAX := y_lo * x_lo
-	JMP exit			; done, return to caller
-
-fullMul:					; full multiplication is required
-
-	MUL ECX			; EAX := LO(y_lo*x_hi)
-	MOV EBX, EAX		; keep the result
-
-	MOV EAX, [EBP+12] 	; y_hi
-	MUL DWORD  [EBP+16]	; EAX := LO(y_hi*x_lo)
-	ADD EBX, EAX 		; EBX := LO(y_lo*x_hi) + LO(y_hi*x_lo)
-
-	MOV EAX, [EBP+8]	; y_lo
-	MUL DWORD   [EBP+16]	; EDX := HI(y_lo*x_lo), EAX := LO(y_lo*x_lo)
-	ADD EDX, EBX		; EDX := y_lo*x_hi + y_hi*x_lo + HI(y_lo*x_lo)
-exit:
-END MulH;
-
-	
-(** Return h DIV g. Rounding and division by zero behaviour is currently undefined. *)
-PROCEDURE {REALTIME} DivH* (x, y: HUGEINT): HUGEINT;
-CODE {SYSTEM.i386}
-	MOV ECX, [EBP+12]	; y-hi
-	MOV EBX, [EBP+8]	; y-lo
-	MOV EDX, [EBP+20]	; x-hi
-	MOV EAX, [EBP+16]	; x-lo				
-	
-	MOV ESI, ECX		; y-hi
-	XOR ESI, EDX		; y-hi ^ x-hi
-	SAR ESI, 31			; (quotient < 0) ? -1 : 0
-	MOV EDI, EDX		; x-hi
-	SAR EDI, 31			; (x < 0) ? -1 : 0
-	XOR EAX, EDI		; if (x < 0)
-	XOR EDX, EDI		; compute 1s complement of x
-	SUB EAX, EDI		; if (x < 0)
-	SBB EDX, EDI		; compute 2s complement of x
-	MOV EDI, ECX		; y-hi
-	SAR EDI, 31			; (y < 0) ? -1 : 0
-	XOR EBX, EDI		; if (y < 0)
-	XOR ECX, EDI		; compute 1s complement of y
-	SUB EBX, EDI		; if (y < 0)
-	SBB ECX, EDI		; compute 2s complement of y
-	JNZ bigDivisor		; y > 2^32-1
-	CMP EDX, EBX		; only one division needed ? (ECX = 0)
-	JAE twoDivs			; need two divisions
-	DIV EBX			; EAX = quotient-lo
-	MOV EDX, ECX		; EDX = quotient-hi = 0
-	; quotient in EDX:EAX
-	XOR EAX, ESI		; if (quotient < 0)
-	XOR EDX, ESI		; compute 1s complement of result
-	SUB EAX, ESI		; if (quotient < 0)
-	SBB EDX, ESI		; compute 2s complement of result
-	JMP exit			; done, return to caller
-	
-twoDivs:
-	MOV ECX, EAX		; save x-lo in ECX
-	MOV EAX, EDX		; get x-hi
-	XOR EDX, EDX		; zero extend it into EDX:EAX
-	DIV EBX			; quotient-hi in EAX
-	XCHG EAX, ECX		; ECX = quotient-hi, EAX = x-lo
-	DIV EBX			; EAX = quotient-lo
-	MOV EDX, ECX		; EDX = quotient-hi
-	; quotient in EDX:EAX
-	JMP makeSign		; make quotient signed
-
-bigDivisor:
-	SUB ESP, 12			; create three local variables
-	MOV [ESP], EAX		; x-lo
-	MOV [ESP+4], EBX	; y-lo
-	MOV [ESP+8], EDX	; x-hi
-	MOV EDI, ECX		; save y-hi
-	SHR EDX, 1			; shift both
-	RCR EAX, 1			; y and
-	ROR EDI, 1			; and x
-	RCR EBX, 1			; right by 1 bit
-	BSR ECX, ECX		; ECX = number of remaining shifts
-	SHRD EBX, EDI, CL	; scale down y and
-	SHRD EAX, EDX, CL	; x such that y
-	SHR EDX, CL		; less than 2^32 (i.e. fits in EBX)
-	ROL EDI, 1			; restore original y-hi
-	DIV EBX			; compute quotient
-	MOV EBX, [ESP]		; x-lo
-	MOV ECX, EAX		; save quotient
-	IMUL EDI, EAX		; quotient * y hi-word (low only)
-	MUL DWORD [ESP+4]	; quotient * y lo-word
-	ADD EDX, EDI		; EDX:EAX = quotient * y
-	SUB EBX, EAX		; x-lo - (quot.*y)-lo
-	MOV EAX, ECX		; get quotient
-	MOV ECX, [ESP+8]	; x-hi
-	SBB ECX, EDX		; subtract y * quot. from x
-	SBB EAX, 0			; adjust quotient if remainder negative
-	XOR EDX, EDX		; clear hi-word of quotient
-	ADD ESP, 12		; remove local variables
-
-makeSign:
-	XOR EAX, ESI		; if (quotient < 0)
-	XOR EDX, ESI		; compute 1s complement of result
-	SUB EAX, ESI		; if (quotient < 0)
-	SBB EDX, ESI		; compute 2s complement of result
-exit:
-END DivH;
-
-
-(** Return ASH(h, n). *)
-PROCEDURE {REALTIME} -ASHH* (h: HUGEINT; n: LONGINT): HUGEINT;
-CODE {SYSTEM.i386}
-	POP ECX
-	POP EAX
-	POP EDX
-	CMP ECX, 0
-	JL right
-	AND ECX, 63	; limit count, like ASH
-	JZ exit
-ll:
-	SHL EAX, 1
-	RCL EDX, 1
-	DEC ECX
-	JNZ ll
-	JMP exit
-right:
-	NEG ECX
-	AND ECX, 63	; limit count, like ASH
-	JZ exit
-lr:
-	SAR EDX, 1
-	RCR EAX, 1
-	DEC ECX
-	JNZ lr
-exit:
-END ASHH;
-
-(** Return a HUGEINT composed of high and low. *)
-PROCEDURE {REALTIME} -LInt2ToHInt* (high, low: LONGINT): HUGEINT;
-CODE {SYSTEM.i386}
-	POP EAX
-	POP EDX
-END LInt2ToHInt;
-
-(** Return h as a LONGREAL, with possible loss of precision. *)
-PROCEDURE {REALTIME} -HIntToLReal* (h: HUGEINT): LONGREAL;
-CODE {SYSTEM.i386, SYSTEM.FPU}
-	FILD QWORD [ESP]
-	FWAIT
-	ADD ESP, 8
-END HIntToLReal;
-
-
 PROCEDURE  Portin8*(port: LONGINT; VAR val: CHAR);
 PROCEDURE  Portin8*(port: LONGINT; VAR val: CHAR);
 END Portin8;
 END Portin8;
 
 

+ 2 - 2
source/WMPerfMonPluginCpu.Mod

@@ -32,10 +32,10 @@ TYPE
 			timestamp := Machine.GetTimer();
 			timestamp := Machine.GetTimer();
 
 
 			IF lastTimeStamp # 0 THEN
 			IF lastTimeStamp # 0 THEN
-				total := Machine.HIntToLReal(timestamp - lastTimeStamp);
+				total := timestamp - lastTimeStamp;
 				FOR cpuNbr := 0 TO Machine.MaxCPU-1 DO
 				FOR cpuNbr := 0 TO Machine.MaxCPU-1 DO
 					IF Objects.idleCycles[cpuNbr] # 0 THEN
 					IF Objects.idleCycles[cpuNbr] # 0 THEN
-						dCycles := Machine.HIntToLReal(Objects.idleCycles[cpuNbr] - lastCycles[cpuNbr]);
+						dCycles := Objects.idleCycles[cpuNbr] - lastCycles[cpuNbr];
 						cpuLoad[cpuNbr] := 100.0 - SHORT(100.0 * (dCycles / total));
 						cpuLoad[cpuNbr] := 100.0 - SHORT(100.0 * (dCycles / total));
 					END;
 					END;
 				END;
 				END;

+ 1 - 1
source/WMPerfMonPluginHeap.Mod

@@ -386,7 +386,7 @@ TYPE
 
 
 		PROCEDURE UpdateDataset;
 		PROCEDURE UpdateDataset;
 		BEGIN
 		BEGIN
-			dataset[0] := Machine.DivH(Heaps.NnewBytes, 1024);
+			dataset[0] := Heaps.NnewBytes DIV 1024;
 		END UpdateDataset;
 		END UpdateDataset;
 
 
 	END BytesAllocated;
 	END BytesAllocated;

+ 4 - 5
source/WMPerfMonPluginNetwork.Mod

@@ -1,8 +1,7 @@
 MODULE WMPerfMonPluginNetwork; (** AUTHOR "staubesv"; PURPOSE "Performance Monitor network performance plugin"; *)
 MODULE WMPerfMonPluginNetwork; (** AUTHOR "staubesv"; PURPOSE "Performance Monitor network performance plugin"; *)
 
 
 IMPORT
 IMPORT
-	Machine, WMPerfMonPlugins,
-	Network, Plugins, Modules;
+	WMPerfMonPlugins, Network, Plugins, Modules;
 
 
 CONST
 CONST
 	PluginName = "NetworkSpeed";
 	PluginName = "NetworkSpeed";
@@ -38,8 +37,8 @@ TYPE
 		PROCEDURE UpdateDataset*;
 		PROCEDURE UpdateDataset*;
 		VAR sentKB, receivedKB : REAL;
 		VAR sentKB, receivedKB : REAL;
 		BEGIN
 		BEGIN
-			sentKB := SHORT(Machine.HIntToLReal(l.sendCount)) / 1024;
-			receivedKB := SHORT(Machine.HIntToLReal(l.recvCount)) / 1024;
+			sentKB := l.sendCount / 1024;
+			receivedKB := l.recvCount / 1024;
 			dataset[0] := sentKB + receivedKB;
 			dataset[0] := sentKB + receivedKB;
 			dataset[1] := sentKB;
 			dataset[1] := sentKB;
 			dataset[2] := receivedKB;
 			dataset[2] := receivedKB;
@@ -92,4 +91,4 @@ BEGIN
 	InitPlugins;
 	InitPlugins;
 END WMPerfMonPluginNetwork.
 END WMPerfMonPluginNetwork.
 
 
-WMPerfMonPluginNetwork.Install ~  SystemTools.Free WMPerfMonPluginNetwork ~
+WMPerfMonPluginNetwork.Install ~  SystemTools.Free WMPerfMonPluginNetwork ~

+ 3 - 3
source/WMPerfMonPluginProcesses.Mod

@@ -81,14 +81,14 @@ TYPE
 		BEGIN
 		BEGIN
 			Objects.GetCpuCycles(process, currentCycles, TRUE);
 			Objects.GetCpuCycles(process, currentCycles, TRUE);
 			timer := Machine.GetTimer();
 			timer := Machine.GetTimer();
-			timeDiff := Machine.HIntToLReal(timer - lastTimer);
+			timeDiff := timer - lastTimer;
 			IF lastSamplesValid THEN
 			IF lastSamplesValid THEN
 				IF (LEN(dataset) = 1) THEN
 				IF (LEN(dataset) = 1) THEN
-					dataset[0]  := SHORT(100.00 * Machine.HIntToLReal(currentCycles[0] - lastCycles[0]) / timeDiff);
+					dataset[0]  := SHORT(100.00 * LONGREAL(currentCycles[0] - lastCycles[0]) / timeDiff);
 				ELSE
 				ELSE
 					pAll := 0.0;
 					pAll := 0.0;
 					FOR i := 1 TO LEN(dataset)-1 DO
 					FOR i := 1 TO LEN(dataset)-1 DO
-						cyclesDiff := Machine.HIntToLReal(currentCycles[i - 1] - lastCycles[i - 1]);
+						cyclesDiff := currentCycles[i - 1] - lastCycles[i - 1];
 						pAll := pAll + cyclesDiff;
 						pAll := pAll + cyclesDiff;
 						dataset[i] := SHORT(100.0 * cyclesDiff / timeDiff);
 						dataset[i] := SHORT(100.0 * cyclesDiff / timeDiff);
 					END;
 					END;

+ 4 - 4
source/WMPerfMonPlugins.Mod

@@ -678,7 +678,7 @@ TYPE
 			IF lastTimestamp # 0 THEN
 			IF lastTimestamp # 0 THEN
 				Objects.GetCpuCycles(me, cpuCycles, TRUE);
 				Objects.GetCpuCycles(me, cpuCycles, TRUE);
 				FOR i := 0 TO LEN(cpuCycles)-1 DO INC (cycles , cpuCycles[i]); END;
 				FOR i := 0 TO LEN(cpuCycles)-1 DO INC (cycles , cpuCycles[i]); END;
-				value := SHORT(100.0 * Machine.HIntToLReal(cycles - lastCycles) / Machine.HIntToLReal(timestamp - lastTimestamp));
+				value := SHORT(100.0 * LONGREAL(cycles - lastCycles) / LONGREAL(timestamp - lastTimestamp));
 				sampleBuffer[sample MOD sampleBufferSize] := value; INC(sample);
 				sampleBuffer[sample MOD sampleBufferSize] := value; INC(sample);
 				lastCycles := cycles;
 				lastCycles := cycles;
 				FOR i := 0 TO sampleBufferSize-1 DO sum := sum + sampleBuffer[i]; END;
 				FOR i := 0 TO sampleBufferSize-1 DO sum := sum + sampleBuffer[i]; END;
@@ -763,7 +763,7 @@ BEGIN
 	endTime := Machine.GetTimer();
 	endTime := Machine.GetTimer();
 	IF nbrOfGcRuns # Heaps.Ngc THEN RETURN FALSE; END;
 	IF nbrOfGcRuns # Heaps.Ngc THEN RETURN FALSE; END;
 	timeDiff := endTime - startTime;
 	timeDiff := endTime - startTime;
-	clockrate := SHORT (Machine.DivH(timeDiff, 1000*1000));
+	clockrate := SHORT (timeDiff DIV (1000*1000));
 	RETURN TRUE;
 	RETURN TRUE;
 END EstimateCpuClockrate;
 END EstimateCpuClockrate;
 
 
@@ -774,7 +774,7 @@ END EstimateCpuClockrate;
 *)
 *)
 PROCEDURE CyclesToMs*(cycles : HUGEINT; mhz : LONGINT) : LONGINT;
 PROCEDURE CyclesToMs*(cycles : HUGEINT; mhz : LONGINT) : LONGINT;
 BEGIN
 BEGIN
-	RETURN SHORT (Machine.DivH(cycles, 1000*mhz));
+	RETURN SHORT (cycles DIV (1000*mhz));
 END CyclesToMs;
 END CyclesToMs;
 
 
 (** Convert number of milliseconds into string of the form d:h:m:s if m >= 1 or x.xxxs if m < 1*)
 (** Convert number of milliseconds into string of the form d:h:m:s if m >= 1 or x.xxxs if m < 1*)
@@ -857,4 +857,4 @@ BEGIN
 	Modules.InstallTermHandler(Cleanup);
 	Modules.InstallTermHandler(Cleanup);
 	NEW(updater);
 	NEW(updater);
 	LoadConfiguration;
 	LoadConfiguration;
-END WMPerfMonPlugins.
+END WMPerfMonPlugins.

+ 1 - 1
source/WMProcessInfo.Mod

@@ -242,7 +242,7 @@ TYPE
 				(* CPU% - 2 *)
 				(* CPU% - 2 *)
 				Objects.GetCpuCycles(processes[i], cycles, FALSE);
 				Objects.GetCpuCycles(processes[i], cycles, FALSE);
 				t0 := cycles[0];
 				t0 := cycles[0];
-				Strings.IntToStr(SHORT (Machine.DivH(Machine.MulH(t0, 100)  , t1)), str);SetText(i, 2, str);
+				Strings.IntToStr(SHORT ((t0 * 100) DIV t1), str);SetText(i, 2, str);
 
 
 
 
 				(* priority - 3 *)
 				(* priority - 3 *)

+ 0 - 157
source/Win32.Machine.Mod

@@ -208,164 +208,7 @@ END SetSP;
 		CLD
 		CLD
 		REP	STOSD
 		REP	STOSD
 	END Fill32;
 	END Fill32;
-	(** -- HUGEINT operations -- *)
 
 
-(** Return h*g. *)
-
-	(** Return h*g. based on code from "AMD Athlon Processor x86 code optimization guide" *)
-	PROCEDURE MulH* (h, g: HUGEINT): HUGEINT;
-	CODE {SYSTEM.i386}
-		MOV EDX, [EBP+12]	; y_hi
-		MOV ECX, [EBP+20]	; x_hi
-		OR EDX, ECX		; are x_hi and y_hi both zeros?
-		MOV EDX, [EBP+16]	; x_lo
-		MOV EAX, [EBP+8]	; y_lo
-		JNZ fullMul			; yes, requires full multiplication
-		MUL EDX			; EDX:EAX := y_lo * x_lo
-		JMP exit			; done, return to caller
-
-	fullMul:					; full multiplication is required
-
-		MUL ECX			; EAX := LO(y_lo*x_hi)
-		MOV EBX, EAX		; keep the result
-
-		MOV EAX, [EBP+12] 	; y_hi
-		MUL DWORD [EBP+16]	; EAX := LO(y_hi*x_lo)
-		ADD EBX, EAX 		; EBX := LO(y_lo*x_hi) + LO(y_hi*x_lo)
-
-		MOV EAX, [EBP+8]	; y_lo
-		MUL DWORD [EBP+16]	; EDX := HI(y_lo*x_lo), EAX := LO(y_lo*x_lo)
-		ADD EDX, EBX		; EDX := y_lo*x_hi + y_hi*x_lo + HI(y_lo*x_lo)
-	exit:
-	END MulH;
-
-	(** Return h DIV g. Rounding and division by zero behaviour is currently undefined. *)
-	PROCEDURE DivH* (x, y: HUGEINT): HUGEINT;
-	CODE {SYSTEM.i386}
-		MOV ECX, [EBP+12]	; y-hi
-		MOV EBX, [EBP+8]	; y-lo
-		MOV EDX, [EBP+20]	; x-hi
-		MOV EAX, [EBP+16]	; x-lo
-
-		MOV ESI, ECX		; y-hi
-		XOR ESI, EDX		; y-hi ^ x-hi
-		SAR ESI, 31			; (quotient < 0) ? -1 : 0
-		MOV EDI, EDX		; x-hi
-		SAR EDI, 31			; (x < 0) ? -1 : 0
-		XOR EAX, EDI		; if (x < 0)
-		XOR EDX, EDI		; compute 1s complement of x
-		SUB EAX, EDI		; if (x < 0)
-		SBB EDX, EDI		; compute 2s complement of x
-		MOV EDI, ECX		; y-hi
-		SAR EDI, 31			; (y < 0) ? -1 : 0
-		XOR EBX, EDI		; if (y < 0)
-		XOR ECX, EDI		; compute 1s complement of y
-		SUB EBX, EDI		; if (y < 0)
-		SBB ECX, EDI		; compute 2s complement of y
-		JNZ bigDivisor		; y > 2^32-1
-		CMP EDX, EBX		; only one division needed ? (ECX = 0)
-		JAE twoDivs			; need two divisions
-		DIV EBX			; EAX = quotient-lo
-		MOV EDX, ECX		; EDX = quotient-hi = 0
-		; quotient in EDX:EAX
-		XOR EAX, ESI		; if (quotient < 0)
-		XOR EDX, ESI		; compute 1s complement of result
-		SUB EAX, ESI		; if (quotient < 0)
-		SBB EDX, ESI		; compute 2s complement of result
-		JMP exit			; done, return to caller
-
-	twoDivs:
-		MOV ECX, EAX		; save x-lo in ECX
-		MOV EAX, EDX		; get x-hi
-		XOR EDX, EDX		; zero extend it into EDX:EAX
-		DIV EBX			; quotient-hi in EAX
-		XCHG EAX, ECX		; ECX = quotient-hi, EAX = x-lo
-		DIV EBX			; EAX = quotient-lo
-		MOV EDX, ECX		; EDX = quotient-hi
-		; quotient in EDX:EAX
-		JMP makeSign		; make quotient signed
-
-	bigDivisor:
-		SUB ESP, 12			; create three local variables
-		MOV [ESP], EAX		; x-lo
-		MOV [ESP+4], EBX	; y-lo
-		MOV [ESP+8], EDX	; x-hi
-		MOV EDI, ECX		; save y-hi
-		SHR EDX, 1			; shift both
-		RCR EAX, 1			; y and
-		ROR EDI, 1			; and x
-		RCR EBX, 1			; right by 1 bit
-		BSR ECX, ECX		; ECX = number of remaining shifts
-		SHRD EBX, EDI, CL	; scale down y and
-		SHRD EAX, EDX, CL	; x such that y
-		SHR EDX, CL		; less than 2^32 (i.e. fits in EBX)
-		ROL EDI, 1			; restore original y-hi
-		DIV EBX			; compute quotient
-		MOV EBX, [ESP]		; x-lo
-		MOV ECX, EAX		; save quotient
-		IMUL EDI, EAX		; quotient * y hi-word (low only)
-		MUL DWORD [ESP+4]	; quotient * y lo-word
-		ADD EDX, EDI		; EDX:EAX = quotient * y
-		SUB EBX, EAX		; x-lo - (quot.*y)-lo
-		MOV EAX, ECX		; get quotient
-		MOV ECX, [ESP+8]	; x-hi
-		SBB ECX, EDX		; subtract y * quot. from x
-		SBB EAX, 0			; adjust quotient if remainder negative
-		XOR EDX, EDX		; clear hi-word of quotient
-		ADD ESP, 12		; remove local variables
-
-	makeSign:
-		XOR EAX, ESI		; if (quotient < 0)
-		XOR EDX, ESI		; compute 1s complement of result
-		SUB EAX, ESI		; if (quotient < 0)
-		SBB EDX, ESI		; compute 2s complement of result
-	exit:
-	END DivH;
-
-(** Return ASH(h, n). *)
-	PROCEDURE -ASHH*( h: HUGEINT;  n: LONGINT ): HUGEINT;
-	CODE {SYSTEM.i386}
-		POP	ECX
-		POP	EAX
-		POP	EDX
-		CMP	ECX, 0
-		JL	right
-		AND	ECX, 63	;  limit count, like ASH
-		JZ	exit
-		ll:
-		SHL	EAX, 1
-		RCL	EDX, 1
-		DEC	ECX
-		JNZ	ll
-		JMP	exit
-		right:
-		NEG ECX
-		AND	ECX, 63	;  limit count, like ASH
-		JZ	exit
-		lr:
-		SAR	EDX, 1
-		RCR	EAX, 1
-		DEC	ECX
-		JNZ	lr
-		exit:
-	END ASHH;
-
-(** Return a HUGEINT composed of high and low. *)
-
-	PROCEDURE -LInt2ToHInt*( high, low: LONGINT ): HUGEINT;
-	CODE {SYSTEM.i386}
-		POP	EAX
-		POP	EDX
-	END LInt2ToHInt;
-
-(** Return h as a LONGREAL, with possible loss of precision. *)
-
-	PROCEDURE -HIntToLReal*( h: HUGEINT ): LONGREAL;
-	CODE {SYSTEM.i386, SYSTEM.FPU}
-		FILD	QWORD[ESP]
-		FWAIT
-		ADD	ESP, 8
-	END HIntToLReal;
 (** -- Processor initialization -- *)
 (** -- Processor initialization -- *)
 
 
 	PROCEDURE -SetFCR( s: SET );
 	PROCEDURE -SetFCR( s: SET );

+ 3 - 3
source/Win32.WinDisks.Mod

@@ -1,6 +1,6 @@
 MODULE WinDisks;   (**  AUTHOR "fof"; PURPOSE "module to access partitions under Windows";  **)
 MODULE WinDisks;   (**  AUTHOR "fof"; PURPOSE "module to access partitions under Windows";  **)
 
 
-IMPORT Kernel32, SYSTEM, Strings, KernelLog, Streams, Commands, Disks, Plugins, Modules, Machine, WinFS;
+IMPORT Kernel32, SYSTEM, Strings, KernelLog, Streams, Commands, Disks, Plugins, Modules, WinFS;
 
 
 VAR
 VAR
 	DeviceIoControl: PROCEDURE {WINAPI} ( hDevice: Kernel32.HANDLE;  dwIoControlCode: LONGINT;  VAR lpInBuffer: ARRAY OF SYSTEM.BYTE;  nInBufferSize: LONGINT;
 	DeviceIoControl: PROCEDURE {WINAPI} ( hDevice: Kernel32.HANDLE;  dwIoControlCode: LONGINT;  VAR lpInBuffer: ARRAY OF SYSTEM.BYTE;  nInBufferSize: LONGINT;
@@ -64,7 +64,7 @@ TYPE
 
 
 			pos := LONG( block ) * LONG( blockSize );
 			pos := LONG( block ) * LONG( blockSize );
 
 
-			poslow := SHORT( pos );  poshigh := SHORT( Machine.ASHH( pos, -32 ) );
+			poslow := SHORT( pos );  poshigh := SHORT( ASH( pos, -32 ) );
 
 
 			large.LowPart := poslow;  large.HighPart := poshigh;
 			large.LowPart := poslow;  large.HighPart := poshigh;
 
 
@@ -439,4 +439,4 @@ WinDisks.Uninstall "PhysicalDrive0" ~
 WinDisks.Uninstall "F:" ~
 WinDisks.Uninstall "F:" ~
 WinDisks.Install "f:" "RW" ~
 WinDisks.Install "f:" "RW" ~
 
 
-SystemTools.Free WinDisks ~
+SystemTools.Free WinDisks ~