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

Harmonised duplicated code

git-svn-id: https://svn.inf.ethz.ch/svn/lecturers/a2/trunk@8065 8c9fc860-2736-0410-a75d-ab315db34111
negelef 7 жил өмнө
parent
commit
87b10b6b41

+ 4 - 4
source/AMD64.IPv4.Mod

@@ -21,7 +21,7 @@ CONST
 	MinIPHdrLen*= 20;
 	MaxIPHdrLen* = 60;
 	TOS = 10X; (* type-of-service on outgoing datagrams *)
-	BroadcastAdr = SHORT(0FFFFFFFFH);
+	BroadcastAdr = LONGINT(0FFFFFFFFH);
 
 TYPE
 	ARPEntry = POINTER TO RECORD
@@ -112,7 +112,7 @@ TYPE
 
 
 		(** Send an IP packet on this interface. *)
-		PROCEDURE Send*(type: LONGINT; fip:IP. Adr; VAR l4hdr, data: ARRAY OF CHAR; h4len, dofs, dlen, TTL: LONGINT);
+		PROCEDURE Send*(type: LONGINT; fip:IP. Adr; CONST l4hdr, data: ARRAY OF CHAR; h4len, dofs, dlen, TTL: LONGINT);
 		VAR
 			l3hdr: ARRAY MaxIPHdrLen OF CHAR;
 
@@ -143,7 +143,7 @@ TYPE
 
 
 		(* Internal procedure to perform the rest of the send operation. Used by "Send" and for IP forwarding. *)
-		PROCEDURE DoSend*(destAdr: IP.Adr; VAR l3hdr, l4hdr, data: ARRAY OF CHAR; h3len, h4len, dofs, dlen: LONGINT) ;
+		PROCEDURE DoSend*(destAdr: IP.Adr; CONST l3hdr, l4hdr, data: ARRAY OF CHAR; h3len, h4len, dofs, dlen: LONGINT) ;
 		VAR
 			linkDst: Network.LinkAdr;
 
@@ -565,7 +565,7 @@ TYPE
 
 
 		(* Queue an IP packet awaiting an ARP reply. *)
-		PROCEDURE ARPQueue(dst: IP.Adr; VAR l3hdr, l4hdr, data: ARRAY OF CHAR; h3len, h4len, dofs, dlen: LONGINT);
+		PROCEDURE ARPQueue(dst: IP.Adr; CONST l3hdr, l4hdr, data: ARRAY OF CHAR; h3len, h4len, dofs, dlen: LONGINT);
 		VAR p: ARPEntry; n: LONGINT;
 		BEGIN {EXCLUSIVE}
 			ASSERT (dst.usedProtocol = 4, 2345);

+ 2 - 4
source/AMD64.UsbKeyboard.Mod

@@ -710,8 +710,7 @@ VAR
 	string : ARRAY 64 OF CHAR;
 	plugin : Plugins.Plugin; kd : KeyboardDriver;
 BEGIN
