You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
 
 
 
 
 
 

771 lines
22 KiB

;:::::::::::::::::::::::::::::::::::::::::::::::::::***********************
; CBOOT. B/P BIOS Cold Boot Module. ** Hardware Specific **
; This MUST be the Last Module in the BIOS because ** for prompts, Env **
; it is overwritten by RAM Data. No Dflt Termcap. ** and Termcap Dflts **
; - D-X Designs Pty Ltd P112 - ***********************
;
; 1.2 - 30 Aug 01 - Cleaned up for GPL release, Set Bank Numbers on boot
; (TPABNK only if MOVCPM) by reading Regs set by ROM. HFB
; 1.1 - 8 May 97 - Added code to activate ASCI channels. HFB
; 1.0 - 13 Aug 96 - Initial Release for P112. HFB
;::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
DSEG
;.....
; Cold boot entry. This code is executed only once and so may be
; overwritten subsequently by the BIOS. In Non-banked systems, this code
; is placed in the Host Buffer, HSTBUF, allowing up to 1024 bytes in the
; section, although much less will fit on the boot tracks. In Banked
; systems, a small resident part (up to 128 bytes) occupies the Directory
; Sector Buffer, DIRBUF, while the remainder is placed in the banked
; HSTBUF, allowing both sectors to be overwritten without penalty.
; To insure minimum disruption in assembling and linking the BIOS, this
; module must be one of the first linked to place HSTBUF/DIRBUF at the
; beginning of B2RAM and DSEG.
CBOOT: DI ; Disable interrupt system
; IN0 A,(DDRA) ; Get Data Definition of Port A
; SET 4,A ; Bit 4 is Input for SCSI "Int" input
; OUT0 (DDRA),A ; and reset bits
; LD A,(HICOMM) ; Set Common Bank start to Header locn
; OUT0 (CBAR),A
; CALL FDRst ; Reset FDC Controller, Re-Initialize
; (Needed in case ROM Timed out for HD Boot)
; CALL MOTOFF ; Turn Floppy motors Off, clear timer
; XOR A ; Get a Byte of Zeros
; OUT0 (SCR),A ; and activate ASCI0/ASCI1 vs MIMIC
LD HL,(IOBYT) ; Get IOBYTE, Default Drive & User
LD (3),HL ; Set values in TPA bank
; Set BIOS Bank Numbers to the RAM base Number as set by Boot ROM. In-context
; RAM will be reflected in CBR which is base. We adjust other bank numbers
; based on configured differences, except for MaxBnk which remains as config'd.
; Since the bootable systems (MOVCPM set to YES) are not banked, the Fast Boot
; option should be OFF, and only the TPABNK will necessarily be Accurate.
; IN0 C,(CBR) ; Read Current 4k base of RAM
; RR C ; divide
; RR C ; by
; RR C ; 8 for 32k Bank base
; LD HL,TPABNK
; LD B,(HL) ; Get configured TPA Bank #
; LD (HL),C ; (Store actual)
; IF NOT MOVCPM
; DEC HL
; LD A,(HL) ; Get Any User Bank
; SUB B ; (compute difference from TPA)
; JR C,NoUsrB ; ..jump if None
; ADD A,C ; Else Compute new User Bank #
; LD (HL),A ; (save)
;NoUsrB: INC HL ; advance to System Bank #
; INC HL
; LD A,(HL) ; fetch
; SUB B ; Compute diff from System Bnk to TPA Bnk
; ADD A,C ; add new base
; LD (HL),A ; (save)
; INC HL ; Advance to RAM Drive Start Bank #
; LD A,(HL)
; SUB B ; compute difference
; ADD A,C ; Add true base
; LD (HL),A ; (save)
; ENDIF ;~Movcpm. Max Bank # Stays as configured
;
IF BANKED
LD SP,USP ; Set to User Stack in High memory
CALL HBX_INIT ; WW
CALL GOSYSB ; Turn on the System bank
XOR A
LD (BIOSTK),A ; Init bank switcher
LD (3),HL ; Set IOBYTE and Default DU in System bank
CALL CBOOT0 ; Execute main part of Cold Setup
LD A,(TPABNK)
CALL SELBNK ; Insure TPA is in context
ELSE
LD SP,80H ; Set stack in Low memory
CALL HBX_INIT ; WW
CALL CBOOT0 ; Execute main part of Cold Setup
ENDIF
IF NOT MOVCPM
LD HL,003CH ; Point to ZMP Flag
LD (HL),0E5H ; say this is first time run
ENDIF
IF FASTWB
; Grab a copy of command processor from TPA and
; cache it in (SYSBNK):100H. We assume that the
; original copy of command processor is in high memory.
LD A,(TPABNK) ; Source bank is TPABNK
LD C,A ; Put it in C
LD A,(SYSBNK) ; Destination bank is SYSBNK
LD B,A ; Put it in B
CALL HBX_XCOPY ; Set banks for extended copy
LD HL,(CPADR) ; Copy from start of command processor
LD DE,100H ; .. to $100 in system bank
LD BC,(CPLEN) ; Length of command processor
CALL HBX_COPY ; Do it
JP WBOOTV ; move it and commence execution
ELSE
JP GOZSYS ; Otherwise just go to Command Processor
ENDIF
IF BANKED
COMMON /B2RAM/
ENDIF
;.....
; If this system is Banked and set for Zsdos2, then ALV Buffers are in the
; system bank and will be dynamically sized during Cold Boot. This permits
; BPCNFG to configure a generic IMG file for specific Hard Drive Partitions.
CBOOT0: LD HL,BRAME ; Get end of banked RAM
LD (HISAV),HL ; and save for later use
IF HARDDSK
LD HL,DPHTBL ; Point to start of DPH Table
LD B,16 ; do all DPHs
DYNLP: LD E,(HL)
INC HL
LD D,(HL) ; Get the pointer for this one
INC HL ; advance to next
LD A,D ; Anything there?
OR E
JR Z,DYNCHK ; jump to end if Nothing
DEC DE ; Else back up Ptr to Driver
DEC DE
LD A,(DE) ; Get driver #
IF RAMDSK
DEC A
DEC A ; Hard Disk (Driver 2)?
JR Z,ADDSIZ ; ..jump if so
DEC A ; RAM Disk (Driver 3)?
ELSE
CP 2 ; Hard Disk (Driver 2)?
ENDIF ; Ramdsk
JR NZ,DYNCHK ; ..jump to end if Not
ADDSIZ: PUSH BC ; Save loop counter
PUSH HL ; and ptr to DPH
EX DE,HL
LD DE,12 ; Offset to DPB Ptr (+2 for Decs)
ADD HL,DE
LD E,(HL)
INC HL
LD D,(HL) ; Get Addr of this DPB
INC HL
INC HL
INC HL ; Advance to ALV Addr location
LD BC,(HISAV) ; get end of used RAM
LD (HL),C ; and save
INC HL
LD (HL),B ; in DPH
LD HL,5
ADD HL,DE ; Advance to Size in DPB
LD E,(HL)
INC HL
LD D,(HL) ; and fetch Size-1
INC DE ; Make = Size in Block
PUSH BC ; (save End Addr in BC)
LD B,3
DVRAME: SRL D ; Divide by 2
RR E
DJNZ DVRAME ; *3 = Div 8
INC DE ; +1
EX DE,HL
POP BC ; Restore Ram End
ADD HL,BC ; Add size to Starting Location
LD (HISAV),HL ; save for next drive/overflow check
POP HL ; Restore DPH ptr
POP BC ; and loop ctr
DYNCHK: DJNZ DYNLP ; Loop til all 16 tested
ENDIF ;harddsk
IF BANKED
LD DE,USP ; Point above critical Bios Ram storage
ELSE
LD DE,DIRBUF
ENDIF
IF Z3
LD HL,(ENVADR) ; And top of memory
ELSE
LD HL,0FFFFH
ENDIF
SBC HL,DE ; Calculate # bytes to clear (CF already clr)
EX DE,HL ; Ptr to HL, Cnt to DE
Clr0: LD (HL),0
INC HL
DEC DE
LD A,D
OR E
JR NZ,Clr0 ; ..loop til all cleared
; In systems where we have enough space, we clear unused High Memory too
IF NOT MOVCPM
LD HL,(ENVADR) ; Clear above the ENV as well
LD DE,100H ; Assuming a 2-record ENV
ADD HL,DE ; Are we already at the top of memory?
JR C,ATTOP ; ..bypass clearing if so
EX DE,HL ; Else we must calculate how much to clear
LD HL,MEMTOP ; From the TOP
SBC HL,DE ; subtract the start
LD C,L
LD B,H ; and use for count
LD L,E ; Copy Start to Source
LD H,D
INC DE ; dest is same + 1
LD (HL),0 ; we fill with Zeros
LDIR ; Do it!
ATTOP:
ENDIF ; ~Movcpm
; Initialize the ZCPR3 buffers
IF NOT MOVCPM
LD HL,(ENVADR) ; Should we move our local ENV block?
LD A,H
OR L
JR NZ,BMOVE ; ..jump if we already have one
ENDIF ; (Always move Env if using MOVCPM type load)
LD HL,Z3ENV ; Else set up pointers
LD (ENVADR),HL
LD DE,ENV
EX DE,HL
LD BC,ENVEND-ENV ; count
LDIR ; and move
IF MOVCPM ; Instead of storing Termcap bytes, Zeroize
LD H,D
LD L,E ; Dupe dest addr
LD (HL),0 ; Clear current byte
LD BC,37-1 ; Set count to remaining Termcap area
INC DE ; Dest is next byte
LDIR ; move Zero along
ENDIF ;Movcpm
BMOVE:
IF NOT MOVCPM ; No need to set values on Boot Track System
LD DE,(ENVADR) ; Get pointer to ENV
IF HAVIOP
LD HL,0FH ; Set offset to IOP Addr in ENV
CALL CALCOF ; get the addr and size
LD (IOPPTR),HL ; and set addr
ENDIF ;haviop
LD HL,18H ; Set offset to Mult Comnd Line in ENV
CALL CALCOF ; get addr and size
LD (CLPTR),HL ; set addr
INC HL
INC HL
INC HL ; Advance to CL+3
LD (CL3PTR),HL ; and set
INC HL ; Advance to CL+4
LD (CMDSET),HL ; set addr in Command Line ptr
LD (CMDSET+2),A ; and CL Size byte
LD HL,09H ; Set offset to Path addr in ENV
CALL CALCOF ; get addr
LD (PTHPTR),HL ; and set
ENDIF ;Movcpm
IF FASTWB ; Do we restore CPR from Bank?
IF MOVCPM
LD DE,BIOSJT-1600H ; Get CPR Starting Addr
LD HL,0800H ; and Default Length
ELSE
LD HL,(ENVADR) ; Get pointer to ENV start
LD DE,3FH ; offset to CPR start
ADD HL,DE
LD E,(HL) ; and get CPR starting address
INC HL
LD D,(HL)
INC HL ; (advance to length)
LD H,(HL) ; Get length in blocks (*2 at this point)
LD L,0 ; convert to Word
SRL H ; Compute Blks * 128
RR L ; to give HL = CPR length in bytes
ENDIF ;~Movcpm
; ;
; ; SETUP FOR FASTWB
; ;
; ; BTTBL IS USED TO SAVE ORIGINAL CPR
; ; SARL IS USED TO RESTORE CPR
; ;
; ; 0-2: SRC ADDRESS (LLHHB)
; ; 3-5: DEST ADDRESS (LLHHB)
; ; 6-7: LEN (LLHH)
; ;
; ; SET TRANSFER LENGTH IN BTTBL AND SARL
; LD (BTTBL+6),HL ; Save length in boot block
; LD (SARL+6),HL ; and DMA WB block
; ;
; ; L=TPA BANK, H=SYS BANK
; LD HL,(TPABNK) ; Get TPA (L) and System (H) Banks
; ;
; ; CONVERT BANK:DE -> BHHLL, SAVE AS SRC IN BTTBL AND DEST IN SARL
; LD A,L ; Load TPA Bank #
; RL D ; Move MSB of Address to Carry
; ADC A,0 ; Add Carry to Bank # (in case cross banks)
; RRA ; shift for DMA Bank #
; LD (SARL+5),A ; save in Warm Boot DMA Block
; LD (BTTBL+2),A ; and initial move to bank
; RR D ; Move Bank # LSB (Carry) to MSB of Address
; LD (SARL+3),DE ; Save CPR logical address in WB DMA block
; LD (BTTBL),DE ; and initial move to bank
; ;
; ; CONVERT BANK:$0100 -> BHHLL, SAVE AS DEST IN BTTBL AND SRC IN SARL
; LD A,H ; Load System Bank #
; LD HL,100H ; Load Bank Address of CPR Image Start
; RL H ; get rid of MSB
; ; Since we know the MSB=0, bypass adc 0
; RRA ; Shift for DMA Bank #
; LD (BTTBL+5),A ; save as initial dest bank byte
; LD (SARL+2),A ; and DMA Source Bank byte
; RR H ; Rotate Carry (Bank LSB) to MSB of Address
; LD (SARL),HL ; Save Source Addr in WB DMA block
; LD (BTTBL+3),HL ; and initial move block
LD (CPLEN),HL ; Save command processor length
LD (CPADR),DE ; Save command processor address (in TPA)
ENDIF ;fastwb
; IF BANKED
; ;
; ; SETUP CPYVEC TO COPY IMAGE OF TPA BANK PAGE ZERO TO SYS BANK PAGE ZERO
; LD HL,0000 ; If we are banked, set to copy Page 0
; LD A,(TPABNK) ; of TPA to System Bank
; OR A
; RRA ; Shift TPA Bank #
; LD (CPYVEC+2),A ; store in DMA Block
; RR H ; adjust Address by Bank LSB (Carry)
; LD (CPYVEC),HL ; and store
; LD H,0
; LD A,(SYSBNK)
; RRA ; Shift System Bank #
; LD (CPYVEC+5),A ; store in DMA Block
; RR H ; adjust Address by Bank LSB (Carry)
; LD (CPYVEC+3),HL ; and store
; LD HL,40H ; Set length of move
; LD (CPYVEC+6),HL ; and store in DMA Block
; ENDIF ;banked
LD (STKSAV),SP ; Save entry stack since we alter it here
LD A,(BLOCKE-BLOCK)/6
LD SP,BLOCK
BLKMV: POP BC ; And number of bytes to move
POP HL ; Source
POP DE ; Get destination
LDIR
DEC A ; Another block moved
JR NZ,BLKMV ; Do more as required
LD SP,(STKSAV) ; Get entry Stack Pointer back so we can return
; All Buffers above BIOS have been cleared already at this point
DEC A ; 0 --> FF
LD (Z3WHL),A ; Set the Wheel Byte
; Get and save the internal HBIOS physical disk
; buffer address which is assumed to be in the
; HBIOS bank.
LD B,18H ; Get buffer function call (assumes already allocated!!!)
LD HL,0 ; ... with address 0 to get HBIOS buf adr
CALL HBX_INVOKE ; ... to return internal HBIOS buffer adr
LD (HB_DSKBUF),HL ; Record the buffer address
IF HAVIOP
LD HL,IOPRET
LD (BIOSJT+1),HL
ENDIF ;haviop
; LD HL,INTTBL ; Set the Interrupt Vector
; LD A,H ; first the page
; LD I,A ; to CPU Register
; OUT0 (IL),L ; then the segment addr
IF BANKED
CALL JDVINI ; Call directly because we are in High Stack
ELSE
CALL DEVINI ; Initialize the I/O system
ENDIF ; And any device specific ram
IF [BANKED AND ZSDOS2]
LD DE,8000H ; If ALVs in Bank, size against Bank2 Top
ELSE
LD DE,(USRSP) ; else against base of User Space
ENDIF
LD HL,(HISAV) ; Load Highest RAM Address used
OR A
SBC HL,DE ; Is Needed Space > Limit?
JR C,MEMOK ; ..jump if So
CALL PRINT ; Else Warn user
DEFB CR,LF,7,'++ Mem Ovfl +','+'+80H
; Sign on the system
MEMOK:
CALL PRINT
IF MOVCPM ; Space is critical for boot tracks
DEFB CR,LF,'P112 - ' ; Save all bytes possible
ELSE ; Otherwise sign on with complete name
DEFB CR,LF,'D-X Designs P112 - '
ENDIF
DEFB 'B/P 50.00k Bios' ;**** Do NOT alter this string ****
DEFB ' V',VERS/16+'0','.',VERS MOD 16+'0',' ' ; Vers in BCD
DATE
IF BANKED
DEFB ' (Banked) '
ELSE
IF NOT MOVCPM
DEFB ' (Non-Banked) ' ; Nothing for boot track system
ENDIF
ENDIF
IF BANKED
DEFB ' with:',CR,LF,LF
DEFB ' ZCPR3+ Env'
IF CLOCK
IF DS1202
DEFB CR,LF,' Dallas DS-1202 Clock, '
IF CLKSET
DEFB 'with '
ELSE
DEFB 'NO '
ENDIF
DEFB 'Set'
ELSE
DEFB CR,LF,' ZSDOS Interrupt Clock'
ENDIF
ENDIF
DEFB CR,LF,' High-Density Floppy'
IF FDDMA
DEFB ' (DMA-driven IO)'
ELSE
DEFB ' (Polled IO)'
ENDIF
IF HARDDSK
IF SCSI
DEFB CR,LF,' SCSI Hard Disk Driver'
ENDIF
IF IDE
DEFB CR,LF,' GIDE Hard Disk Driver'
ENDIF
IF HDSK
IF HBIOS
DEFB CR,LF,' HBIOS Hard Disk Driver'
ELSE
DEFB CR,LF,' SIMH Hard Disk Driver'
ENDIF
ENDIF
IF HDDMA
DEFB ' (DMA-driven IO)'
ELSE
DEFB ' (Polled IO)'
ENDIF
ENDIF
IF FASTWB
DEFB CR,LF,' Warm Boot from RAM'
ENDIF
IF RAMDSK
DEFB CR,LF,' RAM Disk (M:)'
ENDIF
IF BIOERM
DEFB CR,LF,' Full Error Messages'
ENDIF
ENDIF ;Banked
DEFB CR,LF+80H
;WW EI ; Turn Interrupts back on
RET ; ..and return
;.....
; Offset to and get ENV Address and respective element size
CALCOF: ADD HL,DE ; Add offset to Base ENV Addr
LD C,(HL) ; get low byte
INC HL
INC HL ; advance to size byte
LD A,(HL) ; get size
DEC HL ; Back down to Addr hi byte
LD H,(HL) ; and grab
LD L,C ; Ptr to Segment now in HL
RET ; return to caller
; Block Move Parameters
BLOCK: DEFW PATH-CMDSET ; # to move
DEFW CMDSET ; Source
CLPTR: DEFW Z3CL ; Destination
DEFW 10
DEFW AUTOCMD
CL3PTR: DEFW Z3CL+3
DEFW PATHE-PATH
DEFW PATH
PTHPTR: DEFW EXPATH
IF HAVIOP
DEFW IOPLEN+2
DEFW IOPENT
IOPPTR: DEFW IOP
ENDIF
IF HARDDSK AND HDDMA AND (NOT IDE)
DEFW DMALEN
DEFW DMADAT
DEFW DMATBL
ENDIF
BLOCKE EQU $
;.....
; Initial HD DMA Control Block data
IF HARDDSK AND HDDMA
DMADAT: DEFW HSTBUF ; Physical sector address
DEFB 00 ; BNK2 SHR 1 if banked, BNK0 SHR 1 If not
DEFW DMAACK ; Dack port address
DEFB 0
DEFW 400H ; Number of bytes to transfer (1Sct+slop=2Scts)
DMALEN EQU $-DMADAT
ENDIF
CMDSET: DEFW Z3CL+4 ; Point to first character in command buffer
DEFB Z3CLS ; Command buffer size
DEFW 0 ; Clear the command line
PATH: DEFB '$','$',1,15 ; Current, A15:
DEFB 0 ; End of initial path
PATHE EQU $
; Environment Descriptor for ZCPR34
ENV: JP 0 ; Leading jump (address is CBIOS when NZCOM)
ENV1: ; ZCPR3 enviornment descriptor ...
DEFB 'Z3ENV' ; Environment id
DEFB 90H ; Env type (=>80H means extended ENV). YASBEC
; uses 90H to show User Area instead of Prt2
DEFW EXPATH ; External path (path)
DEFB EXPATHS ;
DEFW RCP ; Resident command package (rcp)
DEFB RCPS ;
DEFW IOP ; Input/output package (iop)
DEFB IOPS ;
DEFW FCP ; Flow command package (fcp)
DEFB FCPS ;
DEFW Z3NDIR ; Named directories (ndr)
DEFB Z3NDIRS ;
DEFW Z3CL ; Command line (cl)
DEFB Z3CLS ;
DEFW Z3ENV ; Environment (env)
DEFB Z3ENVS ;
DEFW SHSTK ; Shell stack (sh)
DEFB SHSTKS ;
DEFB SHSIZE ;
DEFW Z3MSG ; Message buffer (msg)
DEFW EXTFCB ; External fcb (fcb)
DEFW EXTSTK ; External stack (stk)
DEFB 0 ; Quiet flag (1=quiet, 0=not quiet)
DEFW Z3WHL ; Wheel byte (whl)
DEFB 16 ; Processor speed (mhz)
DEFB 'P'-'@' ; Max disk letter
DEFB 31 ; Max user number
DEFB 1 ; 1 = Ok to accept DU:, 0 = Not Ok
DEFB 0 ; Crt selection ()
DEFB 0 ; Printer selection ()
DEFB 80 ; Crt 0: width
DEFB 24 ; # of lines
DEFB 22 ; # of text lines
; In Extended ENV, CRT 1 is replaced by System Info
;; DEFB 132 ; . CRT 1: Width
;; DEFB 24 ; # of lines
;; DEFB 22 ; # of text lines
; The Drive Vector is a 16-bit word in which a "1" bit indicates that a drive
; is active in the system. The bits are arranged as: PONMLKJIHGFEDCBA. When
; stored in memory, it is in normal form with the Low byte stored first.
E_DRVL DEFL [DRV_A & 1] + [DRV_B & 2] + [DRV_C & 4] + [DRV_D & 8]
E_DRVL DEFL E_DRVL + [DRV_E & 16] + [DRV_F & 32] + [DRV_G & 64]
E_DRVL DEFL E_DRVL + [DRV_H & 128] ; Low Byte Formed
E_DRVH DEFL [DRV_I & 1] + [DRV_J & 2] + [DRV_K & 4] + [DRV_L & 8]
E_DRVH DEFL E_DRVH + [DRV_M & 16] + [DRV_N & 32] + [DRV_O & 64]
E_DRVH DEFL E_DRVH + [DRV_P & 128] ; High Byte Formed
DEFW E_DRVH * 256 + E_DRVL
DEFB 0 ; (Reserved)
DEFB 80 ; Prt 0: width
DEFB 66 ; # of lines
DEFB 58 ; # of text lines
DEFB 1 ; Ff flag (1=can form feed)
;========= Usurped Prt1 storage for Resident User Space Vectors =========
;; DEFB 96 ; Prt 1: width
;; DEFB 66 ; # of lines
;; DEFB 58 ; # of text lines
;; DEFB 1 ; Ff flag (1=can form feed)
DEFB USPCS ; Remaining Free User Space (recs)
USRSP: DEFW USPC ; Res. User Space base Address (xx00h/xx80h)
DEFB USPCS ; Size of Res. User Space in 128-byte recs
;========================================================================
; In Extended ENV, Printers 2 and 3 are gone, replaced by System Info
;; DEFB 132 ; . PRT 2: Width
;; DEFB 66 ; # of lines
;; DEFB 58 ; # of text lines
;; DEFB 1 ; FF flag (1=can form feed)
;; DEFB 132 ; . PRT 3: Width
;; DEFB 88 ; # of lines
;; DEFB 82 ; # of text lines
;; DEFB 1 ; FF flag (1=can form feed)
DEFW CPR ; Ccp base address
DEFB [DOS-CPR]/128 ; Size of ccp in 128 byte records
DEFW DOS ; Bdos base address (xx00h or xx80h)
DEFB [BIOSJT-DOS]/128 ; Bdos buffer size in 128 byte records
DEFW BIOSJT ; Bios base address (nzbio if nzcom running)
DEFB 'SH ' ; Shell variable filename
DEFB 'VAR' ; Shell variable filetype
DEFB ' ' ; File 1
DEFB ' ' ;
DEFB ' ' ; File 2
DEFB ' ' ;
DEFB ' ' ; File 3
DEFB ' ' ;
DEFB ' ' ; File 4
DEFB ' ' ;
DEFB 0 ; Public drive area (zrdos +)
DEFB 0 ; Public user area (zrdos +)
; Env 128 bytes long
;***************************************************************************
; This TermCap Data for the New Z-System complies with VLIB4D specs and more
; fully describes the terminal and its capabilities. Edit the fields with
; values for your terminal characteristics, or use it as a template for an
; outboard definition loaded from the Startup file.
ENV2: DEFB ' ' ; Terminal Name (13 bytes, space terminated)
IF MOVCPM ; Dummies for boot track systems
B13: DEFB 0
B14: DEFB 0 ; Bit 7 = Normal TCAP
ELSE
B13: DEFB GOELD-ENV2 ; Offset to GOELD in graphics section
B14: DEFB 10000000B ; Bit 7 = Extended TCAP, remainder undefined
ENDIF ;~Movcpm
; B15 b0 Standout 0 = Half-Intensity, 1 = Reverse Video
; B15 b1 Power Up Delay 0 = None, 1 = 10-second delay
; B15 b2 No Wrap 0 = Line Wrap, 1 = No Wrap if char written
; to last character in line
; B15 b3 No Scroll 0 = Scroll, 1 = No Scroll if char written
; to last char in last line of diplay
; B15 b4 ANSI 0 = ASCII, 1 = ANSI
B15: DEFB 00000000B ; Reverse Vid, Wrap, Scroll, ASCII
; Additional single character cursor motion bytes
DEFB 'E'-'@' ; Cursor Up
DEFB 'X'-'@' ; Cursor Down
DEFB 'D'-'@' ; Cursor Right
DEFB 'S'-'@' ; Cursor Left
IF NOT MOVCPM ; Omit in boot systems to save space
; Instead, we simply zero remainder.
DEFB 0 ; CL Delay for Screen Clear
DEFB 0 ; CM Delay for Cursor Motion
DEFB 0 ; CE Delay for Clear to End-of-Line
; Strings start here
DEFB 0 ; (CL) Home Cursor and Clear Screen
DEFB 0 ; (CM) Cursor Motion
DEFB 0 ; (CE) Clear to End-of-Line
DEFB 0 ; (SO) Reverse On
DEFB 0 ; (SE) Reverse Off
DEFB 0 ; (TO) Terminal Init
DEFB 0 ; (TE) Terminal De-init
; Extensions to Standard Z3TCAP
DEFB 0 ; (LD) Delete Line
DEFB 0 ; (LI) Insert Line
DEFB 0 ; (CD) Clear from Cursor to End-of-Scr
; Attributes setting parameters
DEFB 0 ; Set Attributes
DEFB 0 ; Attributes String
; Read items from screen
DEFB 0 ; Report Cursor Pos'n (ESC Y Pn Pn)
DEFB 0 ; Read Line Under Cursor
GOELD: DEFB 0 ; On/Off Delay
; Graphics strings offset from Delay value.
DEFB 0 ; Graphics On
DEFB 0 ; Graphics Off
DEFB 0 ; Cursor Off
DEFB 0 ; Cursor On
; Graphics Characters
DEFB '*' ; Upper-Left corner [*]
DEFB '*' ; Upper-right corner [*]
DEFB '*' ; Lower-Left corner [*]
DEFB '*' ; Lower-right corner [*]
DEFB '-' ; Horizontal Line [-]
DEFB '|' ; Vertical Line [|]
DEFB '#' ; Full Block (hashed block) [*]
DEFB 'X' ; Hashed Block (big X) [#]
DEFB '+' ; Upper Intersect (Upside down "T") [+]
DEFB '+' ; Lower Intersect ("T") [+]
DEFB '+' ; Mid Intersect (Crossing Lines) [+]
DEFB '+' ; Right Intersect ("T" rotated left) [+]
DEFB '+' ; Left Intersect ("T" rotated right) [+]
DEFB 0
DEFB 0
ENDIF ;~Movcpm
ENVEND:
; IOP initial data
IF HAVIOP
IOPENT: JP IOPEND
JP IOPEND
JP IOPEND
JP IOPEND
JP CONST
JP CONIN
JP CONOUT
JP LIST
JP AUXOUT
JP AUXIN
JP LISTST
JP IOPEND
JP IOPEND
JP IOPEND
JP IOPEND
JP IOPEND
DEFB 'Z3IOP'
DEFB 'DUMMY '
IOPLEN EQU $-IOPENT
IOPEND EQU IOP+IOPLEN
XOR A
RET
ENDIF ;haviop
BCODEE EQU $
IF BANKED
INITCS EQU BCODEE-CBOOT0 ; Size of Banked (B2RAM) part of Init Code
ELSE
INITCS EQU BCODEE-CBOOT ; Size of Complete Init Code in DSEG
ENDIF
STKSAV: DEFS 2 ; Storage for Pointer while moving
HISAV: DEFS 2 ; Storage for Hi-ALV address
IF FASTWB
DSEG
BTTBL: DEFS 8 ; Initial WB DMA Block
ENDIF
;======================== End of CBOOT =============================