[comp.sys.ibm.pc] PS/2 COM Port Questions?

clw@hprnd.HP.COM (Carl Wuebker) (02/06/89)

     I wrote a (stupid) terminal emulator program in Turbo Pascal 3.0.  To make
sure that I caught all the characters, I coded a Turbo Pascal ISR for the UART
receive side. It worked pretty well on the IBM-PC.  Here's what's happening
when I try to run it on a PS/2:

     * The main program uses calls 35 and 25 to save the values for the 
          existing COM port 2 ISR.
     * The interrupts are disabled briefly (CLI) then re-enabled (STI).
     * A character is written to the modem.
     * The ISR gets called, saves registers, gets the character (or characters)
          from the UART and stuffs the character in the FIFO.
     * The ISR does an EOI (Port[$20]=$20), restores registers, and IRETs.
     * The program prints a character on the screen.
     * Either the 2nd character never gets sent to the com port (com port not
          ready), the ISR never gets called for the echoed character, or the
          ISR gets called but doesn't return.

     I realize that this isn't a lot to go on; but does anyone have any clues
as to what might be causing problems on the PS/2?

Thanks,
   Carl "upgrade, (n), spend 2 months running in place" Wuebker
   clw@hprnd * HP Roseville Networks Division * (916) 785-4296

clw@hprnd.HP.COM (Carl Wuebker) (02/10/89)

     I've received two responses to this question, one asking me to post the 
