home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
ftp.barnyard.co.uk
/
2015.02.ftp.barnyard.co.uk.tar
/
ftp.barnyard.co.uk
/
cpm
/
walnut-creek-CDROM
/
OSBORNE
/
MEX01OVL.ZIP
/
MXO-OS36.AQM
/
MXO-OS36.ASM
Wrap
Assembly Source File
|
2000-06-30
|
64KB
|
2,686 lines
PAGE 62
TITLE 'MEX-Overlay for OSBORNE 1 V 3.6'
MACLIB Z80 ; you need the MAC assembler from Digital Research
; 19 NOV 90
REV EQU 36
; author:
; Klaus Schauer
; Auf den Kempen 31
; D-4052 Korschenbroich 2
; Germany (West)
; most of the routines based on the overlays
; MXO-OS24(22).ASM and MXO-SM16(14).ASM
; see MXO-OS36.DOC for more information
YES EQU 0FFH
NO EQU 0
; Assembler switches
NUMRES EQU YES ;YES = interpret numeric modem dial result code
DSCDTR EQU YES ;NO = disconnect modem only with ATH
SWTASK EQU YES ;YES = ask you for hardware baud switching
SETPEEK EQU NO ;YES = overlay with PEEK-routine
VTDEBUG EQU YES ;YES = unknown VT100 control chars displayd
; ASCII constants
BELL EQU 7 ;Bell
BS EQU 8 ;Backspace (Cursor Left)
TAB EQU 9 ;Tabulator
LF EQU 0Ah ;Linefeed
VT EQU 0Bh ;Vertical Tab
FF EQU 0Ch ;Form Feed
CR EQU 0Dh ;Carriage Return
XON EQU 11h ;Device Control 1
XOFF EQU 13h ;Device Control 3
CAN EQU 18h ;Cancel
SUBST EQU 1Ah ;Substitute
ESC EQU 1Bh ;Escape
FS EQU 1Ch ;File Separator
GS EQU 1Dh ;Group Separator
RS EQU 1Eh ;Record Separator
US EQU 1Fh ;Unit Separator
SPACE EQU 20h ;Space
DEL EQU 7Fh ;Delete
; OSBORNE 1 control chars
DOWN EQU 0Ah ;Cursor Down
UP EQU 0Bh ;Cursor Up
RIGHT EQU 0Ch ;Cursor RightèCLRSCR EQU 1Ah ;Clear Screen
HOME EQU 1Eh ;Home Cursor
; MEX system constants
MEX EQU 0D00h ;CALL MEX-Service-Routine
INMDM EQU 255 ;RETURN CHAR FROM MDM IN A, CY=NO CHR IN 100MS
TIMER EQU 254 ;delay 100ms * reg B
TMDINP EQU 253 ;B=# sec 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
INBUF EQU 10 ;input buffer, same structure as BDOS 10
PRINT EQU 9 ;simulated BDOS function 9: print string
IN$OUT EQU 6 ;simulated BDOS function 6: direct input/output
CONOUT EQU 2 ;simulated BDOS function 2: console char out
CONIN EQU 1 ;simulated BDOS funktion 1: console char in
START EQU 0EB9h ;JMP addr. to MEX1.14 START
CONVEC EQU 47F4h ;JMP addr. to console output vector
;Note: MEX1.12 -> CONVEC: EQU 468EH
; MEX1.14 -> CONVEC: EQU 47F4H
SEND$VEC EQU 4F09h ;JMP addr. to sendfile-prompt
;set PARITV: to YES included
; OSBORNE 1 and CP/M system constants
BOOT EQU 0 ; CP/M BOOT ADDRESS
JTABL EQU BOOT+1 ; CP/M JUMP TABLE ADDRESS
BDOS EQU 5
TPA EQU 0100h
SCRNPAC EQU 02400h ;Screen-Pac status register
MODCTLP EQU 02A00h ;status register for serial port
MODDATP EQU MODCTLP+1 ;data resister for serial port
VICTLA EQU 02C01h ;Video status register A
ROMRAM EQU 0EF08h ;(1) Bank switch flag: 0 = ROM , 1 = RAM
CURS EQU 0EF5Ah ;CBIOS-addr. for current cursor position
; (CURS+1) (CURS)
; -------- --------
; 1111RRRR RCCCCCCC R = row, C = column
LLIMIT EQU 0EF6Ch ;CBIOS-addr. for max. #column in a logical line
IESTK EQU 0EF6Fh ;save Stack Pointer here
ISTK EQU 0EF99h ;interrupt stack
INTBL EQU 0EFF0h ;(16) interrupt vector table
AHSENB EQU 68h ;CBIOS-offset to scroll flag
SCRSZE EQU 6Ah ;CBIOS-offset to screen sizeèCRSUP EQU 7Fh ;CBIOS-offset of vector to cursor up
PLUGH EQU 00A5h ;CBIOS-offset to Screen-Pac status byte
MAGIC EQU 03E5h ;CBIOS-offset to Sto-Plugh-subroutine (Screen-Pac)
; values to send to 6850 control register for
; 8 bits, no parity, 1 stop bit
; Various bit patterns for the 6850
RESET EQU 00000011b ;reset 6850
BAUD3 EQU 00000010b ;300 baud
BAUD12 EQU 00000001b ;1200 baud
BAUDMSK EQU 00000011b ;mask to get baud rate bits
BITMSK EQU 00011100b ;mask to get parity, etc. bits
RTSBIT EQU 01000000b ;setting this bit turns RTS OFF
BRKBIT EQU 01100000b ;bits to set to send break
MODSNDB EQU 00000010b ;bit to test for ready to send
MODSNDR EQU 00000010b ;modem send ready when high
MODRCVB EQU 00000001b ;bit to test for received data
MODRCVR EQU 00000001b ;modem receive ready when high
ORG TPA
JMP START ;MEX has a JMP START here
PMMIMODEM: DB NO ;yes=PMMI S-100 Modem 103H
SMARTMODEM: DB YES ;yes=HAYES Smartmodem, no=non-PMMI 104H
TOUCHPULSE: DB 'T' ;T=touch, P=pulse (Smartmodem-only) 105H
CLOCK: DB 40 ;clock speed in MHz x10, 25.5 MHz max. 106H
;20=2 MHh, 37=3.68 MHz, 40=4 MHz, etc.
MSPEED: DB 6 ;0=110 1=300 2=450 3=600 4=710 5=1200 107H
;6=2400 7=4800 8=9600 9=19200 default
BYTDLY: DB 1 ;0=0 delay 1=10ms 5=50 ms - 9=90 ms 108H
;default time to send character in ter-
;minal mode file transfer for slow BBS.
CRDLY: DB 1 ;0=0 delay 1=100 ms 5=500 ms - 9=900 ms 109H
;default time for extra wait after CRLF
;in terminal mode file transfer
NOOFCOL: DB 5 ;number of DIR columns shown 10AH
SETUPTST: DB YES ;yes=user-added Setup routine 10BH
SCRNTEST: DB YES ;cursor control routine 10CH
ACKNAK: DB YES ;yes=resend a record after any non-ACK 10DH
;no=resend a record after a valid NAK
BAKUPBYTE: DB YES ;yes=change any file same name to .BAK 10EH
CRCDFLT: DB YES ;yes=default to CRC checking 10FH
TOGGLECRC: DB YES ;yes=allow toggling of CRC to Checksum 110H
CONVBKSP: DB NO ;yes=convert backspace to rub 111H
TOGGLEBK: DB YES ;yes=allow toggling of bksp to rub 112H
ADDLF: DB NO ;no=no LF after CR to send file in 113H
;terminal mode (added by remote echo)
TOGGLELF: DB YES ;yes=allow toggling of LF after CR 114H
TRANLOGON: DB NO ;yes=allow transmission of logon 115H
;write logon sequence at location LOGON
SAVCCP: DB NO ;no=do not save CCP, may be overwritten 116H
LOCONEXTCHR: DB NO ;yes=local command if EXTCHR precedes 117H
;no=external command if EXTCHR precedes
TOGGLELOC: DB YES ;yes=allow toggling of LOCONEXTCHR 118HèLSTTST: DB YES ;yes=printer available on printer port 119H
XOFFTST: DB NO ;yes=checks for XOFF from remote while 11AH
;sending a file in terminal mode
XONWAIT: DB NO ;yes=wait for XON after CR while 11BH
;sending a file in terminal mode
TOGXOFF: DB YES ;yes=allow toggling of XOFF checking 11CH
IGNORCTL: DB NO ;yes=CTL-chars above ^M not displayed 11DH
EXTRA1: DB 0 ;for future expansion 11EH
EXTRA2: DB 0 ;for future expansion 11FH
BRKCHR: DB '@'-40H ;^@ = Send a 300 ma. break tone 120H
NOCONNCT: DB 'N'-40H ;^N = Disconnect from the phone line 121H
LOGCHR: DB 'W'-40H ;^W = Send logon 122H
LSTCHR: DB 'P'-40H ;^P = Toggle printer 123H
UNSAVE: DB 'R'-40H ;^R = Close input text buffer 124H
TRANCHR: DB 'T'-40H ;^T = Transmit file to remote 125H
SAVECHR: DB 'Y'-40H ;^Y = Open input text buffer 126H
EXTCHR: DB '\'-40H ;^\ = Send next character 127H
DS 2 ; 128H
IN$MODCTLP: JMP OSTAT ;get serial port status 12AH
DS 7
OUT$MODDATP: JMP CHN$OUTPUT ;send chars to the serial port 134H
DS 7 ;(CHNOUT: & OSOUT:)
IN$MODDATP: JMP OSIN ;get a char from the serial 13EH
DS 7 ;port (OSIN: & CHNIN:)
ANI$MODRCVB: ANI MODRCVB ! RET ;bit to test for receive ready 148H
CPI$MODRCVR: CPI MODRCVR ! RET ;value of rcv. bit when ready 14BH
ANI$MODSNDB: ANI MODSNDB ! RET ;bit to test for send ready 14EH
CPI$MODSNDR: CPI MODSNDR ! RET ;value of send bit when ready 151H
DCDTST: JMP DCDVEC ; Data carrier detect 154H
RNGDET: JMP RNGVEC ; Ring detect 157H
; Overlay data I (only for overlay functions)
MODCTB: DB 11010101b ;Modem Control Byte
;Receive Interrupt Enable
;MODEM port 8N1
;10010110b = 300 bps / 600 bps
;10010101b = 1200 bps / 2400 bps
;RS-232 port (V.24) 8N1
;11010110b = 300 bps / 600 bps
;11010101b = 1200 bps / 2400 bps
MODIOB: DB 00000000b ;Modem Input - Output byte
;Bit 0 = FT (File Transmit active)
;set by NOPARV and PARITV to
;switch char tables on/off
;Bit 1 = VT (VT Emulation active)
;Bit 2 = II (IBM to ASCII Input conv.)
;Bit 3 = IO (ASCII to IBM Output conv.)
;Bit 4 = KP (VT Keypad Mode active)
;Bit 5 = PFK (VT PF-Key Flag)
;Bit 6 = DSF (Direct Send Flag)
;Bit 7 = SOC (Send Original Char Bit)
DS 2
DSCDTR1: DB YES ;NO= disconnect only with ATH
JMP$SMDISC: JMP DISCON1 ;disconnect with ATH 15FH
DAILV: JMP DIAL ; 162H
JMP$DISCON: JMP DISCON ;disconnect with DTR or ATH 165H
JMP$GOODBYE: JMP GOODBYE ;called before exit to CP/M 168H
JMP$INITMOD: JMP INITMOD ;init OSBORNE 1 and Modem 16BH
JMP$NEWBD: JMP NEWBD ;support optional NEWBD 16EH
NOPARV: JMP TBL$ON ;converting chars on 171H
PARITV: JMP TBL$OFF ;converting chars off 174H
JMP$SETUPR: JMP SETUPR ; 177H
JMP$SPCLMENU: RET ! NOP ! NOP ;not used with MEX 17AH
JMP$SYSVER: JMP SYSVER ; 17DH
JMP$BREAK: JMP SENDBRK ; 180H
; Do not change the following six lines.è
JMP$ILPRT: DS 3 ; 183H
JMP$INBUF DS 3 ; 186H
JMP$INLNCOMP: DS 3 ; 189H
JMP$INMODEM DS 3 ; 18CH
JMP$NXTSCRN: DS 3 ; 18FH
JMP$TIMER: DS 3 ; 192H
CLREOS: RET ;no clear to the end of screen 195H
DB 0,0,0,0,0,0,0,0
CLRSCRN: MVI E,CLRSCR ;clear screen, home cursor 19EH
MVI C,IN$OUT
JMP MEX
; end of fixed area
; ORG 0200H ;overlay start for MEX V2.0
SYSVER: LXI D,SOMESG
MVI C,PRINT
CALL MEX
CALL BDSHOW
CALL BTSHOW
JMP CRLF
; If you put a routine in here, it should NOT do a disconnect when
; using MEX. That's handled by the DISCON routine.
GOODBYE:
MVI C,01010101b ;set serial port to RS-232 (V.24),
CALL OSET1 ;1200 bps, and no interrupt
JMP CLRSCRN ;clear screen
; This is the Osborne initialization routine.
INITMOD:
; Set serial port interrupt
; OSBORNE 1 is set to MODE 2 Interrupts.
; The interrupt tabel is set to EF..h (I = EFh).
; The hardware supported three interrupt inputs
; /IRQ0 from the serial port, low byte of the INT vector is FCh =>> EFFCh
; /IRQ1 from the keyboard, low byte is F8h =>> EFF8h
; /IRQ2 from the parallel port, low byte is F0h =>> EFF0h
; OSBORNE's CBIOS only use keyboard interrupt. At the location EFF8h the
; vector 06FCh points to the ROM BIOS keyboard interrupt routine.
; The highest priority has /IRQ2.
LXI H,SERINT ;load address of the serial INT routine
SHLD INTBL+0Ch ;set serial interrupt vector
; Set serial port parameter and init modem.
MVI A,0FFH
STA MSPEED1 ;set (MSPEED1) = FF to init serial port
LDA MSPEED ;load init speed
CALL NEWBD1 ;set baud rate
RET
; SET-command extention
; Control is passed here after MEX parses a SET command.
SETUPR: MVI C,SBLANK ;any arguments?
CALL MEX
JC SETSHO ;if not, go print out values
LXI D,CMDTBL1 ;parse command
CALL TSRCH ;from table
PUSH H ;any address on stack
RNC ;if we have one, execute it
POP H ;nope, fix stack
SETERR: LXI D,SETEMS ;print error
MVI C,PRINT
JMP MEX
; 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.
CMDTBL1:
DB '?'+80H ;set ?
DW STHELP1
DB 'BAU','D'+80H ;set baud
DW BAUDST
DB 'BIT','S'+80H ;set bits
DW STBITS
DB 'DIA','L'+80H ;set dial
DW TODIAL
DB 'I','N'+80H ;set ASCII/IBM input chars
DW SET$IN
DB 'OU','T'+80H ;set ASCII/IBM output chars
DW SET$OUT
DB 'VT10','0'+80H ;set VT100 emulation
DW SET$VT
DB 0 ;table terminator
; SET ? processor
STHELP1:
LXI D,HLPMSG1
MVI C,PRINT
JMP MEX
; SET BAUD processor
BAUDST: MVI C,BDPARS ;function code
CALL MEX ;let MEX look up code
JC SETERR ;invalid code
CALL NEWBD1 ;no, try to set it
JC SETERR ;not-supported code
CALL CRLF
LDA MODCTB
ANI RTSBIT
CNZ BDSWITCH ;IF RS232 on -> print Switch-Msg.
CALL BDSHOW
CALL CRLF
JMP CRLF
BDSHOW: CALL ILPRT
DB ESC,')',0
LDA MSPEED
MVI C,PRBAUD ;use MEX routine
CALL MEX
CALL ILPRT
DB BS,BS,BS,BS,ESC,'( Baud ',0
RET
; SET BITS number of bits, parity and number of stop bits
STBITS: LXI D,BITTBL ;point to table of commands
CALL TSRCH ; and search it
JC SSETERR
LDA MODCTB
ANI NOT BITMSK ;zero number of bits
ORA L ; and put in new value
STA MODCTB
CALL OSET ;send to 6850
CALL CRLFè CALL BTSHOW
JMP CRLF
BTSHOW: LDA MODCTB ;6850 control register image
ANI BITMSK ;keep only the parity etc. bits
LXI H,SAYTBL ;start of jump table for text routines
RRC ;correct to provide offset into table
MOV E,A
MVI D,0 ;DE now has offset
DAD D ;HL now points to correct entry in table
MOV E,M
INX H
MOV D,M ;DE now has address of correct routine
PUSH D
RET ;jump to it
; These are the routines to display character length, parity and number
; of stop bits. The bits for these values are not independent in the 6850
; which makes this code the easiest way to do it.
SAY7E2: CALL SAY7
CALL SAYHE
JMP SAYH2
SAY7O2: CALL SAY7
CALL SAYHO
JMP SAYH2
SAY7E1: CALL SAY7
CALL SAYHE
JMP SAYH1
SAY7O1: CALL SAY7
CALL SAYHO
JMP SAYH1
SAY8N2: CALL SAY8
CALL SAYN
SAYH2: CALL ILPRT
DB ESC,')2',0
SAYSS: CALL ILPRT
DB ESC,'( Stop Bits',CR,LF,0
RET
SAY8N1: CALL SAY8
CALL SAYN
JMP SAYH1
SAY8E1: CALL SAY8
CALL SAYHE
JMP SAYH1
SAY8O1: CALL SAY8
CALL SAYHO
SAYH1: CALL ILPRT
DB ESC,')1',0
CALL ILPRT
DB ESC,'( Stop Bit',CR,LF,0
RET
SAY7: CALL ILPRT
DB ESC,')7',0è JMP SAYBITS
SAY8: CALL ILPRT
DB ESC,')8',0
SAYBITS:
CALL ILPRT
DB ESC,'( Bits ',0
RET
SAYHE: CALL ILPRT
DB ESC,')EVEN',0
JMP SAYPAR
SAYHO: CALL ILPRT
DB ESC,')ODD',0
JMP SAYPAR
SAYN: CALL ILPRT
DB ESC,')NO',0
SAYPAR: CALL ILPRT
DB ESC,'( Parity ',0
RET
; jump table for the bit text output routines
SAYTBL: DW SAY7E2
DW SAY7O2
DW SAY7E1
DW SAY7O1
DW SAY8N2
DW SAY8N1
DW SAY8E1
DW SAY8O1
; table for BITS
BITTBL: DB '7E','2'+80H
DW 0000H
DB '7O','2'+80H
DW 0004H
DB '7E','1'+80H
DW 0008H
DB '7O','1'+80H
DW 000CH
DB '8N','2'+80H
DW 0010H
DB '8N','1'+80H
DW 0014H
DB '8E','1'+80H
DW 0018H
DB '8O','1'+80H
DW 001CH
DB 0 ;<<== table terminator
; SET DIAL DIAL MODE
TODIAL: LDA TOUCHPULSE
XRI 54H XOR 50H ;toggle 'T' and 'P'
STA TOUCHPULSE
CALL CRLF
CALL DLSHOW
JMP CRLFè
DLSHOW: LDA TOUCHPULSE
CPI 'P'
JRNZ TMSG
CALL ILPRT
DB ESC,')PULSE',ESC,'(',0
DLEND: CALL ILPRT
DB ' Dialing',CR,LF,0
RET
TMSG: CALL ILPRT
DB ESC,')TONE',ESC,'(',0
JMP DLEND
; SET CHAR toggle converting input IBM code to ASCII code
SET$IN: LDA MODIOB ;load MODIOB
XRI 00000100b ;toggle II flag
STA MODIOB ;save it
CALL CRLF
CALL CHR$SHOW
JMP CRLF
SET$OUT:
LDA MODIOB ;load MODIOB
XRI 00001000b ;toggle IO flag
STA MODIOB ;save it
CALL CRLF
CALL CHR$SHOW
JMP CRLF
CHR$SHOW:
LDA MODIOB
BIT 2,A ;test II flag
JRZ ASCII$IN
CALL ILPRT
DB ESC,')IBM',0
JR CHR$PR$IN
ASCII$IN:
CALL ILPRT
DB ESC,')ASCII',0
CHR$PR$IN:
CALL ILPRT
DB ESC,'( Char Input ',0
LDA MODIOB
BIT 3,A ;test IO flag
JRZ ASCII$OUT
CALL ILPRT
DB ESC,')IBM',0
JR CHR$PR$OUT
ASCII$OUT:
CALL ILPRT
DB ESC,')ASCII',0
CHR$PR$OUT:
CALL ILPRT
DB ESC,'( Char Output',CR,LF,0
RET
SET$VT: LXI H,MODIOB
MOV A,M ;load MODIOB
XRI 00000010b ;toggle VT flagè RES 4,A ;reset KP, disable Keypad Mode
MOV M,A ;save it
CALL CRLF
CALL VT$SHOW
JMP CRLF
VT$SHOW:
CALL ILPRT
DB 'VT100 emulation ',ESC,')O',0
LDA MODIOB
BIT 1,A
JRZ VT$OFFMSG
CALL ILPRT
DB 'N',ESC,'(',CR,LF,0
RET
VT$OFFMSG:
CALL ILPRT
DB 'FF',ESC,'(',CR,LF,0
RET
; SSET command extention
; Control is passed here after MEX parses a SSET command.
SSET: MVI C,SBLANK ;any arguments?
CALL MEX
JC SETSHO ;if not, go print out values
LXI D,CMDTBL ;parse command
CALL TSRCH ;from table
PUSH H ;any address on stack
RNC ;if we have one, execute it
POP H ;nope, fix stack
SSETERR:
LXI D,SETEMS ;print error
MVI C,PRINT
JMP MEX
; SSET command table ...see SET command table for more information
CMDTBL: DB '?'+80H ;"set ?"
DW STHELP
DB 'POR','T'+80H ;"set rts"
DW STRTS
DB 'WIDT','H'+80H ;"set width"
DW STWID
DB 'SCROL','L'+80H ;"set scroll"
DW STSCRL
DB 'ARRO','W'+80H ;"set arrow"
DW STARR
IF SETPEEK
DB 'PEE','K'+80H ;"peek memory"
DW PEEK
ENDIF
DB 'SCREE','N'+80H ;"set physical width"
DW SETSCREEN
DB 0 ; table terminator
; SET/SSET <no-args>: print current statistics
SETSHO: LXI H,SHOTBL ;get table of SHOW subroutinesèSETSLP: MOV E,M ;get table address
INX H
MOV D,M
INX H
MOV A,D ;end of table?
ORA E
RZ ;exit if so
PUSH H ;save table pointer
XCHG ;adrs to HL
CALL GOHL ;do it
CALL CRLF ;print newline
MVI C,CHEKCC ;check for console abort
CALL MEX
POP H ;it's done
JRNZ SETSLP ;continue if no abort
RET
GOHL: PCHL
; table of SHOW subroutines
SHOTBL: DW TBL$HEAD
DW BDSHOW
DW BTSHOW
DW DLSHOW
DW RTSHOW
DW CHR$SHOW
DW VT$SHOW
DW WDSHOW
DW SCRSHOW
DW SCSHOW
DW ARSHOW
DW 0 ;<<== table terminator
TBL$HEAD:
CALL ILPRT
DB CLRSCR,'(',ESC,')S',ESC,'()',ESC,')SET ',ESC,'(switches'
DB CR,LF,0
RET
; SSET ? processor
STHELP: LXI D,HLPMSG
MVI C,PRINT
JMP MEX
; SSET SCROLL toggle Auto Scroll
STSCRL: LHLD JTABL ;first page of bios
MVI L,AHSENB ;offset of scroll flag
MOV A,M
XRI 0FFH ;toggle it
MOV M,A
CALL CRLF
CALL SCSHOW
JMP CRLF
SCSHOW: CALL ILPRT
DB 'Auto-scroll ',ESC,')O',0
LHLD JTABL ;first page of bios
MVI L,AHSENB ;offset of scroll flag
MOV A,Mè ORA A
JRZ OFFMSG
CALL ILPRT
DB 'N',ESC,'(',CR,LF,0
RET
OFFMSG: CALL ILPRT
DB 'FF',ESC,'(',CR,LF,0
RET
; SSET WIDTH screen width
STWID: MVI C,EVALA
CALL MEX ;get numeric
MOV A,H ;validate
ORA A
JNZ SSETERR
MOV A,L
CPI 30 ;30 seems small enough
JC SSETERR
CPI 129 ;128 is max
JNC SSETERR
STA LLIMIT ;screen width byte
LHLD JTABL ;first page of CBIOS
MVI L,SCRSZE ;CBOIS-offset to width byte for SETUP.COM
MOV M,A
CALL CRLF
CALL WDSHOW
JMP CRLF
WDSHOW: CALL ILPRT
DB 'Screen Width ',ESC,')',0
LDA LLIMIT
MOV L,A
MVI H,0
MVI C,DECOUT
CALL MEX
CALL ILPRT
DB ESC,'(',CR,LF,0
RET
; SSET ARROW toggle arrow keys
STARR: LHLD JTABL ;first page of bios
MVI L,CRSUP ;offset of vector to cursor up
MOV E,M
INX H
MOV D,M
XCHG ;hl now points to cursor up
MOV A,M
XRI 0BH XOR 05H ;toggle cursor up
MOV M,A
INX H
MOV A,M
XRI 0CH XOR 04H ;toggle cursor right
MOV M,A
INX H
MOV A,M
XRI 0AH XOR 18H ;toggle cursor down
MOV M,A
INX H
MOV A,Mè XRI 08H XOR 13H ;toggle cursor left
MOV M,A
CALL CRLF
CALL ARSHOW
JMP CRLF
ARSHOW: CALL ILPRT
DB 'Arrow Keys ',ESC,')',0
LHLD JTABL ;first page of bios
MVI L,CRSUP ;offset of vector to cursor up key
MOV E,M
INX H
MOV D,M
XCHG ;hl points to cursor up
MOV A,M
CPI 0BH
JRZ CPMSG
CALL ILPRT
DB 'WS',ESC,'(',CR,LF,0
RET
CPMSG: CALL ILPRT
DB 'CPM',ESC,'(',CR,LF,0
RET
; SSET PORT toggle serial ports
STRTS: LDA MODCTB
XRI RTSBIT ;toggle the RTS bit
STA MODCTB
CALL OSET
CALL CRLF
CALL RTSHOW
JMP CRLF
RTSHOW: CALL ILPRT
DB ESC,')',0
LDA MODCTB
ANI RTSBIT
JRNZ INMSG
CALL ILPRT
DB 'MODEM',0
ACTMSG: CALL ILPRT
DB ESC,'(',' port on',CR,LF,0
RET
INMSG: CALL ILPRT
DB 'RS232',0
JR ACTMSG
; SET SCREEN (SCREEN PAC physical width)
SETSCREEN:
CALL SCRNFLG ;liefert immer 11110000B ??? Fehler ???
ANI 04H
JNZ SSETERR ;no SCREEN PAC installed
LXI D,SCRTBL
CALL TSRCH
JC SSETERR
MOV A,L
LHLD JTABL ;load CBIOS address
MVI L,PLUGH ;add address offsetè MOV M,A ;store new screen width
CALL JMPMAGIC ;set SCREEN PAC
ORA A
JRNZ NO$SCRL ;80/104 Spalten >> scroll OFF
MVI A,YES ;oder 52 Spalten >> scroll ON
SETSCRL:
LHLD JTABL ;load CBIOS address
MVI L,AHSENB ;add address offset
MOV M,A ;store new scroll flag
CALL CRLF
CALL SCRSHOW
CALL SCSHOW
JMP CRLF
SCRTBL: DB '5','2'+80H
DW 0000H
DB '8','0'+80H
DW 0003H
DB '10','4'+80H
DW 0001H
DB 0 ;table terminator
NO$SCRL:
XRA A ;80/104 Spalten >> scroll OFF
JR SETSCRL
JMPMAGIC:
LHLD JTABL
MVI L,00H ;set CBIOS base to **00H
LXI D,MAGIC
DAD D ;set new screen width
PCHL ;with special OSBORNE routine
SCRSHOW:
CALL ILPRT
DB 'SCREEN PAC Width ',ESC,')',0
; CALL SCRNFLG ; A = SCREEN PAC flag
;liefert immer 11110000B ??? Fehler ???
LHLD JTABL ;load CBIOS address
MVI L,PLUGH ;add address offset
MOV A,M ;load new screen width
ANI 03H
CPI 01H
JRZ SCR104
CPI 03H
JRZ SCR80
CALL ILPRT
DB '52',0
SCRJMP: CALL ILPRT
DB ESC,'( column',CR,LF,0
RET
SCR104: CALL ILPRT
DB '104',0
JR SCRJMP
SCR80: CALL ILPRT
DB '80',0
JR SCRJMP
; end of SSET commandè
; OUTVEC is pointed ot here to intercept the console output routine.
; This is done to allow screening out some of ASCII characters (00H-7FH).
; See MEXPAT11.ASM for further info on OUTVEC.
;DDROP: JMP CONVEC ;no screening out
; routines to read received char,
; emulate an VT100-Terminal, and convert input IBM-ASCII to 7bit-ASCII
; (return with char in A)
OSIN: PUSH H
PUSH B
OSIN1: LHLD RDCHAR ;load pointer to next read char
MOV C,M ;read received char
INR L ;HL points to next char
SHLD RDCHAR ;save new pointer to next read char
DI
LDA SVCHAR
SUB L
JRNZ CHNIN ;jump if more received chars must be read
LXI H,REVCTL
RES 0,M ;reset Bit0: RDRF (Receive Data Register Full)
CHNIN: EI
MOV A,C ;received char in A
LXI H,MODIOB ;HL point to config table
MOV B,M ;B = (MODIOB)
BIT 0,B ;test FT flag (File Transmit)
JNZ CHN$END1 ;jump if FT is set
BIT 1,B ;test VT flag (VT Emulation)
JRZ NO$ESC ;jump if VT is not set
; VT100 control: The following control chars are always typed.
CPI 20H
JRC ESC$J0 ;jump if control chars
LHLD VT100$ESC ;HL = (VT100$ESC)
PCHL ;branch to it
ESC$J0: CPI FF ;Form Feed
JRNZ ESC$J1
MVI A,LF ;replace with LF
JMP ESC$END3
ESC$J1: CPI VT ;Vertical Tab
JRNZ ESC$J2
MVI A,LF ;replace with LF
JMP ESC$END3
ESC$J2: CPI CAN ;Cancel
JRZ ESC$J3
CPI SUBST ;Substitute
JRNZ ESC$J4
ESC$J3: MVI A,DEL ;replace with DEL - Error indication -
JMP ESC$END2 ;and abort the current escape sequence
ESC$J4: CPI XON
JRNZ ESC$J5
POP B
POP H
RET ;return to MEX
ESC$J5: CPI XOFF
JRNZ ESC$J6
POP B
POP H
RET ;return to MEX
ESC$J6: CPI ESC
JRNZ ESC$END0 ; return with Control Char and continue
; with the escape sequence execution
XRA A ;clear A reg
LXI H,ESCAPE1 ;HL = ESCAPE1
JMP ESC$END
NO$ESC: LXI H,MODIOB ;HL point to MODIOB
MOV B,Mè BIT 2,B ;test II (IBM Input convert)
JRZ DEL$CHR ;jump if II is not set
LXI H,CHR$TABL1 ;HL point to char table
MOV B,M ;set loop counter
LOOP1: INX H
CMP M ;if A = M -> Z=1
INX H
JRZ LPEND1 ;jump if A = M
DJNZ LOOP1 ;loop end ?
DEL$CHR:
BIT 7,A
JRZ CHN$END1 ;jump if char < 127
MVI A,DEL ;replace char with DEL
CHN$END1:
STA LAST$CHAR ;save last received char
LXI H,REVCTL
BIT 0,M ;test RDRF (Receive Data Register full)
JRNZ OSIN2 ;jump if Modem Input Buffer is not empty
POP B
POP H
RET ;return to MEX with char in A
LPEND1: MOV A,M ;change IBM char to ASCII
STA LAST$CHAR ;save last received char
ESC$END0:
LXI H,REVCTL
BIT 0,M ;test RDRF (Receive Data Register full)
JRNZ OSIN2 ;jump if Modem Input Buffer is not empty
POP B
POP H
RET ;return to MEX with char in A
OSIN2: PUSH D
MOV E,A
MVI C,CONOUT
CALL BDOS
POP D
JMP OSIN1
ESC$END1:
LXI H,NO$ESC
SHLD VT100$ESC ;(VT100$ESC) = HL
POP B
POP H
RET ;return to MEX with control char in A
ESC$END2:
LXI H,NO$ESC
SHLD VT100$ESC ;(VT100$ESC) = HL
ESC$END3:
LXI H,REVCTL
BIT 0,M ;test RDRF (Receive Data Register Full)
JRNZ OSIN3 ;jump if Modem Input Buffer is not empty
POP B
POP H
RET ;return to MEX with control char in A
OSIN3: MOV C,A
CALL BCOUT
JMP OSIN1
CHR$TABL1:
DB 07H ;table length
DB 084H,07BH ;'ae'
DB 094H,07CH ;'oe'
DB 081H,07DH ;'ue'
DB 08EH,05BH ;'Ae'
DB 099H,05CH ;'Oe'
DB 09AH,05DH ;'Ue'
DB 0E1H,07EH ;'sz'
CHN$OUTPUT:
PUSH H
PUSH B
LXI H,MODIOB ;HL point to config table
MOV B,M ;load (MODIOB)
BIT 0,B ;test FT flag (File Transmit)
JRNZ CHN$END2 ;jump if FT is set
BIT 1,B ;test VT flag (VT Emulation)
JNZ VT100$OUT ;jump if VT flag is set
CHN$OUT1:
LXI H,MODIOB ;HL point to MODIOB
BIT 3,M ;test IO flag (IBM Output convert)
JRZ CHN$END2 ;jump if IO flag is not set
LXI H,CHR$TABL1 ;HL point to char table length
MOV B,M ;set loop counter
LXI H,CHN$OUTPUT ;HL point to the table end + 1
LOOP2: DCX H
CMP M ;affect flags: (A)=(M) --> Z=1
DCX H
JRZ LPEND2 ;jump if A = (M)
DJNZ LOOP2 ;loop end ?
CHN$END2:è POP B
POP H
JMP OSOUT ;send char to the serial port
;and return to MEX
LPEND2: MOV A,M ;change ASCII char to IBM
POP B
POP H
JMP OSOUT ;send char to the serial port
;and return to MEX
; VT100 Input Emulation
ESCAPE1:
CPI ESC ;ignore the following ESC's
JRNZ ESC$JP
XRA A
JMP ESC$END ;always (VT100$ESC) = ESCAPE1
ESC$JP: CPI '['
JNZ ESCX ;jump if ESC + letter
XRA A ;clear rg A
STA ROW ;clear in row & col arrays
STA COL
LXI H,ESCAPE2
JMP ESC$END
ESCAPE2:
CPI '?' ;if it is ESC [ ? ignore the
JZ SKIP ;following parameters
CPI 40H ;is this a final letter code ?
JC GETP ;if not, get parameters
è; OTHERWISE, FIGURE OUT WHAT NEEDS TO BE DONE
UPLOW: CPI 60H ;IS IT LOWER CASE?
JNC LOWC
CPI 'K' ;ESC [ K = clear to end of line
JRNZ ESC1
MVI C,ESC
CALL BCOUT
MVI C,'T'
CALL BCOUT ;type ESC T
JMP ESC$ENDX1
ESC1: CPI 'J'
JRNZ ESC2
LDA ROW
ANA A ;affect flags
CPI 02H ;ESC [ 2 J = clear screen
JRNZ CLREOS1 ;jump if A reg <> 2
CALL CALCUR ;CUR$CURS = curent cursor position
MVI C,CLRSCR
CALL BCOUT
LHLD CUR$CURS
JMP LCP14 ;restore cursor
CLREOS1:
MVI C,ESC ;ESC [ J = clear to end of screen
CALL BCOUT
MVI C,'T'
CALL BCOUT ;ESC T = clear to end of line
CALL CALCUR ;CUR$CURS = curent cursor position
;and load curent cursor position in HL
MVI A,23 ;23+1 lines on screen
SUB H
JZ LCP14 ;jump if cursor in line 23, no insert line
PUSH H
MOV B,A ;numbers of lines to insert - 1
PUSH B
MVI C,DOWN
CALL BCOUT ;cursor down
POP B
MVI C,ESC
ELP1: PUSH B
CALL BCOUT
MVI C,'E'
CALL BCOUT ;B X ESC E = insert line
POP B
DJNZ ELP1
POP H
JMP LCP14 ;restore cursor
ESC2: CPI 'D' ; ESC [ P1 D = BACKSPACE
JRNZ ESC3
CALL CALCUR ;curent cursor position in HL
LDA ROW ;get parameter
ANA A ;affect flags
JRNZ ELD2
MVI A,01H ; IF A WAS ZERO, DO ONCE ANYWAY
ELD2: MOV C,A
MOV A,L
SUB C ;new column in A
JRNC ELP2 ;if column - P1 < 0, send CR
MVI C,CR
CALL BCOUT
JMP ESC$ENDX1
ELP2: MOV L,A ;new column in L
JMP LCP14è
ESC3: CPI 'B' ; ESC [ P1 B = CURSOR-DOWN
JRNZ ESC4
CALL CALCUR ;curent cursor position in HL
LDA ROW ;get parameter
ANA A ;affect flags
JRNZ ELD3
ELJ3: MVI A,01H ; IF A WAS ZERO, DO ONCE ANYWAY
ELD3: ADD H ;new row in A
CPI 24 ;row must be < 24
JRC ELQ3
MVI A,23
ELQ3: MOV H,A ;new row in H
JMP LCP14
ESC4: CPI 'F' ;ESC [ P1 F = previous line
JRZ ELQ4
CPI 'A' ;ESC [ P1 A = CURSOR-UP
JNZ ESC5
ELQ4: CALL CALCUR ;curent cursor position in HL
LDA ROW ;get parameter
ANA A ;affect flags
JRNZ ELD4
ELJ4: MVI A,01H ; IF A WAS ZERO, DO ONCE ANYWAY
ELD4: MOV C,A
MOV A,H
SUB C ;new row in A
JRNC ELP4 ;if row - P1 < 0 replace with 0
MVI A,0
ELP4: MOV H,A ;new row in H
JMP LCP14
ESC5: CPI 'C' ; ESC [ P1 C = cursor right
JRNZ ESC6
CALL CALCUR ;curent cursor position in HL
LDA ROW ;get parameter
ANA A ;affect flags
JRNZ ELD5
MVI A,01H ; IF A WAS ZERO, DO ONCE ANYWAY
ELD5: ADD L ;new column in A
CPI 80 ;column must be < 80
JRC ELQ5
MVI A,79
ELQ5: MOV L,A ;new column in H
JMP LCP14
ESC6: CPI 'H' ; ESC [ P1;P2 H, POSTION CURSOR
JZ PUTCUR
ESC7: CPI 'L' ; ESC [ P1 L, INSERT LINE(S)
JRNZ ESC8
LDA ROW ;get parameter
ANA A ;affect flags
MVI B,01H
JRZ ELJ7 ; IF A WAS ZERO, DO ONCE ANYWAY
MOV B,A
ELJ7: PUSH B
MVI C,ESC
CALL BCOUTè MVI C,'E'
CALL BCOUT
MVI C,ESC
CALL BCOUT
MVI C,'T'
CALL BCOUT
POP B
DJNZ ELJ7 ;type B x ESC E ESC T
JMP ESC$ENDX1
ESC8: CPI 'X' ;ESC [ P1 X = erase char(s)
JRZ ELQ8
CPI 'P' ;ESC [ P1 P = delete char(s)
JRNZ ESC9
ELQ8: MVI C,'W'
JMP PRT$CTL ;send ESC W = delete char at cursor pos.
ESC9: CPI 'M' ; ESC [ P1 M, DELETE LINE(S)
JRNZ ESC10
MVI C,'R'
JMP PRT$CTL ;send ESC R = delete line(s)
ESC10: CPI '@' ; ESC [ P1 @, insert char(s)
JRNZ ESC11
MVI C,'Q'
JMP PRT$CTL ;send ESC Q = insert char at cursor pos.
ESC11: CPI 'E' ; ESC [ P1 E = next line/new line (CR+LF)
JRNZ ESC12
LDA ROW ;get parameter
ANA A ;affect flags
MVI B,01H
JRZ ELP11 ; IF A WAS ZERO, DO ONCE ANYWAY
MOV B,A
ELP11: MVI C,LF
ELL11: PUSH B
CALL BCOUT ;type LF
POP B
DJNZ ELL11
MVI C,CR
CALL BCOUT ;type CR
JMP ESC$ENDX1
ESC12: CPI 'G' ; ESC [ P1 G, horizontal absolute
JRNZ ESC13
CALL CALCUR ;curent cursor position in HL
LDA ROW ;get parameter
ANA A ;affect flags
CPI 0
JRZ ELP12
DCR A
CPI 80 ;OSBORNE 1 only has 80 column
JRC ELP12
MVI A,79
ELP12: MOV L,A ;L = column
JMP LCP14
ESC13: CPI 'S' ;ESC [ P1 S = scroll down (one line down)
JZ EXJ6
ESC14: CPI 'T' ;ESC [ P1 T = Scroll Reverse (one line up)
JZ EXJ9
ESC15: CPI 'I' ;ESC [ P1 I = Tabulator
JRNZ ESC16è LDA ROW ;get parameter
ANA A ;affect flags
MVI B,01H
JRZ ELD15 ; IF A WAS ZERO, DO ONCE ANYWAY
MOV B,A
ELD15: MVI E,TAB
MVI C,CONOUT
ELP15: PUSH B
CALL BDOS
POP B
DJNZ ELP15
JMP ESC$ENDX1
ESC16: CPI 'Z' ;ESC [ P1 Z = backward tabulation
IF VTDEBUG
JRNZ ESC20
ENDIF
IF NOT VTDEBUG
JNZ ESC$ENDX1 ;ignore not selected chars
ENDIF
CALL CALCUR ;curent cursor position in HL
LDA ROW ;get parameter
ANA A ;affect flags
JRNZ ELD16
INR A ; IF A WAS ZERO, DO ONCE ANYWAY
ELD16: MOV B,A
XRA A
MVI E,8
MOV C,L ;curent column in C
ELP16: ADD E
CMP C
JRC ELP16 ;add 8 to A, until A > C
ELQ16: SUB E
JRZ ELJ16 ;send CR, if A = 0
DJNZ ELQ16 ;subtract P1 x 8 = P1 x Backtab
MOV L,A
JMP LCP14 ;set cursor to new postion
ELJ16: MVI C,CR
CALL BCOUT ;type CR
JMP ESC$ENDX1
IF VTDEBUG
ESC20: LXI H,ESC$TBL
MVI B,0
MOV C,M ;load jump counter
INX H ;HL points to first char
CCIR ;Z80 CPIR
JZ ESC$ENDX1 ;jump if equal char found, ignore char
JMP UNKE ;not sure what this is
ESC$TBL:
DB ESC$TBL$E-ESC$TBL-1 ;table length
; DB 'N' ;ignore ESC [ P1 N = Erase in Field
; DB 'O' ;ignore ESC [ P1 O = Erase in Area
; DB 'R' ;ignore ESC [ P1 R = scroll up
DB 'U' ;ignore ESC [ P1 U = next page
DB 'V' ;ignore ESC [ P1 V = preceding page
; DB 'W' ;ignore ESC [ P1 W = tabulator control
; DB 'Y' ;ignore ESC [ P1 Y = vertical tabulation
ESC$TBL$E:
ENDIFè
; LOWER CASE FINAL LETTER CODE
LOWC: CPI 'm' ; ESC [ P1;...;Pn m = graphic code
JNZ LCX10
XRA A
STA PARCT ;(PARCT) = 0, first parameter
LDA ROW ;get parameter
ANA A ;affect flags
JRNZ LCX0 ;ESC [ 0 m = clear all parameters
MVI C,ESC
CALL BCOUT
MVI C,28h
CALL BCOUT ;ESC,28h = dim off
MVI C,ESC
CALL BCOUT
MVI C,6Dh
CALL BCOUT ;ESC,6Dh = underline off
JR LCX9
LCX0: CPI 01H
JRZ LCX1 ;ESC [ 1 m = high intensity
CPI 08H
JRNZ LCX2 ;ESC [ 8 m = low intensity
LCX1: MVI C,ESC
CALL BCOUT
MVI C,29h
CALL BCOUT ;ESC,28h = dim on
JR LCX9
LCX2: CPI 02H
JRNZ LCX3 ;ESC [ 2 m = normal intensity
MVI C,ESC
CALL BCOUT
MVI C,28h
CALL BCOUT ;ESC,28h = dim off
JR LCX9
LCX3: CPI 04H
JRZ LCX4 ;ESC 4 m = underline
CPI 05H
JRZ LCX4 ;ESC 5 m = slow blink
CPI 06H
JRZ LCX4 ;ESC 6 m = fast blink
CPI 07H
JRNZ LCX9 ;ESC 7 m = reverse video
LCX4: MVI C,ESC
CALL BCOUT
MVI C,6Ch
CALL BCOUT ;ESC,6Dh = underline on
LCX9: LDA PARCT
CPI 01H
JZ ESC$ENDX1 ;only 2 parameters alowed
INR A ;A = 1
STA PARCT ;(PARCT) = 1, second parameter
LDA COL ;get parameter
ANA A ;affect flags
JZ ESC$ENDX1 ;return if A = 0, no 2. parameter
JMP LCX0
LCX10: CPI 'r' ; SET SCROLLING REGION
JRNZ LCX11 ; OSBORNE 1 CAN'T HANDLE THIS,
MVI C,HOME ; BUT NEED TO HOME CURSOR
CALL BCOUT
JMP ESC$ENDX1 ; SINCE VT100 DOES IT
LCX11: CPI 'f'è JZ PUTCUR ; HORIZ & VERT POSITION - USE PUTCUR
LCX12: CPI 'b' ; ESC [ P1 b = repeat last character
JRNZ LCX13
LDA ROW ;get parameter
ANA A ;affect flags
MVI B,01H
JRZ LCD12 ;if A = 0, do once anyway
MOV B,A
LCD12: LDA LAST$CHAR
MOV C,A
LCP12: PUSH B
CALL BCOUT
POP B
DJNZ LCP12
JMP ESC$ENDX1
LCX13: CPI 's' ; ESC [ s, save cursor position
JRNZ LCX14
LCD13: CALL CALCUR ;curent cursor position in HL
SHLD SAVE$CURS
JMP ESC$ENDX1
LCX14: CPI 'u' ; ESC [ u, restore cursor position
JRNZ LCX15
LCD14: LHLD SAVE$CURS
LCP14: PUSH H
MVI C,ESC
CALL BCOUT
MVI C,'=' ;ESC,'=',row+20H,column+20H
CALL BCOUT
POP H
MOV A,H ;row in A
ADI 20H
MOV C,A
PUSH H
CALL BCOUT ;type row
POP H
MOV A,L ;column in A
ADI 20H
MOV C,A
CALL BCOUT ;type column
JMP ESC$ENDX1
LCX15: CPI 'd' ;ESC [ P1 d = vertical position absolute
IF VTDEBUG
JRNZ LCX16
ENDIF
IF NOT VTDEBUG
JNZ ESC$ENDX1 ;ignore not selected char
ENDIF
LDA ROW ;get parameter
ANA A ;affect flags
LHLD CURS
RES 7,L ;L = column
CPI 0
JRZ LCD15
DCR A
CPI 24 ;OSBORNE 1 only has 24 rowsè JRC LCD15
MVI A,23
LCD15: MOV H,A ;H = row
JMP LCP14
IF VTDEBUG
LCX16: LXI H,LCX$TBL
MVI B,0
MOV C,M ;load jump counter
INX H ;HL points to first char
CCIR ;Z80 CPIR
JZ ESC$ENDX1 ;jump if char equal, ignore char
JMP UNKE ;not sure what this is
LCX$TBL:
DB LCX$TBL$E-LCX$TBL-1 ;table length
DB 'a' ;ignore ESC [ P1 a = horizontal relative
; DB 'c' ;ignore DEVICE ATTRIBUTE
DB 'e' ;ignore ESC [ P1 e = vertical position rel
; DB 'g' ;ignore TAB STOP SET
; DB 'h' ;ignore SETTING MODE
; DB 'i' ;ignore PRINT COMMANDS
; DB 'l' ;ignore RESETTING MODE
; DB 'n' ;ignore REPORTING
DB 'o' ;ignore ESC [ P1 o = define area qualific
DB 'p' ;ignore ESC [ P1;P2 p = keyboard redefinition
DB 'q' ;ignore KEYBOAD LEDS
DB 'y' ;ignore SELF TESTS
LCX$TBL$E:
ENDIF
; ESCAPE SEQUENCE PROCESSING
ESCX: CPI 'D' ;ESC D = Index (IND) -one line down-
JRNZ EX7
EXJ6: CALL CALCUR ;curent cursor position in HL
MOV A,H ;A = row
CPI 23
JNC EXK6
MVI C,DOWN
CALL BCOUT ;only cursor down if cursor in row 0-22
JMP ESC$ENDX1
EXK6: PUSH H
MVI C,HOME
CALL BCOUT
MVI C,ESC
CALL BCOUT
MVI C,'R'
CALL BCOUT ;delete first line (scroll up)
POP H
JMP LCP14 ;restore cursor in line 23
EX7: CPI 'K' ;ESC K = Partial Line Down
JRZ EXJ6
EX8: CPI 'L' ;ESC L = Partial Line Up
JRZ EXJ9
EX9: CPI 'M' ;ESC M = Reverse Index (RI) -one line up-
JRNZ EX10
EXJ9: CALL CALCUR ;curent cursor position in HL
XRA A
CMP H ;row > 0
JNC EXK9
MVI C,UP ;only cursor up if cursor in row 1-23
CALL BCOUT
JMP ESC$ENDX1
EXK9: PUSH H
MVI C,HOME
CALL BCOUT
MVI C,ESC
CALL BCOUT
MVI C,'E'
CALL BCOUT ;delete first line (scroll up)
MVI C,ESC
CALL BCOUT
MVI C,'T'
CALL BCOUT ;insert line in first row (scroll down)
POP H
JMP LCP14 ;restore cursor in line 0
EX10: CPI 'E' ;ESC E = next line/new line -CR+LF- (NEL)è JRNZ EX11
MVI C,CR
CALL BCOUT ;type CR
MVI C,LF
CALL BCOUT ;type LF
JMP ESC$ENDX1
EX11: CPI '7' ;ESC 7 = Save Cursor (DECSC)
JZ LCD13
CPI '8' ;ESC 8 = Restore Cursor (DECRC)
JZ LCD14
CPI 'O' ;ESC O .. = single shift to char set 3
JRNZ EX12
XRA A
LXI H,ESC$ENDX1 ;DROP NEXT CHARACTER TOO
JMP ESC$END
EX12: CPI '#' ;ESC # .. = ignore Line Attributes (DEC..)
JRNZ EX13
XRA A
LXI H,ESC$ENDX1 ;DROP NEXT CHARACTER TOO
JMP ESC$END
EX13: CPI '(' ;ESC ( .. = ignore Select Character Set (SCS)
JRNZ EX14
XRA A
LXI H,ESC$ENDX1 ;DROP NEXT CHARACTER TOO
JMP ESC$END
EX14: CPI ')' ;ESC ) .. = ignore Select Character Set (SCS)
JRNZ EX15
XRA A
LXI H,ESC$ENDX1 ;DROP NEXT CHARACTER TOO
JMP ESC$END
EX15: CPI '=' ;ESC = = put Terminal in Keypad-Transmit mode
JRNZ EX16
LXI H,MODIOB
SETB 4,M ;set KP flag
JMP ESC$ENDX1
EX16: CPI '>' ;ESC > = out of Keypad-Transmit mode
JRNZ EX17
LXI H,MODIOB
RES 4,M ;reset KP flag
JMP ESC$ENDX1
EX17: CPI '?' ;ignore ESC ? .. .. = mode selection
JZ SKIP
CPI 2Fh ;skip over other intermidiate chars
JC ESC$ENDX2
IF NOT VTDEBUG
JMP ESC$ENDX1 ;ignore all not supported chars
ENDIF
IF VTDEBUG
; drop all known not supported chars
LXI H,EX$TBL
MVI B,0
MOV C,M ;load jump counter in BC
INX H ;HL points to first char
CCIR ;Z80 CPIR
JZ ESC$ENDX1 ;jump if known char found, ignore char
PUSH PSW ; if received <ESC>, but next char is
MVI C,7FH ; unknown, send solid block then the
CALL BCOUT ; original character
POP PSW
MOV C,A
CALL BCOUT
JMP ESC$ENDX1
EX$TBL: DB EX$TBL$E-EX$TBL-1 ;tabel length
DB '<' ;ESC < = switch to ANSI mode
; DB 'A' ;ESC A =
; DB 'F' ;ESC F = Start of Selected Area
; DB 'G' ;ESC G = End of Selected Area
; DB 'H' ;ESC H = Horizotal Tabulaton Set (HTS)
; DB 'I' ;ESC I = Hor. Tab with Justificationè; DB 'J' ;ESC J = Vertical Tabulation Set
; DB 'N' ;ESC N = single shift to char set 2
; DB 'P' ;ESC P = Device Control String
; DB 'Q' ;ESC Q = ANSI: for Private Use 1
; DB 'R' ;ESC R = ANSI: for Private Use 2
; DB 'S' ;ESC S = Set Transmit State
; DB 'T' ;ESC T = Cancel Character
; DB 'U' ;ESC U = Request Status Report
; DB 'V' ;ESC V = Start of Protected Area
; DB 'W' ;ESC W = End of Protected Area
; DB 'Z' ;ESC Z = Identify Terminal (DECID)
DB ']' ;ESC ] = Operating System Control
; DB '\' ;ESC \ = String Terminator
DB '^' ;ESC ^ = Private Message
; DB '_' ;ESC _ = Application Program Control
; DB 'a' ;ESC a = Running Prozess Interrupt
; DB 'c' ;ESC c = Reset to Initial State (RIS)
; DB 'e' ;ESC e =
; DB 'r' ;ESC r = clear screen, restore cursor
; DB 's' ;ESC s =
EX$TBL$E:
ENDIF
SKIP: LXI H,SKIP2 ;skip over next parameters
JMP ESC$ENDX2 ;until letter hit, then skip too
SKIP2: CPI 40H
JC ESC$ENDX2
JMP ESC$ENDX1
; type control sequences, parameter: control char in D
PRT$CTL:
LDA ROW ;get parameter
ANA A ;affect flags
MVI B,1
JRZ PRT$J1 ;if A = 0, do once anyway
MOV B,A
PRT$J1: PUSH B
MVI C,ESC
CALL BCOUT ;type ESC
POP B
PUSH B
CALL BCOUT ;type control char in C
POP B
DJNZ PRT$J1
;fall in ESC$ENDX1
ESC$ENDX1:
LXI H,NO$ESC
ESC$ENDX2:
XRA A ;clear rg A
ESC$END:
SHLD VT100$ESC ;(VT100$ESC) = HL
LXI H,REVCTL
BIT 0,M ;test RDRF (Receive Data Register full)
JNZ OSIN1 ;jump if Modem Input Buffer is not empty
POP B
POP H
RET ;return to MEX
;VT100 Emulation: convert output chars
VT100$OUT:è BIT 6,B ;test DSF (Direct Send Flag)
JNZ CHN$END2 ;send char to the port directly
BIT 7,B ;test SOC (Send Origial Char Bit)
JRZ VT$OUTJ ;jump if SOC is not set
RES 7,M
JMP CHN$END2
VT$OUTJ:
BIT 5,B ;test PFK (PF-Key Flag set)
JRZ VT$OUT3 ;jump if PFK is not set
RES 5,M ;reset PFK
; make VT100 PF-Key sequence (ESC,O,..)
PFK1: LXI H,KEYMSG ;HL points to <ESC>,O,0 string
CPI UP
JRNZ PFK2
CALL ESC$SEND
MVI A,'P' ;send ESC O P to the port (PFK1)
JMP CHN$END2
PFK2: CPI DOWN
JRNZ PFK3
CALL ESC$SEND
MVI A,'Q' ;send ESC O Q to the port (PFK2)
JMP CHN$END2
PFK3: CPI BS
JRNZ PFK4
CALL ESC$SEND
MVI A,'R' ;send ESC O R to the port (PFK3)
JMP CHN$END2
PFK4: CPI RIGHT
JNZ VT$OUT0
CALL ESC$SEND
MVI A,'S' ;send ESC O S to the port (PFK4)
JMP CHN$END2
; make VT100 Cursor sequence (ESC,[,..)
VT$OUT3:
LXI H,ESCMSG ;HL points to VT100 escape sequence
CPI BS
JRNZ VT$OUT4
CALL ESC$SEND
MVI A,'D' ;send ESC [ D to the port
JMP CHN$END2
VT$OUT4:
CPI DOWN
JRNZ VT$OUT5
CALL ESC$SEND
MVI A,'B' ;send ESC [ B to the port
JMP CHN$END2
VT$OUT5:
CPI UP
JRNZ VT$OUT6
CALL ESC$SEND
MVI A,'A' ;send ESC [ A to the port
JMP CHN$END2
VT$OUT6:
CPI RIGHT
JRNZ VT$OUT7 ;no cursor keys, return to convert routine
CALL ESC$SENDè MVI A,'C' ;send ESC [ C to the port
JMP CHN$END2
; test if PF-Key init char is typed (RS = 1Eh = ^^)
VT$OUT7:
LXI H,MODIOB
CPI RS
JRNZ KEYPD
SETB 5,M ;set PFK (PF-Key Flag)
POP B
POP H
RET ;return to MEX
; make Keypad sequence (ESC,O,char+40h)
; convert CR 0D to 4D
; ',' 2C to 6C
; '-' 2D to 2D
; '.' 2E to 6E
; '0' 30 to 70
; .
; '9' 39 to 79
KEYPD: BIT 4,M ;test KP flag (Keypad mode active)
JRZ VT$OUT0 ;jump if no Keypad-Mode
CPI CR
JRZ KEYPD1 ;convert CR
CPI ','
JC VT$OUT0 ;jump if char < 2Ch
CPI '/'
JRC KEYPD1 ;convert ',', '-' and '.'
JZ CHN$OUT1 ;return with '/' to output convert routine
CPI ':'
JNC CHN$OUT1 ;return with chars > 3Ah to output convert
;routine
KEYPD1: PUSH PSW ;push typed char
LXI H,KEYMSG
CALL ESC$SEND ;send ESC O to the port
POP PSW
ADI 40H
JMP CHN$END2 ;send last typed char+40H to the port
; test if SOC (Send Original Char Bit) init char (US) is typed
; used to send the original chars (typed US,^L sequence sends ^L)
VT$OUT0:
CPI US ;Unit Separator
JRNZ VT$OUT1
SETB 7,M ;set SOC Bit of MODIOB
POP B
POP H
RET ;return to MEX
; convert control char or return
VT$OUT1:
CPI GS ;Group Separator
JRNZ VT$OUT2
MVI A,BS
JMP CHN$END2 ;convert <GS> to <BS>
VT$OUT2:
CPI FS ;File Separator
JNZ CHN$OUT1 ;send typed char, return to convert routine
MVI A,VT
JMP CHN$END2 ;convert <FS> to <VT> = ^K
;^K is needed for Editors with WordStar Keys
;OSBORNE's Cursor Up Key (^K) is converted
;to the VT100 Sequence ESC [ A -see VT$OUT5-
OVR1: EQU $
IF OVR1 / 0D00H
+++ overlay area 1 too large +++
ENDIF
; MEX-overlay area: 0100H - 0CFF for patches !!!
╗ 0D00╚ ║ start of MEX V1.14 config-table (see MEXPAT22.ASM)
ORG 0D07H
MEMRY: DW OVREND ;first free memory pointer (orginal: 6098H)
; ORG 0D0DH ;OUTVEC MEX-console output vec.
;OUTVEC: DW DDROP
ORG 0D1FH
ESCCHR: DB ESC ;terminal mode escape char
ORG 0D34H
INIMEX: DB YES ;YES=runs INI.MEX (if present) at startup
ORG 0D39H
SILENT: DB NO ;NO=silence multi-line & READ cmd echo
; Following is the GLOBAL secondary table.
; To set an option to global, change its ASCII character to a 0H.
ORG 0D3EH
RESTT: DB 'ABDE',0,'LQRS',0,'VX'
DS 7
QUEUE: DB 1 ;1=allow queueing, 0=no
TIMBAS: DW 208 ;Timing constant
MODE: DB 0 ;mode of modem I/O
SMINIT: DS 2 ;Smartmodem INIT routine adrs
SSETV: DW SSET ;SSETV MEX-SSET-Vector
SMEXIT: DS 2 ;Smartmodem EXIT routine adrs
ORG 3B0AH
JMP$PARITY:
DW SET$PARITV ;jump to new routine
; MEX V1.14 ends with 6097H. To give additional space these area is
; protected with setting MEMRY: to OVREND pointer.
ORG 6098H
; Overlay Data II
MSPEED1: DS 1 ;aktueller MSPEED-Wert
VT100$ESC: DW NO$ESC ;input convert pointer
LAST$CHAR: DB 0 ;last received char
PARCT: DB 0 ;parameter counts
ROW: DB 0 ;Cursor Row pos, or other param.
COL: DB 0 ;Cursor Column pos., or 2rd param.
CUR$CURS: DB 0,0 ;curent cursor position
SAVE$CURS: DB 0,0 ;saved cursor position
;(SAVE$CURS) = column position
;(SAVE$CURS+1) = row position
ESCMSG: DB ESC,'[',0 ;VT100 ESC init sequence
KEYMSG: DB ESC,'O',0 ;VT100 KEY init sequence
; HAYES Modem dial routine data area
SMDIAL: DB 'ATDTW ' ;W=Wait for Dial Tone
DIALBF: DS 52 ;2* 24 CHAR MAX, + CR + NULL + SLOP
DIALPT: DS 2 ;DIAL POSITION POINTER
; Serial port Interrupt save area
ORG 60FBh
REVCTL: DB 00001100b ;Receive Control Byte
;Bit 0 = RDRF (Receive Data Register Full)
;Bit 1 = 0
;Bit 2 = /DCD (Data Carrier Detect)
;Bit 3 = /CTS (Clear to Send)
;Bit 4 = FE (Framing Error)
;Bit 5 = OVRN (Receiver Overrun)
;Bit 6 = PE (Parity Error)
;Bit 7 =
SVCHAR: DW SAVEFD ;address of the next save char
RDCHAR: DW SAVEFD ;address of the last read char
SAVEFD: DS 100h ;Save field with 255 chars
;it must beginn with a new page (..00h) !
; HAYES Modem control words
SMATN: DB '+++',0
SMDISC: DB 'ATH',CR,0
SMRES: DB 'ATZ',CR,0 ;reset modem
SMDP1: DB 'AT&P1',CR,0 ;set Dial Pulse Ratio to 33/66
; some help routines
; for Modem Input - Output
; Die Umsetzung von IBM-Umlauten fuehrt zu Fehlern, wenn die Konvertierungs-
; routine vor einem Filetransfer (S-Kommando) nicht abgeschaltet wird.
; Die hierfuer verwendete Sprungadresse PARITV: wird nur bei den SB, RB,
; und R ordnungsgemaess angesprungen.
; Die SET$PARITV: Routine ist in den S-Filetransfer eingefuegt, und schaltet
; mit PARITV: die Konvertierungstabelle ab.
; Die folgende Routine ist im MEX-Original bei ... eingebaut:
; ..
; 3B06 CALL 3B0D
; 3B09 JMP NC,4F09 <-- JETZT: SET$PARITV
; 3B0C RET
; ..
SET$PARITV:
CALL PARITV
JMP SEND$VEC ; SEND$VEC: EQU 4F09
; disable char converting and VT100 emulation
TBL$ON: LXI H,MODIOB ;HL point to MODIOB
RES 0,M
CALL ILPRT
DB ESC,28H,BELL,0
RET
; enable char converting and VT100 emulation
TBL$OFF:
LXI H,MODIOB ;HL point to MODIOB
SETB 0,M
CALL ILPRT
DB ESC,29H,0
RET
; for SET - SSET functions
; Compare next input-stream item in table @DE; CY=1
; if not found, else HL=matched data itemè
TSRCH: MVI C,LOOKUP ;get function code
JMP MEX ;pass to MEX processor
; for general use
; Print in-line message ... blows away C register
ILPRT: MVI C,ILP ;get function code
JMP MEX ;go do it
; Newline on console
CRLF: MVI A,CR
CALL TYPE
MVI A,LF ;fall into TYPE
; type char in A on console
TYPE: PUSH H
PUSH D
PUSH B
MOV E,A ;align output character
MVI C,CONOUT ;print via MEX
CALL MEX
POP B
POP D
POP H
RET
; Direct Consol Output - char in C
BCOUT: LHLD JTABL
MVI L,0Ch ;CBIOS Consol Output routine offset
PCHL ;branch to it
; for VT100 Emulation
;get Parameters & save them
GETP: CPI 31H ;skip over chars < 30H (0)
;or suppress leading zeros
JC ESC$ENDX2
CPI ';' ; CHECK IF FIRST PARAMETER = 0
JZ GETCOL
ANI 0FH ;strip upper bits
STA ROW ;store ones digit
XRA A
LXI H,GETP1
JMP ESC$END ; GET NEXT PARAMETER
GETP1: CPI 40H ; IF NONE, GO TO LETTER DETECT
JNC UPLOW
CPI 30H ;skip over chars < 30H (0)
JC ESC$ENDX2
CPI ';' ; ONLY ONE DIGIT?
JRZ GETCOL
LXI H,ROW ;HL = ROW
ANI 0FH ;strip bits 4-7
MOV C,A ;move A to C, now once place
MOV A,M ;move (ROW) to A,now tens place
RLC ;multiply by two
MOV B,A ;store 2X in B
RLC ; 4X
RLC ; 8X
ADD B ; 2X + 8X = 10X
MOV B,A ;set aside in B reg.
MOV A,C ;& get ones digit
ADD B ;Result in in A reg.
MOV M,A ;now, save parameter
XRA A
LXI H,GETP2
JMP ESC$END ; GET NEXT PARAMETER
GETP2: CPI 40H ; IF NONE, GO TO LETTER DETECT
JNC UPLOW
CPI 30H ;skip over chars < 30H (0)è JC ESC$ENDX2
CPI ';' ; IF THREE DIGITS, SKIP IT
JNZ SKIP ; NOT SURE WHAT TO DO
GETCOL: XRA A
LXI H,GETCOL1
JMP ESC$END ; GET NEXT PARAMETER, SKIP OVER ';'
GETCOL1:
CPI 40H ; IF NO COL, GO TO LETTER DETECT
JNC UPLOW
CPI 31H ;skip over chars < 30H (0)
;or suppress leading zeros
JC ESC$ENDX2
ANI 0FH ;strip upper bits
STA COL ;store ones digit
XRA A
LXI H,GETCOL2
JMP ESC$END ; GET NEXT PARAMETER
GETCOL2:
CPI 40H ; IF NONE, GO TO LETTER DETECT
JNC UPLOW
CPI 30H ;skip over chars < 30H (0)
JC ESC$ENDX2
LXI H,COL ;HL = COL
ANI 0FH ;strip bits 4-7
MOV C,A ;move A to C, now once place
MOV A,M ;move (COL) to A,now tens place
RLC ;multiply by two
MOV B,A ;store 2X in B
RLC ; 4X
RLC ; 8X
ADD B ; 2X + 8X = 10X
MOV B,A ;set aside in B reg.
MOV A,C ;& get ones digit
ADD B ;Result in in A reg.
MOV M,A ;now, save parameter
GETNXT: XRA A
LXI H,GETNXT1
JMP ESC$END ; GET THIRD PARAMETER (IGNORED)
GETNXT1:
CPI 40H ; IF NONE, GO TO LETTER DETECT
JNC UPLOW
JR GETNXT ; OTHERWISE, LOOP UNTIL WE FIND ONE
; Calculate curent cursor position
CALCUR: LHLD CURS ; load curent cursor position
; H L
; -------- --------
; 1111RRRR RCCCCCCC R=row, C=column
MOV A,H
ANI 0FH ;strip out bits 4-7
ORA A ;clear C-flag
RALR L ;bit 7 in C-flag, bit 0 = 0
RAL ;now bit 7 from L in bit 0
RRCR L ;L = 0CCCCCCC C=column
MOV H,A ;H = 000RRRRR R=row
SHLD CUR$CURS ;store curent cursor position in CUR$CURS
RET
; Direct cursur addressing
PUTCUR: MVI C,ESC ;all required chars received.
CALL BCOUT ;now create OSBORNE 1 equivalent
MVI C,'=' ;ESC = row column
CALL BCOUT
LDA ROW ;get parameter
ADI 20H ;OSBORNE 1 CODES START AT 20H
CPI 20H ;OSBORNE 1 ROWS=0-23, VT100=1-24
JRZ PUTROW
DCR A
CPI 38H ; OSBORNE 1 ONLY HAS 24 ROWS
JRC PUTROW ;jump if row < 23
MVI A,37H
PUTROW: MOV C,A
CALL BCOUT
LDA COL ;get parameter
ADI 20H ; OSBORNE 1 CODES START AT 20H
CPI 20H ; DECREMENT UNLESS AT ZERO
JRZ PUTCOL
DCR A
CPI 70H ; LIMIT COLS TO 80
JRC PUTCOL
MVI A,6FH
PUTCOL: MOV C,A
CALL BCOUT ;type column
JMP ESC$ENDX1
; send an ESC sequence to modem
ESC$SEND:
LDA MODIOB ;load Modem Input - Output Byte
PUSH PSW
SETB 6,A ;set DSF => skip over output convert routines
STA MODIOB
CALL SMSEND
POP PSW
RES 6,A ;reset DSF
STA MODIOB
RET
; print unknown control sequence
UNKE: PUSH PSW ;IF RECEIVED <ESC [>, BUT NEXT
MVI C,7FH ; 3 CHARACTERS UNRECOGNIZABLE,è CALL BCOUT ; SEND A SOLID BLOCK, A "[",
MVI C,'[' ; AND THEN THE PARAMETER
CALL BCOUT ; CHARACTERS IN HEX.
LDA ROW
CALL BYTHXA
MOV C,L
PUSH B
MOV C,H
CALL BCOUT
POP B
CALL BCOUT
MVI C,';'
CALL BCOUT
LDA COL
CALL BYTHXA
MOV C,L
PUSH B
MOV C,H
CALL BCOUT
POP B
CALL BCOUT
POP PSW
MOV C,A
CALL BCOUT
JMP ESC$ENDX1
; *** BYTE-to-HEX-ASCII routine ***
; converts char in A rg to hex chars in HL rg
BYTHXA: PUSH PSW
RRC
RRC
RRC
RRC
CALL NIBHX1
MOV H,A
POP PSW
PUSH PSW
CALL NIBHX1
MOV L,A
POP PSW
RET
; *** NIBBLE-to-HEX-ASCII routine ***
NIBHX1: ANI 0FH
ADI 90H
DAA
ACI 40Hè DAA
RET
; serial port baud rate setting
NEWBD: LXI H,MSPEED1 ;NEWBD entry
CMP M
JRZ STBD3 ;jmp if bps not changed
CALL NEWBD1
JC SETERR ;not-supported baud code
LDA MODCTB
ANI RTSBIT
JNZ BDSWT ;IF RS232 on -> print Switch-Msg.
STBD3: CALL BDSHOW
STBD2: CALL ILPRT
DB CR,LF,'++ Tel.: ',0
RET
NEWBD1: ;startup and set baud entry
LXI H,MSPEED1 ;lade HL-Register
CMP M ;? Wert von MSPEED mit Wert von MSPEED1
RZ ;vergleichen, wenn gleich -> zurueck
CPI 1 ; ? MSPEED=1
JRZ OK300
CPI 5 ; ? MSPEED=5
JRZ OK1200
CPI 6 ; ? MSPEED=6
JRZ OK2400
XRA A ;entry error
STC ;cy = 1
RET
OK2400: CALL ST2400
JMP STBAUD
OK300: CALL ST2400
CALL ST300
CALL PAUSE ;Pause
JMP STBAUD
OK1200: CALL ST2400
CALL ST300
LDA MODCTB ;last 6850 control byte
ANI NOT BAUDMSK ;clear out baud bits
ORI BAUD12 ;put new baud bits in
STA MODCTB ;set new bps
CALL OSET ;set O-1 to 1200 bps
CALL PAUSE ;pause
STBAUD: CALL MODP1 ;Impuls-Pausen-Verhaeltnis einstellen
LDA MSPEED ;load MSPEED
RET
ST2400: STA MSPEED1 ;aktuellen MSPEED-Wert setzen
STA MSPEED ;MSPEED auf 2400 bps setzen
LDA MODCTB ;last 6850 control byte
ANI NOT BAUDMSK ;clear out baud bits
ORI BAUD12 ;put new baud bits in
STA MODCTB ;set new bps
CALL OSET ;st O-1 to 1200 bps
CALL MDRES ;1.Modemreset + Pause
JMP MDRES ;2.Modemreset > 2400 bps Hardwareschalter è
ST300: LDA MODCTB ;last 6850 control byte
ANI NOT BAUDMSK ;clear out baud bits
ORI BAUD3 ;put new baud bits in
STA MODCTB ;aktuellen BAUD-Wert setzen
CALL OSET ;O-I auf 300 bps setzen
;fall in Modemreset + Pause
MDRES: LXI H,SMRES ;Modemreset
CALL SMSEND
;fall in PAUSE
PAUSE: MVI B,15 ;1.5 sec warten
MVI C,TIMER
JMP MEX
MODP1: LXI H,SMDP1 ;AT&P1-Befehl
CALL SMSEND
JMP PAUSE ;Pause
BDSWT: CALL BDSWITCH
CALL BDSHOW
IF SWTASK
CALL ILPRT
DB 'and press <RET> ',0
MVI C,IN$OUT
MVI E,0FFH
WAITIN: CALL MEX
ORA A
JRZ WAITIN ;waiting for input
ENDIF
JMP STBD2
BDSWITCH:
CALL ILPRT
DB '++ Set RS232 to ',0
RET
; Smartmodem utility routine: send string to modem
SMSEND: MVI C,SNDRDY ;WAIT FOR MODEM READY
CALL MEX
JRNZ SMSEND
MOV A,M ;FETCH NEXT CHARACTER
INX H
ORA A ;END?
RZ ;DONE IF SO
MOV B,A ;NO, POSITION FOR SENDING
MVI C,SNDCHR ;NOPE, SEND THE CHARACTER
CALL MEX
JR SMSEND
; The DIAL routine is free to use any of the registers, but must return
; the above code after an end-dial sequence
DIAL: LHLD DIALPT ;FETCH POINTER
CPI 254 ;START DIAL?
JRZ STDIAL ;JUMP IF SO
CPI 255 ;END DIAL?
JRZ 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 TOUCHPULSE ;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
JRNC 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
JRNC SMTEST ;JUMP IF MODEM HAD A CHAR
PUSH B
MVI C,CHEKCC
CALL MEX ;test for ^C from console
JRZ CTL$C ;jump if ^C is typed
POP B
DCR C ;no
JRNZ SMWLP ;continue
MVI A,2 ;return abort code (no connection)
RET
CTL$C: MVI B,CR
MVI C,SNDCHR
CALL MEX ;shut down the modem
MVI A,3 ;return abort code
POP B
RET
; MODEM GAVE US A RESULT, CHECK IT
SMTEST: ANI 7FH ;IGNORE ANY PARITY
CALL SMANAL ;TEST THERESULT
MOV A,B ;A=RESULT (CY SIGNIFICANT HERE TOO)
PUSH PSW ;SAVE IT
SMTLP: MVI C,INMDM ;FLUSH ANY REMAINING COMMAND LINE
CALL MEX
JRC SMCHEK ;JUMP IF NO INPUT
CPI LF ;GOT SOME ... WAITING FOR EOL
JRNZ 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
IF NUMRES
CPI '1' ;NUMERIC VERSION OF "CONNECT+CONNECT 2400(10)"
RZ
CPI '5' ;NUMERIC VERSION OF "CONNECT 1200"
RZ
CPI '9' ;NUMERIC VERSION OF "CONNECT 600"
RZ
ENDIF
INR B ;PREP BUSY CODE B=1
CPI 'B'
RZ
IF NUMRES
CPI '7' ;NUMERIC VERSION OF "BUSY"
RZ
ENDIFè INR B ;PREP NO CONNECT MSG B=2
CPI 'N' ;N=NO CONNECT
RZ ;(NO CARRIER,NO DIALTONE,NO ANSWER)
IF NUMRES
CPI '3' ;NUMERIC VERSION OF "NO CARRIER"
RZ
CPI '6' ;NUMERIC VERSION OF "NO DIALTONE"
RZ ;
CPI '8' ;NUMERIC VERSION OF "NO ANSWER"
RZ
ENDIF
MVI B,4 ;PREP MODEM ERROR
CPI 'E' ;E=ERROR
RZ
IF NUMRES
CPI '4' ;NUMERIC VERSION OF "ERROR"
RZ
ENDIF
STC ;UNKNOWN...
RET
; Sends a 300 msec break. Will work only with the modem connector.
SENDBRK:
LDA MODCTB
ANI RTSBIT
JRNZ BRKERR ;no break on RS232
PUSH H
LDA MODCTB ;turn on break
ORI BRKBIT
CALL OSET
MVI B,3 ;wait for 300 ms
MVI C,TIMER
CALL MEX
LDA MODCTB ;turn off break
CALL OSET
POP H
RET
BRKERR: LXI D,BRKEMS ;print error
MVI C,PRINT
JMP MEX
; Drops RTS for 3 sec. RTS is not available on the RS232 connector.
DISCON: XRA A
ORI DSCDTR
JZ DISCON1 ;disconnect with ATH
LDA MODCTB
ANI RTSBIT
JNZ DISCON1 ;no DTR ON->OFF on RS232
PUSH H
LDA MODCTB ;drop RTS
ORI RTSBIT
CALL OSET
MVI B,30 ;wait for 3 sec
MVI C,TIMER
CALL MEX
LDA MODCTB ;restore RTS
CALL OSET
POP H
RETè
; FOLLOWING ROUTINE DISCONNECTS THE MODEM USING SMARTMODEM
; CODES. ALL REGISTERS ARE AVAILABLE FOR THIS FUNCTION.
; NOTHING RETURNED TO CALLER.
DISCON1:
PUSH H
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
POP H
RET
; Return data carrier detect (DCD) status
; 0 = no carrier
; 255 = carrier present
; 254 = we don't know (DCD not supported)
DCDVEC: MVI A,254 ; Return 'we don't know'
RET
; SSET PEEK display memory location in hex and ascii
IF SETPEEK
PEEK: CALL CRLF
MVI C,EVALA
CALL MEX ;get numeric
PUSH H
MVI B,16 ;will do 16 bytes
PKLP1: MOV A,M ;get byte
MOV C,A
RAR ;swap nibbles
RAR
RAR
RAR
CALL HEX1 ;put out first nibble
MOV A,C
CALL HEX1 ;put out second nibble
MVI A,' '
CALL TYPE
INX H
DCR B
JRNZ PKLP1 ;keep doing it
CALL CRLFè POP H ;point to starting byte again
MVI B,16
PKLP2: MVI A,' '
CALL TYPE
MOV A,M
CPI 20H
JRC NOTASC ;must be control
CPI 7FH
JRNC NOTASC ;del and above
CALL TYPE ;put out printable
JMP ASC
NOTASC: MVI A,'.' ;put out a '.' for non-printable
CALL TYPE
ASC: MVI A,' '
CALL TYPE
INX H
DCR B
JRNZ PKLP2 ;keep doing it
CALL CRLF
JMP CRLF
HEX1: ANI 0FH ;zero top nibble
ADI 90H ;thanks to
DAA ; Kelly Smith
ACI 40H ; for this strange
DAA ; looking code
CALL TYPE
RET
ENDIF
SOMESG: DB CR,LF
DB 'OSBORNE 1 overlay V',REV/10+'0','.',REV MOD 10+'0',CR,LF
DB ' (C) 90 Kl. Schauer',CR,LF
DB 'Type (',ESC,')S',ESC,'()',ESC,')SET ?',ESC,'( for help',CR,LF
DB LF,'$'
èSETEMS: DB CR,LF,'++ Entry Error ++',CR,LF
DB 'Type (',ESC,')S',ESC,'()',ESC,')SET ?',ESC,'( for help',CR,LF
DB LF,BELL,'$'
BRKEMS: DB CR,LF,ESC,')++ no BREAK on RS232 ++',ESC,'(',CR,LF
DB LF,BELL,'$'
HLPMSG1:
DB CLRSCR,'SET Options',CR,LF
DB LF
DB ESC,')SET BAUD',ESC,'( <',ESC,')300',ESC,'(> <'
DB ESC,')1200',ESC,'(> <',ESC,')2400',ESC,'(>',CR,LF
DB LF
DB ESC,')SET BITS',ESC,'( <',ESC,')7E2',ESC,'(> <',ESC,')7O2'
DB ESC,'(> <',ESC,')7E1',ESC,'(> <',ESC,')7O1',ESC,'(>',CR,LF
DB ' <',ESC,')8N2',ESC,'(> <',ESC,')8N1',ESC,'(> <'
DB ESC,')8E1',ESC,'(> <',ESC,')8O1',ESC,'(>',CR,LF
DB ' NOTE: <8E1> <8O1> only with <300> BAUD',CR,LF
DB LF
DB ESC,')SET IN',ESC,'(',CR,LF
DB ESC,')SET OUT',ESC,'(',TAB,'...toggle Chars',CR,LF
DB LF
DB ESC,')SET VT100',ESC,'(',TAB,'...toggle VT100 emulation',CR,LF
DB LF
DB ESC,')SET DIAL',ESC,'(',TAB,'...toggle Dial Mode',CR,LF
DB LF,'$'
HLPMSG: DB CLRSCR,'SSET Options',CR,LF
DB LF
DB ESC,')SSET PORT',ESC,'(',TAB
DB ' ...toggle Serial Ports',CR,LF
DB LF
DB ESC,')SSET WIDTH',ESC,'( <',ESC,')nnn',ESC,'(>'
DB ' ...set Screen Width',CR,LF
DB LF
DB ESC,')SSET SCREEN ',ESC,'(<',ESC,')52',ESC,'(> <',ESC,')80',ESC,'(> <'
DB ESC,')104',ESC,'(> ...set SCREEN-PAC',CR,LF
DB LF
DB ESC,')SSET SCROLL',ESC,'(',TAB,' ...toggle Auto Scroll',CR,LF
DB LF
DB ESC,')SSET ARROW',ESC,'(',TAB
DB ' ...toggle Arrow Keys',CR,LF
DB LF,'$'
; Osborne Serial Port Input/Output routines
; Stuff the control register on the 6850
OSET: MOV C,A
OSET1: LHLD JTABL ;load BIOS+3, C=MODCTB
MVI L,3CH ;special OSBORNE 1 routine (SBAUD: E13C)
PCHL ;branch to it & return to MEX if finished
è; routines must be at a memory location above 4000h !!!
OSOUT: DI ;DISABLE INTERRUPTS
OUT 0 ;SWITDH TO ALTERNATE PAGE
STA MODDATP ;SEND DATA BYTE
OUT 1 ;SWITCH PAGES BACK
EI ;RE-ENABLE INTERRUPTS
RET ;return to MEX
OSTAT: DI ;DISABLE INTERRUPTS
PUSH B
OUT 0 ;SWITCH TO ALTERNATE PAGE
LDA MODCTLP ;GET STATUS BYTE
OUT 1 ;SWITCH PAGES BACK
ANI 00000010b ;select TDRE (Transmit Data Register Empty)
MOV B,A
LDA REVCTL ;load Receive Control Bits
ORA B ;put TDRE in
POP B
EI ;RE-ENABLE INTERRUPTS
RET ;return to MEX
;Serial port interrupt routine
;incomming char saved to print them later
SERINT: DI
SSPD IESTK ;save interrupted process stack
LXI SP,ISTK ;load interrupt stack address
PUSH PSW
PUSH B
PUSH H
LXI H,MODCTLP
OUT 0
MOV A,M ;get Status Byte
ANI 01111101b ;clear TDRE (Transmit Data Register Empty)
;and /IRQ (Interrupt Request) out
STA REVCTL ;store Receive Control Bits
; BIT 2,A ;bit 2: /DCD (Data Carrier Detected)
;used as RTS (CTS) on RS-232 interface
; JRZ INTJ1 ;jump if RTS is ON
; LDA MODCTB ;load Modem Control Byte
; MOV B,A
; ORI RESET ;ACIA Master Reset
; OUT 0
; MOV M,A ;force Master Reset
; MOV M,B ;set control byte
; OUT 1
; JMP INTRET
INTJ1: INX H ;HL points to MODDATP
MOV A,M ;get received char
LHLD SVCHAR ;read save address pointer
MOV M,A ;store received char
INR L ;HL points to next save address
SHLD SVCHAR ;save new address pointer
INTRET: LDA ROMRAM ;load ROM/RAM flag
MOV C,A
OUTP A ;return to ROM or RAM
POP H
POP B
POP PSW
LSPD IESTK ;load interrupted stack address
EI
RET
; Return ring indicator status
; 0 = not ringing
; 255 = ring detected
; 254 = we don't know (RI not supported)
RNGVEC: DI ;DISABLE INTERRUPTS
OUT 0 ;SWITCH TO ALTERNATE PAGE
LDA VICTLA ;get Video Control Byte A (Bit 6: RI flag)
OUT 1 ;SWITCH PAGES BACK
BIT 6,A
MVI A,255 ; RING detected
JRNZ RNGV1 ;jump if RI detected, return with A = 255
XRA A ;A = 0
RNGV1: EI ;RE-ENABLE INTERRUPTS
RET
;get Screen-Pac flag
SCRNFLG:
DI ;DISABLE INTERRUPTS
OUT 0 ;SWITCH TO ALTERNATE PAGE
LDA SCRNPAC ;GET SCREEN-PAC FLAG
OUT 1 ;SWITCH PAGES BACK
EI ;RE-ENABLE INTERRUPTS
RET
OVREND: END