;***************************************************************************;
;                                                                           ;
;                    New York Alpha Micro Users Society                     ;
;                     AMOS/L Telecommunications Utility                     ;
;                           By David F. Pallmann                            ;
;                                                                           ;
;***************************************************************************;
;
; File uses universal (.UNV) files other
; than SYS, SYSSYM, and TRM.
; These are on the AMUS network

       OBJNAM  TELCOM.LIT

       MAYCREF
       SEARCH  SYS
       SEARCH  SYSSYM
       SEARCH  TRM
       SEARCH  STRUCT
       CREF

;edit history

       VMAJOR=2
       VMINOR=2
       VWHO=0
       VSUB=0
       VEDIT=100.                      ;03-May-83 DFP creation
       VEDIT=101.                      ;06-May-83 DFP add code for V2.1
       VEDIT=102.                      ;09-May-83 DFP add parity option
       VEDIT=103.                      ;09-May-83 DFP check for attached terminal
       VEDIT=104.                      ;30-May-83 DFP add no-LF option
       VEDIT=105.                      ;18-Jun-84 CF mask command line parity
;registers

       MEM=A1                          ;buffer index
       MAX=A2                          ;buffer end
       TRM=A3                          ;terminal definition area index
       REM=A4                          ;remote terminal definition area index
       IMP=A5                          ;impure area base register
       EXT=D4                          ;exit character
       AMT=D5                          ;amount of characters in buffer

;equates

       Z=4                             ;PSW Z-bit
       N=10                            ;PSW N-bit
       LF=12                           ;ASCII line feed
       CR=15                           ;ASCII carriage return

;impure area

OFINI
OFDEF  REMDDB,D.DDB                    ;DDB for remote terminal I/O
OFDEF  DSKDDB,D.DDB                    ;DDB for disk I/O
OFDEF  FLAGS,2                         ;flags--.
       F.OPN=1                         ; disk DDB is open
       F.SUS=2                         ; communications suspended
       F.HDX=4                         ; half-duplex mode
       F.SIL=10                        ; silent mode
       F.RP1=20                        ; receive parity 1
       F.SP1=40                        ; send parity 1
       F.REM=100                       ; remote terminal has been attached
       F.NLF=200                       ; don't send LFs
OFSIZ  IMPSIZ

       PAGE
;************
;*          *
;*  INITIA  *
;*          *
;************

INITIA: PHDR    -1,0,PH$REE!PH$REU      ;program header
       GETIMP  IMPSIZ,IMP,EXIT         ;allocate local memory (exit on error)
       TYPESP  TELCOM
       LEA     A0,INITIA+2
       VCVT    @A0,OT$TRM              ;display version number
       CRLF                            ;newline

;get remote terminal name

GETREM: BYP
       TRM                             ;argument on cmd line?
       BNE     10$                     ; yes
       CRLF                            ; no
       TYPESP  Enter name of remote terminal:
       KBD     EXIT
10$:    FILNAM  REMDDB+D.FIL(IMP),XXX   ;get remote terminal name

;look-up remote terminal name in terminal definition chain

LKPREM: MOV     TRMDFC,REM              ;index base of terminal def chain
10$:    CMM     4(REM),REMDDB+D.FIL(IMP);matching trmdef name?
       BEQ     CHKTRM                  ; yes
       MOV     @REM,D0                 ; no - advance to next entry
       BEQ     BADTRM                  ;zero means end of table - error
       MOV     D0,REM                  ;otherwise keep scanning
       BR      10$

BADTRM: TYPECR  ?bad terminal name
       JMP     EXIT

;make sure user has not given his own terminal name as the remote

CHKTRM: MOV     JOBCUR,A0               ;index own JCB
       MOV     JOBTRM(A0),TRM          ;index own trmdef area
       CMM     -4(TRM),REMDDB+D.FIL(IMP);same terminal name?
       BNE     CHKATT                  ;  no - no problem
       TYPECR  ?that is your terminal name
       JMP     EXIT                    ;  yes - can't do it

;check that terminal is not attached to a job

CHKATT: ADD     #10,REM                 ;fix header offset for remote
       TST     T.JLK(REM)              ;terminal attached?
       BEQ     SETTRM                  ; no
       TYPECR  ?terminal must be detached first
       JMP     EXIT

;set own terminal and remote terminal to data mode, no-echo

SETTRM: BISW    #T$DAT!T$ECS,@TRM       ;set data mode, no-echo (user)
       BISW    #T$DAT!T$ECS,@REM       ;set data mode, no-echo (remote)
       BISW    #F.REM,FLAGS(IMP)
       CLR     T.ICC(REM)              ;clear remote data-in buffer

