TITLE   'MEX SMARTMODEM OVERLAY V1.5'
;
; (DELETE ABOVE TITLE LINE IF ASSEMBLING WITH ASM)
;
; Smartmodem overlay for MEX: revision 1.5
; Written 04/16/84 by Ronald G. Fowler (V1.0)
;
; 02/20/85: Converted for MEX 1.2 - Al Jewer
;           Also added 'space bar return busy' function.
;
; 07/16/84: Added equate NUMRES to enable/disable numeric result code
;           interpretation.  Under TurboDos, the first digit of the
;           phone number was being interpreted as a result code as it
;           was echoed by the Anchor modem as it dialed.  Set NUMRES false
;           to disable numeric results. (Bob Puckett)
;
; 06/06/84: Fixed problem for Anchor users, where, when the modem returned
;           "DIAL TONE", the "N" in "TONE" was being regarded as a NO-CONNECT
;           code.  Now we flush the entire result line before reading another.
;           Also added code for numeric version of "CONNECT 1200".  --RGF
;
; Small bug repaired: (V1.1) 05/14/84 (Steve Grandi): Smartmodem was not being
;       flushed after a dial string so that last digit of the phone number
;       was being interpreted as a numeric result code causing the program,
;       for certain numbers, to give up even as the modem merrily dialed away.
;
; This modules adapts MEX for the DC Hayes Smartmodem (as well
; as many others -- including US Robotics -- that use a similar
; command language). The main function of this module is to pro-
; vide dialing capability; the disconnect vector is ancillary.
; You may use this module as a model to develop dialing routines
; for non-standard modems (e.g., the Racal-Vadic).  The only
; pertinent entry point is the DIAL routine; you'll find entry
; specs for that below.
;
; The only conditional you might want to change in this
; module is the DISC equate below -- if left on, MEX will
; use the Smartmodem's disconnect code.  If you prefer to
; provide your own in your overlay's DISCV vector (e.g.,
; by dropping DTR), then set DISC to FALSE and re-assemble.
; (If you don't understand this, then play it safe, and
; leave the equate set as it is).
; NOTE: Leave DISC set TRUE for MEX 1.2x
;
; This overlay will work with any modem overlay that terminates
; prior to 0B00H
;
FALSE   EQU     0
TRUE    EQU     NOT FALSE
;
;
NUMRES  EQU     FALSE           ; TRUE = INTERPRET NUMERIC RESULT CODES
                               ; FALSE = IGNORE NUMERIC RESULT CODES
;
DISC    EQU     TRUE            ;<<== CHANGE TO FALSE IF YOU DISC. WITH DTR
                               ;       leave set TRUE for MEX 1.2
;
;
;
; NOTE: This overlay converted for MEX 1.2 compatiblility
;       and 8086 translation 2/20/85 by Al Jewer.
;
YES     EQU     0FFH            ;THIS IS FOR 8086 TRANSLATOR - DO NOT CHANGE
NO      EQU     0
I8080   EQU     YES             ;DEFINE PROCESSOR TYPE
I8086   EQU     NO
MEX2    EQU     NO              ;SET TRUE IF MEX 2.X, FALSE IF MEX 1.X
TPULSV  EQU     0105H           ;TONE/PULSE FLAG IN MODEM OVERLAY
NDISCV  EQU     015FH           ;NEW SMART MODEM DISCONNECT HERE
DIALV   EQU     0162H           ;LOCATION OF DIAL VECTOR IN OVERLAY
DISCV   EQU     0165H           ;LOCATION OF HARDWARE DISCONNECT VECTOR
DIALOC  EQU     0B00H           ;DIALING CODE GOES HERE
MEXLOC  EQU     0D00H           ;"CALL MEX" HERE
SMTABL  EQU     0D55H           ;SMARTMODEM INIT, DE-INIT AND SSET VECTORS
;
;
; FOLLOWING ARE FUNCTION CODES FOR THE MEX SERVICE CALL PROCESSOR
;
INMDM   EQU     255             ;RETURN CHAR FROM MDM IN A, CY=NO CHR IN 100MS
TIMER   EQU     254
TMDINP  EQU     253             ;B=# SECS TO WAIT FOR CHAR, CY=NO CHAR
CHEKCC  EQU     252             ;CHECK FOR ^C FROM KBD, Z=PRESENT
SNDRDY  EQU     251             ;TEST FOR MODEM-SEND READY
RCVRDY  EQU     250             ;TEST FOR MODEM-RECEIVE READY
SNDCHR  EQU     249             ;SEND A CHARACTER TO THE MODEM (AFTER SNDRDY)
RCVCHR  EQU     248             ;RECV A CHAR FROM MODEM (AFTER RCVRDY)
ILP     EQU     240             ;INLINE PRINT
KSTAT   EQU     11              ;KEYBOARD STATUS
KBDIN   EQU     01              ;KEYBOARD INPUT
;
CR      EQU     13
LF      EQU     10
;
; ***** CODE STARTS HERE *****
;
;
IF (NOT MEX2)
;
; NOTE:
;               This file contains control characters used by our
; 8080-8086 translator, XLAT. These are in the form of "\" characters
; inserted as the first character of the comment field. Please do
; not change or delete these, so that future versions of this overlay
; will directly convert to 8086 operation. Thanks,    - al
;
; For MEX 1.2, the first byte of the overlay MUST contain a "jump" opcode.
; The is a 0C3H for 8080 and an 0E9H for 8086. MEX 1.2 checks this byte
; before it loads the overlay, to make sure you don't load the wrong
; type of overlay. This byte will not affect pre- 1.2 versions.
;
; Also, MEX 1.2 contains a new vector at 15FH which is the smart-modem
; disconnect vector (now separate from the hardware vector at 165H).
; The hardware vector typically toggles the DTR line to cause a hangup,
; while the smart-modem vector sends the hangup string to the modem.
; Mex 1.2 will ignore the vector at 165H in this overlay.
;
       ORG     100H            ;BASE OF TPA