source of the program and one telling me that, while the IBM PC had edge-
sensitive interrupts, the PS/2 has level sensitive interrupts.  The second
response asked me if I read the status register to clear the interrupts.
(Yes, see PROCEDURE isr, below).  Thanks to both responders (our mailers
couldn't get mail to the second responder.

     FYI, here is the source of the terminal emulator/stock info getter.  If
you modify the program to include your phone numbers/ids, and start the 
program with the line:

     STERM <password> <stock input file> <stock output file>

the thing will dial up The Source, get into stock mode and pick up stock
prices.  The stock info will be put into the stock output file, which is
suitable for loading into a spreadsheet.  If you type a character (a space
will do) after the program types ATZ, it skips the standard procedure and
turns into a terminal emulator.  I've used it successfully with Turbo Pascal
3.0 and a standard IBM PC with a RS232 card/Hayes compatable modem on Com
Port 1.  My friend cannot use it with Turbo 3.0, a standard IBM PS/2 and a
RS232 card/Hayes compatable modem on Com Port 2.  Any suggestions or fixes
would really be appreciated!!

Thanks,
   Carl Wuebker * clw@hprnd * HP Roseville Networks Division * (916) 785-4296

--- cut here

{$C-}
PROGRAM sterm;

CONST
     ds: INTEGER = 0;
   maxc = 255;
     cr = #13;
     lf = #10;
  cport = 1;       { COM port = 1 or 2 }
  timeo = 3000;    { aprox. # of ms to wait for terminal quiet }

TYPE
     str255 = STRING[255];
   pstklist = ^stklist;
    stklist = PACKED RECORD
                 nex: pstklist;
                  ss: str255;
              END;
      queue = PACKED RECORD
                 getp,putp: INTEGER;
                 curc,hi_c: INTEGER;
                       buf: PACKED ARRAY[1..maxc] OF CHAR
              END;
      cap_s = PACKED ARRAY[-32767..32767] OF CHAR;
      cap_t = ^cap_s;

VAR
              pbas: INTEGER;
                 c: CHAR;
     i,j,isro,isrs: INTEGER;
                rg: RECORD AX,BX,CX,DX,BP,SI,DI,DS,ES,Flags: INTEGER END;
             tq,rq: queue;
           running: BOOLEAN;
             cap_b: cap_t;
             cap_p: INTEGER;
             cap_r: BOOLEAN;
                ff: STRING[80];
              lctl: INTEGER;
              crlf: STRING[2];
   rx_time,rx_nchr: INTEGER;
             hs,ps: pstklist;
            stkstr: str255;

             fi,fo: TEXT;

PROCEDURE getq(VAR q: queue; VAR c: CHAR);
{ get a character from a queue }

BEGIN
WITH q DO
   IF (curc<=0) THEN
      { no characters left }
      c := #0
   ELSE
      BEGIN
      c := buf[getp];
      curc := curc-1;
      getp := getp+1;
      IF (getp>maxc) THEN
         getp := 1;
      END;
END;

PROCEDURE putq(VAR q: queue; c: CHAR);
{ put a character into a queue }

BEGIN
WITH q DO
   IF (curc<maxc) THEN
      BEGIN
      { queue space available }
      buf[putp] := c;
      curc := curc+1;
      IF (curc>hi_c) THEN
         hi_c := curc;
      putp := putp+1;
      IF (putp>maxc) THEN
         putp := 1;
      END;
END;

PROCEDURE isr;

BEGIN
inline(
   $50/$53/$51/$52/$56/$57/$1E/$06/  { PUSH AX,BX,CX,DX,SI,DI,DS,ES }
   $2E/$8E/$1E/ds);                  { MOV DS,CS[ds] }

WHILE (Port[pbas+$A]=4) DO           { 0?,1 or 2 characters here }
   putq(rq,CHAR(Port[pbas+$8]));

Port[$20] := $20;                    { EOI }

inline(
   $07/$1F/$5F/$5E/$5A/$59/$5B/$58/  { POP ES,DS,DI,SI,DX,CX,BX,AX }
   $8B/$E5/$5D/$CF);                 { MOV SP,BP / POP BP / IRET }
END;

PROCEDURE subs(pat,repl: str255; VAR source: str255);

VAR sp: INTEGER;

BEGIN
sp := POS(pat,source);
WHILE (sp>0) DO
   BEGIN
   Delete(source,sp,Length(pat));
   Insert(repl,source,sp);
   sp := POS(pat,source)
   END;
END;

PROCEDURE r2s;

VAR
         rc: INTEGER;
         rx: CHAR;
   cap_char: BOOLEAN;

BEGIN
{ Receiver -> Screen & possibly Capture Buffer }
IF (rq.curc>0) THEN
   BEGIN
   { Rx char received => zero Rx timeout, inc Rx character count }
   rx_time := 0;
   IF (rx_nchr<32767) THEN
      rx_nchr := rx_nchr+1;
   { get Rx character }
   inline($FA); getq(rq,rx); inline($FB);
   rc := INTEGER(rx) AND $7F; rx := CHAR(rc);
   { Rx character -> Screen }
   cap_char := TRUE;
   CASE rc OF
                  10: WRITELN;
      8,9,13,32..127: WRITE(rx);
                 ELSE cap_char := FALSE;
   END;
   IF (rc=17) THEN
      WRITE(' *D1* ');
   { Rx character -> Capture Buffer }
   IF cap_char AND cap_r AND (cap_p<32767) THEN
      BEGIN
      cap_b^[cap_p] := rx;
      cap_p := cap_p+1
      END;
   END
ELSE
   { No Rx char => Increment Rx timeout }
   IF (rx_time<32767) THEN
      rx_time := rx_time+1;
END;

PROCEDURE k2x;

BEGIN
{ Keyboard | Xmit Queue -> Transmitter }
IF ODD(Port[pbas+$D] SHR 5) THEN
   IF Keypressed THEN
      BEGIN
      READ(KBD,c);
      IF ((c=#27) AND KeyPressed) THEN
         BEGIN
         READ(KBD,c);
         CASE ORD(c) OF
            62: { F4 };
            71: { Home }
                GOTOXY(1,1);
            73: { PgUp }
                ClrScr;
            79: { End }
                running := FALSE;
            83: BEGIN
                { Break }
                Port[pbas+$B] := Port[pbas+$B] OR $40;
                Delay(100);
                Port[pbas+$B] := Port[pbas+$B] AND $BF
                END
           ELSE
         END;
         END
      ELSE
         Port[pbas+$8] := ORD(c);
      END;
END;

PROCEDURE write_(s: str255);

VAR cp: INTEGER;

BEGIN
cp := 1;
WHILE running AND (NOT Keypressed) AND (cp<=Length(s)) DO
   IF ODD(Port[pbas+$D] SHR 5) THEN
      BEGIN
      { Tx ready; send out character }
      Port[pbas+$8] := ORD(s[cp]);
      cp := cp+1;
      END
   ELSE
      r2s;
END;

PROCEDURE wai(tim: INTEGER);

BEGIN
WHILE running AND (NOT Keypressed) AND (rx_time<tim) DO
   BEGIN
   r2s;
   Delay(1)
   END;
END;

PROCEDURE write_2(s: str255; tim: INTEGER);
{ Write, then wait for characters to stop coming back }

BEGIN
write_(s);
wai(tim);
END;

PROCEDURE write_1(s: str255; nchr,tim: INTEGER);
{ Write, then wait for characters to start coming back, then wait for characters
  to stop coming back }

BEGIN
write_(s);
rx_nchr := 0;
WHILE running AND (NOT Keypressed) AND (rx_nchr<nchr) DO
   r2s;
wai(tim);
END;

{ Main }
BEGIN
IF (ParamCount<>3) THEN
   BEGIN
   WRITELN('Usage: STERM <PASSWORD> <STOCK NAME FILE> <OUTPUT FILE>');
   HALT;
   END;

ff := ParamStr(2);
ASSIGN(fi,ff);
RESET(fi);
hs := NIL;
ps := NIL;
WHILE NOT EOF(fi) DO
   BEGIN
   READLN(fi,ff);
   WHILE POS(' ',ff)>0 DO
      Delete(ff,POS(' ',ff),1);
   IF (Length(ff)>0) THEN
      BEGIN
      IF (hs=NIL) THEN
         BEGIN
         NEW(hs);
         ps := hs;
         ps^.nex := NIL;
         ps^.ss := '';
         END;
      IF (Length(ps^.ss)+Length(ff)>76) THEN
         BEGIN
         NEW(ps^.nex);
         ps := ps^.nex;
         ps^.nex := NIL;
         ps^.ss := '';
         END;
      IF (Length(ps^.ss)>0) THEN
         ps^.ss := ps^.ss+' ';
      ps^.ss := ps^.ss+ff
      END;
   END;
CLOSE(fi);

IF cport = 1 THEN
   pbas := $3F0
ELSE
   pbas := $2F0;

crlf := #13+#10;

rq.getp := 1;                { initialize receive queue }
rq.putp := 1;
rq.curc := 0;
rq.hi_c := 0;

rx_time := 0;                { initialize Rx activity info }
rx_nchr := 0;

NEW(cap_b);                  { allocate capture buffer }
cap_p := -32767;
cap_r := FALSE;

ds := Dseg;                  { save DS for ISR communications }

rg.AX := $350D-cport;        { save existing ISR data (1->C,2->B) }
INTR($21,rg);
isrs := rg.ES; isro := rg.BX;
rg.AX := $250D-cport;        { set our ISR }
rg.DS := Cseg; rg.DX := Ofs(isr);
INTR($21,rg);

inline($FA);                 { disable interrupts }

{ Set up RS232 chip }
lctl := 30;                  {  3 => 8 bits, 1 stop bit, no parity }
                             { 30 => 7 bits, 2 stop bits, even parity }
Port[pbas+$9] := 0;          { disable chip interrupts }
Port[pbas+$C] := 3;          { set DTR, RTS; clear chip interrupt path }
Port[pbas+$B] := $80;        { access divisor latch }
Port[pbas+$9] := 0;          { div 300 -   1  1200 -  0 }
Port[pbas+$8] := 96;         { div 300 - 128  1200 - 96 }
Port[pbas+$B] := lctl;       { bits, stop bit(s) & parity }
i := Port[pbas+$8];          { clear out garbage }
Port[pbas+$9] := 1;          { enable receiver interrupts }
Port[pbas+$C] := 11;

IF cport = 1 THEN
   Port[$21] := Port[$21] AND $EF
ELSE
   Port[$21] := Port[$21] AND $F7;

inline($FB);                 { enable interrupts }

running := TRUE;

write_2('ATZ'+cr,timeo);
write_1('ATZ'+cr,2,timeo);
write_1('ATDTnnnnnnn'+cr ,4,timeo);        { replace w/your phone number }
{ Telenet Sign-On Procedure }
Delay(500); write_(cr);
Delay(500); write_1(cr,2,timeo);
write_1('D1'+cr,2,timeo);
write_1('C XXXXX'+cr,8,timeo);             { replace with your C # }
write_1('ID XXXXXX'+cr,8,timeo);           { replace with your ID # }
write_1(ParamStr(1)+cr,4,timeo);
write_1('Q'+cr,3,timeo);
write_1('STOCKCHECK 1'+cr,25,timeo);
cap_r := TRUE;
ps := hs;
WHILE (ps<>NIL) DO
   BEGIN
   write_1(ps^.ss+cr,25,timeo);
   ps := ps^.nex
   END;
cap_r := FALSE;
write_1(cr,25,timeo);
write_1('Q'+cr,3,timeo);
write_1('OFF'+cr,10,timeo);
Delay(1500);
write_('+++');
Delay(1500);
write_1('ATH'+cr,2,timeo);

{ Terminal Emulation Loop }
IF Keypressed THEN
   WHILE running DO
      BEGIN
      r2s;
      k2x
      END;

{ Restore original ISR }
rg.AX := $250D-cport;        { restore original ISR (1->C,2->B) }
rg.DS := isrs; rg.DX := isro;
INTR($21,rg);

inline($FA);                 { disable interrupts }
IF cport = 1 THEN
   Port[$21] := Port[$21] OR $10
ELSE
   Port[$21] := Port[$21] OR $08;
inline($FB);                 { enable interrupts }

{ Save capture buffer if applicable }
IF (cap_p>-32767) THEN
   BEGIN
   ff := ParamStr(3);
   ASSIGN(fo,ff);
   REWRITE(fo);
   i := -32767;
   WHILE (i<cap_p) DO
      BEGIN
      { Scan for LF }
      WHILE (i<cap_p) AND (cap_b^[i]<>#10) DO
         i := i+1;
      { Inspect char after LF }
      i := i+1;
      IF (i<cap_p) AND (cap_b^[i] IN ['0','1']) THEN
         BEGIN
         { Copy line to string }
         stkstr := '';
         WHILE (i<cap_p) AND (cap_b^[i]<>#13) DO
            BEGIN
            stkstr := stkstr+cap_b^[i];
            i := i+1
            END;
         { Edit string }
         stkstr := stkstr+' ';            { handle fraction at end of line }
         subs(' .. ',' 0 ',stkstr);       { strange notation for no change }
         subs(' 1/8 ','.125 ',stkstr);    { cvt stock fractions to decimal }
         subs(' 1/4 ','.25 ' ,stkstr);
         subs(' 3/8 ','.375 ',stkstr);
         subs(' 1/2 ','.5 '  ,stkstr);
         subs(' 5/8 ','.625 ',stkstr);
         subs(' 3/4 ','.75  ',stkstr);
         subs(' 7/8 ','.875 ',stkstr);
         { Edit string; quote 1st 3 fields (right to left preserves char #) }
         j := 13;
         WHILE (j<=Length(stkstr)) AND (stkstr[j]<>' ') DO
            j := j+1;
         Insert('"',stkstr,j);
         Insert('"',stkstr,13);
         Insert('"',stkstr,12);
         Insert('"',stkstr, 7);
         Insert('"',stkstr, 6);
         Insert('"',stkstr, 1);
         { trim rightmost blanks, delete extraneous blanks & emit string }
         WHILE (stkstr[Length(stkstr)]=' ') DO
            Delete(stkstr,Length(stkstr),1);
         subs('  ',' ',stkstr);
         WRITELN(fo,stkstr);
         END;
      END;
   CLOSE(fo);
   cap_p := -32767;
   END;

{ Report buffer fullness }
WRITELN;
WRITELN('Receive Buffer Utilization (Max): ',rq.hi_c)
END.