فهرست منبع

use builtin MIN/MAX
removed implementation clause

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

eth.metacore 6 سال پیش
والد
کامیت
e28acebd4c

+ 2 - 7
source/BIOS.BootShell.Mod

@@ -375,7 +375,7 @@ TYPE
 		BEGIN
 			lock.Acquire;
 			d := Difference(firstLineShown, firstLine, LEN(lines));
-			nofLines := Min(nofLines, d - 1);
+			nofLines := MIN(nofLines, d - 1);
 			IF (nofLines > 0) THEN
 				firstLineShown := Subtract(firstLineShown, nofLines, LEN(lines));
 			END;
@@ -388,7 +388,7 @@ TYPE
 		BEGIN
 			lock.Acquire;
 			d := Difference(lastLine, firstLineShown, LEN(lines));
-			nofLines := Min(nofLines, d - 1);
+			nofLines := MIN(nofLines, d - 1);
 			IF (nofLines > 0) THEN
 				firstLineShown := Add(firstLineShown, nofLines, LEN(lines));
 			END;
@@ -653,11 +653,6 @@ BEGIN
 	RETURN (ch = SPACE) OR (ch = TAB) OR (ch = CR) OR (ch = LF);
 END IsWhitespace;
 
-PROCEDURE Min(a, b : LONGINT) : LONGINT;
-BEGIN
-	IF (a <= b) THEN RETURN a; ELSE RETURN b; END;
-END Min;
-
 PROCEDURE Invalidate(textBuffer : TextBuffer);
 VAR offset, index, i, nofLines : LONGINT; line : Line; character : Character; ch : CHAR;
 BEGIN

+ 2 - 8
source/BIOS.i810Sound.Mod

@@ -473,7 +473,7 @@ TYPE
 				WHILE item # NIL DO
 					IF item.channel.state = StatePlaying THEN
 						playSamplingRate[playCurrentBufferIndex] :=
-							Max(playSamplingRate[playCurrentBufferIndex], item.channel.samplingRate);
+							MAX(playSamplingRate[playCurrentBufferIndex], item.channel.samplingRate);
 						silent := FALSE
 					END;
 					item := item.next
@@ -776,7 +776,7 @@ TYPE
 				recSamplingRate := 1;
 				item := firstRecChannel;
 				WHILE item # NIL DO
-					recSamplingRate := Max(recSamplingRate, item.channel.samplingRate);
+					recSamplingRate := MAX(recSamplingRate, item.channel.samplingRate);
 					item := item.next;
 				END;
 
@@ -1447,12 +1447,6 @@ TYPE
 		RETURN n IN SYSTEM.VAL(SET, a);
 	END TestBit;
 
-	(* Return maximum value *)
-	PROCEDURE Max(i, j : LONGINT) : LONGINT;
-	BEGIN
-		IF i > j THEN RETURN i ELSE RETURN j END
-	END Max;
-
 	(* Get physical address for DMA transfers *)
 	PROCEDURE GetPhysicalAdr(adr: ADDRESS; size : SIZE) : Machine.Address32;
 	VAR

+ 6 - 13
source/BluetoothL2CAP.Mod

@@ -607,7 +607,7 @@ TYPE
 			hdr[0] := CHR(len MOD 100H); hdr[1] := CHR(len DIV 100H);
 			hdr[2] := CHR(did MOD 100H); hdr[3] := CHR(did DIV 100H);
 
-			count := Min(Bluetooth.MaxACLDataLen - 4, len); (* Min(l2cap.aclMTU - 4, len); *)
+			count := MIN(Bluetooth.MaxACLDataLen - 4, len); (* MIN(l2cap.aclMTU - 4, len); *)
 			IF TraceChannel THEN
 				KernelLog.String(ModuleName);
 				KernelLog.String("Channel.Send: first packet (payload: "); KernelLog.Int(count, 0); KernelLog.String(" bytes)");
@@ -620,7 +620,7 @@ TYPE
 
 			DEC(len, count); INC(ofs, count);
 			WHILE (len > 0) DO
-				count := Min(Bluetooth.MaxACLDataLen, len); (* Min(l2cap.aclMTU, len); *)
+				count := MIN(Bluetooth.MaxACLDataLen, len); (* MIN(l2cap.aclMTU, len); *)
 				IF TraceChannel THEN
 					KernelLog.String(ModuleName);
 					KernelLog.String("Channel.Send: continuing packet (payload: "); KernelLog.Int(count, 0); KernelLog.String(" bytes)");
@@ -687,7 +687,7 @@ TYPE
 				KernelLog.Ln; KernelLog.Ln; KernelLog.String("**** Warning: MTU = 0 ****"); KernelLog.Ln; KernelLog.Ln; KernelLog.Ln;
 				mtu := 1000H
 			END;
-			len := Min(len, mtu);
+			len := MIN(len, mtu);
 			res := Send(buffer, ofs, len);
 			IF (res = 0) THEN
 				size := len