IF I8080
       DB      0C3H            ;DEFINE 8080 OVERLAY
ENDIF   ;I8080
IF I8086
       DB      0E9H            ;8086 FLAG
ENDIF   ;I8086
;
       ORG     TPULSV
TPULSE: DB      'T'             ;TOUCHTONE FLAG
;
       IF      DISC            ;IF PROVIDING DISCONNECT CODE
       ORG     NDISCV          ;SMART MODEM DISCONNECT VECTOR (MEX 1.20)
       JMP     DISCON
       ELSE
       RET                     ;FOR MEX 1.2, IN CASE SOMEBODY SCREWS UP....
       ENDIF
;
       ORG     DIALV           ;OVERLAY THE DIALING VECTOR
       JMP     DIAL
;
       IF      DISC            ;IF PROVIDING DISCONNECT CODE
       ORG     DISCV           ;OVERLAY THE VECTOR (MEX 1.1X)
       JMP     DISCON
       ENDIF
;
;
ENDIF   ;NOT MEX2
;
IF MEX2
;
; (note: re-enable ASEG & CSEG if MEX2)
;
;       ASEG                    ;JUMP TABLE IS ABSOLUTE
;
       ORG     10FH            ;MEX2 JUMPS START HERE
       JMP     DIAL            ;FIRST IS DIAL VECTOR
       DS      3               ;THEN HARDWARE DISCONNECT VECTOR
       JMP     DISCON          ;THEN SOFTWARE DISCONNECT VECTOR
       JMP     JUSTRT          ;SMART MODEM INIT
       JMP     JUSTRT          ;SMART MODEM DEINIT
       JMP     NOTIMP          ;SSET COMMAND
;
;       CSEG                    ;REST IS CODE SEGMENT
;
ENDIF   ;MEX2
;
;
; This is the DIAL routine called by MEX to dial a digit. The digit
; to be dialed is passed in the A register.  Note that two special
; codes must be intercepted as non-digits: 254 (start dial sequence)
; and 255 (end-dial sequence).  Mex will always call DIAL with 254
; in the accumulator prior to dialing a number.  Mex will also call
; dial with 255 in A as an indication that dialing is complete. Thus,
; the overlay may use these values to "block" the number, holding it
; in a buffer until it is completely assembled (in fact, that's the
; scheme employed here for the Smartmodem).
;
; After the 254-start-dial sequence, MEX will call the overlay with
; digits, one-at-a-time.  MEX will make no assumptions about the dig-
; its, and will send each to the DIAL routine un-inspected (some modems,
; like the Smartmodem, allow special non-numeric characters in the
; phone number, and MEX may make no assumptions about these).
;
; After receiving the end-dial sequence (255) the overlay must take
; whatever end-of-dial actions are necessary *including* waiting for
; carrier at the distant end.  The overlay should monitor the keyboard
; during this wait (using the MEX keystat service call), and return
; an exit code to MEX in the A register, as follows:
;
;       0 - Carrier detected, connection established
;       1 - Far end busy (only for modems that can detect this condition)
;       2 - No answer (or timed out waiting for modem response)
;       3 - Keyboard abort (^C only: all others should be ignored)
;       4 - Error reported by modem
;
; <No other codes should be returned after an end-dial sequence>
;
; The overlay should not loop forever in the carrier-wait routine, but
; instead use either the overlay timer vector, or the INMDMV (timed 100
; ms character wait) service call routine.
;
; The DIAL routine is free to use any of the registers, but must return
; the above code after an end-dial sequence
;
IF (NOT MEX2)
       ORG     DIALOC
