.COMMENT & MXH-CZ10.Z80 MEX Overlay for CardZ180 Apple CP/M Card CardZ180 is available from: Slot 8 Associates POB 10098 Rochester, NY 14610 Revision History: v1.1 Bob Sass 8/3/89 - fixed download problem with mex114, was a "typo" v1.0 Jim Lill - replaces all previous MXO versions - changed MXO to MXH for MEXplus, still works with MEX114 - added 'synthesized' break - add h/w disconnect via dropping RTS (ASCI0 only) - GOODBYE just leaves program now w/o affecting port. ........................................................................ 64180 ASCI0 (modem port) notes: - like the Apple SSC, nothing is received unless CD is on. Lack of CD might even cause hangs. If your modem has a switch, force CD on. Otherwise jumper it in the cable. For null modem duty, jumper RTS to CD - the 64180 does NOT provide DTR. The usual method is to use RTS. This overlay uses RTS for h/w disconnect. ....................................................................... CardZ180 Serial Port Pinouts (n/c unless marked): Modem (ASCI0) Port: 1 20 \ DTR (actually RTS) TXD 2 19 | RXD 3 18 | RTS 4 17 | <== if ribbon cable is used you CTS 5 16 | may wish to add this jumper 6 15 | (14-20) on PCB if your PCB GND 7 14 / does not have it. DCD 8 13 9 12 10 11 The Modem port cable may be easily made with 20 conductor Ribbon cable, an IDC DB25 connector and an IDS20 header connector. Keep the ribbon cable at the 'low number end' of the DB25 connector. You must either add the above jumper or run the ribbon cable "thru" the DB25 and connect lines 4 and 20. Terminal (ASCI1) Port: 1 20 RXD 2 19 TXD 3 18 CTS 4 17 5 16 GND 6 15 7 14 8 13 9 12 10 11 ....................................................................... Assemble with Z80ASM! & REV EQU 11 ; Overlay revision level ; ; Misc equates ; NO EQU 0 YES EQU NOT NO TPA EQU 100H CR EQU 13 LF EQU 10 TAB EQU 9 ; ; HD64180 port definitions PORT EQU 0 ; ASCI 0 or 1 ; IF PORT EQ 0 ; use ASCI0 CNTLA EQU 00H ; Control port CNTLB EQU 02H ; Baud rate port (+ even/odd parity) STATP EQU 04H ; Status port MODOUT EQU 06H ; Data port out MODIN EQU 08H ; Data port in ELSE ; use ASCI1 CNTLA EQU 01H ; Control port CNTLB EQU 03H ; Baud rate port (+ even/odd parity) STATP EQU 05H ; Status port MODOUT EQU 07H ; Data port out MODIN EQU 09H ; Data port in ENDIF ; ; HD64180 bit definitions ; MDRCVB EQU 80H ; Receive bit (DAV) MDRCVR EQU 80H ; Receive ready MDSNDB EQU 02H ; Send bit MDSNDR EQU 02H ; Send ready bit ; ;................................ ; ; So Z80 assemblers can handle it ; IN0 MACRO ?A,?B DB 0EDH DB 38H DB ?B ENDM ; OUT0 MACRO ?B,?A DB 0EDH DB 39H DB ?B ENDM ; ;................................... ; ; MEX service processor stuff ; MEX EQU 0D00H ; Address of the service processor 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 BDPARS EQU 245 ; Parse baud-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 PRBAUD EQU 238 ; Print baud rate ; ; CONOUT EQU 2 ; Simulated BDOS function 2: console char out PRINT EQU 9 ; Simulated BDOS function 9: print string INBUF EQU 10 ; Input buffer, same structure as BDOS 10 ; ORG TPA ; We begin ; DB 0C3h ; for MEXplus DS 2 ; MEX has a JMP 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: DB NO ; Yes=PMMI modem \ / These 2 locations are not SMODEM: DB YES ; Yes=Smartmodem / \ referenced by MEX TPULSE: DB 'T' ; T=touch, P=pulse (not referenced by MEX) CLOCK: DB 114 ; Clock speed (mhz) x 10, up to 25.5 mhz. ; ; ***NOTE! *** There seems to be a bug in MEX+ which occurs when the ; 'clock' variable is set to any number >114. Since a 9.24 mhz 180 ; chip runs as fast as a 12mhz. Z80, this creates a problem. The ; symptoms include: ; ; - Dial string aborting immediately with a 'no answer' message ; - Persistent errors in Ymodem batch transfer ; ; MSPEED: DB 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: DB 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: DB 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: DB 5 ; Number of directory columns SETFL: DB YES ; Yes=user-defined SET command SCRTST: DB YES ; Yes=if home cursor and clear screen ; Routine at CLRSCRN DB 0 ; Was once ACKNAK, now spare BAKFLG: DB YES ; Yes=make .BAK file CRCDFL: DB YES ; Yes=default to CRC checking ; No=default to Checksum checking TOGCRC: DB YES ; Yes=allow toggling of Checksum to CRC CVTBS: DB NO ; Yes=convert backspace to rub TOGLBK: DB YES ; Yes=allow toggling of bksp to rub ADDLF: DB NO ; No=no LF after CR to send file in ; Terminal mode (added by remote echo) TOGLF: DB YES ; Yes=allow toggling of LF after CR TRNLOG: DB NO ; Yes=allow transmission of logon ; Write logon sequence at location LOGON SAVCCP: DB YES ; Yes=do not overwrite CCP LOCNXT: DB YES ; Yes=local cmd if EXTCHR precedes ; No=not local cmd if EXTCHR precedes TOGLOC: DB YES ; Yes=allow toggling of LOCNXTCHR LSTTST: DB YES ; Yes=allow toggling of printer on/off ; In terminal mode. Set to no if using ; The printer port for the modem XOFTST: DB NO ; Yes=allow testing of XOFF from remote ; While sending a file in terminal mode XONWT: DB NO ; Yes=wait for XON after sending CR while ; Transmitting a file in terminal mode TOGXOF: DB YES ; Yes=allow toggling of XOFF testing IGNCTL: DB NO ; Yes=do not send control characters ; Above CTL-M to CRT in terminal mode ; No=send any incoming CTL-char to CRT EXTRA1: DB 0 ; For future expansion EXTRA2: DB 0 ; For future expansion BRKCHR: DB '@'-40H ; ^@ = Send a 300 ms. break tone NOCONN: DB 'N'-40H ; ^N = Disconnect from phone line LOGCHR: DB 'L'-40H ; ^L = Send logon LSTCHR: DB 'P'-40H ; ^P = Toggle printer UNSVCH: DB 'R'-40H ; ^R = Close input text buffer TRNCHR: DB 'T'-40H ; ^T = Transmit file to remote SAVCHR: DB 'Y'-40H ; ^Y = Open input text buffer EXTCHR: DB 1BH ; ESC = Send next character DB 0 ; Not used DB 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) ; INSTAT: IN0 A,(STATP) ; In modem status port RET DB 0,0,0,0,0,0 ; Spares ; OTDATA: OUT0 (MODOUT),A ; Out modem data port RET DB 0,0,0,0,0,0 ; Spares ; INDATA: IN0 A,(MODIN) ; In modem data port RET DB 0,0,0,0,0,0 ; Spares ; ; 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 ; DCDTEST: JP DCDDET ;\_ for MEXplus RNGTEST: JP RNGDET ;/ DS 6 ; ; Special modem function jump table: if your overlay cannot handle ; some of these, change the jump to "DS 3", so the code present in ; MEX will be retained. Thus, if your modem can't dial, change the ; JMP PDIAL at DIALV to DS 3, and MEX will print a "not-implemented" ; diagnostic for any commands that require dialing. ; ; GOODBV is called just before MEX exits to CP/M. If your overlay ; requires some exit cleanup, do it here. ; ; INMODV is called when MEX starts up; use INMODV to initialize the modem. ; ; NEWBDV is used for phone-number baud rates and is called with a baud-rate ; code in the A register, value as follows: ; ; A=0: 110 baud A=1: 300 baud A=2: 450 baud ; A=3: 600 baud A=4: 710 baud A=5: 1200 baud ; A=6: 2400 baud A=7: 4800 baud A=8: 19200 baud ; LOGON: DS 2 ; Needed for MDM compat, not ref'd by MEX DIALV: DS 3 ; Dial routine is in modem overlay DISCV: JP DISCON ; Disconnect the modem (in modem overlay) GOODBV: JP EXXIT ; Called before exit to CP/M INMODV: JP NITMOD ; Initialization. Called at cold-start NEWBDV: JP PBAUD ; Set baud rate NOPARV: DS 3 ; Set modem for no-parity (not implemented) PARITV: DS 3 ; Set modem parity (not implemented) SETUPV: JP SETCMD ; SET command processor SPMENV: DS 3 ; Not used with MEX VERSNV: JP SYSVER ; Overlay's voice in the sign-on message BREAKV: JP SNDBRK ; Send a break ; ; ILPRTV: DS 3 ; Replace with MEX function 9 INBUFV: DS 3 ; Replace with MEX function 10 ILCMPV: DS 3 ; Replace with table lookup funct. 247 INMDMV: DS 3 ; Replace with MEX function 255 NXSCRV: DS 3 ; Not supported by MEX (returns w/no action) TIMERV: DS 3 ; Replace with MEX function 254 ; ; ; Clear/screen and clear/end-of-screen. Each routine must use the ; full 9 bytes alloted (may be padded with nulls). ; ; CLREOS: LD DE,EOSMSG LD C,PRINT CALL MEX RET ; ; CLS: LD DE,CLSMSG LD C,PRINT CALL MEX RET ;................................ ; ; *** END OF FIXED FORMAT AREA *** ; org 0200h ; give MEXplus enough room ;............................... ; ; DCD Detect, used by MEXplus REO DCDDET: RET ;................................. ; ; Ring Detect, reserved but never used by MEXplus RNGDET: RET ;................................. ; ; Send a synthesized break SNDBRK: LD A,20h ;divisor for 19200 OUT0 (CNTLB),A ;set baud LD HL,575 LD DE,1 SEND0: PUSH HL PUSH DE SMDRY: LD C,SNDRDY ;\ CALL MEX ; \ JR NZ,SMDRY ; make sure modem is ready LD B,0 ;\ LD C,SNDCHR ; \ CALL MEX ; send a null to modem POP DE POP HL SBC HL,DE ;because a 16-bit DEC doesn't affect flags JR NZ,SEND0 LD A,(MSPEED) ;reset to normal baud JP PBAUD ;................................... ; ; Disconnect via hardware, drop RTS ; DISCON: IF PORT EQ 0 ; only ASCI0 has RTS LD B,5 ;\ LD C,TIMER ; \ CALL MEX ; wait a 1/2sec for things to settle down IN0 A,(CNTlA) ; get the current settings PUSH AF ; save 'em OR 00010000b ;\ OUT0 (CNTLA),A ; turn off RTS LD B,20 ;\ LD C,TIMER ; \ CALL MEX ; leave it off 2 sec POP AF ; get the original settings AND 11101111b ; make sure RTS is on OUT0 (CNTLA),A ; and turn RTS back on LD B,5 ;\ LD C,TIMER ; \ CALL MEX ; time for modem to recover ENDIF RET ;.................................. ; ; Modem initialization. ; NITMOD: PUSH HL LD HL,(XPARITY) LD A,(BITS) OR L LD L,A ; LD A,(STOPS) OR L LD L,A ; IN0 A,(CNTLA) LD (SAVCT1),A OR 01100000b ; tx, rx enabled, rts' true AND 01100000b ; multi-processor off, reset error flags, ; clear all parity & stopbit settings OR L ; 'or' in the new p&s settings OUT0 (CNTLA),A ; IN0 A,(CNTLB) ; get ctrl B LD (SAVBAUD),A AND 00101111b ; clear multi-proc mode, set even parity OR H ; 'or' in our default settings OUT0 (CNTLB),A ; LD A,0 OUT0 (STATP),A ; no rx or tx interrupts! ; POP HL LD A,(MSPEED) JP PBAUD ;................................. ; ; EXIT routine ; EXXIT: ; ; LD A,(SAVBAUD) ;we wanna leave and come back ; OUT0 (CNTLB),A ; ; LD A,(SAVCT1) ; OUT0 (CNTLA),A RET ;................................ ; ; Set baud-rate code in A (if supported by your modem overlay). NOTE: this ; routine (ie, the one vectored through NEWBDV) should update MSPEED with ; the passed code, but ONLY if that rate is supported by the hardware. ; PBAUD: PUSH HL ; Don't alter anybody PUSH DE PUSH BC LD E,A ; Code to DE LD D,0 LD HL,BAUDTB ; Offset into table ADD HL,DE LD A,(HL) ; Fetch code OR A ; 0? (means unsupported code) SCF ; Return error for STBAUD caller JP Z,PBEXIT ; Exit if so AND 7FH ; Change 80H to zero (if 3.072 MHz clock) LD L,A IN0 A,(CNTLB) AND 0D0H OR L OUT0 (CNTLB),A ; Good rate, set it LD A,E ; Get speed code back LD (MSPEED),A ; Make it current PBEXIT: POP BC ; All done POP DE POP HL RET ; ; table of baud rate divisors for supported rates ; BAUDTB: DB 0,26H,0,25H,0 ;110,300,450,600,710 DB 24H,23H,22H,21H,20H ;1200,2400,4800,9600,19200 ;............................... ; Sign-on message ; SYSVER: LD DE,SOMESG LD C,PRINT CALL MEX RET ; SOMESG: DB CR,LF DB 'CardZ180 Overlay v' DB REV/10+'0' DB '.' DB REV MOD 10+'0',' Port: ASCI' DB PORT + 30h DB CR,LF,LF,'$' ; NOMESG: DB 'no $' CARMSG: DB 'carrier present',CR,LF,'$' ;............................. ; ; 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 ; Align output character LD C,CONOUT ; Print via MEX CALL MEX POP BC POP DE POP HL RET ;................................ ; ; strings to clear-to-end-of-screen, and clear-screen ; EOSMSG: DB 1BH,'Y' ;byte or string to clear to bottom of CRT DB '$' ;Clear to end-of-screen CLSMSG: DB 1BH,'*' ;byte or string to clear entire CRT DB '$' ;Clear whole screen ; ; Data area ; BITS: DB 4 XPARITY:DW 0 STOPS: DB 0 SAVCT1: DS 1 SAVBAUD:DS 1 ;............................... ; ; SET Processor ; SETCMD: LD C,SBLANK ; Any arguments? CALL MEX JP C,SETSHO ; If not, go print out values LD DE,CMDTBL ; Parse command CALL TSRCH ; From table PUSH HL ; Any 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 RET ; SETEMS: DB CR,LF,'SET command error',CR,LF,'$' ; ; SET command table ... CMDTBL: DB '?'+80H ; "set ?" DW STHELP DB 'BAU','D'+80H ; "set baud" DW STBAUD DB 'BIT','S'+80H ; "set bits" DW SETBITS DB 'PARIT','Y'+80H ; "set parity" DW STPRITY DB 'PA','R'+80H DW STPRITY DB 'STO','P'+80H ; "set stopbits" DW SETSTP DB 'STOP','S'+80H DW SETSTP DB 'DIA','L'+80H ; "set dial" DW STDIAL ; DB 0 ; <<=== table terminator ; ; SET : print current statistics ; SETSHO: 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: DW BDSHOW DW SHBITS DW SHPAR DW SHSTOPS DW SHDIAL DW 0 ; <<== table terminator ; ; SET ? processor ; STHELP: LD DE,HLPMSG LD C,PRINT CALL MEX RET ; ; The help message ; HLPMSG: DB CR,LF,'SET command, HD64180 version:',CR,LF,LF DB CR,LF,'SET BAUD (300,600,1200,2400,4800,9600,19200)' DB CR,LF,'SET BITS (7 or 8)' DB CR,LF,'SET PARITY (EVEN,ODD,NONE)' DB CR,LF,'SET STOP (1 or 2)' DB CR,LF,'SET DIAL (PULSE or TONE)' DB CR,LF,'$' ; ; SET BAUD processor ; STBAUD: LD C,BDPARS ; Function code CALL MEX ; Let MEX look up code JP C,SETERR ; Invalid code CALL PBAUD ; No, try to set it JP C,SETERR ; Not-supported code BDSHOW: CALL ILPRT ; Display baud DB 'Baud rate:',TAB,' ',0 LD A,(MSPEED) LD C,PRBAUD ; Use MEX routine CALL MEX RET ; ; ; SET BITS processor ; SETBITS:LD DE,BITTBL CALL TSRCH JP C,SETERR IN0 A,(CNTLA) AND 0FBH OR L OUT0 (CNTLA),A SHBITS: CALL ILPRT DB 'Data Bits:',TAB,' ',0 IN0 A,(CNTLA) AND 04H LD A,'7' JR Z,XBITS INC A XBITS: CALL TYPE RET ; BITTBL: DB '7'+80H DW 0 DB '8'+80H DW 4 DB 0 ; ; SET PARITY processor ; STPRITY:LD DE,PARTBL CALL TSRCH JP C,SETERR IN0 A,(CNTLA) AND 0FDH OR L OUT0 (CNTLA),A IN0 A,(CNTLB) AND 0EFH OR H OUT0 (CNTLB),A SHPAR: CALL ILPRT DB 'Parity:',TAB,TAB,' ',0 IN0 A,(CNTLA) AND 02H LD DE,NONE JR Z,PAREX IN0 A,(CNTLB) AND 10H LD DE,EVEN JR Z,PAREX LD DE,ODD PAREX: LD C,PRINT CALL MEX RET ; NONE: DB 'None$' EVEN: DB 'Even$' ODD: DB 'Odd$' PARTBL: DB 'NON','E'+80H DW 0000H DB 'N'+80H DW 0000H DB 'EVE','N'+80H DW 0002H DB 'E'+80H DW 0002H DB 'OD','D'+80H DW 1002H DB 'O'+80H DW 1002H DB 0 ; ; SET STOPBITS processor ; SETSTP: LD DE,STPTBL CALL TSRCH JP C,SETERR IN0 A,(CNTLA) AND 0FEH OR L OUT0 (CNTLA),A SHSTOPS:CALL ILPRT DB 'Stop Bits:',TAB,' ',0 IN0 A,(CNTLA) AND 01H ADD A,'1' CALL TYPE RET ; STPTBL: DB '1'+80H DW 0 DB '2'+80H DW 1 DB 0 ; ; SET DIAL processor ; STDIAL: LD DE,DIALTBL CALL TSRCH JP C,SETERR LD A,'T' CP L JR Z,XDIAL LD A,'P' XDIAL: LD (TPULSE),A SHDIAL: CALL ILPRT DB 'Dial mode:',TAB,' ',0 LD A,(TPULSE) CP 'T' LD DE,TOUCH JR Z,YDIAL LD DE,PULSE YDIAL: LD C,PRINT CALL MEX RET ; TOUCH: DB 'Touch-tone$' PULSE: DB 'Pulse$' DIALTBL:DB 'TON','E'+80H DB 'T',0 DB 'TOUC','H'+80H DB 'T',0 DB 'T'+80H DB 'T',0 DB 'PULS','E'+80H DB 'P',0 DB 'P'+80H DB 'P',0 DB 0 ;................................ ; ; 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 ;................................ ; ; Print in-line message ... blows away C register ; ILPRT: LD C,ILP ; Get function code JP MEX ; Go do it ; END ; MXH-CZnn.Z80