;set up DDBs

SETDDB: MOVW    #[TRM],REMDDB+D.DEV(IMP)
       INIT    REMDDB(IMP)

;prompt for command

READY:  CRLF

PROMPT: TYPESP  <T)alk, S)end, R)eceive, C)onfigure, E)xit:>

GETCMD: KBD                             ;get cmd (1 char)
       AND     #177,D1                 ;mask off parity [CF]
       UCS                             ;fold to upper for comparisons
       CMPB    D1,#'T
       JEQ     TALK
       CMPB    D1,#'S
       JEQ     SEND
       CMPB    D1,#'R
       JEQ     RECEIV
       CMPB    D1,#'C
       JEQ     CONFIG
       CMPB    D1,#'E
       JEQ     QUIT
       BR      GETCMD

       PAGE
;**********
;*        *
;*  TALK  *
;*        *
;**********

;perform conversational I/O with remote system;  characters typed by user
;are tramsmitted to the remote system, and characters received from the
;remote system are displayed on the user's terminal.

TALK:   TYPECR  Talk                    ;confirm cmd
       CALL    GETEXT                  ;get exit char

T.LOOP: CALL    SCNTRM                  ;char ready from user?
       JMI     READY                   ; yes - is exit char - end of session
       BNE     T.RECV                  ; no
                                       ; yes - fall through
T.SEND: CALL    XMIT                    ;send char to remote
       BITW    #F.HDX,FLAGS(IMP)       ;half-duplex mode?
       BEQ     T.RECV                  ; no
       TTY                             ; yes - echo char

T.RECV: CALL    SCNREM                  ;char ready from remote?
       BNE     T.LOOP                  ; no - keep looping
       TTY                             ; yes - echo char
       BR      T.LOOP                  ;reenter main loop

       PAGE
;**********
;*        *
;*  SEND  *
;*        *
;**********

;Send an ASCII file to the remote system;  the user may abort this by
;hitting any key on the keyboard.

SEND:   TYPECR  Send                    ;confirm cmd
       CALL    GETFIL                  ;get filespec
       LOOKUP  DSKDDB(IMP)             ;file exist?
       BEQ     S.OPEN                  ; yes - this helps
       TYPECR  ?file not found         ; no - can do nothing
       JMP     READY                   ;    - return to cmd prompt

S.OPEN: OPENI   DSKDDB(IMP)             ;open disk DDB for input
       BISW    #F.OPN,FLAGS(IMP)       ;flag as much

S.LOOP: CALL    SCNTRM                  ;char ready from user?
       BEQ     S.CLOS                  ; yes - abort transmission
       CALL    SCNREM                  ;char ready from remote?
       BNE     S.SEND                  ; no - okay to send next byte
       CMPB    D1,#'S-'@               ;^S?
       BNE     S.SEND                  ; no - okay to send next byte

S.WAIT: CALL    SCNTRM                  ;char ready from user?
       BEQ     S.CLOS                  ; yes - abort transmission
       CALL    SCNREM                  ;char ready from remote?
       BNE     S.WAIT                  ; no
       CMPB    D1,#'Q-'@               ;^Q?
       BNE     S.WAIT                  ; no
                                       ; yes - resume transmission
S.SEND: FILINB  DSKDDB(IMP)             ;read next byte from file
       TST     DSKDDB+D.SIZ(IMP)       ;end of file?
       BEQ     S.CLOS                  ; yes - end of transmission
       BITW    #F.SIL,FLAGS(IMP)       ;silent mode?
       BNE     10$                     ; yes - don't echo char
       TTY                             ; no - echo char
10$:    MOV     D1,D0
       AND     #177,D0
       CMPB    D0,#LF                  ;LF?
       BNE     20$                     ; no
       BITW    #F.NLF,FLAGS(IMP)       ;Okay to send LFs?
       BNE     30$                     ; no
20$:    CALL    XMIT                    ;transmit to remote
30$:    BR      S.LOOP                  ;repeat until EOF or interrupted

S.CLOS: CLOSE   DSKDDB(IMP)             ;close disk file
       BICW    #F.OPN,FLAGS(IMP)       ;flag as much
       JMP     READY                   ;end of SEND code

       PAGE
;************
;*          *
;*  RECEIV  *
;*          *
;************

;Receive a file from the remote system;  this function operates analogously
;to TALK (i.e. two-way communication), but everything is recorded in a
;disk file.  Can be used to transmit an actual file or just to record a
;communications session.