ENDIF   ;NOT MEX2
;
DIAL:   LHLD    DIALPT          ;FETCH POINTER
       CPI     254             ;START DIAL?
       JZ      STDIAL          ;\JUMP IF SO
       CPI     255             ;END DIAL?
       JZ      ENDIAL          ;\JUMP IF SO
;
; Not start or end sequence, must be a digit to be sent to the modem
;
       MOV     M,A             ;PUT CHAR IN BUFFER
       INX     H               ;\ADVANCE POINTER
       SHLD    DIALPT          ;STUFF PNTR
       RET                     ;ALL DONE
;
; Here on a start-dial sequence
;
STDIAL: LXI     H,DIALBF        ;SET UP BUFFER POINTER
       SHLD    DIALPT
       RET
;
; Here on an end-dial sequence
;
ENDIAL: MVI     M,CR            ;STUFF END-OF-LINE INTO BUFFER
       INX     H               ;\FOLLOWED BY TERMINATOR
       MVI     M,0
       LDA     TPULSE          ;GET OVERLAY'S TOUCH-TONE FLAG
       STA     SMDIAL+3        ;PUT INTO STRING
       LXI     H,SMDIAL        ;POINT TO DIALING STRING
       CALL    SMSEND          ;SEND IT
WAITSM: MVI     C,INMDM
       CALL    MEX             ;CATCH ANY OUTPUT FROM THE MODEM
       JNC     WAITSM          ;\LOOP UNTIL NO MORE CHARACTERS
;
; THE FOLLOWING LOOP WAITS FOR A RESULT FROM THE MODEM (UP TO
; 60 SECONDS: YOU MAY CHANGE THIS VALUE IN THE FOLLOWING LINE).
; NOTE THAT THE SMARTMODEM HAS AN INTERNAL 30 SECOND TIMEOUT WHILE
; FOR A CARRIER ON THE OTHER END.  YOU CAN CHANGE BY PLAYING WITH THE
; S7 VARIABLE (I.E. SEND THE SMARTMODEM "AT S7=20" TO LOWER THE 30 SECOND
; WAIT TO 20 SECONDS).
;
RESULT: MVI     C,60            ;<<== MAXIMUM TIME TO WAIT FOR RESULT
SMWLP:  PUSH    B
       MVI     B,1             ;CHECK FOR A CHAR, UP TO 1 SEC WAIT
       MVI     C,TMDINP        ;DO TIMED INPUT
       CALL    MEX
       POP     B
       JNC     SMTEST          ;\JUMP IF MODEM HAD A CHAR
       PUSH    B               ;NO, TEST FOR CONTROL-C FROM CONSOLE
       MVI     C,KSTAT         ;CHECK FOR KEYPRESS
       CALL    MEX
       ORA     A
       POP     B
       JZ      SMNEXT          ;\JUMP IF NO KEYPRESS
       PUSH    B               ;GET KEYPRESS
       MVI     C,KBDIN
       CALL    MEX
       POP     B
       CPI     'C'-40H         ;IS ^C?
       JNZ     NOCC            ;\JUMP IF NOT
       MVI     A,3             ;PREP RETURN CODE
       PUSH    PSW             ;\SAVE IT
ABCOM:  MVI     B,CR            ;YES, SHUT DOWN THE MODEM
       MVI     C,SNDCHR
       CALL    MEX
       POP     PSW             ;\RETURN ABORT CODE
       RET
NOCC:   CPI     ' '             ;SPACE BAR?
       JNZ     SMNEXT          ;\IGNORE ALL OTHERS
       MVI     A,1             ;PREP RETURN CODE
       PUSH    PSW             ;\
       JMP     ABCOM           ;\FINISH IN COMMON CODE
SMNEXT: DCR     C               ;NO
       JNZ     SMWLP           ;\CONTINUE
;
; ONE MINUTE WITH NO MODEM RESPONSE (OR NO CONNECTION)
;
SMTIMO: MVI     A,2             ;RETURN TIMEOUT CODE
       RET