-	context.arg.GetString(string);
-	IF (context.arg.res = Streams.Ok) & (string # "") THEN
+	IF context.arg.GetString(string) THEN
 		plugin := Usb.usbDrivers.Get(string);
 		IF plugin # NIL THEN
 			IF plugin IS KeyboardDriver THEN
@@ -723,8 +722,7 @@ BEGIN
 	ELSE context.error.String("UsbKeyboard: Expected <dev> parameter."); context.error.Ln;
 	END;
 	IF kd # NIL THEN
-		context.arg.GetString(string);
-		IF (context.arg.res = Streams.Ok) & (string # "") THEN
+		IF context.arg.GetString(string) THEN
 			kd.base.SetLayout(string);
 			context.out.String("Layout set to "); context.out.String(string); context.out.Ln;
 		END;

+ 139 - 10
source/BIOS.AMD64.ATADisks.Mod

@@ -145,7 +145,7 @@ TYPE
 		lbaHigh, lbaLow: LONGINT;
 	END;
 
-	CommandPacket = POINTER TO CommandPacketDesc;
+	CommandPacket* = POINTER TO CommandPacketDesc;
 	CommandPacketDesc = RECORD (CommandDesc)
 		packet*: Packet;
 		features*: SET;
@@ -814,7 +814,6 @@ TYPE
 			IF res # Res_OK THEN
 				(* Most likely, there is no device .... Show("Could not select device"); KernelLog.Ln; *)
 			END;
-
 			(* Check if registers are valid. FAST DETECTION  *)
 			Machine.Portout8(cmdbase+Ofs_CountLow, 055X);
 			NanoDelay(400);
@@ -1596,7 +1595,6 @@ TYPE
 			command.size := LEN(buf);
 			command.packet[4] := CHR(LEN(buf));
 			res := controller.ExecuteCommand(command, ATAPITimeout, status);
-
 			IF TraceVerbose & (trace * (TraceErrors + TraceSense) # {}) & (res # Res_OK) THEN
 				Show(name); KernelLog.String(" request sense failed"); KernelLog.Ln;
 			END;
@@ -1936,7 +1934,7 @@ PROCEDURE ResetCommand(cmd: Command; size: SIZE);
 BEGIN
 	ASSERT(cmd # NIL);
 	ASSERT(size MOD 4 = 0);
-	Machine.Fill32(SYSTEM.VAL(ADDRESS, cmd), size, 0);
+	Machine.Fill32(ADDRESS OF cmd.dev, size, 0);
 END ResetCommand;
 
 PROCEDURE GetPhysAdr(bufAdr: ADDRESS; size: LONGINT; VAR physAdr: ADDRESS): BOOLEAN;
@@ -2217,12 +2215,13 @@ BEGIN
 	AddController(c);
 END IdentifyController;
 
+
 PROCEDURE ScanPCI(vendor, id: LONGINT);
 VAR idx, bus, dev, fkt: LONGINT;
 BEGIN
-	idx := 0;
+	idx := 0; Dot();
 	WHILE PCI.FindPCIDevice(id, vendor, idx, bus, dev, fkt) = PCI.Done DO
-		Show("Found PCI device "); KernelLogHex(vendor, 4, 0); KernelLog.String(":"); KernelLogHex(id, 4, 0); KernelLog.Ln;
+		Show("Found PCI device "); KernelLogHex(vendor, 4, 0); KernelLog.String(":"); KernelLogHex(id, 4, 0); KernelLog.Ln; 
 		IdentifyController(bus, dev, fkt);
 		INC(idx);
 	END;
@@ -2231,20 +2230,39 @@ END ScanPCI;
 PROCEDURE ScanPCIClass(class: LONGINT);
 VAR idx, bus, dev, fkt: LONGINT;
 BEGIN
-	idx := 0;
+	idx := 0; Dot();
 	WHILE PCI.FindPCIClassCode(class, idx, bus, dev, fkt) = PCI.Done DO
 		Show("Found PCI device on bus "); KernelLog.Int(bus, 0); KernelLog.String(", device "); KernelLog.Int(dev, 0);
-		KernelLog.String(", function "); KernelLog.Int(fkt, 0); KernelLog.Ln;
+		KernelLog.String(", function "); KernelLog.Int(fkt, 0); KernelLog.Ln; 
 		IdentifyController(bus, dev, fkt);
 		INC(idx);
 	END;
 END ScanPCIClass;
 
+PROCEDURE ScanIterate;
+VAR pci: PCI.Pci; res,r0,r8,class: LONGINT;
+BEGIN
+	PCI.StartIterate(pci);
+	WHILE PCI.Iterate(pci) DO
+	 	res := PCI.ReadConfigDword(pci.bus, pci.device, pci.function, 0, r0);
+		IF r0 # LONGINT(0FFFFFFFFH) THEN
+			res := PCI.ReadConfigDword(pci.bus, pci.device, pci.function, 8, r8);
+			class := r8 DIV 100H MOD 1000000H;
+			IF (class DIV 10000H = 01H) (* mass storage *)
+				(*(class >= 010100H) & (class <= 0101FFH) OR (class >= 010600H) & (class <= 0106FFH)
+				OR (class >= 010400H) & (class <= 0104FFH) OR (class >= 018000H) & (class <= 0180FFH) *) THEN
+				IdentifyController(pci.bus, pci.device, pci.function);
+			END
+		END;
+	END;
+END ScanIterate;
+
 PROCEDURE IdentifyControllers;
 VAR
 	class: LONGINT;
-	str: ARRAY 32 OF CHAR;
+	str: ARRAY 128 OF CHAR;
 	c: Controller;
+	i, num1, num2: LONGINT;
 BEGIN
 	nofControllers := 2;
 	Machine.GetConfig("ATADetect", str);
@@ -2269,13 +2287,17 @@ BEGIN
 		ScanPCI(105AH, 0D30H);	(* Asus A7V Promise *)
 		ScanPCI(1078H, 0102H);		(* Cyrix IDE *)
 		ScanPCI(1166H, 0211H);		(* Serverworks *)
+		ScanPCI(8086H, 27C0H); (* found on TL device *)
+
  	ELSIF str = "legacy" THEN
  		Show("Legacy mode..."); KernelLog.Ln;
 		NEW(c, 1F0H, 3F0H, 0, 14);
 		AddController(c);
 		NEW(c, 170H, 370H, 0, 15);
 		AddController(c);
-	ELSE
+	ELSIF ~ParseConfigString(str) THEN
+		ScanIterate; (* much faster *)
+		(*
 		Show("Scanning PCI bus for IDE & SATA class devices ..."); KernelLog.Ln;
 		FOR class := 010100H TO 0101FFH DO ScanPCIClass(class); END;	(* IDE *)
 		FOR class := 010600H TO 0106FFH DO ScanPCIClass(class); END;	(* SATA *)
@@ -2287,6 +2309,7 @@ BEGIN
 			Show("Scanning PCI bus for PCI mass storage class devices..."); KernelLog.Ln;
 			FOR class := 018000H TO 0180FFH DO ScanPCIClass(class); END;	(* Mass Storage *)
 		END;
+		*)
 	END;
 END IdentifyControllers;
 
@@ -2354,11 +2377,117 @@ BEGIN
 	expectedCount := 0;
 END ResetCounter;
 
+VAR dots: LONGINT;
+
+PROCEDURE Dot;
+BEGIN
+	KernelLog.String(".");
+	INC(dots); 	IF dots >= 128 THEN KernelLog.Ln; dots := 0 END;
+END Dot;
+
 PROCEDURE Show(CONST string : ARRAY OF CHAR);
 BEGIN
+	IF dots > 0 THEN KernelLog.Ln END;
+	dots := 0;
 	KernelLog.String("ATADisks: "); KernelLog.String(string);
 END Show;
 
+
+PROCEDURE ParseConfigString(CONST s: ARRAY OF CHAR): BOOLEAN;
+VAR pos: LONGINT; ch: CHAR; cmdbase, cnlbase, bmbase, irq: LONGINT; c: Controller;
+
+	PROCEDURE Char(VAR ch: CHAR);
+	BEGIN ch := s[pos]; IF ch # 0X THEN INC(pos) END;
+	END Char;
+
+	PROCEDURE Hex(VAR n: LONGINT): BOOLEAN;
+	VAR ch: CHAR;
+	BEGIN
+		ch := s[pos];
+		IF (ch >= "0") & (ch <= "9") THEN n := ORD(ch)-ORD("0"); INC(pos); RETURN TRUE
+		ELSIF (ch >= "A") & (ch <= "F") THEN n := ORD(ch)-ORD("A")+10; INC(pos); RETURN TRUE
+		ELSE RETURN FALSE
+		END;
+	END Hex;
+
+	PROCEDURE Number(VAR num: LONGINT);
+	VAR n: LONGINT;
+	BEGIN
+		num := 0;
+		WHILE Hex(n) DO num := num* 10H + n END;
+	END Number;
+
+BEGIN
+	IF s[0] = "X" THEN
+		pos := 1; (* skip "X" "*)
+		Show("Using predefined configuration string "); KernelLog.String(s); KernelLog.Ln;
+		REPEAT
+			Number(cmdbase); Char(ch);
+			Number(cnlbase); Char(ch);
+			Number(bmbase); Char(ch);
+			Number(irq); Char(ch);
+			NEW(c,cmdbase, cnlbase, bmbase, irq);
+			AddController(c);
+		UNTIL ch # ",";
+		RETURN TRUE
+	ELSE
+		RETURN FALSE
+	END;
+END ParseConfigString;
+
+PROCEDURE GetConfigString*(VAR s: ARRAY OF CHAR);
+VAR i: LONGINT; c: Controller; first: BOOLEAN; pos: LONGINT
+
+	PROCEDURE Char(c: CHAR);
+	BEGIN
+		s[pos] := c;
+		IF pos < LEN(s)-1 THEN INC(pos) END;
+	END Char;
+
+	PROCEDURE Hex(x: LONGINT): CHAR;
+	BEGIN
+		IF x < 10 THEN RETURN CHR(ORD("0")+x)
+		ELSE RETURN CHR(ORD("A")+x-10);
+		END;
+	END Hex;
+
+	PROCEDURE Number(n: LONGINT);
+	VAR h: ARRAY 8 OF CHAR; i: LONGINT;
+	BEGIN
+		ASSERT(n>=0);
+		i := 0;
+		REPEAT
+			h[i] := Hex(n MOD 10H); n := n DIV 10H; INC(i);
+		UNTIL n = 0;
+		WHILE(i>0) DO
+			DEC(i); Char(h[i]);
+		END;
+	END Number;
+
+BEGIN
+	pos := 0;
+	first := TRUE;
+	Char("X");
+	FOR i := 0 TO MaxControllers-1 DO
+		c := controller[i];
+		IF c # NIL THEN
+			IF ~first THEN Char(",") ELSE first := FALSE END;
+			Number(c.cmdbase);Char(":");
+			Number(c.cnlbase);Char(":");
+			Number(c.bmbase); Char(":");
+			Number(c.irq);
+		END;
+	END;
+	Char(0X);
+END GetConfigString;
+
+PROCEDURE ShowConfigString*;
+VAR s: ARRAY 128 OF CHAR;
+BEGIN
+	GetConfigString(s);
+	KernelLog.String("config = "); KernelLog.String(s); KernelLog.Ln;
+END ShowConfigString;
+
 (* Clean up unloaded module. *)
 PROCEDURE Cleanup;
 VAR i: LONGINT; d: Device;

+ 11 - 11
source/BIOS.AMD64.Keyboard.Mod

@@ -24,10 +24,10 @@ TYPE
 		PROCEDURE HandleInterrupt;
 		VAR m: SET; i: LONGINT; msg: Inputs.KeyboardMsg; k: INTEGER; c: CHAR;
 		BEGIN {EXCLUSIVE}
-			SYSTEM.PORTIN(060H, c);	(* get scan code *)
-			SYSTEM.PORTIN(061H, SYSTEM.VAL(CHAR, m));
-			INCL(m, 7); SYSTEM.PORTOUT(061H, SYSTEM.VAL(CHAR, m));
-			EXCL(m, 7); SYSTEM.PORTOUT(061H, SYSTEM.VAL(CHAR, m));	(* ack *)
+			Machine.Portin8(060H, c);	(* get scan code *)
+			Machine.Portin8(061H, SYSTEM.VAL(CHAR, m));
+			INCL(m, 7); Machine.Portout8(061H, SYSTEM.VAL(CHAR, m));
+			EXCL(m, 7); Machine.Portout8(061H, SYSTEM.VAL(CHAR, m));	(* ack *)
 			IF TraceKeys THEN KernelLog.Hex(ORD(c), -3) END;
 			k := MapScanCode(c, msg.keysym);
 			IF k >= 0 THEN msg.ch := CHR(k) ELSE msg.ch := 0X END;
@@ -308,7 +308,7 @@ VAR t: Kernel.MilliTimer; s: SET;
 BEGIN
 	Kernel.SetTimer(t, 20);	(* wait up to 17 ms *)
 	REPEAT
-		SYSTEM.PORTIN(64H, SYSTEM.VAL(CHAR, s))
+		Machine.Portin8(64H, SYSTEM.VAL(CHAR, s))
 	UNTIL ~(1 IN s) OR Kernel.Expired(t)
 END Wait;
 
@@ -316,7 +316,7 @@ END Wait;
 
 PROCEDURE SendByte(port: LONGINT; value: SYSTEM.BYTE);
 BEGIN
-	Wait; SYSTEM.PORTOUT(port, SYSTEM.VAL(CHAR, value));
+	Wait; Machine.Portout8(port, SYSTEM.VAL(CHAR, value));
 	lastport := port; lastvalue := value
 END SendByte;
 
@@ -493,12 +493,12 @@ BEGIN
 		(* clear the keyboard's internal buffer *)
 	i := 8;
 	LOOP
-		SYSTEM.PORTIN(64H, SYSTEM.VAL(CHAR, s));
+		Machine.Portin8(64H, SYSTEM.VAL(CHAR, s));
 		IF ~(0 IN s) OR (i = 0) THEN EXIT END;
-		SYSTEM.PORTIN(60H, c);	(* read byte *)
-		SYSTEM.PORTIN(61H, SYSTEM.VAL(CHAR, s));
-		INCL(s, 7); SYSTEM.PORTOUT(61H, SYSTEM.VAL(CHAR, s));
-		EXCL(s, 7); SYSTEM.PORTOUT(61H, SYSTEM.VAL(CHAR, s));	(* ack *)
+		Machine.Portin8(60H, c);	(* read byte *)
+		Machine.Portin8(61H, SYSTEM.VAL(CHAR, s));
+		INCL(s, 7); Machine.Portout8(61H, SYSTEM.VAL(CHAR, s));
+		EXCL(s, 7); Machine.Portout8(61H, SYSTEM.VAL(CHAR, s));	(* ack *)
 		DEC(i)
 	END;
 	flags := {SetTypematic};

+ 5 - 2
source/BIOS.AMD64.Traps.Mod

@@ -17,7 +17,6 @@ TYPE
 		type-, size-, n-, tdadr-: LONGINT
 	END;
 
-
 VAR
 	trapState: ARRAY Machine.MaxCPU OF LONGINT;	(* indexed by Machine.ID() *)
 	modes: ARRAY 25 OF CHAR;
@@ -66,6 +65,8 @@ VAR
 				-14:	(* page fault *)
 					IF (int.CS MOD 4 > Machine.KernelLevel) & (exc.pf+4 = int.SP) THEN
 						w.String("stack overflow"); overflow := TRUE
+					ELSE
+						w.String("memory access violation (page fault)");
 					END
 				|0: w.String("division error")
 				|1: w.String("WITH guard failed")
@@ -79,6 +80,7 @@ VAR
 				|9: w.String("array dimension error")
 				|14: w.String("out of memory")
 				|16: w.String("procedure returned")
+				|17: w.String("nil pointer access")
 				ELSE
 					IF (exc.halt > MAX(INTEGER)+1) OR (exc.halt < MIN(INTEGER)) THEN
 						w.String("module freed?")
@@ -120,7 +122,8 @@ VAR
 			IF (int.INT = Machine.PF) & (ABS(int.PC-exc.CR[2]) < 100H) THEN	(* PF close to PC *)
 				KernelLog.Memory(int.ESP-16, 64)	(* show stack *)
 			END;*)
-			Reflection.StackTraceBack(w, int.PC, int.BP, Objects.GetStackBottom(p), long, overflow);
+			w.String( "StackTraceBack:" );  w.Ln;
+			Reflection.StackTraceBack(w, int.PC, int.BP, int.SP, Objects.GetStackBottom(p), long, overflow);
 		END;
 		w.String("---------------------------------"); w.Ln;
 		w.Char(02X);	(* "end of trap" *)

+ 2 - 2
source/BIOS.I386.BenchInterrupts.Mod

@@ -44,7 +44,7 @@ END SoftwareInterrupt;
 PROCEDURE Bench*(context : Commands.Context); (** [nofSamples] ~ *)
 VAR nofSamples, index, oldNgc, ignore : LONGINT;
 BEGIN {EXCLUSIVE}
-	context.arg.SkipWhitespace; context.arg.Int(nofSamples, FALSE);
+	context.arg.GetInteger(nofSamples, FALSE);
 	IF (nofSamples < MinNofSamples) THEN nofSamples := MinNofSamples;
 	ELSIF (nofSamples > MaxNofSamples) THEN nofSamples := MaxNofSamples;
 	END;
@@ -84,7 +84,7 @@ VAR
 	nofSamples, min, avg, max, i : LONGINT; sum : HUGEINT;
 	diff, diffSum, standardDeviation : LONGREAL;
 BEGIN {EXCLUSIVE}
-	context.arg.SkipWhitespace; context.arg.Int(mhz, FALSE);
+	context.arg.GetInteger(mhz, FALSE);
 	IF (data # NIL) THEN
 		nofSamples := LEN(data);
 		min := MAX(LONGINT); max := MIN(LONGINT); sum := 0;

+ 1 - 1
source/BIOS.I386.Keyboard.Mod

@@ -513,7 +513,7 @@ PROCEDURE SetLayout*(context : Commands.Context); (** KeyboardLayoutFile ~ *)
 VAR layoutFilename : ARRAY 256 OF CHAR;
 BEGIN {EXCLUSIVE}
 	IF (keyboard # NIL) THEN
-		context.arg.SkipWhitespace; context.arg.String(layoutFilename);
+		context.arg.GetString(layoutFilename);
 		table := TableFromFile(layoutFilename);
 	ELSE
 		context.error.String("Keyboard: No keyboard found."); context.error.Ln;

+ 1 - 2
source/BIOS.I386.Traps.Mod

@@ -318,7 +318,7 @@ VAR
 	BEGIN
 		t := Objects.running[Machine.ID()];
 		IF Machine.IFBit IN state.FLAGS THEN	(* enable interrupts again if they were enabled *)
-			Machine.Sti()(* avoid Processors.StopAll deadlock when waiting for locks below (fixme: remove) *)
+			Machine.Sti()	(* avoid Processors.StopAll deadlock when waiting for locks below (fixme: remove) *)
 		END;
 		IF (t = NIL) OR ~Machine.ExtendStack(t.stack, Machine.CR2()) THEN
 			IF TraceVerbose THEN
@@ -343,7 +343,6 @@ VAR
 		END
 	END PageFault;
 
-
 	PROCEDURE Init;
 	VAR i: LONGINT; s: ARRAY 8 OF CHAR;
 	BEGIN