RECEIV: TYPECR  Receive                 ;confirm cmd
       CALL    GETFIL                  ;get output filespec
       CALL    GETEXT                  ;get exit char
       LOOKUP  DSKDDB(IMP)             ;file exist?
       BNE     R.OPEN                  ; no
       TYPECR  ?file already exists    ; yes - output err msg
       JMP     READY                   ;return to cmd prompt

R.OPEN: OPENO   DSKDDB(IMP)             ;open output file
       BISW    #F.OPN,FLAGS(IMP)       ;flag as much

R.SET:  USRFRE  MEM                     ;set buffer index
       USREND  MAX                     ;set end of buffer
       SUB     #4000,MAX               ;allow for overflow (2K buffer)
       CLR     AMT                     ;no chars received yet

R.LOOP: CALL    SCNTRM                  ;char ready from user?
       BMI     R.CLOS                  ; yes - is exit char - done w/xfer
       BNE     R.RECV                  ; no
                                       ; yes - fall through
R.SEND: BITW    #F.HDX,FLAGS(IMP)       ;half-duplex mode?
       BEQ     10$                     ; no
       TTY                             ; yes
10$:    CALL    XMIT                    ;transmit char to remote
       BR      R.LOOP                  ;keep looping

R.RECV: CALL    SCNREM                  ;char ready from remote?
       BNE     R.CHEK                  ; no
       BITW    #F.SIL,FLAGS(IMP)       ;silent mode?
       BNE     10$                     ; no
       TTY                             ; yes - echo it
10$:    MOVB    D1,(MEM)+               ;store char
       INC     AMT                     ;update amount counter
       MOV     MEM,D0
       CMP     D0,MAX                  ;end of buffer?
       BLO     R.LOOP                  ; no
       BHI     R.LOOP                  ; no
                                       ; yes
R.XOFF: MOV     #'S-'@,D1               ;send XOFF to remote
       CALL    XMIT
       BISW    #F.SUS,FLAGS(IMP)       ;flag communications suspended
       BR      R.LOOP                  ;keep looping

R.CHEK: BITW    #F.SUS,FLAGS(IMP)       ;^S sent?
       JEQ     R.LOOP                  ; no - keep looping
       TST     AMT                     ;anything to store?
       JEQ     R.LOOP                  ; no - keep looping
       USRFRE  A0

R.SAVE: MOVB    (A0)+,D1                ;get char
       FILOTB  DSKDDB(IMP)             ;store char
       SOB     AMT,R.SAVE              ;loop till entire buffer stored

R.XON:  MOV     #'Q-'@,D1               ;send ^Q to remote
       CALL    XMIT
       BISW    #F.SUS,FLAGS(IMP)       ;flag as much
       USRFRE  MEM                     ;reset buffer index
       JMP     R.LOOP                  ;keep looping

R.CLOS: TST     AMT                     ;anything in buffer to xfer?
       BEQ     20$                     ; no
       USRFRE  A0                      ; yes
10$:    MOVB    (A0)+,D1                ;load char
       FILOTB  DSKDDB(IMP)             ;write char
       SOB     AMT,10$                 ;loop till entire buffer stored
20$:    CLOSE   DSKDDB(IMP)             ;close output file
       BICW    #F.OPN,FLAGS(IMP)       ;flag as much
       JMP     READY                   ;done w/RECEIVE

       PAGE
;************
;*          *
;*  CONFIG  *
;*          *
;************

;This action allows the user to change the various communications options
;available.  Currently, these are:
;
;       duplex (HALF or FULL) - determines whether or not TELCOM echoes
;                               the user's input characters during a TALK
;                               or a RECEIVE.
;       xmit/receive mode (DISPLAY or SILENT) - normally, the contents of
;                               a file being transmitted or received are
;                               displayed on the user's terminal while
;                               the I/O is in progress;  if the user elects
;                               to set SILENT mode, nothing is displayed.
;       LF/no-LF - normally, LFs are transmitted during SEND operations as
;                               are all other chars;  with the no-LF option
;                               in effect, LFs are supressed.  This is
;                               desireable when the remote system,
;                               automatically inserts LFs after every CR.

CONFIG: TYPECR  Configure

DUPLEX: TYPESP  duplex:
       BITW    #F.HDX,FLAGS(IMP)
       BEQ     10$
       TYPE    HALF
       BR      20$
10$:    TYPE    FULL
20$:    TYPE    <;  change? >
       CALL    YESNO
       BNE     RCVPAR
       XORW    #F.HDX,FLAGS(IMP)