;
; MODEM GAVE US A RESULT, CHECK IT
;
SMTEST: ANI     7FH             ;IGNORE ANY PARITY
       CALL    SMANAL          ;TEST THE RESULT
       MOV     A,B             ;A=RESULT (CY SIGNIFICANT HERE TOO)
       PUSH    PSW             ;SAVE IT
SMTLP:  MVI     C,INMDM         ;FLUSH ANY REMAINING COMMAND LINE
       CALL    MEX
       JC      SMCHEK          ;\JUMP IF NO INPUT
       CPI     LF              ;GOT SOME ... WAITING FOR EOL
       JNZ     SMTLP           ;\EAT ANY IN-BETWEEN
SMCHEK: POP     PSW             ;A HAS MEX RETURN-CODE, CY=1 IF UNKNOWN
       JC      RESULT          ;\IF RESULT UNKNOWN, IGNORE IT
       RET
;
SMANAL: MVI     B,0             ;PREP CONNECT CODE
       CPI     'C'             ;"CONNECT"?
       RZ                      ;\R1\

       IF      NUMRES
       CPI     '1'             ;NUMERIC VERSION OF "CONNECT"
       RZ                      ;\R1\
       CPI     '5'             ;NUMERIC VERSION OF "CONNECT 1200"
       RZ                      ;\R1\
       ENDIF

       INR     B               ;PREP BUSY CODE B=1
       CPI     'B'
       RZ                      ;\R1\
       INR     B               ;PREP NO CONNECT MSG B=2
       CPI     'N'             ;N=NO CONNECT
       RZ                      ;\R1\

       IF      NUMRES
       CPI     '3'             ;NUMERIC VERSION OF "NO CONNECT"
       RZ                      ;\R1\
       ENDIF

       MVI     B,4             ;PREP MODEM ERROR
       CPI     'E'             ;E=ERROR
       RZ                      ;\R1\

       IF      NUMRES
       CPI     '4'             ;NUMERIC VERSION OF "ERROR"
       RZ                      ;\R1\
       ENDIF

       STC                     ;UNKNOWN...
R1:     RET
;
; FOLLOWING ROUTINE DISCONNECTS THE MODEM USING SMARTMODEM
; CODES. ALL REGISTERS ARE AVAILABLE FOR THIS FUNCTION.
; NOTHING RETURNED TO CALLER.
;
       IF      DISC
;
DISCON: MVI     B,20
       MVI     C,TIMER         ;WAIT 2 SECONDS
       CALL    MEX
       LXI     H,SMATN         ;SEND '+++'
       CALL    SMSEND
       MVI     B,20            ;WAIT 2 MORE SECONDS
       MVI     C,TIMER
       CALL    MEX
       LXI     H,SMDISC        ;SEND 'ATH'
       CALL    SMSEND
       MVI     B,1             ;WAIT 1 SECOND
       MVI     C,TIMER
       CALL    MEX
       RET
;
SMATN:  DB      '+++',0
SMDISC: DB      'ATH',CR,0
;
       ENDIF
;
; SMARTMODEM UTILITY ROUTINE: SEND STRING TO MODEM
;
SMSEND: MVI     C,SNDRDY        ;WAIT FOR MODEM READY
       CALL    MEX
       JNZ     SMSEND          ;\
       MOV     A,M             ;FETCH NEXT CHARACTER
       INX     H               ;\
       ORA     A               ;END?
       RZ                      ;\R1\DONE IF SO
       MOV     B,A             ;NO, POSITION FOR SENDING
       MVI     C,SNDCHR        ;NOPE, SEND THE CHARACTER
       CALL    MEX
       JMP     SMSEND          ;\
;
; DATA AREA
;
SMDIAL: DB      'ATDT '
DIALBF: DS      52              ;2* 24 CHAR MAX, + CR + NULL + SLOP
DIALPT: DS      2               ;DIAL POSITION POINTER
;
;
NOTIMP: MVI     C,ILP
       CALL    MEX
       DB      CR,LF,'Not Implemented',CR,LF,0
JUSTRT: RET
;
;
       ORG     MEXLOC          ;"CALL MEX"
MEX:
;
;
IF (NOT MEX2)
       ORG     SMTABL          ;TABLE OF SMART MODEM VECTORS HERE
;
       DW      JUSTRT          ;SMART MODEM INIT
       DW      NOTIMP          ;SSET COMMAND (NOT IMPLEMENTED)
       DW      JUSTRT          ;SMART MODEM EXIT
ENDIF   ;NOT MEX2
;
       END