@@ -727,7 +727,7 @@ TYPE
 				END;
 				*)
 					(*
-					FOR i := 0 TO Min(readerData.len, min-size)-1 DO
+					FOR i := 0 TO MIN(readerData.len, min-size)-1 DO
 						buffer[size] := readerData.data[i]; INC(size)
 					END;
 					readerData := NIL
@@ -1927,7 +1927,7 @@ TYPE
 					signallingChannel.WaitForReply(id, RTXTimeout, response);
 					IF (response # NIL) THEN
 						result := 0;
-						length := Min(response.length, LEN(echoData));
+						length := MIN(response.length, LEN(echoData));
 						FOR i := 0 TO length-1 DO echoData[i] := response.data[response.ofs+i] END
 					ELSE
 						result := 1	(* Ping timeout *)
@@ -1959,7 +1959,7 @@ TYPE
 						it := ORD(response.data[response.ofs])+LONG(ORD(response.data[response.ofs+1]))*100H;
 						IF (infoType = it) THEN
 							result := ORD(response.data[response.ofs+2])+LONG(ORD(response.data[response.ofs+3]))*100H;
-							size := Min(response.length-4, LEN(infoData));
+							size := MIN(response.length-4, LEN(infoData));
 							FOR i := 0 TO size-1 DO infoData[i] := response.data[response.ofs+4+i] END
 						ELSE
 							result := 1	(* wrong infoType in reply *)
@@ -2235,13 +2235,6 @@ BEGIN
 END SetL2CAPHeader;
 *)
 
-PROCEDURE Min(a,b: LONGINT): LONGINT;
-BEGIN
-	IF (a <= b) THEN RETURN a
-	ELSE RETURN b
-	END
-END Min;
-
 PROCEDURE InitL2CAP*(hci : HCI.HCI);
 BEGIN
 	NEW(hciManager,hci);

+ 2 - 7
source/Coop.Windows.Display.Mod

@@ -401,11 +401,6 @@ VAR
 		IF hCurrentCursor # hCursor THEN hCurrentCursor := hCursor;  ChangeCursor() END
 	END SetCursor;
 
-	PROCEDURE Min( a, b: LONGINT ): LONGINT;
-	BEGIN
-		IF a < b THEN RETURN a ELSE RETURN b END;
-	END Min;
-
 	PROCEDURE HandleMouse( win: Window;  uMsg: LONGINT;  wParam: User32.WParam;  lParam: User32.LParam );
 	VAR m: AosInputs.AbsMouseMsg;  oldx, oldy: LONGINT;  keys: SET; ret: Kernel32.BOOL;
 	BEGIN
@@ -418,11 +413,11 @@ VAR
 		m.dx := 0;  m.dy := 0;  m.dz := 0;
 
 		IF (m.x <= 0) THEN m.dx := win.track.dx - 2;
-		ELSIF (m.x >= Min( win.width, disp.width ) - 1) THEN m.x := disp.width - 1;  m.dx := win.track.dx + 2;
+		ELSIF (m.x >= MIN( win.width, disp.width ) - 1) THEN m.x := disp.width - 1;  m.dx := win.track.dx + 2;
 		END;
 
 		IF (m.y <= 0) THEN m.dy := win.track.dy - 2;
-		ELSIF (m.y >= Min( win.height, disp.height ) - 1) THEN m.y := disp.height - 1;  m.dy := win.track.dy + 2;
+		ELSIF (m.y >= MIN( win.height, disp.height ) - 1) THEN m.y := disp.height - 1;  m.dy := win.track.dy + 2;
 		END;
 
 		win.track.dx := m.dx;  win.track.dy := m.dy;

+ 2 - 11
source/DTPData.Mod

@@ -1187,8 +1187,8 @@ TYPE
 		VAR cx, cy, cw, ch: REAL;
 		BEGIN
 			cx := x; cy := y; cw := w; ch := h;
-			x := Min(cx, cx+cw); y := Min(cy, cy+ch);
-			w := Max(cx, cx+cw)-Min(cx, cx+cw); h := Max(cy, cy+ch)-Min(cy, cy+ch);
+			x := MIN(cx, cx+cw); y := MIN(cy, cy+ch);
+			w := MAX(cx, cx+cw)-MIN(cx, cx+cw); h := MAX(cy, cy+ch)-MIN(cy, cy+ch);
 
 		END FixExtent;
 
@@ -1470,14 +1470,5 @@ BEGIN
 	RETURN newObject;
 END NewObject;
 
-PROCEDURE Min(a, b: REAL): REAL;
-BEGIN
-	IF a <= b THEN RETURN a ELSE RETURN b END;
-END Min;
-
-PROCEDURE Max(a, b: REAL): REAL;
-BEGIN
-	IF a >= b THEN RETURN a ELSE RETURN b END;
-END Max;
 
 END DTPData.	

+ 0 - 11
source/DTPEditor.Mod

@@ -2387,17 +2387,6 @@ VAR
 	plugRegistry*: PluginRegistry;
 	Unassigned: DTPData.ContentFactory;
 
-(*
-PROCEDURE Min(a, b: REAL): REAL;
-BEGIN
-	IF a <= b THEN RETURN a ELSE RETURN b END;
-END Min;
-
-PROCEDURE Max(a, b: REAL): REAL;
-BEGIN
-	IF a >= b THEN RETURN a ELSE RETURN b END;
-END Max;
-*)
 
 PROCEDURE OpenNew*;
 VAR instance : Window;

+ 7 - 7
source/DTPText.Mod

@@ -154,7 +154,7 @@ TYPE
 				(* KernelLog.String("LineNR: "); KernelLog.Int(nofLines, 0); KernelLog.Ln; *)
 				LayoutLine(pos, lines[nofLines], nofLines);
 				realHeight := realHeight + lines[nofLines].height; textHeight := ENTIER(realHeight);
-				textWidth := ENTIER(DTPUtilities.Max(textWidth, lines[nofLines].width));
+				textWidth := MAX(textWidth, lines[nofLines].width);
 				ASSERT(pos > oldpos);
 				IF TraceLayout IN Trace THEN KernelLog.String("Line from : "); KernelLog.Int(lines[nofLines].pos, 5); KernelLog.Ln END;
 				(* lines[nofLines].align := AlignLeft; *)
@@ -195,7 +195,7 @@ TYPE
 					*)	IF (l >= LEN(lines)) THEN tempHeight := 0.0 ELSE tempHeight := lines[l].height; END;
 						realHeight := realHeight -  tempHeight;
 						LayoutLine(pos, lines[l], l);
-						textWidth := ENTIER(DTPUtilities.Max(textWidth, lines[l].width));
+						textWidth := MAX(textWidth, lines[l].width);
 						realHeight := realHeight + lines[nofLines].height;
 						INC(dl);
 						IF TraceLayout IN Trace THEN KernelLog.String("Line from : "); KernelLog.Int(lines[nofLines].pos, 5); KernelLog.Ln END;
@@ -210,7 +210,7 @@ TYPE
 					linesChanged := TRUE;
 					realHeight := realHeight - lines[l].height;
 					LayoutLine(pos, lines[l], l);
-					textWidth := ENTIER(DTPUtilities.Max(textWidth, lines[l].width));
+					textWidth := MAX(textWidth, lines[l].width);
 					realHeight := realHeight + lines[nofLines].height;
 					INC(dl);
 					IF TraceLayout IN Trace THEN KernelLog.String("Line from : "); KernelLog.Int(lines[nofLines].pos, 5); KernelLog.Ln END;