RCVPAR: TYPESP  receive parity:
       BITW    #F.RP1,FLAGS(IMP)
       BEQ     10$
       TYPE    1
       BR      20$
10$:    TYPE    0
20$:    TYPE    <;  change? >
       CALL    YESNO
       BNE     SNDPAR
       XORW    #F.RP1,FLAGS(IMP)

SNDPAR: TYPESP  send parity:
       BITW    #F.SP1,FLAGS(IMP)
       BEQ     10$
       TYPE    1
       BR      20$
10$:    TYPE    0
20$:    TYPE    <;  change? >
       CALL    YESNO
       BNE     TFRMOD
       XORW    #F.SP1,FLAGS(IMP)

TFRMOD: TYPESP  transfer mode:
       BITW    #F.SIL,FLAGS(IMP)
       BEQ     10$
       TYPE    SILENT
       BR      20$
10$:    TYPE    DISPLAY
20$:    TYPE    <;  change? >
       CALL    YESNO
       BNE     LF.NLF
       XORW    #F.SIL,FLAGS(IMP)

LF.NLF: TYPESP  transmit line feeds:
       BITW    #F.NLF,FLAGS(IMP)
       BEQ     10$
       TYPE    N
       BR      20$
10$:    TYPE    Y
20$:    TYPE    <;  change? >
       CALL    YESNO
       JNE     READY
       XORW    #F.NLF,FLAGS(IMP)
       JMP     READY

;subroutine to get Y/N reply
;Z=1 on Y, Z=2 on N (or CR)

YESNO:  KBD
       AND     #177,D1         ; 7/10/84 [CF] strip high bit
       UCS
       CMPB    D1,#'Y
       BEQ     10$
       CMPB    D1,#'N
       BEQ     20$
       CMPB    D1,#CR
       BEQ     20$
       BR      YESNO
10$:    TYPECR  Yes
       LCC     #Z
       RTN
20$:    TYPECR  No
       LCC     #0
       RTN

;**********
;*        *
;*  EXIT  *
;*        *
;**********

QUIT:   TYPECR  Exit

EXIT:   BITW    #F.REM,FLAGS(IMP)
       BEQ     10$
       BICW    #T$DAT!T$ECS,@REM       ;set ASCII mode, echo (remote)
10$:    CRLF
       EXIT

       PAGE
;############
;#          #
;#  GETEXT  #
;#          #
;############

;get exit character

GETEXT: TYPESP  exit character:
       KBD
       MOV     D1,EXT
       CMPB    D1,#40
       BHIS    10$
       TYPE    ^
       ADD     #'@,D1
10$:
  TTY
       CRLF
       RTN

       PAGE
;############
;#          #
;#  GETFIL  #
;#          #
;############

;get filename

GETFIL: BICW    #T$DAT!T$ECS,@TRM
       TYPESP  filename:
       KBD     EXIT
       BISW    #T$DAT!T$ECS,@TRM
       FSPEC   DSKDDB(IMP),TXT
       INIT    DSKDDB(IMP)
       RTN

       PAGE
;############
;#          #
;#  SCNTRM  #
;#          #
;############

;scan for terminal input character
;return Z=0 (no char ready) or Z=1 (char ready, D1 := char)
;return N=0 (not exit char) or N=1 (exit char typed)

SCNTRM: TST     T.ICC(TRM)
       BNE     10$
       LCC     #0
       RTN
10$:    KBD
       CMPB    D1,EXT
       BNE     30$
       BITW    #F.SP1,FLAGS(IMP)
       BEQ     20$
       OR      #200,D1
20$:    LCC     #N!Z
       RTN
30$:    LCC     #Z
       RTN

       PAGE
;############
;#          #
;#  SCNREM  #
;#          #
;############

;scan for remote terminal input
;return Z=0 (no char ready) or Z=1 (char ready, D1 := char)

SCNREM: TST     T.ICC(REM)
       BNE     10$
       LCC     #0
       RTN
10$:    XCH     A5,REM
       TTYIN
       AND     #177,D1
       XCH     REM,A5
       BITW    #F.RP1,FLAGS(IMP)
       BEQ     20$
       OR      #200,D1
20$:    LCC     #Z
       RTN

       PAGE
;##########
;#        #
;#  XMIT  #
;#        #
;##########

;transmit char in D1 to remote terminal

XMIT:   OPENO   REMDDB(IMP)
       FILOTB  REMDDB(IMP)
       CLOSE   REMDDB(IMP)
       RTN

       END
).(