BIOS.V24.Mod 19 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521
  1. MODULE V24; (** AUTHOR "AFI"; PURPOSE "V24/RS-232 driver" *)
  2. (** Supports a maximum of 8 COM serial ports at speeds up to 115'200 BPS.
  3. No longer compatible with ETH Native Oberon.
  4. The I/O base address and the IRQ corresponding to each COM port must be
  5. declared in Aos.Par, except that COM1 and COM2 are declared by default
  6. with their standard values
  7. COM1="3F8H,4"
  8. COM2="2F8H,3"
  9. and must be specified if these values do not apply to a particular machine.
  10. Bluebottle operates in 32-bit addressing mode and cannot interrogate
  11. the base address by accessing the port directly in BIOS.
  12. The ports are numbered in the order of appeareance in Aos.Par, starting from 0
  13. and are named logically starting from COM1.
  14. Includes a facility to determine the UART type and a facility to trace the data.
  15. References:
  16. Serial and UART Tutorial by Frank Durda
  17. "http://freebsd.org/doc/en_US.ISO8859-1/articles/serial-uart"
  18. "http://www.lammertbies.nl/comm/info/RS-232_uart.html"
  19. *
  20. * History:
  21. *
  22. * 14.06.2006 Adapted to changes in Serials.Mod (staubesv)
  23. * 26.06.2006 ClearMC, SetMC & GetMC procedure bodies made exclusive, performance counters implemented (staubesv)
  24. *)
  25. IMPORT SYSTEM, Objects, Machine, Streams, Commands, KernelLog, Serials;
  26. CONST
  27. MaxPortNo = 8; (* Up to 8 serial ports supported *)
  28. BufSize = 1024;
  29. (* Port registers *)
  30. (* RBR = 0; Select with DLAB = 0 - Receive Buffer Register - read only
  31. Select with DLAB = 1 - Baud Rate Divisor LSB *)
  32. IER = 1; (* Select with DLAB = 0 - Interrupt Enable Register - R/W
  33. Select with DLAB = 1 - Baud Rate Divisor MSB *)
  34. IIR = 2; (* Interrupt Identification Register - read only *)
  35. FCR = 2; (* 16550 FIFO Control Register write only *)
  36. LCR = 3; (* Line Control Register - R/W *)
  37. MCR = 4; (* Modem Control Register - R/W *)
  38. LSR = 5; (* Line Status Register - read only*)
  39. MSR = 6; (* Modem Status Register - R/W *)
  40. SCR = 7; (* Scratch Register - R/W *)
  41. (** Modem control lines *)
  42. DTR* = 0; RTS* = 1; (** output *)
  43. Break* = 2; (** input/output - Bit 6 in LCR *)
  44. DSR* = 3; CTS* = 4; RI* = 5; DCD* = 6; (** input *)
  45. ModuleName = "V24";
  46. Verbose = TRUE;
  47. TYPE
  48. RS232Port = OBJECT (Serials.Port);
  49. VAR
  50. baseaddr, irq, maxbps: LONGINT;
  51. buf: ARRAY BufSize OF CHAR;
  52. head, tail: LONGINT;
  53. open, ox16: BOOLEAN;
  54. diagnostic: LONGINT;
  55. PROCEDURE &Init*(basespec, irqspec : LONGINT);
  56. BEGIN
  57. baseaddr := basespec;
  58. irq := irqspec;
  59. open := FALSE; ox16 := CheckOX16PCI954(basespec);
  60. IF ox16 THEN
  61. maxbps := 460800
  62. ELSE
  63. maxbps := 115200
  64. END
  65. END Init;
  66. PROCEDURE Open*(bps, data, parity, stop : LONGINT; VAR res: WORD);
  67. BEGIN {EXCLUSIVE}
  68. IF open THEN
  69. IF Verbose THEN KernelLog.String(ModuleName); KernelLog.String(": "); KernelLog.String(name); KernelLog.String(" already open"); KernelLog.Ln; END;
  70. res := Serials.PortInUse;
  71. RETURN
  72. END;
  73. SetPortState(bps, data, parity, stop, res);
  74. IF res = Serials.Ok THEN
  75. open := TRUE;
  76. head := 0; tail:= 0;
  77. charactersSent := 0; charactersReceived := 0;
  78. (* install interrupt handler *)
  79. Objects.InstallHandler(HandleInterrupt, Machine.IRQ0 + irq);
  80. Machine.Portout8((baseaddr) + IER, 01X); (* Enable receive interrupts *)
  81. IF Verbose THEN KernelLog.String(ModuleName); KernelLog.String(": "); KernelLog.String(name); KernelLog.String(" opened"); KernelLog.Ln END;
  82. END
  83. END Open;
  84. (** Send a single character to the UART. *)
  85. PROCEDURE SendChar*(ch: CHAR; VAR res : WORD);
  86. VAR s: SET;
  87. BEGIN {EXCLUSIVE}
  88. IF ~open THEN res := Serials.Closed; RETURN; END;
  89. res := Serials.Ok;
  90. REPEAT (* wait for room in Transmitter Holding Register *)
  91. Machine.Portin8((baseaddr) + LSR, SYSTEM.VAL(CHAR, s)) (* now send that character *)
  92. UNTIL 5 IN s;
  93. Machine.Portout8((baseaddr), ch);
  94. INC(charactersSent);
  95. END SendChar;
  96. (** Wait for the next character is received in the input buffer. The buffer is fed by HandleInterrupt *)
  97. PROCEDURE ReceiveChar*(VAR ch: CHAR; VAR res: WORD);
  98. BEGIN {EXCLUSIVE}
  99. IF ~open THEN res := Serials.Closed; RETURN END;
  100. AWAIT(tail # head);
  101. IF tail = -1 THEN
  102. res := Serials.Closed;
  103. ELSE
  104. ch := buf[head]; head := (head+1) MOD BufSize;
  105. res := diagnostic;
  106. END
  107. END ReceiveChar;
  108. (** On detecting an interupt request, transfer the characters from the UART buffer to the input buffer *)
  109. PROCEDURE HandleInterrupt;
  110. VAR n: LONGINT; ch: CHAR; s: SET;
  111. BEGIN {EXCLUSIVE}
  112. LOOP (* transfer all the data available in the UART buffer to buf *)
  113. Machine.Portin8((baseaddr) + IIR, ch);
  114. IF ODD(ORD(ch)) THEN EXIT END; (* nothing pending *)
  115. diagnostic := 0;
  116. Machine.Portin8((baseaddr) + LSR, SYSTEM.VAL(CHAR, s)); (* Inspect if error *)
  117. IF (7 IN s) OR (1 IN s) THEN (* Establish a diagnostic of the error *)
  118. IF (1 IN s) THEN diagnostic := Serials.OverrunError;
  119. ELSIF (2 IN s) THEN diagnostic := Serials.ParityError
  120. ELSIF (3 IN s) THEN diagnostic := Serials.FramingError
  121. ELSIF (4 IN s) THEN diagnostic := Serials.BreakInterrupt
  122. END;
  123. END;
  124. Machine.Portin8((baseaddr), ch); (* Receive a character from the UART - baseaddr points to RBR *)
  125. n := (tail+1) MOD BufSize;
  126. IF n # head THEN buf[tail] := ch; tail := n END;
  127. INC(charactersReceived);
  128. END;
  129. END HandleInterrupt;
  130. PROCEDURE Available*(): LONGINT;
  131. BEGIN {EXCLUSIVE}
  132. RETURN (tail - head) MOD BufSize
  133. END Available;
  134. (* Set the port state: speed in bps, no. of data bits, parity, stop bit length. *)
  135. PROCEDURE SetPortState(bps, data, parity, stop : LONGINT; VAR res: WORD);
  136. CONST TCR = 2;
  137. VAR s: SET; tcr: LONGINT;
  138. BEGIN
  139. IF (bps > 0) & (maxbps MOD bps = 0) THEN
  140. IF (data >= 5) & (data <= 8) & (parity >= Serials.ParNo) & (parity <= Serials.ParSpace) &
  141. (stop >= Serials.Stop1) & (stop <= Serials.Stop1dot5) THEN
  142. IF ox16 THEN
  143. IF bps <= 115200 THEN
  144. tcr := 0
  145. ELSE
  146. tcr := 115200*16 DIV bps;
  147. ASSERT((tcr >= 4) & (tcr < 16));
  148. bps := 115200
  149. END;
  150. IF ReadICR(baseaddr, TCR) # CHR(tcr) THEN
  151. WriteICR(baseaddr, TCR, CHR(tcr))
  152. END
  153. END;
  154. bps := 115200 DIV bps;
  155. (* disable interrupts *)
  156. Machine.Portout8((baseaddr)+LCR, 0X); (* clear DLAB *)
  157. Machine.Portout8((baseaddr)+IER, 0X); (* Disable all interrupts *)
  158. (* clear latches *)
  159. Machine.Portin8((baseaddr)+LSR, SYSTEM.VAL(CHAR, s));
  160. Machine.Portin8((baseaddr)+IIR, SYSTEM.VAL(CHAR, s));
  161. Machine.Portin8((baseaddr)+MSR, SYSTEM.VAL(CHAR, s));
  162. Machine.Portout8((baseaddr)+FCR, 0C1X); (* See if one can activate the FIFO *)
  163. Machine.Portin8((baseaddr)+IIR, SYSTEM.VAL(CHAR, s)); (* Read how the chip responded in bits 6 & 7 of IIR *)
  164. IF s * {6,7} = {6,7} THEN (* FIFO enabled on 16550 chip and later ones *)
  165. Machine.Portout8((baseaddr) + FCR, 47X) (* 16550 setup: EnableFifo, CLRRX, CLRTX, SIZE4 *)
  166. ELSIF s * {6,7} = {} THEN (* Bits 6 and 7 are always zero on 8250 / 16450 chip *)
  167. Machine.Portout8((baseaddr) + FCR, 0X)
  168. ELSE KernelLog.String("Not prepared to deal with this COM port situation"); (* This case should not exist *)
  169. END;
  170. (* set parameters *)
  171. Machine.Portout8((baseaddr) + LCR, 80X); (* Set the Divisor Latch Bit - DLAB = 1 *)
  172. Machine.Portout8((baseaddr), CHR(bps)); (* Set the Divisor Latch LSB *)
  173. Machine.Portout8((baseaddr)+1, CHR(bps DIV 100H)); (* Set the Divisor Latch MSB *)
  174. (* Prepare parameters destined to LCR data, stop, parity *)
  175. CASE data OF (* word length *)
  176. 5: s := {}
  177. | 6: s := {0}
  178. | 7: s := {1}
  179. | 8: s := {0,1}
  180. END;
  181. IF stop # Serials.Stop1 THEN INCL(s, 2) END;
  182. CASE parity OF
  183. Serials.ParNo:
  184. | Serials.ParOdd: INCL(s, 3)
  185. | Serials.ParEven: s := s + {3,4}
  186. | Serials.ParMark: s := s + {3,5}
  187. | Serials.ParSpace: s := s + {3..5}
  188. END;
  189. (* Finalize the LCR *)
  190. Machine.Portout8((baseaddr)+LCR, SYSTEM.VAL(CHAR, s)); (* DLAB is set = 0 at the same time *)
  191. (* Set DTR, RTS, OUT2 in the MCR *)
  192. Machine.Portout8((baseaddr)+MCR, SYSTEM.VAL(CHAR, {DTR,RTS,3}));
  193. (* Machine.Portout8((baseaddr)+IER, 01X); *)
  194. res := Serials.Ok
  195. ELSE res := Serials.WrongData (* bad data/parity/stop *)
  196. END
  197. ELSE res := Serials.WrongBPS (* bad BPS *)
  198. END
  199. END SetPortState;
  200. (** Get the port state: state (open/closed), speed in bps, no. of data bits, parity, top bit length. *)
  201. PROCEDURE GetPortState*(VAR openstat : BOOLEAN; VAR bps, data, parity, stop : LONGINT);
  202. CONST TCR = 2;
  203. VAR savset, set: SET; ch: CHAR;
  204. BEGIN {EXCLUSIVE}
  205. (* get parameters *)
  206. openstat := open;
  207. Machine.Portin8((baseaddr) + LCR, SYSTEM.VAL(CHAR, savset));
  208. set := savset + {7};
  209. Machine.Portout8((baseaddr) + LCR, SYSTEM.VAL(CHAR, set)); (* INCL the Divisor Latch Bit - DLAB = 1 *)
  210. Machine.Portin8((baseaddr)+1, ch);
  211. bps := ORD(ch);
  212. Machine.Portin8((baseaddr), ch);
  213. IF (bps = 0 ) & (ch = 0X) THEN
  214. ELSE
  215. bps := 115200 DIV (100H*bps + ORD(ch))
  216. END;
  217. IF ox16 THEN
  218. ch := ReadICR(baseaddr, TCR);
  219. IF (ch >= 04X) & (ch < 16X) THEN
  220. bps := bps*16 DIV ORD(ch)
  221. END
  222. END;
  223. Machine.Portout8((baseaddr)+LCR, SYSTEM.VAL(CHAR, savset)); (* Reset the Divisor Latch Bit - DLAB = 0 *)
  224. Machine.Portin8((baseaddr)+LCR, SYSTEM.VAL(CHAR, set));
  225. IF set * {0, 1} = {0, 1} THEN data := 8
  226. ELSIF set * {0, 1} = {1} THEN data := 7
  227. ELSIF set * {0, 1} = {0} THEN data := 6
  228. ELSE data := 5
  229. END;
  230. IF 2 IN set THEN
  231. IF set * {0, 1} = {} THEN stop := 3
  232. ELSE stop := 2
  233. END;
  234. ELSE stop := 1
  235. END;
  236. IF set * {3..5} = {3..5} THEN parity := 4
  237. ELSIF set * {3,5} = {3,5} THEN parity := 3
  238. ELSIF set * {3,4} = {3,4} THEN parity := 2
  239. ELSIF set * {3} = {3} THEN parity := 1
  240. ELSE parity := 0
  241. END;
  242. END GetPortState;
  243. (** Clear the specified modem control lines. s may contain DTR, RTS & Break. *)
  244. PROCEDURE ClearMC*(s: SET);
  245. VAR t: SET;
  246. BEGIN {EXCLUSIVE}
  247. IF s * {DTR, RTS} # {} THEN
  248. Machine.Portin8((baseaddr) + MCR, SYSTEM.VAL(CHAR, t));
  249. t := t - (s * {DTR, RTS}); (* modify only bits 0 & 1 *)
  250. Machine.Portout8((baseaddr) + MCR, SYSTEM.VAL(CHAR, t))
  251. END;
  252. IF Break IN s THEN
  253. Machine.Portin8((baseaddr) + LCR, SYSTEM.VAL(CHAR, t));
  254. EXCL(t, 6); (* break off *)
  255. Machine.Portout8((baseaddr) + LCR, SYSTEM.VAL(CHAR, t))
  256. END
  257. END ClearMC;
  258. (** Set the specified modem control lines. s may contain DTR, RTS & Break. *)
  259. PROCEDURE SetMC*(s: SET);
  260. VAR t: SET;
  261. BEGIN {EXCLUSIVE}
  262. IF s * {DTR, RTS} # {} THEN
  263. Machine.Portin8((baseaddr) + MCR, SYSTEM.VAL(CHAR, t));
  264. t := t + (s * {DTR, RTS}); (* modify only bits 0 & 1 *)
  265. Machine.Portout8((baseaddr) + MCR, SYSTEM.VAL(CHAR, t))
  266. END;
  267. IF Break IN s THEN
  268. Machine.Portin8((baseaddr) + LCR, SYSTEM.VAL(CHAR, t));
  269. INCL(t, 6); (* break on *)
  270. Machine.Portout8((baseaddr) + LCR, SYSTEM.VAL(CHAR, t))
  271. END
  272. END SetMC;
  273. (** Return the state of the specified modem control lines. s contains the current state of DSR, CTS, RI, DCD & Break Interrupt. *)
  274. PROCEDURE GetMC*(VAR s: SET);
  275. VAR t: SET;
  276. BEGIN {EXCLUSIVE}
  277. s := {};
  278. Machine.Portin8((baseaddr) + MSR, SYSTEM.VAL(CHAR, t)); (* note: this clears bits 0-3 *)
  279. IF 4 IN t THEN INCL(s, CTS) END;
  280. IF 5 IN t THEN INCL(s, DSR) END;
  281. IF 6 IN t THEN INCL(s, RI) END;
  282. IF 7 IN t THEN INCL(s, DCD) END;
  283. Machine.Portin8((baseaddr) + LSR, SYSTEM.VAL(CHAR, t)); (* note: this clears bits 1-4 *)
  284. IF 4 IN t THEN INCL(s, Break) END
  285. END GetMC;
  286. PROCEDURE Close*;
  287. VAR s: SET;
  288. BEGIN {EXCLUSIVE}
  289. IF ~open THEN
  290. IF Verbose THEN KernelLog.String(ModuleName); KernelLog.String(": "); KernelLog.String(name); KernelLog.String(" not open"); KernelLog.Ln; END;
  291. RETURN
  292. END;
  293. REPEAT (* wait for last byte to leave *)
  294. Machine.Portin8((baseaddr)+LSR, SYSTEM.VAL(CHAR, s))
  295. UNTIL 6 IN s; (* No remaining word in the FIFO or transmit shift register *)
  296. tail := -1; (* Force a pending Receive to terminate in error. *)
  297. (* disable interrupts *)
  298. Machine.Portout8((baseaddr) + IER, 0X);
  299. (* remove interrupt handler *)
  300. Objects.RemoveHandler(HandleInterrupt, Machine.IRQ0 + irq);
  301. open := FALSE;
  302. IF Verbose THEN KernelLog.String(ModuleName); KernelLog.String(": "); KernelLog.String(name); KernelLog.String(" closed"); KernelLog.Ln; END;
  303. END Close;
  304. END RS232Port;
  305. PROCEDURE ReadICR(baseaddr, index: LONGINT): CHAR;
  306. CONST SPR = 7; ICR = 5; ICREnable = 6;
  307. VAR ch: CHAR;
  308. BEGIN
  309. Machine.Portout8((baseaddr) + SPR, 0X);
  310. Machine.Portout8((baseaddr) + ICR, SYSTEM.VAL(CHAR, {ICREnable}));
  311. Machine.Portout8((baseaddr) + SPR, CHR(index));
  312. Machine.Portin8((baseaddr) + ICR, ch);
  313. Machine.Portout8((baseaddr) + SPR, 0X);
  314. Machine.Portout8((baseaddr) + ICR, 0X);
  315. RETURN ch
  316. END ReadICR;
  317. PROCEDURE WriteICR(baseaddr, index: LONGINT; ch: CHAR);
  318. CONST SPR = 7; ICR = 5;
  319. BEGIN
  320. Machine.Portout8((baseaddr) + SPR, CHR(index));
  321. Machine.Portout8((baseaddr) + ICR, ch)
  322. END WriteICR;
  323. PROCEDURE CheckOX16PCI954(baseaddr: LONGINT): BOOLEAN;
  324. CONST ID1 = 8; ID2 = 9; ID3 = 10; REV = 11;
  325. BEGIN
  326. RETURN (baseaddr >= 1000H) & (ReadICR(baseaddr, ID1) = 016X) & (ReadICR(baseaddr, ID2) = 0C9X) &
  327. (ReadICR(baseaddr, ID3) = 050X) & (ReadICR(baseaddr, REV) = 001X)
  328. END CheckOX16PCI954;
  329. PROCEDURE ShowModule(out : Streams.Writer);
  330. BEGIN
  331. out.String(ModuleName); out.String(": ");
  332. END ShowModule;
  333. (** Scan the installed serial ports and determine the chip type used *)
  334. PROCEDURE Scan*(context : Commands.Context);
  335. VAR i: LONGINT; port: RS232Port; serialPort : Serials.Port; portstatus: SET; found : BOOLEAN;
  336. PROCEDURE DetectChip(baseaddr: LONGINT);
  337. VAR ch: CHAR;
  338. BEGIN
  339. context.out.String(" Detected UART ");
  340. Machine.Portout8((baseaddr) + FCR, 0C1X); (* See if one can activate the FIFO *)
  341. Machine.Portin8((baseaddr) + IIR, ch); (* Read how the chip responded in the 2 most significant bits of IIR *)
  342. Machine.Portout8((baseaddr) + FCR, 00X); (* Deactivate the FIFO *)
  343. CASE ASH(ORD(ch), -6) OF
  344. 0: Machine.Portout8((baseaddr) + SCR, 0FAX); (* See if one can write in the SCR *)
  345. Machine.Portin8((baseaddr) + SCR, ch);
  346. IF ch = 0FAX THEN
  347. Machine.Portout8((baseaddr) + SCR, 0AFX);
  348. Machine.Portin8((baseaddr) + SCR, ch);
  349. IF ch = 0AFX THEN
  350. context.out.String("16450, 8250A")
  351. ELSE
  352. context.out.String("8250, 8250-B, (has flaws)")
  353. END
  354. ELSE (* No SCR present *)
  355. context.out.String("8250, 8250-B, (has flaws)")
  356. END
  357. | 1: context.out.String("Unknown chip")
  358. | 2: context.out.String("16550, non-buffered (has flaws)")
  359. | 3: IF CheckOX16PCI954(baseaddr) THEN
  360. context.out.String("OX16PCI954")
  361. ELSE
  362. context.out.String("16550A, buffer operational")
  363. END
  364. END
  365. END DetectChip;
  366. BEGIN
  367. ShowModule(context.out); context.out.String("Serial port detection and inspection:"); context.out.Ln;
  368. found := FALSE;
  369. FOR i := 1 TO Serials.MaxPorts DO
  370. serialPort := Serials.GetPort(i);
  371. IF (serialPort # NIL) & (serialPort IS RS232Port) THEN
  372. port := serialPort (RS232Port); found := TRUE;
  373. IF port.baseaddr # 0 THEN (* Port has a valid base address *)
  374. context.out.String(port.name); context.out.String(": "); context.out.Hex(port.baseaddr, 10); context.out.Char("H"); context.out.Int(port.irq, 4);
  375. DetectChip(port.baseaddr);
  376. port.GetMC(portstatus);
  377. IF CTS IN portstatus THEN context.out.String(" - CTS signals the presence of a DCE / Modem") END;
  378. context.out.Ln
  379. END
  380. END;
  381. END;
  382. IF ~found THEN context.out.String("No COM port found."); context.out.Ln; END;
  383. END Scan;
  384. (** Set the essential port operating parameters as specified in Aos.Par
  385. If omitted, default standard values are assigned to COM1 and COM2 *)
  386. PROCEDURE Install*(context : Commands.Context);
  387. VAR i, p : LONGINT; name, s: ARRAY 16 OF CHAR; BASE, IRQ: LONGINT; port : RS232Port;
  388. BEGIN
  389. FOR i := 0 TO MaxPortNo-1 DO
  390. COPY("COM ", name);
  391. name[3] := CHR(ORD("1") + i);
  392. Machine.GetConfig(name, s);
  393. p := 0;
  394. BASE := Machine.StrToInt(p, s);
  395. IF s[p] = "," THEN
  396. INC(p); IRQ := Machine.StrToInt(p, s)
  397. END;
  398. IF (i = 0) & (BASE = 0) THEN BASE := 3F8H; IRQ := 4 END; (* COM1 port default values *)
  399. IF (i = 1) & (BASE = 0) THEN BASE := 2F8H; IRQ := 3 END; (* COM2 port default values *)
  400. IF BASE # 0 THEN
  401. NEW(port, BASE, IRQ);
  402. (* Check the presence of a UART at the specified base address *)
  403. Machine.Portin8((port.baseaddr) + MCR, s[0]);
  404. IF ORD(s[0]) < 32 THEN (* Bits 7..5 of the MCR are always 0 when a UART is present *)
  405. (* Register this RS232Port with an identical index in Serials.registeredSerials array *)
  406. Serials.RegisterOnboardPort (i+1, port, name, "Onboard UART");
  407. IF context # NIL THEN
  408. ShowModule(context.out); context.out.String("Port "); context.out.String(name); context.out.String(" installed."); context.out.Ln;
  409. END;
  410. ELSE
  411. IF context # NIL THEN
  412. ShowModule(context.out); context.out.String("No UART present at address specified for ");
  413. context.out.String(name);
  414. context.out.Ln
  415. END;
  416. END
  417. END
  418. END;
  419. END Install;
  420. PROCEDURE Init*; (* compatibility with windows ... *)
  421. BEGIN
  422. END Init;
  423. END V24.
  424. V24.Install ~ SystemTools.Free V24 ~
  425. V24.Scan ~
  426. Example Aos.Par information (typical values usually assigned to the 4 first serial ports)
  427. COM1="3F8H,4"
  428. COM2="2F8H,3"
  429. COM3="3E8H,6"
  430. COM4="2E8H,9"
  431. ~
  432. In Bluebottle, the generalization of the serial port support lead to the following adjustments:
  433. New low-level module
  434. V24.Mod -> V24.Obx is completely new.
  435. A new object-oriented driver supporting up to 8 serial ports (COM1 .. COM8) at speeds up to
  436. 115'200 BPS. No longer compatible with ETH Native Oberon.
  437. The I/O base address and the IRQ corresponding to each COM port must be declared in Aos.Par,
  438. which contains configuration data, except that COM1 and COM2 are declared by default
  439. with their standard values, as used on most machines
  440. COM1="3F8H,4"
  441. COM2="2F8H,3"
  442. These two ports must be declared only in the case that the indicated standard do not apply.
  443. Bluebottle operates in 32-bit addressing mode and it is not possible to interrogate the base address
  444. by accessing the port directly in BIOS.
  445. The port information is registered in the order of appearance in Aos.Par and the ports are:
  446. - named from the user's viewpoint starting from COM1 by name and 1 by number and
  447. - numbered internally starting from 0
  448. The module includes the facilities
  449. - to verify that the ports declared in Aos.Par exist effectively
  450. - to determine the UART chip type used by the ports
  451. - to detect the presence of a modem
  452. - to trace the data stream (in the next update round)
  453. Error detection and handling during the reception have been improved, but the reception is
  454. not error prone anyway.
  455. Very low-level module using a serial port
  456. KernelLog.Mod -> KernelLog.Obx
  457. Offers the possibility of tracing the boot process on another machine connected via a serial port
  458. without the assistance of any other V24 support mentioned in this context.
  459. Like V24.Mod, it collects the base address of the available serial ports from Aos.Par
  460. and the port is selected from this list by reading the TracePort value in Aos.Par
  461. In the original version the port base address was hard-coded in the module.
  462. The module produces only an outgoing data stream.
  463. Modified low-level module
  464. Aos.V24.Mod -> V24.Obx
  465. In the earlier Bluebottle versions, this module offered the low-level serial port support.
  466. It is now an application module exploiting V24.Obx. Consequently, it is much simpler
  467. although it offers all the functionality of its predecessor.
  468. Backward compatibility with the original version is thus provided for client modules.
  469. New developments should avoid using it and make use of the enhanced V24.Obx.