@@ -1258,8 +1258,8 @@ TYPE
 							(* KernelLog.String("nofSpaces: "); KernelLog.Int(nofSpaces, 0); KernelLog.Ln; *)
 						END;
 						IF (leadi = -1) THEN leadi := ascent + descent; END;
-						ascent := DTPUtilities.Max(ascent, a); descent := DTPUtilities.Max(descent, d);
-						leading := DTPUtilities.Max(leading, leadi);
+						ascent := MAX(ascent, a); descent := MAX(descent, d);
+						leading := MAX(leading, leadi);
 						IF (wrap # {}) & (i > 0) & (x + dx > wrapwidth) THEN
 							eol := TRUE; DEC(pos); wrapPos := pos;
 							(* Go left for last space *)
@@ -1367,7 +1367,7 @@ TYPE
 				IF (align = 3) THEN l.spaceSize := spaceRSize; ELSE l.spaceSize := 0; END;
 			END;
 			l.firstIndent := firstIndent; l.leftIndent := leftIndent; l.rightIndent := rightIndent; l.align := align;
-			l.ascent := ascent; l.height := leading; (* DTPUtilities.Max(leading, ascent + descent); *)
+			l.ascent := ascent; l.height := leading; (* MAX(leading, ascent + descent); *)
 (*			KernelLog.String("Height(ascent): "); DTPUtilities.OutReal(ascent, 4); KernelLog.Ln;
 			KernelLog.String("Height(descent): "); DTPUtilities.OutReal(descent, 4); KernelLog.Ln;
 			KernelLog.String("Size(height): "); DTPUtilities.OutReal(ascent + descent, 4); KernelLog.Ln;
@@ -1916,7 +1916,7 @@ TYPE
 			h := 0; w := 0;
 			FOR i := la TO lb DO
 				realH := realH + (layout.lines[i].height);
-				w := ENTIER(DTPUtilities.Max(w, layout.lines[i].width));
+				w := MAX(w, layout.lines[i].width);
 			END;
 			h := Limit(ENTIER(realH), 20, 200);
 			w := Limit(w, 20, 400);

+ 0 - 9
source/DTPUtilities.Mod

@@ -2081,15 +2081,6 @@ VAR
 	ctxAlignLeft, ctxAlignCenter, ctxAlignRight, ctxAlignJustified: ContextMenuData;
 	ctxRegular, ctxBold, ctxItalic, ctxBoldItalic: ContextMenuData;
 
-PROCEDURE Min*(a, b: REAL): REAL;
-BEGIN
-	IF a <= b THEN RETURN a ELSE RETURN b END;
-END Min;
-
-PROCEDURE Max*(a, b: REAL): REAL;
-BEGIN
-	IF a >= b THEN RETURN a ELSE RETURN b END;
-END Max;
 
 PROCEDURE Inc*(VAR a, b: REAL);
 BEGIN

+ 1 - 1
source/DTPView.Mod

@@ -654,7 +654,7 @@ TYPE
 							ELSE
 							END;
 							ccontent := cframe.GetContent(); ccontent.SetSize(ENTIER(cframe.GetWidth()*zoomFactor), ENTIER(cframe.GetHeight()*zoomFactor));
-							InvalidateRect(WMRectangles.MakeRect(ENTIER(DTPUtilities.Min(cframe.GetX(), DTPUtilities.Min(oldfx0, oldfx1))*zoomFactor)+docOriginX-10, ENTIER(DTPUtilities.Min(cframe.GetY(), DTPUtilities.Min(oldfy0, oldfy1))*zoomFactor)+docOriginY-10, ENTIER(DTPUtilities.Max((cframe.GetX()+cframe.GetWidth()), DTPUtilities.Max(oldfx1, oldfx0))*zoomFactor)+docOriginX+15, ENTIER(DTPUtilities.Max(cframe.GetY()+cframe.GetHeight(), DTPUtilities.Max(oldfy1, oldfy0))*zoomFactor)+docOriginY+15));
+							InvalidateRect(WMRectangles.MakeRect(ENTIER(MIN(cframe.GetX(), MIN(oldfx0, oldfx1))*zoomFactor)+docOriginX-10, ENTIER(MIN(cframe.GetY(), MIN(oldfy0, oldfy1))*zoomFactor)+docOriginY-10, ENTIER(MAX((cframe.GetX()+cframe.GetWidth()), MAX(oldfx1, oldfx0))*zoomFactor)+docOriginX+15, ENTIER(MAX(cframe.GetY()+cframe.GetHeight(), MAX(oldfy1, oldfy0))*zoomFactor)+docOriginY+15));
 							oldfx0 := cframe.GetX(); oldfy0 := cframe.GetY(); oldfx1:= cframe.GetX()+cframe.GetWidth(); oldfy1:= cframe.GetY()+cframe.GetHeight();
 						ELSIF moveguide THEN									(* move guide *)
 							IF cguide.GetHorizontal() THEN

+ 10 - 19
source/GfxRegions.Mod

@@ -137,15 +137,6 @@ MODULE GfxRegions; (** portable *)	(* eos  *)
 		again, at the same time eliminating multiple points and overlapping spans.
 	*)
 
-	PROCEDURE Min (x, y: INTEGER): INTEGER;
-	BEGIN
-		IF x <= y THEN RETURN x ELSE RETURN y END
-	END Min;
-
-	PROCEDURE Max (x, y: INTEGER): INTEGER;
-	BEGIN
-		IF x >= y THEN RETURN x ELSE RETURN y END
-	END Max;
 
 	(* encode point coordinates and curve direction into a LONGINT *)
 	PROCEDURE Encode (VAR item: LONGINT; u, v, dir: LONGINT);
@@ -373,7 +364,7 @@ MODULE GfxRegions; (** portable *)	(* eos  *)
 
 		WHILE (n < N) & (m < M) DO
 			tmp := p;
-			v := Min(nv, mv);
+			v := MIN(nv, mv);
 
 			(* eliminate overlapping spans before copying them *)
 			sum := 0;
@@ -572,7 +563,7 @@ MODULE GfxRegions; (** portable *)	(* eos  *)
 				Decode(data[n], u, v, dir)
 			UNTIL v > y;
 			hi := n;
-			top := Min(v, ury);
+			top := MIN(v, ury);
 
 			(* enumerate spans of current slice *)
 			n := lo;
@@ -583,7 +574,7 @@ MODULE GfxRegions; (** portable *)	(* eos  *)
 					IF dir = enter THEN
 						x := u
 					ELSE
-						enum(x, y, Min(u, urx), top, edata)
+						enum(x, y, MIN(u, urx), top, edata)
 					END
 				END;
 				INC(n);
@@ -787,8 +778,8 @@ MODULE GfxRegions; (** portable *)	(* eos  *)
 		END;
 
 		rdata := reg.data; adata := arg.data;
-		bot := Max(reg.lly, arg.lly);
-		top := Min(reg.ury, arg.ury);
+		bot := MAX(reg.lly, arg.lly);
+		top := MIN(reg.ury, arg.ury);
 		FindLower(reg, bot, rn);
 		FindLower(arg, bot, an);
 		Decode(rdata[rn], ru, rv, rdir);
@@ -966,11 +957,11 @@ MODULE GfxRegions; (** portable *)	(* eos  *)
 				Decode(rdata[rn], ru, rv, rdir);
 				Decode(adata[an], au, av, adir);
 				rslice := rn; aslice := an;
-				top := Min(reg.ury, arg.ury);
+				top := MIN(reg.ury, arg.ury);
 
 				WHILE (av < top) OR (rv < top) DO
 					(* merge slices *)
-					ry := rv; ay := av; y := Max(ry, ay);
+					ry := rv; ay := av; y := MAX(ry, ay);
 					REPEAT
 						IF (av > ay) OR (rv = ry) & (ru <= au) THEN
 							IF rv # y THEN	(* do not duplicate points *)
@@ -1042,10 +1033,10 @@ MODULE GfxRegions; (** portable *)	(* eos  *)
 				Decode(adata[an], au, av, adir);
 
 				rslice := rn; aslice := an;
-				top := Min(reg.ury, arg.ury);
+				top := MIN(reg.ury, arg.ury);
 				WHILE (rv < top) OR (av < top) DO
 					(* merge slices *)
-					ry := rv; ay := av; y := Max(ry, ay);
+					ry := rv; ay := av; y := MAX(ry, ay);
 					REPEAT
 						IF (av > ay) OR (rv = ry) & (ru <= au) THEN
 							IF rv # y THEN	(* do not duplicate points *)
@@ -1140,7 +1131,7 @@ MODULE GfxRegions; (** portable *)	(* eos  *)
 
 			WHILE rv < reg.ury DO
 				(* merge intersecting slices *)
-				ry := rv; ay := av; y := Max(ry, ay);
+				ry := rv; ay := av; y := MAX(ry, ay);
 				Append(reg, LBound, y, Exit);
 				REPEAT
 					IF (av > ay) OR (rv = ry) & (ru <= au) THEN

+ 0 - 22
source/TCP.Mod

@@ -1172,28 +1172,6 @@ BEGIN
 	END
 END RangeSet;
 
-(*
-PROCEDURE -Min(a, b: LONGINT): LONGINT;
-CODE {SYSTEM.i386}
-	POP EBX
-	POP EAX
-	CMP EAX, EBX
-	JLE end
-	MOV EAX, EBX
-end:
-END Min;
-
-PROCEDURE -Max(a, b: LONGINT): LONGINT;
-CODE {SYSTEM.i386}
-	POP EBX
-	POP EAX
-	CMP EAX, EBX
-	JGE end
-	MOV EAX, EBX
-end:
-END Max;
-*)
-
 PROCEDURE WriteTime(t: LONGINT);
 VAR s: ARRAY 8 OF CHAR;
 BEGIN

+ 4 - 8
source/VNC.Mod

@@ -334,13 +334,13 @@ BEGIN
 		dst := 0; len := 0;
 		LOOP
 			IF size <= 0 THEN EXIT END;
-			n := Min(c.rcvbuflen, size);	(* n is number of bytes to copy from buffer now *)
+			n := MIN(c.rcvbuflen, size);	(* n is number of bytes to copy from buffer now *)
 			IF n = 0 THEN	(* buffer empty *)
 					(* attempt to read at least size bytes, but at most a full buffer *)
 				c.pcb.Receive(c.rcvbuf^, 0, LEN(c.rcvbuf), size, n, c.res);
 				IF c.res # Ok THEN EXIT END;
 				c.rcvbufpos := 0; c.rcvbuflen := n;
-				n := Min(n, size)	(* n is number of bytes to copy from buffer now *)
+				n := MIN(n, size)	(* n is number of bytes to copy from buffer now *)
 			END;
 			ASSERT(dst+n <= LEN(buf));	(* index check *)
 			SYSTEM.MOVE(ADDRESSOF(c.rcvbuf[c.rcvbufpos]), ADDRESSOF(buf[dst]), n);
@@ -389,10 +389,6 @@ BEGIN
 	buf[0] := x; c.pcb.Send(buf, 0, 1, FALSE, c.res)
 END Send;
 
-PROCEDURE Min(x, y: LONGINT): LONGINT;
-BEGIN
-	IF x <= y THEN RETURN x ELSE RETURN y END
-END Min;
 
 (* Get the server's version number and send our version number. *)
 
@@ -424,7 +420,7 @@ BEGIN
 		IF x = 0 THEN	(* failed *)
 			ReceiveLInt(c, len);	(* read reason *)
 			WHILE (len > 0) & (c.res = Ok) DO
-				len0 := Min(len, LEN(buf));
+				len0 := MIN(len, LEN(buf));
 				ReceiveBytes(c, buf, len0, len0);
 				DEC(len, len0)
 			END;
@@ -500,7 +496,7 @@ BEGIN
 				KernelLog.Exit
 			END;
 			WHILE (len > 0) & (c.res = Ok) DO
-				len0 := Min(len, LEN(buf));
+				len0 := MIN(len, LEN(buf));
 				ReceiveBytes(c, buf, len0, len0);
 				DEC(len, len0)
 			END;

+ 2 - 7
source/VNCTetrisServer.Mod

@@ -337,12 +337,12 @@ PROCEDURE AddGame;
 BEGIN {EXCLUSIVE}
 	INC(gamesTotal);
 	INC(gamesRunning);
-	maxConcurrent := Max(gamesRunning, maxConcurrent)
+	maxConcurrent := MAX(gamesRunning, maxConcurrent)
 END AddGame;
 
 PROCEDURE ReportScore(score:LONGINT);
 BEGIN {EXCLUSIVE}
-	highScore := Max(score, highScore)
+	highScore := MAX(score, highScore)
 END ReportScore;
 
 PROCEDURE GetGamesTotal():LONGINT;
@@ -377,11 +377,6 @@ END SubGame;
 
 (* Standard Procedures *)
 
-PROCEDURE Max(x, y: LONGINT): LONGINT;
-BEGIN
-	IF x > y THEN RETURN x ELSE RETURN y END
-END Max;
-
 PROCEDURE Run*(context : Commands.Context);
 BEGIN
 	ReadData;

+ 3 - 7
source/W3dClusterWatch.Mod

@@ -150,7 +150,7 @@ TYPE
 				s := el.GetName(); IF s^ = "Entry" THEN
 					s := el.GetAttributeValue("Host");
 					NEW(x, world, pos, s^, interval, Render); x.index := index; INC(index); w.infoList.Add(x);
-					x.pos := pos; mx := Max(pos.x, mx);
+					x.pos := pos; mx := MAX(pos.x, mx);
 					pos.x := pos.x + BoxDistance
 				END
 			END
@@ -164,7 +164,7 @@ TYPE
 				p := cont.GetNext();
 				el := p(XML.Element);
 				s := el.GetName(); IF s^ = "Line" THEN
-					ParseLine(el, pos); mz := Max(pos.z, mz);
+					ParseLine(el, pos); mz := MAX(pos.z, mz);
 					pos.z := pos.z + BoxDistance
 				END
 			END
@@ -197,7 +197,7 @@ TYPE
 				el := p(XML.Element);
 				IF el IS XML.Element THEN
 					s := el(XML.Element).GetName(); IF s^ = "Layer" THEN
-						ParseLayer(el(XML.Element), pos); my := Max(pos.z, my);
+						ParseLayer(el(XML.Element), pos); my := MAX(pos.z, my);
 						pos.y := pos.y + BoxDistance;
 					END
 				END
@@ -311,10 +311,6 @@ END Watch;
 PROCEDURE Cleanup;
 END Cleanup;
 
-PROCEDURE Max(a, b: LONGREAL):LONGREAL;
-BEGIN IF a > b THEN RETURN a ELSE RETURN b END
-END Max;
-
 BEGIN
 	timg := WMGraphics.LoadImage("W3dClusterWatchIcons.tar://tux.bmp", TRUE);
 	IF timg # NIL THEN

+ 5 - 12
source/W3dMenu.Mod

@@ -156,7 +156,7 @@ TYPE
 					s := el.GetAttributeValue("cmd"); IF s = NIL THEN NEW(x, world, pos, "hello") ELSE NEW(x, world, pos, s^) END;
 					x.index := index; INC(index); infoList.Add(x);
 
-					x.pos := pos; mx := Max(pos.x, mx);
+					x.pos := pos; mx := MAX(pos.x, mx);
 					pos.x := pos.x + BoxDistance;
 					s := el.GetAttributeValue("img");
 					IF s = NIL THEN NEW(s, 16) END;
@@ -169,7 +169,7 @@ TYPE
 					s := el.GetAttributeValue("cmd"); IF s = NIL THEN NEW(x, world, pos, "hello") ELSE NEW(x, world, pos, s^) END;
 					x.index := index; INC(index); winstance.infoList.Add(x);
 
-					x.pos := pos; mx := Max(pos.x, mx);
+					x.pos := pos; mx := MAX(pos.x, mx);
 					pos.x := pos.x + BoxDistance;
 					s := el.GetAttributeValue("img"); IF s = NIL THEN NEW(s, 16) END;
 					t := el.GetAttributeValue("title"); IF t = NIL THEN NEW(t, 16) END;
@@ -190,7 +190,7 @@ TYPE
 				p := cont.GetNext();
 				el := p(XML.Element);
 				s := el.GetName(); IF s^ = "Line" THEN
-					ParseLine(el, pos); mz := Max(pos.z, mz);
+					ParseLine(el, pos); mz := MAX(pos.z, mz);
 					pos.z := pos.z + BoxDistance
 				END
 			END
@@ -227,7 +227,7 @@ TYPE
 					IF p IS XML.Element THEN
 						el := p(XML.Element);
 						s := el(XML.Element).GetName(); IF s^ = "Layer" THEN
-							ParseLayer(el(XML.Element), pos); my := Max(pos.z, my);
+							ParseLayer(el(XML.Element), pos); my := MAX(pos.z, my);
 							pos.y := pos.y + BoxDistance
 						END
 					END
@@ -409,7 +409,7 @@ BEGIN
 	Raster.Fill(img, 9, 14, 54, 60, pix, mode);
 	timg := WMGraphics.LoadImage(icon, TRUE);	tex := NIL;
 	IF res THEN
-		tw := Min(timg.width, 46); th := Min(timg.height, 46);
+		tw := MIN(timg.width, 46); th := MIN(timg.height, 46);
 		dx := (46 - tw) DIV 2 + 9;
 		dy := (46 - th) DIV 2 + 14;
 		Raster.Copy(timg, img, 0, 0, tw, th, dx, dy, mode)
@@ -468,13 +468,6 @@ BEGIN
 	IF winstance # NIL THEN winstance.Close END
 END Cleanup;
 
-PROCEDURE Min(a, b: LONGINT):LONGINT;
-BEGIN IF a < b THEN RETURN a ELSE RETURN b END
-END Min;
-
-PROCEDURE Max(a, b: LONGREAL):LONGREAL;
-BEGIN IF a > b THEN RETURN a ELSE RETURN b END
-END Max;
 
 BEGIN
 	NEW(textures);

+ 2 - 7
source/W3dRasterizer.Mod

@@ -795,7 +795,7 @@ TYPE
 				dz := ((1 / (invz + SubDiv * invdz)) - z) * SubDivInv;
 
 				i := 0;
-				FOR ix := ENTIER(xr) TO Min(width, ENTIER(b.x + 0.5)) - 1 DO
+				FOR ix := ENTIER(xr) TO MIN(width, ENTIER(b.x + 0.5)) - 1 DO
 					INC(i);
 					IF i = SubDiv THEN
 						z := 1 / invz;
@@ -833,7 +833,7 @@ TYPE
 				dz := ((1 / (invz + SubDiv * invdz)) - z) * SubDivInv;
 
 				i := 0;
-				FOR iy := ENTIER(yr) TO Min(height, ENTIER(b.y + 0.5)) - 1 DO
+				FOR iy := ENTIER(yr) TO MIN(height, ENTIER(b.y + 0.5)) - 1 DO
 					INC(i);
 					IF i = SubDiv THEN
 						z := 1 / invz;
@@ -854,9 +854,4 @@ TYPE
 
 	END Rasterizer;
 
-PROCEDURE Min(a, b: LONGINT): LONGINT;
-BEGIN
-	IF a < b THEN RETURN a ELSE RETURN b END
-END Min;
-
 END W3dRasterizer.

+ 2 - 9
source/W3dWorld.Mod

@@ -359,21 +359,14 @@ TYPE
 
 	END World;
 
-PROCEDURE Min(a, b: LONGREAL):LONGREAL;
-BEGIN IF a < b THEN RETURN a ELSE RETURN b END
-END Min;
-
-PROCEDURE Max(a, b: LONGREAL):LONGREAL;
-BEGIN IF a > b THEN RETURN a ELSE RETURN b END
-END Max;
 
 PROCEDURE GrowAABB(VAR aabb : AABB; p : Vectors.TVector3d);
 BEGIN
 	IF aabb.empty THEN
 		aabb.a := p; aabb.b := p; aabb.empty := FALSE
 	ELSE
-		aabb.a.x := Min(aabb.a.x, p.x); aabb.a.y := Min(aabb.a.y, p.y); aabb.a.z := Min(aabb.a.z, p.z);
-		aabb.b.x := Max(aabb.b.x, p.x); aabb.b.y := Max(aabb.b.y, p.y); aabb.b.z := Max(aabb.b.z, p.z)
+		aabb.a.x := MIN(aabb.a.x, p.x); aabb.a.y := MIN(aabb.a.y, p.y); aabb.a.z := MIN(aabb.a.z, p.z);
+		aabb.b.x := MAX(aabb.b.x, p.x); aabb.b.y := MAX(aabb.b.y, p.y); aabb.b.z := MAX(aabb.b.z, p.z)
 	END
 END GrowAABB;
 

+ 8 - 16
source/WMFigures.Mod

@@ -630,10 +630,10 @@ TYPE
 			IF (points=NIL) OR (points.next=NIL) THEN RETURN END;
 			p := points;
 			q := points.next;
-			rect.l := Min(p.x, q.x);
-			rect.r := Max(p.x, q.x);
-			rect.t := Min(p.y, q.y);
-			rect.b := Max(p.y, q.y);
+			rect.l := MIN(p.x, q.x);
+			rect.r := MAX(p.x, q.x);
+			rect.t := MIN(p.y, q.y);
+			rect.b := MAX(p.y, q.y);
 			IF (*Filled IN state *) FALSE THEN (*canvas.FillPolygonFlat(pointArray^, nofPoints, color.Get(), WMGraphics.ModeSrcOverDst);*) (*! to be done *)
 			ELSE WMGraphicUtilities.DrawRect(canvas, rect, color.Get(), WMGraphics.ModeSrcOverDst);
 			END;
@@ -841,12 +841,12 @@ BEGIN
 	points[0].x := SHORT(ENTIER(RX[1])); points[0].y := SHORT(ENTIER(RY[1]));
 	L := MAX(LONGINT);  B := MAX(LONGINT); R := MIN(LONGINT); T := MIN(LONGINT);
 	i := 1; WHILE i <= n DO
-		L := Min(L,SHORT(ENTIER(RX[i]))); B := Min(B,SHORT(ENTIER(RY[i])));
-		R := Max(R,SHORT(ENTIER(RX[i]))); T := Max(T,SHORT(ENTIER(RY[i])));
+		L := MIN(L,SHORT(ENTIER(RX[i]))); B := MIN(B,SHORT(ENTIER(RY[i])));
+		R := MAX(R,SHORT(ENTIER(RX[i]))); T := MAX(T,SHORT(ENTIER(RY[i])));
 		INC(i);
 	END;
 
-	dW := Max(1,Min((Max(R-L ,T-B)  * 3 DIV n DIV 20),4));
+	dW := MAX(1,MIN((MAX(R-L ,T-B)  * 3 DIV n DIV 20),4));
 	i := 1; k := 1;
 	WHILE i < n DO
 		GetPolynom(RX[i], RX[i+1], RXstrich[i], RXstrich[i+1], px);
@@ -1013,7 +1013,7 @@ VAR  w, h, pw, ph, det,len : LONGINT;
 	PROCEDURE Between(x, a, b: LONGINT): BOOLEAN;
 	VAR min, max: LONGINT;
 	BEGIN
-		min := Min(a, b); max := Max(a, b);
+		min := MIN(a, b); max := MAX(a, b);
 		RETURN (min - gravity <= x) & (x <= max + gravity);
 	END Between;
 
@@ -1049,14 +1049,6 @@ BEGIN dx := x - x0; dy := y - y0;
 	RETURN ENTIER(Math.sqrt(dx * dx + dy * dy))
 END Distance;
 
-PROCEDURE Min(x, y: LONGINT): LONGINT;
-BEGIN IF x < y THEN RETURN x ELSE RETURN y END
-END Min;
-
-PROCEDURE Max(x, y: LONGINT): LONGINT;
-BEGIN IF x > y THEN RETURN x ELSE RETURN y END
-END Max;
-
 PROCEDURE GenLine*() : XML.Element; (* needs AddPoint(); AddPoint(), before a prototype becomes visible  *)
 VAR line : Line;
 BEGIN

+ 2 - 12
source/WMRectangles.Mod

@@ -6,16 +6,6 @@ TYPE
 			This is to ensure consistency between the continuous and discrete case
 		*)
 
-	PROCEDURE Min(a, b:LONGINT):LONGINT;
-	BEGIN
-		IF a<b THEN RETURN a ELSE RETURN b END;
-	END Min;
-
-	PROCEDURE Max(a, b:LONGINT):LONGINT;
-	BEGIN
-		IF a>b THEN RETURN a ELSE RETURN b END;
-	END Max;
-
 	(** move the rectangle by deltaX, deltaY *)
 	PROCEDURE MoveRel*(VAR x:Rectangle; deltaX, deltaY:LONGINT);
 	BEGIN
@@ -79,8 +69,8 @@ TYPE
 	(** Extend old to contain addition *)
 	PROCEDURE ExtendRect*(VAR old, addition : Rectangle);
 	BEGIN
-		old.l := Min(old.l, addition.l); old.r := Max(old.r,addition.r);
-		old.t := Min(old.t, addition.t); old.b := Max(old.b, addition.b)
+		old.l := MIN(old.l, addition.l); old.r := MAX(old.r,addition.r);
+		old.t := MIN(old.t, addition.t); old.b := MAX(old.b, addition.b)
 	END ExtendRect;
 
 	(** return the Rectangle (l, t, r, b) *)

+ 2 - 12
source/WMVNCView.Mod

@@ -116,9 +116,9 @@ TYPE
 						(* calculate bottom rectangle *)
 						IF wr.b < r.b THEN Rect.SetRect(nr, r.l, wr.b, r.r, r.b); Draw(nr, cur.prev) END;
 						(* calculate left rectangle *)
-						IF wr.l > r.l THEN Rect.SetRect(nr, r.l, Max(r.t, wr.t), wr.l, Min(r.b, wr.b)); Draw(nr, cur.prev) END;
+						IF wr.l > r.l THEN Rect.SetRect(nr, r.l, MAX(r.t, wr.t), wr.l, MIN(r.b, wr.b)); Draw(nr, cur.prev) END;
 						(* calculate left rectangle *)
-						IF wr.r < r.r THEN Rect.SetRect(nr, wr.r, Max(r.t, wr.t), r.r, Min(r.b, wr.b)); Draw(nr, cur.prev) END;
+						IF wr.r < r.r THEN Rect.SetRect(nr, wr.r, MAX(r.t, wr.t), r.r, MIN(r.b, wr.b)); Draw(nr, cur.prev) END;
 						(* calculate overlapping *)
 						nr := r; Rect.ClipRect(nr, wr);
 						IF ~Rect.RectEmpty(nr) THEN InternalDraw(nr, cur) END
@@ -210,16 +210,6 @@ TYPE
 
 VAR v: VVList;
 
-PROCEDURE Min(a, b:LONGINT):LONGINT;
-BEGIN
-	IF a<b THEN RETURN a ELSE RETURN b END;
-END Min;
-
-PROCEDURE Max(a, b:LONGINT):LONGINT;
-BEGIN
-	IF a>b THEN RETURN a ELSE RETURN b END;
-END Max;
-
 PROCEDURE Bound(VAR x:LONGINT; min, max:LONGINT);
 BEGIN
 	IF x < min THEN x := min ELSE IF x > max THEN x := max END END

+ 4 - 14
source/WindowManager.Mod

@@ -349,9 +349,9 @@ TYPE
 							(* calculate bottom rectangle *)
 							IF wr.b < r.b THEN Rect.SetRect(nr, r.l, wr.b, r.r, r.b); Draw(nr, cur.prev) END;
 							(* calculate left rectangle *)
-							IF wr.l > r.l THEN Rect.SetRect(nr, r.l, Max(r.t, wr.t), wr.l, Min(r.b, wr.b)); Draw(nr, cur.prev) END;
+							IF wr.l > r.l THEN Rect.SetRect(nr, r.l, MAX(r.t, wr.t), wr.l, MIN(r.b, wr.b)); Draw(nr, cur.prev) END;
 							(* calculate left rectangle *)
-							IF wr.r < r.r THEN Rect.SetRect(nr, wr.r, Max(r.t, wr.t), r.r, Min(r.b, wr.b)); Draw(nr, cur.prev) END;
+							IF wr.r < r.r THEN Rect.SetRect(nr, wr.r, MAX(r.t, wr.t), r.r, MIN(r.b, wr.b)); Draw(nr, cur.prev) END;
 							(* calculate overlapping *)
 							nr := r; Rect.ClipRect(nr, wr);
 							IF ~Rect.RectEmpty(nr) THEN InternalDraw(nr, cur) END
@@ -1237,9 +1237,9 @@ TYPE
 						(* calculate bottom rectangle *)
 						IF bounds.b < r.b THEN Rect.SetRect(nr, r.l, bounds.b, r.r, r.b);Sub(x.next, nr) END;
 						(* calculate left rectangle *)
-						IF bounds.l > r.l THEN Rect.SetRect(nr, r.l, Max(r.t, bounds.t), bounds.l, Min(r.b, bounds.b)); Sub(x.next, nr) END;
+						IF bounds.l > r.l THEN Rect.SetRect(nr, r.l, MAX(r.t, bounds.t), bounds.l, MIN(r.b, bounds.b)); Sub(x.next, nr) END;
 						(* calculate right rectangle *)
-						IF bounds.r < r.r THEN Rect.SetRect(nr, bounds.r, Max(r.t, bounds.t), r.r, Min(r.b, bounds.b)); Sub(x.next, nr) END
+						IF bounds.r < r.r THEN Rect.SetRect(nr, bounds.r, MAX(r.t, bounds.t), r.r, MIN(r.b, bounds.b)); Sub(x.next, nr) END
 					ELSE (* the window x is not in front *)
 						Sub(x.next, r)
 					END
@@ -1568,16 +1568,6 @@ VAR
 	CharToUnicode: ARRAY 256 OF LONGINT; (** mapping from Oberon character codes to Unicodes **)
 
 
-PROCEDURE Min(a, b:LONGINT):LONGINT;
-BEGIN
-	IF a < b THEN RETURN a ELSE RETURN b END;
-END Min;
-
-PROCEDURE Max(a, b:LONGINT):LONGINT;
-BEGIN
-	IF a > b THEN RETURN a ELSE RETURN b END;
-END Max;
-
 PROCEDURE Bound(VAR x:LONGINT; min, max:LONGINT);
 BEGIN
 	IF x < min THEN x := min ELSE IF x > max THEN x := max END END

+ 2 - 7
source/Windows.Display.Mod

@@ -441,11 +441,6 @@ VAR
 		IF hCurrentCursor # hCursor THEN hCurrentCursor := hCursor;  ChangeCursor() END
 	END SetCursor;
 
-	PROCEDURE Min( a, b: LONGINT ): LONGINT;
-	BEGIN
-		IF a < b THEN RETURN a ELSE RETURN b END;
-	END Min;
-
 	PROCEDURE HandleMouse( win: Window;  uMsg: LONGINT;  wParam: User32.WParam;  lParam: User32.LParam );
 	VAR m: AosInputs.AbsMouseMsg;  oldx, oldy: LONGINT;  keys: SET; ret: Kernel32.HANDLE;
 	BEGIN
@@ -458,11 +453,11 @@ VAR
 		m.dx := 0;  m.dy := 0;  m.dz := 0;
 
 		IF (m.x <= 0) THEN m.dx := win.track.dx - 2;
-		ELSIF (m.x >= Min( win.width, disp.width ) - 1) THEN m.x := disp.width - 1;  m.dx := win.track.dx + 2;
+		ELSIF (m.x >= MIN( win.width, disp.width ) - 1) THEN m.x := disp.width - 1;  m.dx := win.track.dx + 2;
 		END;
 
 		IF (m.y <= 0) THEN m.dy := win.track.dy - 2;
-		ELSIF (m.y >= Min( win.height, disp.height ) - 1) THEN m.y := disp.height - 1;  m.dy := win.track.dy + 2;
+		ELSIF (m.y >= MIN( win.height, disp.height ) - 1) THEN m.y := disp.height - 1;  m.dy := win.track.dy + 2;
 		END;
 
 		win.track.dx := m.dx;  win.track.dy := m.dy;

+ 2 - 9
source/Windows.ODBC.Mod

@@ -443,13 +443,6 @@ VAR
 
 
 
-(*	-------------------------- internal functions --------------------------	*)
-
-PROCEDURE Min(x, y: LONGINT): LONGINT;
-BEGIN
-	IF x > y THEN RETURN y ELSE RETURN x END
-END Min;
-
 (*	-------------------------- interface to core functions --------------------------	*)
 
 PROCEDURE AllocConnect*(hdbc: HDBC; VAR res: INTEGER);
@@ -510,7 +503,7 @@ PROCEDURE StatementError*(hstmt: HSTMT; VAR SqlState: ARRAY OF CHAR; VAR NativeE
 VAR ErrorMsg: ARRAY OF CHAR; VAR res: INTEGER);
 	VAR state: ARRAY 6 OF CHAR; len, msgSize: INTEGER;
 BEGIN
-	len:= SHORT(Min(MAXMESSAGELENGTH-1, LEN(ErrorMsg)));
+	len:= SHORT(MIN(MAXMESSAGELENGTH-1, LEN(ErrorMsg)));
 	res:= SQLError(0, 0, hstmt.hstmt, ADDRESSOF(state), ADDRESSOF(NativeError), ADDRESSOF(ErrorMsg), len,
 		ADDRESSOF(msgSize));
 	COPY (state, SqlState);
@@ -520,7 +513,7 @@ PROCEDURE ConnectionError*(hdbc: HDBC; VAR SqlState: ARRAY OF CHAR; VAR NativeEr
 ErrorMsg: ARRAY OF CHAR; VAR res: INTEGER);
 	VAR state: ARRAY 6 OF CHAR; len, msgSize: INTEGER;
 BEGIN
-	len:= SHORT(Min(MAXMESSAGELENGTH-1, LEN(ErrorMsg)));
+	len:= SHORT(MIN(MAXMESSAGELENGTH-1, LEN(ErrorMsg)));
 	IF hdbc # NIL THEN
 		res:= SQLError(0, hdbc.hdbc, 0, ADDRESSOF(state), ADDRESSOF(NativeError), ADDRESSOF(ErrorMsg), len, ADDRESSOF(msgSize))
 	ELSE

+ 4 - 14
source/XMLComponents.Mod

@@ -493,8 +493,8 @@ TYPE
 		PROCEDURE ClipRect*(x, y, w, h: LONGINT);
 		VAR ur: LONGINT;
 		BEGIN
-			ur := Min(SELF.x + SELF.w, x + w); SELF.x := Max(SELF.x, x); SELF.w := Max(0, ur - SELF.x);
-			ur := Min(SELF.y + SELF.h, y + h); SELF.y := Max(SELF.y, y); SELF.h := Max(0, ur - SELF.y)
+			ur := MIN(SELF.x + SELF.w, x + w); SELF.x := MAX(SELF.x, x); SELF.w := MAX(0, ur - SELF.x);
+			ur := MIN(SELF.y + SELF.h, y + h); SELF.y := MAX(SELF.y, y); SELF.h := MAX(0, ur - SELF.y)
 		END ClipRect;
 
 		PROCEDURE Extend*(box: Box);
@@ -505,8 +505,8 @@ TYPE
 		PROCEDURE ExtendRect*(x, y, w, h: LONGINT);
 		VAR ur: LONGINT;
 		BEGIN
-			ur := Max(SELF.x + SELF.w, x + w); SELF.x := Min(SELF.x, x); SELF.w := ur - SELF.x;
-			ur := Max(SELF.y + SELF.h, y + h); SELF.y := Min(SELF.y, y); SELF.h := ur - SELF.y
+			ur := MAX(SELF.x + SELF.w, x + w); SELF.x := MIN(SELF.x, x); SELF.w := ur - SELF.x;
+			ur := MAX(SELF.y + SELF.h, y + h); SELF.y := MIN(SELF.y, y); SELF.h := ur - SELF.y
 		END ExtendRect;
 
 	END Box;
@@ -1099,16 +1099,6 @@ TYPE
 		RETURN s
 	END NewString;
 
-	PROCEDURE Min*(a, b: LONGINT): LONGINT;
-	BEGIN
-		IF a > b THEN RETURN b ELSE RETURN a END
-	END Min;
-
-	PROCEDURE Max*(a, b: LONGINT): LONGINT;
-	BEGIN
-		IF a < b THEN RETURN b ELSE RETURN a END
-	END Max;
-
 (*	PROCEDURE DrawClipRect*(ctxt: Gfx.Context; x, y, w, h: LONGINT);
 	VAR llx, lly, urx, ury: INTEGER;
 	BEGIN