TITLE 'MEX overlay for the SB180 with the XECOM MOSART' ;This is the MEX overlay for the SB180 COMM180-M board using the XECOM 12xx ;MOSART. Since the MOSART does not use Hayes-compatible commands, and has ;only a single pair of ports, which serve for both control/status bytes as ;well as data bytes, the overlay is not written in separate 'MXH-' ;hardware-dependent and 'MXM-' modem-specific overlays. See the accompanying ;.DOC file for a discussion of the reasons for this structure. Modifying ;this overlay for other MOSART installations merely requires changing the ;value of the DATA equate below to that appropriate for the new system. VERS equ 10 ;Overlay revision level ;Misc equates NO equ 1 eq 2 ;change to 'equ 0' if your assembler complains YES equ not NO BELL equ 07H ;Bell TAB equ 09H ;Tab LF equ 0AH ;Line feed CR equ 0DH ;Carriage return ESC equ 1BH ;Escape TPA equ 100H ;Transient prog area MEX equ 0D00H ;Address of the service processor I8080 equ NO ;change to YES for 8080-compatible code if I8080 ; Define Z80-specific op codes as macros for 8080 processors JR macro cond,addr if NUL addr jp cond else jp cond,addr endif endm DJNZ macro loopadd dec b jp nz,loopadd endm endif ; MOSART addresses and bit definitions ;MOSART Port Addresses DATA equ 0E0H ;Data STATUS equ DATA + 1 ;Status/control ;MOSART Status Byte TXRDY equ 01H ;Transmitter ready RXRDY equ 02H ;Receive data available bit TBE equ 04H ;Transmit buffer empty bit PERR equ 08H ;Parity error ORERR equ 10H ;Overrun error FRERR equ 20H ;Framing error DET equ 40H ;Ring detect bit DSR equ 80H ;Data set ready bit DCDMASK equ DET + DSR ;Data carrier detect mask DCDLOST equ DET ;value if carrier lost ;MOSART Control Byte TXEN equ 01H ;Transmitter enable DTR equ 02H ;Data Terminal Ready - reset to hang up RXEN equ 04H ;Receiver enable SBRK equ 08H ;Send break ERRST equ 10H ;Error reset RTS equ 20H ;Request To Send - set for data, ;Reset for MOSART command INTRST equ 40H ;Internal reset ENTHNT equ 80H ;Enter hunt (synchronous only) FNMOD equ TXEN+DTR+RXEN+ERRST ;Set function mode DATMOD equ TXEN+DTR+RXEN+ERRST+RTS ;Set data mode BRKMOD equ FNMOD+SBRK ;send break - leave MOSART in function mode MOSRST equ TXEN+DTR+RXEN+ERRST+RTS+INTRST ;Reset MOSART ;MOSART Mode byte B1200 equ 00000001B ;1200 BPS B300 equ 00000010B ;300 BPS B110 equ 00000011B ;110 BPS BIT7 equ 00001000B ;7 bit data BIT8 equ 00001100B ;8 bit data PARENA equ 00010000B ;Enable parity checking PAREVN equ 00100000B ;Even parity STOP1 equ 01000000B ;1 stop bit STOP15 equ 10000000B ;1.5 stop bits STOP2 equ 11000000B ;2 stop bits ;MOSART Mode bytes. Most commonly-used modes are defined here. Select ;the one appropriate for the systems you use, and install it in the ;MOSINI: routine. M12N81 equ B1200+BIT8+STOP1 ;1200 BPS, 8 bit, no parity, 1 stop M12N82 equ B1200+BIT8+STOP2 ;1200 BPS, 8 bit, no parity, 2 stop M12E71 equ B1200+BIT7+PARENA+PAREVN+STOP1 ;1200 BPS, 7 bit, even parity, 1 stop M12O71 equ B1200+BIT7+PARENA+STOP1 ;1200 BPS, 7 bit, odd parity, 1 stop M3N81 equ B300+BIT8+STOP1 ;300 BPS, 8 bit, no parity, 1 stop M3N82 equ B300+BIT8+STOP2 ;300 BPS, 8 bit, no parity, 2 stop M3E71 equ B300+BIT7+PARENA+PAREVN+STOP1 ;300 BPS, 7 bit, even parity, 1 stop M3O71 equ B300+BIT7+PARENA+STOP1 ;300 BPS, 7 bit, odd parity, 1 stop M1N81 equ B110+BIT8+STOP1 ;110 BPS, 8 bit, no parity, 1 stop ; Define MEX items in MOSART terms MODCT1 equ STATUS MODDAT equ DATA MDRCVB equ RXRDY MDRCVR equ RXRDY MDSNDB equ TXRDY MDSNDR equ TXRDY ;Since the MOSART indicates the LOSS of the carrier during a connection, ;rather than the presence of the carrier, the next two definitions are ;not used the way they are in other overlays. MDDCDB equ DCDMASK ;Carrier detect bit MDDCDA equ DSR ;Value when active ;Following are function codes for the MEX service call processor ;MEX supports an overlay service processor, located at 0D00h (and maintained ;at this address from version to version). If your overlay needs to call ;BDOS for any reason, it should call MEX instead. Function calls below ;about 240 are simply passed on to the BDOS (console and list I/O calls are ;specially handled to allow modem port queueing, which is why you should ;call MEX instead of BDOS). MEX uses function calls above about 244 for ;special overlay services (described below). ;Some sophisticated overlays may need to do file i/o; if so, use the parsfn ;MEX call with a pointer to the fcb in de to parse out the name. This fcb ;should support a spare byte immediately pre- ceeding the actual fcb (to ;contain user # information). If you've used mex-10 for input instead of ;BDOS-10 (or you're parsing part of a set command line that's already been ;input), then MEX will take care of du specs, and set up the fcb ;accordingly. There- after all file i/o calls done through the MEX service ;processor will handle drive and user with no further effort necessary on ;the part of the programmer. INMDM equ 255 ;Get char from port to A, CY=no more in 100 ms TIMER equ 254 ;Delay 100ms * reg B 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) LOOKUP equ 247 ;Table search: see CMDTBL comments for info PARSFN equ 246 ;Parse filename from input stream BPSPAR equ 245 ;Parse BPS-rate from input stream SBLANK equ 244 ;Scan input stream to next non-blank EVALA equ 243 ;Evaluate numeric from input stream LKAHED equ 242 ;Get nxt char w/o removing from input GNC equ 241 ;Get char from input, cy=1 if none ILP equ 240 ;Inline print DECOUT equ 239 ;Decimal output PRBPS equ 238 ;Print BPS rate PRNTBL equ 237 ;Print table PRID equ 236 ;Print [mex] id ONOFF equ 235 ;Parse on/off fm input strm a=0 or 1 (c=err) ;Doesn't seem to be in mex 1.12? KBDIN equ 1 ;Keyboard input CONOUT equ 2 ;Simulated BDOS function 2: console char out DCONIO equ 6 ;Direct console i/o: passed through to BDOS DCONIN equ YES ;Flag in E register for input on func 6 PRINT equ 9 ;Simulated BDOS function 9: print string INBUF equ 10 ;Input buffer,same structure as BDOS 10 KSTAT equ 11 ;Keyboard status subttl 'MEX SB180/XECOM 12xx MOSART Hardware Overlay' org TPA org $ + 3 ;MEX has a 'jp START' here ;The following variables are located at the beginning of the program ;to facilitate modification without the need of re-assembly. They will ;be moved in MEX 2.0. PMODEM: defb NO ;Yes=PMMI modem \ / These 2 locations are not SMODEM: defb NO ;Yes=Smartmodem / \ referenced by MEX TPULSE: defb 'T' ;T=tone, P=pulse (not referenced by MEX) CLOCK: defb 61 ;Clock speed x .1, up to 25.5 mhz. MSPEED: defb 5 ;Sets display time for sending a file ;0=110 1=300 2=450 3=600 4=710 ;5=1200 6=2400 7=4800 8=9600 9=19200 BYTDLY: defb 5 ;Default time to send character in ;terminal mode file transfer (0-9) ;0=0 delay, 1=10 ms, 5=50 ms, 9=90 ms CRDLY: defb 5 ;End-of-line delay after CRLF in terminal ;mode file transfer for slow BBS systems ;0=0 delay, 1=100 ms, 5=500 ms, 9=900 ms COLUMS: defb 5 ;Number of directory columns SETFL: defb YES ;Yes=user-defined SET command SCRTST: defb YES ;Yes=if home cursor and clear screen ;routine at CLRSCRN defb 0 ;Was once ACKNAK,now spare BAKFLG: defb YES ;Yes=make .BAK file CRCDFL: defb YES ;Yes=default to CRC checking ;No=default to Checksum checking TOGCRC: defb YES ;Yes=allow toggling of Checksum to CRC CVTBS: defb NO ;Yes=convert backspace to rub TOGLBK: defb YES ;Yes=allow toggling of bksp to rub ADDLF: defb NO ;No=no LF after CR to send file in ;terminal mode (added by remote echo) TOGLF: defb YES ;Yes=allow toggling of LF after CR TRNLOG: defb NO ;Yes=allow transmission of logon ;write logon sequence at location LOGON SAVCCP: defb YES ;Yes=do not overwrite CCP LOCNXT: defb NO ;Yes=local cmd if EXTCHR precedes ;No=not local cmd if EXTCHR precedes TOGLOC: defb YES ;Yes=allow toggling of LOCNXTCHR LSTTST: defb YES ;Yes=allow toggling of printer on/off ;in terminal mode. Set to no if using ;the printer port for the modem XOFTST: defb NO ;Yes=allow testing of XOFF from remote ;while sending a file in terminal mode XONWT: defb NO ;Yes=wait for XON after sending CR while ;transmitting a file in terminal mode TOGXOF: defb YES ;Yes=allow toggling of XOFF testing IGNCTL: defb YES ;Yes=do not send control characters ;above CTL-M to CRT in terminal mode ;no=send any incoming CTL-char to CRT EXTRA1: defb 0 ;For future expansion EXTRA2: defb 0 ;For future expansion BRKCHR: defb '@'-40H ;^@ = Send a 300 ms. break tone NOCONN: defb 'N'-40H ;^N = Disconnect from phone line LOGCHR: defb 'L'-40H ;^L = Send logon LSTCHR: defb 'P'-40H ;^P = Toggle printer UNSVCH: defb 'R'-40H ;^R = Close input text buffer TRNCHR: defb 'T'-40H ;^T = Transmit file to remote SAVCHR: defb 'Y'-40H ;^Y = Open input text buffer EXTCHR: defb '^'-40H ;^^ = Send next character ;Equates used only by PMMI routines grouped together here. PRATE: defb 250 ;125=20pps dialing, 250=10pps defb 0 ;Not used ;Low-level modem I/O routines: this will be replaced with ;a jump table in MEX 2.0 (you can insert jumps here to longer ;routines if you'd like ... I'd recommend NOT putting part of ;a routine in this area,then jumping to the rest of the routine ;in the non-fixed area;that will complicate the 2.0 conversion) INCTL1: in a,(MODCT1) ;In modem control port ret ; defb 0,0,0,0,0,0,0 ;Spares if needed for non-PMMI OTCTL1: out (MODCT1),a ;Output byte to control port (non-standard) ret defb 0,0,0,0 ;rest of spare bytes OTDATA: out (MODDAT),a ;Out modem data port ret defb 0,0,0,0,0,0,0 ;Spares if needed for non=PMMI INPORT: in a,(MODDAT) ;In modem data port ret defb 0,0,0,0,0,0,0 ;Spares if needed for non-PMMI ;Bit-test routines. These will be merged with the above ;routines in MEX 2.0 to provide a more reasonable format MASKR: and MDRCVB ret ;Bit to test for receive ready TESTR: cp MDRCVR ret ;Value of receive bit when ready MASKS: and MDSNDB ret ;Bit to test for send ready TESTS: cp MDSNDR ret ;Value of send bit when ready ;Unused area: was once used for special PMMI functions, ;Now used only to retain compatibility with MDM overlays. ;You may use this area for any miscellaneous storage you'd ;like but the length of the area *must* be 12 bytes. org $ + 12 ;Special modem function jump table: if your overlay cannot handle ;some of these, change the jump to 'defs 3', so the code present in ;MEX will be retained. Thus, if your modem can't dial, change the ;'jp DIAL' at DIALV to 'defs 3', and MEX will print a "not-implemented" ;diagnostic for any commands that require dialing. ;DIALV dials the digit in A. See the comments at DIAL for specs. ;DISCV disconnects the modem ;GOODBV is called just before MEX exits to CP/M. If your overlay ; requires some exit cleanup, do it here. Should NOT disconnect ; from the phone line. ;INMODV is called when MEX starts up; use INMODV to initialize the modem. ;NEWBPS is used for phone-number BPS rates and is called with a BPS-rate ; code in the A register, value as follows: ; A=0: 110 BPS A=1: 300 BPS A=2: 450 BPS ; A=3: 600 BPS A=4: 710 BPS A=5: 1200 BPS ; A=6: 2400 BPS A=7: 4800 BPS A=8: 19200 BPS ; If your overlay supports the passed BPS rate,it should store the ; value passed in A at MSPEED (107H), and set the requested rate. If ; the value passed is not supported, you should simply return (with- ; out modifying MSPEED) -or- optionally request a BPS-rate from the ; user interactively. ;NOPARV is called at the end of each file transfer; your overlay may simply ; return here, or you may want to restore parity if you set no-parity ; in the following vector (this is the case with the PMMI overlay). ; ;PARITV is called at the start of each file transfer; your overlay may simply ; return here, or you may want to enable parity detection (this is the ; case with the PMMI overlay). ;SETUPV is the user-defined command ... to use this routine to build your own ; MEX command, set the variable SETFL (117H) non-zero,and add your SET ; code. You can use the routine presented in the PMMI overlay as a ; guide for parsing, table lookup, etc. ;SPMENU is provided only for MDM compatibility, and is not used by MEX 1.0 ; for any purpose (it will be gone in MEX 2). ;VERSNV is called immediately after MEX prints its sign-on message at cold ; startup -- use this to identify your overlay in the sign-on message ; (include overlay version number in the line). ;BREAKV is provided for sending a BREAK (-B in terminal mode). If your ; modem doesn't support BREAK, or you don't care to code a BREAK rou- ; tine, you may simply execute a RET instruction. LOGON: org $ + 2 ;Needed for MDM compat, not ref'd by MEX DIALV: jp DIAL ;Dial digit in A (routine in modem section) DISCV: jp MHANGP ;Disconnect the modem GOODBV: ret ;Called before exit to CP/M nop nop INMODV: jp MOSINI ;Initialization. Called at cold-start NEWBPS: jp PBPS ;Set BPS rate NOPARV: ret nop nop PARITV: ret nop nop SETUPV: jp SETCMD ;SET cmd SPMENV: ret nop nop ;not used with MEX VERSNV: jp SYSVER ;Overlay's voice in the sign-on message BREAKV: jp PBREAK ;Send a break ;The following jump vector provides the overlay with access to special ;routines in the main program (retained and supported in the main pro- ;gram for MDM overlay compatibility). These should not be modified by ;the overlay. ;Note that for MEX 2.0 compatibility, you should not try to use these ;routines, since this table will go away with MEX 2.0 (use the MEX ;service call processor instead). ILPRTV: org $ + 3 ;Replace with MEX function 9 INBUFV: org $ + 3 ;Replace with MEX function 10 ILCMPV: org $ + 3 ;Replace with table lookup funct. 247 INMDMV: org $ + 3 ;Replace with MEX function 255 NXSCRV: org $ + 3 ;Not supported by MEX (returns w/no action) TIMERV: org $ + 3 ;Replace with MEX function 254 ;Routine to clear to end of screen. If using CLREOS and CLRSCRN, set ;SCRNTEST to YES at 010AH (above). Each routine must use the ;full 9 bytes alloted (may be padded with nulls). ;These routines (and other screen routines that MEX 2.0 will sup- ;port) will be accessed through a jump table in 2.0, and will be ;located in an area that won't tie the screen functions to the ;modem overlay (as the MDM format does). CLREOS: ld de,EOSMSG ld c,PRINT call MEX ret CLS: ld de,CLSMSG ld c,PRINT call MEX ret ; *** End of Fixed-address overlay area *** ;The following screen-clearing sequences are appropriate for Wyse, ;Televideo, and several other terminals. If your terminal requires ;different sequences, simply replace them with the correct ones for ;your hardware. They are printed using the MEX version of the BDOS ;'print string' function (function 9), so they must end with a '$'. EOSMSG: defb ESC,'y$' ;clear to end of screen with nulls CLSMSG: defb 1ah,'$' ;clear screen ; Initialize the MOSART; sets up BPS, data bits, stop bit(s), and ; parity. If your systems need something other than 1200/8/1/none, ; replace the 'M12N81' below with the appropriate mode byte for your ; systems. Derived from the Term III MOSART package from Echelon. ; Since this routine is called each time MEX is started, it checks to ; see if a connection exists. If so, it returns without doing anything. ; This allows you to leave MEX, do something else, and return to MEX ; with the connection still present. MOSINI: in a,(MODCT1) ;get MOSART status and DSR ;see if connection already established ret nz ;if so, don't change anything ld a,M12N81 ;set mode: 1200 BPS/no parity/8 bit/1 stop ld (CURMOD),a MOSNBP: ;enter here for new BPS rate (SET BPS command ;or dial number with BPS rate in phone # list) call DOINIT ;this routine revised by David McCord. ld a,08h ;fixed a bug where the MOSART did not LOOP: push af ;initialize reliably the FIRST time it ld a,0ffh ;was instructed to, after a power-on. LOOP1: call MDELAY ;now we do it twice, if the first time dec a ;didn't work. jr nz,LOOP1 pop af dec a jr nz,LOOP in a,(STATUS) and 05 ;return code 05 indicates MOSART is OK cp 05 jr z,DONE call DOINIT DONE: ld a,(TPULSE) ;set desired dial mode ld c,a call CMDOUT call FNSTAT ;wait for completion jp SETDAT ;set data mode DOINIT: xor a out (STATUS),a ;clear MOSART by sending three zeros call MDELAY out (STATUS),a call MDELAY out (STATUS),a ld a,MOSRST ;issue internal reset out (STATUS),a call MDELAY ld a,(CURMOD) ;current mode byte out (STATUS),a call MDELAY ld a,FNMOD ;set function mode out (STATUS),a call MDELAY ret MDELAY: ex (sp),hl ;long delay with no side effects ex (sp),hl ex (sp),hl ex (sp),hl ret CURMOD: defb M12N81 ;current MOSART mode CURCTL: defb FNMOD ;current control byte ; Set the MOSART BPS rate PBPS: or a ;0=110 BPS jr z,OK110 ;Set to 110 cp 1 ;1=300 BPS jr z,OK300 ;Set to 300 cp 5 ;5=1200 BPS jr z,OK1200 ;Set to 1200 scf ;set carry as error flag ret ;no match - not supported OK110: ld b,B110 ;set 110 BPS xor a ;110 BPS value jr LOADBP ;Go load it OK300: ld b,B300 ;set 300 BPS ld a,1 ;300 BPS value jr LOADBP OK1200: ld b,B1200 ;set 1200 BPS async ld a,5 ;1200 BPS value LOADBP: ld (MSPEED),a ;Change modem speed value ld a,(CURMOD) ;get current mode value and 11111100b ;mask off BPS rate or b ;set in new BPS rate bits ld (CURMOD),a ;save new mode byte jr MOSNBP ;(Re)initialize modem ;Sign-on message SYSVER: ld de,SOMESG ld c,PRINT call MEX CARRSH: ld de,NOMESG ;Tell about carrier call CARRCK ;Check for it ld c,PRINT call z,MEX ;Print the "no" if no carrier ld de,CARMSG ;Print "carrier present" ld c,PRINT call MEX ret SOMESG: defb 'SB180 with XECOM 12xx MOSART - Version ' defb VERS/10+'0','.' defb VERS MOD 10+'0',' ' defb CR,LF,'$' NOMESG: defb 'No $' CARMSG: defb 'carrier present',CR,LF,'$' ;check the MOSART for carrier-present (Z=no) CARRCK: ld a,(CONNECT) ;see if we had a connection or a jr nz,CARCK1 ;if so, see if lost in a,(MODCT1) ;get status ld (TMPMOD),a ;save it and DSR ;see if connection present jr nz,CAROK ;jump if we have it ld a,(TMPMOD) ;if not, see if we have an info byte and DSR + RXRDY ;see if connection present cp RXRDY jr z,CAROK ;if so, assume connection still good jr CARLST ;otherwise, flag as no carrier CARCK1: in a,(MODCT1) ;Get status byte and DCDMASK ;mask off bits of interest cp DCDLOST jr z,CARLST CAROK: or 0ffh ;set non-zero if carrier present ret CARLST: xor a ;set zero flag to show carrier lost ret CONNECT: defb 0 ;set non-zero after connection made TMPMOD: defb 0 ;temporary storage for modem status ; Output a command to the MOSART ; Input: C = command character ; Note that the MOSART is left in FUNCTION Mode!! CMDOUT: ld a,FNMOD ;set function mode ld (CURCTL),a ;save control status out (STATUS),a ld a,c ;get command out (DATA),a ret ; Get the current MOSART phone line status GETSTAT: ;get status of call ld c,'M' ;set monitor mode call CMDOUT ; Get MOSART function status ; Waits for the MOSART to complete the function, then gets the ; information byte, if present. ; Output: Zero flag set = no error. ; Non-zero = error. A holds the information byte. FNSTAT: in a,(STATUS) ;get status byte ld c,a ;save it and TXRDY jr z,FNSTAT ;loop until function completes ld a,c ;get back status and RXRDY ;see if RxRdy set, indicating error ret z ;return OK if no error in a,(DATA) ;if error, get information byte or a ;and set flag ret ; Set MOSART to data mode SETDAT: ld a,(CURCTL) ;set data mode or RTS ld (CURCTL),a out (STATUS),a ret ;The following routine sends a break "character" to the remote computer. PBREAK: ld c,BRKMOD ;set break mode call CMDOUT ld b,3 ;300 ms delay value ld c,TIMER ;MEX service function #254 call MEX ;Wait that long jr SETDAT ;reset break & set to data mode ; Hang up the MOSART MHANGP: xor a ;no messages if MEX calls HANGUP: push af ;save possible status byte ld a,(BOOTFL) ;see if boot fail selected or a jr z,HANGP1 ;if not, don't worry about messages pop af ;get back status byte push af or a jr z,HANGP1 ;zero means no message needed add a ;double status code for table offset ld hl,MESTBL ;table address into HL ld c,a ;offset into BC ld b,0 add hl,bc ;point to the address of the message ld e,(hl) inc hl ld d,(hl) ;put message pointer in DE ld c,PRINT call MEX ;let MEX print the message HANGP1: xor a ;send a zero to hang up out (STATUS),a ld b,5 ;wait 500 ms ld c,TIMER call MEX ld a,(CURCTL) ;get current control byte and not DTR ;clear DTR to show no connection ld (CURCTL),a out (STATUS),a xor a ;clear connection flag ld (CONNECT),a pop af ret MESTBL: defw DUMMS ;dummy message defw BUSYMS defw NOANMS defw ABRTMS defw MDERMS defw NORGMS defw NODTMS DUMMS: defb '$' BUSYMS: defb CR,LF,'Phone Busy$' NOANMS: defb CR,LF,'No answer$' ABRTMS: defb CR,LF,'Keyboard abort$' MDERMS: defb CR,LF,'Modem Dialing Error$' NORGMS: defb CR,LF,'Timeout - No Ring heard$' NODTMS: defb CR,LF,'Timeout - No Dial Tone$' ;The remainder of the hardware section implements the SET command. SETCMD: ld c,SBLANK ;Any arguments? call MEX jr c,SETSHO ;If not, go print out values ld de,CMDTBL ;Parse command call TSRCH ;From table push hl ;put (possible) function address on stack ret nc ;If we have one, execute it pop hl ;Nope, fix stack SETERR: ld de,SETEMS ;Print error ld c,PRINT call MEX jr STHELP ;and show what is allowed SETEMS: defb CR,LF,'SET command error',CR,LF,BELL,'$' ;SET command table ... note that tables are constructed of command- ;name (terminated by high bit=1) followed by word-data-value returned ;in HL by MEX service processor LOOKUP. Table must be terminated by ;a binary zero. ;Note that LOOKUP attempts to find the next item in the input stream ;in the table passed to it in HL. If found, the table data item is ;returned in HL; if not found, LOOKUP returns carry set. CMDTBL: defb '?'+80H ;"set ?" defw STHELP defb 'BP','S'+80H ;"set BPS" defw SETBPS defb 'SPK','R'+80H ;"set spkr" defw SETSPK defb 'DIA','L'+80H ;"set dial" defw STDIAL defb 'WAI','T'+80h ;"set wait" defw STWAIT defb 'PARIT','Y'+80h ;"set parity" defw SETPAR defb 'BI','T'+80h ;"set bit" defw SETBIT defb 'BOOTFAI','L'+80h ;"set bootfail" defw SETBFL defb 0 ;<<=== table terminator ;SET : print current statistics SETSHO: call CARRSH ;Show carrier present/not present ld hl,SHOTBL ;Get table of SHOW subroutines SETSLP: ld e,(hl) ;Get table address inc hl ld d,(hl) inc hl ld a,d ;End of table? or e ret z ;Exit if so push hl ;Save table pointer ex de,hl ;Adrs to HL call GOHL ;Do it call CRLF ;Print newline ld c,CHEKCC ;Check for console abort call MEX pop hl ;It's done jr nz,SETSLP ;Continue if no abort ret GOHL: jp (hl) ;table of SHOW subroutines SHOTBL: defw BPSHOW defw BISHOW defw PASHOW defw DISHOW defw SPSHOW defw WASHOW defw BFSHOW defw 0 ;<<== table terminator ;SET ? processor STHELP: ld de,HLPMSG ld c,PRINT call MEX ret ;The help message HLPMSG: defb CR,LF,LF,'SET commands for the MOSART:' defb CR,LF,LF,' SET BPS 1200 300 110' defb CR,LF,' SET SPKR OFF ON' defb CR,LF,' SET WAIT 20 40 60' defb CR,LF,' SET DIAL TONE PULSE' defb CR,LF,' SET PARITY NONE EVEN ODD' defb CR,LF,' SET BIT 8 7' defb CR,LF,' SET BOOTFAIL ON OFF' defb CR,LF,LF,'$' ;SET BPS processor ;This is not legal if a connection exists SETBPS: ld c,BPSPAR ;Function code call MEX ;Let MEX look up code jp c,SETERR ;Invalid code push af ;save BPS rate in a,(MODCT1) ;get MOSART status and DSR ;see if connection already established jr z,DOBPS ;OK to proceed if not call ILPRT defb CR,LF,"Can't change BPS rate while connected!",0 pop af ;clean up stack ret DOBPS: pop af ;get back BPS rate desired call PBPS jp c,SETERR ;Not-supported code BPSHOW: call ILPRT ;Display BPS defb 'BPS rate: ',0 ld a,(MSPEED) ld c,PRBPS ;Use MEX routine call MEX ret ;Speaker On/Off, Wait time, and Dial Mode may be changed without affecting ;an existing connection. ;SET SPKR processor SETSPK: ld de,SPKTBL ;lookup next input item in table call TSRCH jp c,SETERR ;if not found, error ld (SPKRST),a ;save value ld c,a call CMDOUT ;send the command to the MOSART call SETDAT ;set data mode SPSHOW: call ILPRT ;show spkr mode defb 'Speaker: ',0 ld a,(SPKRST) ;get spkr byte cp 'X' jr z,SPON ;spkr on SPOFF: call ILPRT defb 'Off',0 ret SPON: call ILPRT defb 'On',0 ret SPKTBL: defb 'OF','F'+80H ;set spkr off defb 'x',0 defb 'O','N'+80H ;set spkr on defb 'X',0 defb 0 ;<<=== table terminator SPKRST: defb 'X' ;speaker on/off status ;SET DIAL processor STDIAL: ld de,DIATBL ;lookup next input item in table call TSRCH jp c,SETERR ;if not found, error ld (TPULSE),a ;save new value ld c,a call CMDOUT ;output the command call SETDAT ;set data mode DISHOW: call ILPRT ;show dial mode defb 'Dial mode: ',0 ld a,(TPULSE) ;get dial byte cp 'T' jr z,DTONE call ILPRT defb 'Rotary pulse',0 ret DTONE: call ILPRT defb 'Tone',0 ret ;DIAL argument table DIATBL: defb 'TON','E'+80H ;tone defb 'T',0 defb 'PULS','E'+80H ;pulse defb 'R',0 defb 0 ;<<=== table terminator ;SET WAIT processor STWAIT: ld de,WAITBL ;lookup next input item in table call TSRCH jp c,SETERR ;if not found, error ld (WAITVL),a ;save value WASHOW: call ILPRT ;show current wait value defb 'Wait: ',0 ld a,(WAITVL) ld e,'2' cp 1 jr z,SECOUT ld e,'4' cp 2 jr z,SECOUT ld e,'6' SECOUT: ld c,CONOUT call MEX ;let MEX print the character call ILPRT defb '0 seconds.',0 ret WAITBL: defb '2','0'+80H ;set 20 sec wait defb 1,0 defb '4','0'+80H ;set 40 sec wait defb 2,0 defb '6','0'+80H ;set 60 sec wait defb 3,0 defb 0 ;<<=== table terminator ;Parity and number of data bits may be changed without disturbing an existing ;connection (if the other end can do the same!) ;SET PARITY processor SETPAR: ld de,PARTBL ;lookup next input item in table call TSRCH jp c,SETERR ;if not found, error ld (PARVAL),a ;save value ld c,a call CMDOUT ;send the command to the MOSART call SETDAT ;set data mode PASHOW: call ILPRT ;show current wait value defb 'Parity: ',0 ld a,(PARVAL) cp '>' jr z,EVNPAR cp '<' jr z,ODDPAR call ILPRT defb 'None',0 ld b,0 ;set up no parity jr DOPAR EVNPAR: call ILPRT defb 'Even',0 ld b,PARENA + PAREVN ;set up even parity jr DOPAR ODDPAR: call ILPRT defb 'Odd',0 ld b,PARENA ;else odd parity DOPAR: ld a,(CURMOD) ;get current mode value and 11001111b ;mask off parity bits or b ;set in new parity bits ld (CURMOD),a ;save new mode byte ret PARTBL: defb 'NON','E'+80H ;set no parity defb '=',0 defb 'EVE','N'+80H ;set even parity defb '>',0 defb 'OD','D'+80H ;set odd parity defb '<',0 defb 0 ;<<=== table terminator PARVAL: defb '=' ;SET BIT processor SETBIT: ld de,BITTBL ;lookup next input item in table call TSRCH jp c,SETERR ;if not found, error ld (BITVAL),a ;save value ld c,a call CMDOUT ;send the command to the MOSART call SETDAT ;set data mode BISHOW: call ILPRT ;show current wait value defb 'Data bits: ',0 ld a,(BITVAL) cp 'E' - '@' jr z,EIGHTBT call ILPRT defb 'Seven',0 ld b,BIT7 ;set up 7 bit jr DOBIT EIGHTBT: call ILPRT defb 'Eight',0 ld b,BIT8 ;set up 8 bit DOBIT: ld a,(CURMOD) ;get current mode value and 11110011b ;mask off data length bits or b ;set in new length bits ld (CURMOD),a ;save new mode byte ret BITTBL: defb '8'+80H ;set 8 bits defb 'E' - '@',0 defb '7'+80H ;set 7 bits defb 'S' - '@',0 defb 0 ;<<=== table terminator BITVAL: defb 'E' - '@' ;SET BOOTFAIL processor ;The BOOTFAIL parameter implements limited (very!) conditional execution ;for MEX READ files. When set ON, this causes the DIAL routine to do a warm ;boot if dialing fails. This allows a MEX READ file running under ZEX, XSUB, ;or another text-capable batch processor, to abort MEX if the call fails, so ;the next job on the list can be processed. SETBFL: ld de,BFLTBL ;lookup next input item in table call TSRCH jp c,SETERR ;if not found, error sub '0' ;convert to 0 or 1 hex ld (BOOTFL),a ;save value ld c,a BFSHOW: call ILPRT ;show boot fail mode defb 'Boot Fail: ',0 ld a,(BOOTFL) ;get boot fail flag or a jr nz,BTFLON ;boot fail on call ILPRT defb 'Off',0 ret BTFLON: call ILPRT defb 'On',0 ret BFLTBL: defb 'OF','F'+80H ;set boot fail off defb '0',0 defb 'O','N'+80H ;set boot fail on defb '1',0 defb 0 ;<<=== table terminator BOOTFL: defb 0 ;boot fail on/off status ;Compare next input-stream item in table @DE; CY=1 if not found, ;else HL=matched data item TSRCH: ld c,LOOKUP ;Get function code jp MEX ;Pass to MEX processor ;Newline on console CRLF: ld a,CR call TYPE ld a,LF ;Fall into TYPE ;type char in A on console TYPE: push hl ;Save 'em push de push bc ld e,a ld c,CONOUT ;Print via MEX call MEX pop bc pop de pop hl ret ;Print an in-line message using MEX ILPRT: ld c,ILP ;Get function code jp MEX ;Go do it DIALOC equ 0900H ;Dialing code goes here if $ gt DIALOC ;see if we are too fat .printx 'Hardware Section is too long!!' else EXROOM equ DIALOC - $ ;expansion room endif subttl 'MEX XECOM 12xx MOSART Modem Overlay' ;The MOSART disconects from the line by having the control program reset the ;DTR bit in the control byte. This equates to the 'hardware' disconnect, ;which is found in the hardware section. There is no equivalent of the ;Smartmodem-compatible 'software' disconnect. NDISCV equ 015FH ;New (MexPlus) smart modem disconnect here org NDISCV jp DISCV ;No software disconnect available org DIALOC ;The 'signature word' that is located here in the 'MXM-' type overlays is ;not used in this overlay, since the hardware and modem sections are not ;independent. Loading the modem overlay without loading the hardware section ;at the same time would do very strange things to the system. ;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. This version uses this fact to buffer the digits ;until the end-dial sequence is received, then the entire number is dialed. ;After the 254 start-dial sequence, MEX will call the overlay with digits, ;one at a time. MEX will make no assumptions about the digits, and will send ;each to the DIAL routine un-inspected. This overlay uses this fact to ;support the pause characters 'P' (5 sec pause) and 'p' (2 sec pause), the ;'wait for next dialtone' characters 'W' or 'w', and the 'use installed prefix ;number' characters 'Q', 'q', 'Y', and 'y'. ;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) ; 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 ; 5 - No ring detected (only for modems that can detect this condition) ; 6 - No dial tone (only for modems that can detect this condition) ;The MOSART supports all of these status returns. ; ***No other codes should be returned after an end-dial sequence*** ;The DIAL routine is free to use any of the registers, but must return one of ;the above codes after an end-dial sequence DIAL: cp 255 ;End dial? jr z,ENDIAL ;jump if so cp 254 ;Start dial? jr nz,DODIG ;Go send to modem if not ;'Start Dial' (254) byte received ld hl,NUMBER ;set up number pointer ld (NUMPTR),hl ret NUMBER: defs 30 ;space for number (MEX's max size is 27) NUMPTR: defw NUMBER ;pointer to current digit in number ;Put next digit into string DODIG: ld hl,(NUMPTR) ;get pointer to number string ld (hl),a ;save the digit inc hl ;bump to next position ld (NUMPTR),hl ;save updated pointer ret ;'End Dial' (255) byte received ENDIAL: ld a,(BOOTFL) ;see if warm-boot-on-fail set or a jr z,ENDL1 ;skip if not ld hl,0 ;if boot fail requested, put 0 on the push hl ;stack as the 'return' address ENDL1: ld hl,(NUMPTR) ;get number pointer xor a ;put a null there to terminate string ld (hl),a ENDL2: ld hl,NUMBER ;point to number string ld a,10 ;initialize dial tone wait loop counter ld (TONECT),a ld a,(TWAIT) ;see if the last number ended in 'W' or a call z,MHANGP ;make sure phone is on hook if not call DIALIT ;Dial the completed string - status in A cp 6 ;see if no dial tone from MOSART jr nz,ENDL3 ;skip if not ld a,(TWAIT) ;if so, see if in dial tone wait loop or a jr nz,ENDL2 ;if so, try again ld a,6 ;if not, return error status ret ENDL3: cp 4 ;check for dialing error ret z cp 3 ;see if DIALIT got a keyboard abort ret z ;After completing the dialing of the number (including any prefix specified), ;the following loop waits for a result from the modem, up to about 1 minute; ;this value may be adjusted in increments of 17 seconds (the timeout value ;the MOSART uses) by changing the loop counter value below. ld (RANG),a ;flag no ring heard ld a,3 ;timeout loop counter WAITVL: equ $ - 1 ;address of byte to change ld (TIMCTR),a ;3 * 17 seconds is about 1 minute STATLP: call GETSTAT ;get the result byte from the MOSART jp z,ONLINE ;zero means connection established ; If no connection established, find out what happened DIALER: cp 'B' jr z,BUSY cp 'D' jr z,DIALTONE cp 'R' jp z,RINGING cp 'V' jp z,VOICE cp 'F' jp z,FAILED cp 'I' jp z,INAPP ;Drop through for timeout ('T') status call CKABRT ;check for keyboard abort or a ;A = 0 if no abort jr z,CKTIME ;continue if not ld a,3 ;flag abort status jp HANGUP ;hang up on user abort CKTIME: ld hl,TIMCTR ;decrement timeout loop counter dec (hl) jr nz,STATLP ;loop back if not timed out ld a,(RANG) ;see if ring has been heard or a ld a,2 ;flag 'Timed out waiting for Modem' jp nz,HANGUP ;return if ring was heard ld a,5 ;return 'No ring heard' code jp HANGUP CKABRT: ld c,KSTAT ;Check for keypress call MEX or a ret z ;return zero if none ld e,DCONIN ld c,DCONIO ;Get key hit, with no echo call MEX cp 'C' - '@' ;check for Ctrl-C ret z ;return if so xor a ;clear A ret BUSY: ld a,(TWAIT) ;if in a tone wait loop, try again or a jp nz,ENDL2 ld a,1 ;return code for BUSY jp HANGUP ;Frequently, the other end starts transmitting as soon as it answers. This ;can sound like a dial tone. This routine checks to see if a dial tone was ;expected ('w' in the number); if not, it attempts to originate a connection ;in case the 'dial tone' is really the other end's answer tone. DIALTONE: ld a,(TWAIT) ;see if number ended with dial tone wait or a jr z,CKRANG ;if not, see if ring heard ld a,(BOOTFL) ;if dial tone wait, dial tone is OK or a ;see if boot fail requested ret z ;return if not pop hl ;if so, pop the extra 0 off the stack xor a ret ;return with good status CKRANG: ld a,(RANG) ;see if the phone rang or a jp nz,ONLINE ;if so, this must really be an answer tone ;Sometimes the other end answers before the MOSART has time to recognize a ;ring; try to originate a connection just in case. call ILPRT ;let user know what we're doing defb CR,LF,'Possible Second Dial Tone...',0 ld c,'O' ;send 'originate' command call CMDOUT jp STATLP ;let the normal code figure it out; note that ;the 'O' command does not return a 'D' status, ;so we don't have to worry about getting ;stuck in a loop. TWAIT: defb 0 ;non-zero if number ended with 'W' FAILED: call ILPRT ;error if answer tone heard but no connection defb CR,LF,'Connection Failed',0 FAIL1: ld a,4 jp HANGUP ;Depending on where in the ring cycle the connection completes,the MOSART may ;take up to 10 seconds to recognize that the other end is ringing. Since the ;other modem will frequently answer and start transmitting before the MOSART ;recognizes a ring, the Monitor ('M') function will return 'Inappropriate' as ;the status, because it is trying to establish a connection and one already ;exists. Thus, the 'I' status byte also indicates a successful connection. INAPP: jr ONLINE ;'Inappropriate' returned if the connection is ;already established, i.e. the other end ;started talking immediately VOICE: call PAUSE2 ;let's check this one again... call GETSTAT ;since switching transients look like a voice cp 'V' jp nz,STATLP ;if not still voice, recheck call ILPRT ;Whoops, we have ourselves a human. defb BELL,'VOICE!! ',0 ;Print a warning ld a,3 ;Return with abort so we don't to it again jp HANGUP RINGING: call ILPRT defb CR,LF,'Ringing... ',0 ld (RANG),a ;set flag that ring was heard ld b,7 ;set up ring loop counter - 20 seconds call PAUSE2 ;pause 2 seconds RINGLP: call GETSTAT ;get status cp 'R' jp nz,STATLP ;when ring stops, jump back to main loop djnz RINGLP ;loop for next ring ld a,2 ;if we time out, return 'No Answer' code jp HANGUP RANG: defb 0 ;non-zero if ring heard PAUSE2: ld c,'p' ;2 second pause call CMDOUT jp FNSTAT ;wait for completion ; Place any setup routines here that you want to be executed once the ; connection is established. Such routines might include setting a ; timer or turning the speaker off (code provided below; just remove ; the semicolons). Make sure the 'xor a' is the last thing before ; the return. ONLINE: call ILPRT defb CR,LF,'On line',0 ld a,0ffh ;set flag for connection established ld (CONNECT),a ; ld a,'x' ;turn the speaker off ; ld (SPKRST),a ; ld c,a ; call CMDOUT call SETDAT ;set data mode ld a,(BOOTFL) or a ;see if boot fail requested ret z ;return if not pop hl ;if so, pop the extra 0 off the stack, xor a ;return 'connected' status ret ;The dialing routine. This routine processes the number string. The ;following valid characters are recognized: ; 0 - 9: Dials the corresponding digit. ; Q: Dials the installed prefix sequence as soon as the 'Q' is seen; ; this should be the first character in the number. ; Y: Dials the alternate prefix; must be first if used. ; W: Waits for a dial tone before continuing. ;Note that EVERYTHING in the number except 'W', 'Q,' or 'Y' is sent to the ;MOSART. If the string includes other characters, the MOSART will respond ;according to its command set, which might result in changing the mode of ;operation, initiating an undesired command, or attempting to execute an ;unimplemented function. Be careful when you construct your phone libraries ;to ensure that only valid characters are included in the numbers. Neither ;the MEX program or this overlay attempts to check the validity of the ;characters. DIALIT: ld c,'W' ;wait for dial tone call CMDOUT ;(times out in 5 seconds) call FNSTAT jr z,DIALLP ;continue if heard OK call CKABRT ;check for console abort or a jr z,DIALT1 ld a,3 ;load abort code & exit jp HANGUP DIALT1: ld a,(TONECT) ;bump loop counter dec a ld (TONECT),a jr nz,DIALIT ;loop if more time left ;we have timed out without getting a dial tone ld a,(BOOTFL) ;see if HANGUP will print the message or a jr nz,DIALT2 ;skip if so call ILPRT ;if not, we'll tell him ourselves defb CR,LF,'Timed out waiting for Dial Tone',0 DIALT2: ld a,6 ;'No Dial Tone' result code jp HANGUP ;hang up if not TONECT: defb 10 ;'wait-for-dial-tone' loop counter DIALLP: ld a,(hl) ;get the digit to dial inc hl ;point to next digit or a jr nz,DIALP2 ;continue if not end of string ;end of the digit string ld a,(PREFLG) ;see if we were dialing a prefix or a ret z ;return zero if not xor a ld (PREFLG),a ;if so, reset the prefix string flag ld hl,(NUMPTR) ;get back the pointer to the real number jr DIALLP ;and resume the dialing loop DIALP2: cp 'W' ;see if dialtone wait jr z,DWAIT ;if so, wait for another dial tone cp 'w' ;lower case is OK too jr nz,CKPRE ;if not, check for 'Q' DWAIT: call ILPRT ;let user know what's going on defb CR,LF,'Waiting for the next Dial Tone...',0 ld a,10 ;reinitialize loop counter ld (TONECT),a ld (TWAIT),a ;flag dial tone wait jp DIALIT ;and start over on the new dial tone CKPRE: cp 'Q' ;check for prefix jr z,DOPRE cp 'q' ;lower case is just as good jr nz,CKALT ;otherwise, check for alternate prefix DOPRE: call CKFRST ;make sure the 'Q' was the first character jp nz,HANGUP ;exit with bad status if not dec a ;decrementing from 0 is guaranteed to not be 0 ld (PREFLG),a ;set flag for processing prefix string ld (NUMPTR),hl ;save the pointer to the real number ld hl,PRENUM ;point to the prefix string jr DIALLP ;and loop back to dial it first PRENUM: defb '18005551212W12345678W',0 ;MUST end with a null! defs 40 - ($ - PRENUM) ;allow for long prefix strings PREFLG: defb 0 ;non-zero when dialing the prefix string CKALT: cp 'Y' ;check for alternate prefix jr z,DOALT cp 'y' ;lower case is just as good jr nz,DONUM ;otherwise, assume it is a digit to dial DOALT: call CKFRST ;make sure the 'Y' was the first character jp nz,HANGUP ;exit with bad status if not dec a ld (PREFLG),a ;set flag for processing prefix string ld (NUMPTR),hl ;save the pointer to the real number ld hl,ALTPRE ;point to the alternate prefix string jp DIALLP ;and loop back to dial it first ALTPRE: defb '18001234567W87654321W',0 ;MUST end with a null! defs 40 - ($ - ALTPRE) ;allow for long prefix strings DONUM: ld c,a xor a ;clear dial tone wait flag ld (TWAIT),a call CMDOUT ;dial the digit call FNSTAT ;wait for completion jp z,DIALLP ;loop until done as long as status good ld a,4 ;flag dialing error ret CKFRST: ld de,NUMBER + 1 ;this is where the pointer should be if I8080 ld a,h ;make sure D and H are the same sub d jp nz, PRERR ld a,l ;check the low byte of the pointer sub e ret z ;if OK, return good else ex de,hl ;save HL or a ;make sure carry is cleared sbc hl,de ;see if HL points to the right place ex de,hl ;swap back ld a,l ;set up A for decrement ret z ;return OK if the same endif PRERR: call ILPRT defb CR,LF,"'Q' or 'Y' prefix specifier must be first in number.",0 ld a,4 or a ;set error flag if not the first character ret TIMCTR: defb 3 ;timeout loop counter if $ gt MEX .printx 'Modem Section is too big!!' else MDMSPA equ MEX - $ ;modem section expansion space endif end