MODULE V24;
IMPORT SYSTEM, Objects, Machine, Streams, Commands, KernelLog, Serials;
CONST
MaxPortNo = 8;
BufSize = 1024;
IER = 1;
IIR = 2;
FCR = 2;
LCR = 3;
MCR = 4;
LSR = 5;
MSR = 6;
SCR = 7;
DTR* = 0; RTS* = 1;
Break* = 2;
DSR* = 3; CTS* = 4; RI* = 5; DCD* = 6;
ModuleName = "V24";
Verbose = TRUE;
TYPE
RS232Port = OBJECT (Serials.Port);
VAR
baseaddr, irq, maxbps: LONGINT;
buf: ARRAY BufSize OF CHAR;
head, tail: LONGINT;
open, ox16: BOOLEAN;
diagnostic: LONGINT;
PROCEDURE &Init*(basespec, irqspec : LONGINT);
BEGIN
baseaddr := basespec;
irq := irqspec;
open := FALSE; ox16 := CheckOX16PCI954(basespec);
IF ox16 THEN
maxbps := 460800
ELSE
maxbps := 115200
END
END Init;
PROCEDURE Open*(bps, data, parity, stop : LONGINT; VAR res: LONGINT);
BEGIN {EXCLUSIVE}
IF open THEN
IF Verbose THEN KernelLog.String(ModuleName); KernelLog.String(": "); KernelLog.String(name); KernelLog.String(" already open"); KernelLog.Ln; END;
res := Serials.PortInUse;
RETURN
END;
SetPortState(bps, data, parity, stop, res);
IF res = Serials.Ok THEN
open := TRUE;
head := 0; tail:= 0;
charactersSent := 0; charactersReceived := 0;
Objects.InstallHandler(HandleInterrupt, Machine.IRQ0 + irq);
Machine.Portout8((baseaddr) + IER, 01X);
IF Verbose THEN KernelLog.String(ModuleName); KernelLog.String(": "); KernelLog.String(name); KernelLog.String(" opened"); KernelLog.Ln END;
END
END Open;
PROCEDURE SendChar*(ch: CHAR; VAR res : LONGINT);
VAR s: SET;
BEGIN {EXCLUSIVE}
IF ~open THEN res := Serials.Closed; RETURN; END;
res := Serials.Ok;
REPEAT
Machine.Portin8((baseaddr) + LSR, SYSTEM.VAL(CHAR, s))
UNTIL 5 IN s;
Machine.Portout8((baseaddr), ch);
INC(charactersSent);
END SendChar;
PROCEDURE ReceiveChar*(VAR ch: CHAR; VAR res: LONGINT);
BEGIN {EXCLUSIVE}
IF ~open THEN res := Serials.Closed; RETURN END;
AWAIT(tail # head);
IF tail = -1 THEN
res := Serials.Closed;
ELSE
ch := buf[head]; head := (head+1) MOD BufSize;
res := diagnostic;
END
END ReceiveChar;
PROCEDURE HandleInterrupt;
VAR n: LONGINT; ch: CHAR; s: SET;
BEGIN {EXCLUSIVE}
LOOP
Machine.Portin8((baseaddr) + IIR, ch);
IF ODD(ORD(ch)) THEN EXIT END;
diagnostic := 0;
Machine.Portin8((baseaddr) + LSR, SYSTEM.VAL(CHAR, s));
IF (7 IN s) OR (1 IN s) THEN
IF (1 IN s) THEN diagnostic := Serials.OverrunError;
ELSIF (2 IN s) THEN diagnostic := Serials.ParityError
ELSIF (3 IN s) THEN diagnostic := Serials.FramingError
ELSIF (4 IN s) THEN diagnostic := Serials.BreakInterrupt
END;
END;
Machine.Portin8((baseaddr), ch);
n := (tail+1) MOD BufSize;
IF n # head THEN buf[tail] := ch; tail := n END;
INC(charactersReceived);
END;
END HandleInterrupt;
PROCEDURE Available*(): LONGINT;
BEGIN {EXCLUSIVE}
RETURN (tail - head) MOD BufSize
END Available;
PROCEDURE SetPortState(bps, data, parity, stop : LONGINT; VAR res: LONGINT);
CONST TCR = 2;
VAR s: SET; tcr: LONGINT;
BEGIN
IF (bps > 0) & (maxbps MOD bps = 0) THEN
IF (data >= 5) & (data <= 8) & (parity >= Serials.ParNo) & (parity <= Serials.ParSpace) &
(stop >= Serials.Stop1) & (stop <= Serials.Stop1dot5) THEN
IF ox16 THEN
IF bps <= 115200 THEN
tcr := 0
ELSE
tcr := 115200*16 DIV bps;
ASSERT((tcr >= 4) & (tcr < 16));
bps := 115200
END;
IF ReadICR(baseaddr, TCR) # CHR(tcr) THEN
WriteICR(baseaddr, TCR, CHR(tcr))
END
END;
bps := 115200 DIV bps;
Machine.Portout8((baseaddr)+LCR, 0X);
Machine.Portout8((baseaddr)+IER, 0X);
Machine.Portin8((baseaddr)+LSR, SYSTEM.VAL(CHAR, s));
Machine.Portin8((baseaddr)+IIR, SYSTEM.VAL(CHAR, s));
Machine.Portin8((baseaddr)+MSR, SYSTEM.VAL(CHAR, s));
Machine.Portout8((baseaddr)+FCR, 0C1X);
Machine.Portin8((baseaddr)+IIR, SYSTEM.VAL(CHAR, s));
IF s * {6,7} = {6,7} THEN
Machine.Portout8((baseaddr) + FCR, 47X)
ELSIF s * {6,7} = {} THEN
Machine.Portout8((baseaddr) + FCR, 0X)
ELSE KernelLog.String("Not prepared to deal with this COM port situation");
END;
Machine.Portout8((baseaddr) + LCR, 80X);
Machine.Portout8((baseaddr), CHR(bps));
Machine.Portout8((baseaddr)+1, CHR(bps DIV 100H));
CASE data OF
5: s := {}
| 6: s := {0}
| 7: s := {1}
| 8: s := {0,1}
END;
IF stop # Serials.Stop1 THEN INCL(s, 2) END;
CASE parity OF
Serials.ParNo:
| Serials.ParOdd: INCL(s, 3)
| Serials.ParEven: s := s + {3,4}
| Serials.ParMark: s := s + {3,5}
| Serials.ParSpace: s := s + {3..5}
END;
Machine.Portout8((baseaddr)+LCR, SYSTEM.VAL(CHAR, s));
Machine.Portout8((baseaddr)+MCR, SYSTEM.VAL(CHAR, {DTR,RTS,3}));
res := Serials.Ok
ELSE res := Serials.WrongData
END
ELSE res := Serials.WrongBPS
END
END SetPortState;
PROCEDURE GetPortState*(VAR openstat : BOOLEAN; VAR bps, data, parity, stop : LONGINT);
CONST TCR = 2;
VAR savset, set: SET; ch: CHAR;
BEGIN {EXCLUSIVE}
openstat := open;
Machine.Portin8((baseaddr) + LCR, SYSTEM.VAL(CHAR, savset));
set := savset + {7};
Machine.Portout8((baseaddr) + LCR, SYSTEM.VAL(CHAR, set));
Machine.Portin8((baseaddr)+1, ch);
bps := ORD(ch);
Machine.Portin8((baseaddr), ch);
IF (bps = 0 ) & (ch = 0X) THEN
ELSE
bps := 115200 DIV (100H*bps + ORD(ch))
END;
IF ox16 THEN
ch := ReadICR(baseaddr, TCR);
IF (ch >= 04X) & (ch < 16X) THEN
bps := bps*16 DIV ORD(ch)
END
END;
Machine.Portout8((baseaddr)+LCR, SYSTEM.VAL(CHAR, savset));
Machine.Portin8((baseaddr)+LCR, SYSTEM.VAL(CHAR, set));
IF set * {0, 1} = {0, 1} THEN data := 8
ELSIF set * {0, 1} = {1} THEN data := 7
ELSIF set * {0, 1} = {0} THEN data := 6
ELSE data := 5
END;
IF 2 IN set THEN
IF set * {0, 1} = {} THEN stop := 3
ELSE stop := 2
END;
ELSE stop := 1
END;
IF set * {3..5} = {3..5} THEN parity := 4
ELSIF set * {3,5} = {3,5} THEN parity := 3
ELSIF set * {3,4} = {3,4} THEN parity := 2
ELSIF set * {3} = {3} THEN parity := 1
ELSE parity := 0
END;
END GetPortState;
PROCEDURE ClearMC*(s: SET);
VAR t: SET;
BEGIN {EXCLUSIVE}
IF s * {DTR, RTS} # {} THEN
Machine.Portin8((baseaddr) + MCR, SYSTEM.VAL(CHAR, t));
t := t - (s * {DTR, RTS});
Machine.Portout8((baseaddr) + MCR, SYSTEM.VAL(CHAR, t))
END;
IF Break IN s THEN
Machine.Portin8((baseaddr) + LCR, SYSTEM.VAL(CHAR, t));
EXCL(t, 6);
Machine.Portout8((baseaddr) + LCR, SYSTEM.VAL(CHAR, t))
END
END ClearMC;
PROCEDURE SetMC*(s: SET);
VAR t: SET;
BEGIN {EXCLUSIVE}
IF s * {DTR, RTS} # {} THEN
Machine.Portin8((baseaddr) + MCR, SYSTEM.VAL(CHAR, t));
t := t + (s * {DTR, RTS});
Machine.Portout8((baseaddr) + MCR, SYSTEM.VAL(CHAR, t))
END;
IF Break IN s THEN
Machine.Portin8((baseaddr) + LCR, SYSTEM.VAL(CHAR, t));
INCL(t, 6);
Machine.Portout8((baseaddr) + LCR, SYSTEM.VAL(CHAR, t))
END
END SetMC;
PROCEDURE GetMC*(VAR s: SET);
VAR t: SET;
BEGIN {EXCLUSIVE}
s := {};
Machine.Portin8((baseaddr) + MSR, SYSTEM.VAL(CHAR, t));
IF 4 IN t THEN INCL(s, CTS) END;
IF 5 IN t THEN INCL(s, DSR) END;
IF 6 IN t THEN INCL(s, RI) END;
IF 7 IN t THEN INCL(s, DCD) END;
Machine.Portin8((baseaddr) + LSR, SYSTEM.VAL(CHAR, t));
IF 4 IN t THEN INCL(s, Break) END
END GetMC;
PROCEDURE Close*;
VAR s: SET;
BEGIN {EXCLUSIVE}
IF ~open THEN
IF Verbose THEN KernelLog.String(ModuleName); KernelLog.String(": "); KernelLog.String(name); KernelLog.String(" not open"); KernelLog.Ln; END;
RETURN
END;
REPEAT
Machine.Portin8((baseaddr)+LSR, SYSTEM.VAL(CHAR, s))
UNTIL 6 IN s;
tail := -1;
Machine.Portout8((baseaddr) + IER, 0X);
Objects.RemoveHandler(HandleInterrupt, Machine.IRQ0 + irq);
open := FALSE;
IF Verbose THEN KernelLog.String(ModuleName); KernelLog.String(": "); KernelLog.String(name); KernelLog.String(" closed"); KernelLog.Ln; END;
END Close;
END RS232Port;
PROCEDURE ReadICR(baseaddr, index: LONGINT): CHAR;
CONST SPR = 7; ICR = 5; ICREnable = 6;
VAR ch: CHAR;
BEGIN
Machine.Portout8((baseaddr) + SPR, 0X);
Machine.Portout8((baseaddr) + ICR, SYSTEM.VAL(CHAR, {ICREnable}));
Machine.Portout8((baseaddr) + SPR, CHR(index));
Machine.Portin8((baseaddr) + ICR, ch);
Machine.Portout8((baseaddr) + SPR, 0X);
Machine.Portout8((baseaddr) + ICR, 0X);
RETURN ch
END ReadICR;
PROCEDURE WriteICR(baseaddr, index: LONGINT; ch: CHAR);
CONST SPR = 7; ICR = 5;
BEGIN
Machine.Portout8((baseaddr) + SPR, CHR(index));
Machine.Portout8((baseaddr) + ICR, ch)
END WriteICR;
PROCEDURE CheckOX16PCI954(baseaddr: LONGINT): BOOLEAN;
CONST ID1 = 8; ID2 = 9; ID3 = 10; REV = 11;
BEGIN
RETURN (baseaddr >= 1000H) & (ReadICR(baseaddr, ID1) = 016X) & (ReadICR(baseaddr, ID2) = 0C9X) &
(ReadICR(baseaddr, ID3) = 050X) & (ReadICR(baseaddr, REV) = 001X)
END CheckOX16PCI954;
PROCEDURE ShowModule(out : Streams.Writer);
BEGIN
out.String(ModuleName); out.String(": ");
END ShowModule;
PROCEDURE Scan*(context : Commands.Context);
VAR i: LONGINT; port: RS232Port; serialPort : Serials.Port; portstatus: SET; found : BOOLEAN;
PROCEDURE DetectChip(baseaddr: LONGINT);
VAR ch: CHAR;
BEGIN
context.out.String(" Detected UART ");
Machine.Portout8((baseaddr) + FCR, 0C1X);
Machine.Portin8((baseaddr) + IIR, ch);
Machine.Portout8((baseaddr) + FCR, 00X);
CASE ASH(ORD(ch), -6) OF
0: Machine.Portout8((baseaddr) + SCR, 0FAX);
Machine.Portin8((baseaddr) + SCR, ch);
IF ch = 0FAX THEN
Machine.Portout8((baseaddr) + SCR, 0AFX);
Machine.Portin8((baseaddr) + SCR, ch);
IF ch = 0AFX THEN
context.out.String("16450, 8250A")
ELSE
context.out.String("8250, 8250-B, (has flaws)")
END
ELSE
context.out.String("8250, 8250-B, (has flaws)")
END
| 1: context.out.String("Unknown chip")
| 2: context.out.String("16550, non-buffered (has flaws)")
| 3: IF CheckOX16PCI954(baseaddr) THEN
context.out.String("OX16PCI954")
ELSE
context.out.String("16550A, buffer operational")
END
END
END DetectChip;
BEGIN
ShowModule(context.out); context.out.String("Serial port detection and inspection:"); context.out.Ln;
found := FALSE;
FOR i := 1 TO Serials.MaxPorts DO
serialPort := Serials.GetPort(i);
IF (serialPort # NIL) & (serialPort IS RS232Port) THEN
port := serialPort (RS232Port); found := TRUE;
IF port.baseaddr # 0 THEN
context.out.String(port.name); context.out.String(": "); context.out.Hex(port.baseaddr, 10); context.out.Char("H"); context.out.Int(port.irq, 4);
DetectChip(port.baseaddr);
port.GetMC(portstatus);
IF CTS IN portstatus THEN context.out.String(" - CTS signals the presence of a DCE / Modem") END;
context.out.Ln
END
END;
END;
IF ~found THEN context.out.String("No COM port found."); context.out.Ln; END;
END Scan;
PROCEDURE Install*(context : Commands.Context);
VAR i, p : LONGINT; name, s: ARRAY 16 OF CHAR; BASE, IRQ: LONGINT; port : RS232Port;
BEGIN
FOR i := 0 TO MaxPortNo-1 DO
COPY("COM ", name);
name[3] := CHR(ORD("1") + i);
Machine.GetConfig(name, s);
p := 0;
BASE := Machine.StrToInt(p, s);
IF s[p] = "," THEN
INC(p); IRQ := Machine.StrToInt(p, s)
END;
IF (i = 0) & (BASE = 0) THEN BASE := 3F8H; IRQ := 4 END;
IF (i = 1) & (BASE = 0) THEN BASE := 2F8H; IRQ := 3 END;
IF BASE # 0 THEN
NEW(port, BASE, IRQ);
Machine.Portin8((port.baseaddr) + MCR, s[0]);
IF ORD(s[0]) < 32 THEN
Serials.RegisterOnboardPort (i+1, port, name, "Onboard UART");
ShowModule(context.out); context.out.String("Port "); context.out.String(name); context.out.String(" installed."); context.out.Ln;
ELSE
ShowModule(context.out); context.out.String("No UART present at address specified for ");
context.out.String(name);
context.out.Ln
END
END
END;
END Install;
END V24.
V24.Install ~ SystemTools.Free V24 ~
V24.Scan ~
Example Aos.Par information (typical values usually assigned to the 4 first serial ports)
COM1="3F8H,4"
COM2="2F8H,3"
COM3="3E8H,6"
COM4="2E8H,9"
~
In Bluebottle, the generalization of the serial port support lead to the following adjustments:
New low-level module
V24.Mod -> V24.Obx is completely new.
A new object-oriented driver supporting up to 8 serial ports (COM1 .. COM8) at speeds up to
115'200 BPS. No longer compatible with ETH Native Oberon.
The I/O base address and the IRQ corresponding to each COM port must be declared in Aos.Par,
which contains configuration data, except that COM1 and COM2 are declared by default
with their standard values, as used on most machines
COM1="3F8H,4"
COM2="2F8H,3"
These two ports must be declared only in the case that the indicated standard do not apply.
Bluebottle operates in 32-bit addressing mode and it is not possible to interrogate the base address
by accessing the port directly in BIOS.
The port information is registered in the order of appearance in Aos.Par and the ports are:
- named from the user's viewpoint starting from COM1 by name and 1 by number and
- numbered internally starting from 0
The module includes the facilities
- to verify that the ports declared in Aos.Par exist effectively
- to determine the UART chip type used by the ports
- to detect the presence of a modem
- to trace the data stream (in the next update round)
Error detection and handling during the reception have been improved, but the reception is
not error prone anyway.
Very low-level module using a serial port
KernelLog.Mod -> KernelLog.Obx
Offers the possibility of tracing the boot process on another machine connected via a serial port
without the assistance of any other V24 support mentioned in this context.
Like V24.Mod, it collects the base address of the available serial ports from Aos.Par
and the port is selected from this list by reading the TracePort value in Aos.Par
In the original version the port base address was hard-coded in the module.
The module produces only an outgoing data stream.
Modified low-level module
Aos.V24.Mod -> V24.Obx
In the earlier Bluebottle versions, this module offered the low-level serial port support.
It is now an application module exploiting V24.Obx. Consequently, it is much simpler
although it offers all the functionality of its predecessor.
Backward compatibility with the original version is thus provided for client modules.
New developments should avoid using it and make use of the enhanced V24.Obx.