reorganize everything

This commit is contained in:
Dennis Gunia
2024-06-24 20:38:02 +02:00
parent ea1069e59c
commit 1ed6034d99
3867 changed files with 16188 additions and 13447 deletions

View File

@@ -0,0 +1 @@
../../monitor_v2/zout/symbols.s

File diff suppressed because it is too large Load Diff

View File

@@ -0,0 +1,271 @@
CS_PIO_BD .EQU 0xF5
CS_PIO_BC .EQU 0xF7
CS_PIO_AD .EQU 0xF4
CS_PIO_AC .EQU 0xF6
CS_I2C_S1 .EQU 0xF3
CS_I2C_SX .EQU 0xF2
iic_init:
LD A,0xCF
OUT (CS_PIO_AC), A
LD A,11110101b
OUT (CS_PIO_AC), A
LD A,00000000b ; Reset PCF8584 minimum 30 clock cycles
OUT (CS_PIO_AD), A
LD BC,0x1000
CALL _pause_loop
LD A,0000010b
OUT (CS_PIO_AD), A
LD BC,0x2000
CALL _pause_loop
LD A, 0x80 ;S1 -> Select S0, PIN disabled, ESO = 0, Interrupt disabled, STA, STA, ACK = 0
OUT (CS_I2C_S1),A
CALL _slow_access
;CALL _slow_access
LD A,0x55 ;S0 -> Loads byte 55H into register S0'; effective own address becomes AAH
OUT (CS_I2C_SX),A
CALL _slow_access
LD A, 0xA0 ;S1 -> Loads byte A0H into register S1, i.e. next byte will be loaded into the clock control register S2.
OUT (CS_I2C_S1),A
CALL _slow_access
; 000100000
LD A,0x18 ;Load 18H into S2 register (clock control - 4.43 MHz, 90 KHz)
LD A,0x00 ;Load 18H into S2 register (clock control - 4.43 MHz, 90 KHz)
OUT (CS_I2C_SX),A
CALL _slow_access
;CALL _slow_access
;CALL _slow_access
;CALL _slow_access
LD A,0xC1 ;S1 -> loads byte C1H into register S1; register enable
;serial interface, set I 2C-bus into idle mode;
;SDA and SCL are HIGH. The next write or read
;operation will be to/from data transfer register
;S0 if A0 = LOW.;
OUT (CS_I2C_S1),A
CALL _slow_access
RET
;------------------------------------------------------------------------------
; iic_send
;
; Sends data over the i2c bus
; A contains BYTE COUNTER
; B contains ADDRESS
; DE contains location of Data Buffer
;------------------------------------------------------------------------------
iic_send:
;CALL PRINTINLINE;
;defb "SEND A",10,13,0
PUSH BC
PUSH AF
CALL iic_bus_rdy
;CALL PRINTINLINE
;defb "SEND START",10,13,0
LD A,B ;Load 'slave address' into S0 register:
OUT (CS_I2C_SX),A
CALL _slow_access
LD A, 0xC5 ;Load C5H into S1. 'C5H' = PCF8584 generates
;the 'START' condition and clocks out the slave
;address and the clock pulse for slave acknowledgement.
OUT (CS_I2C_S1),A
POP AF
LD C,A
INC C
_iic_send_1: ; LOOP 1 : Wait for bus ready
IN A,(CS_I2C_S1) ; Read byte from S1 register
BIT 7,A ; Is bus free? (S1 ~BB=1?)
JR NZ,_iic_send_1 ; No - loop
BIT 4,A ; slave acknowledged? (LRB = 0?)
JR NZ, _iic_send_stop ; if not, cancel transmission
LD A,(DE) ; Load next byte from buffer
INC DE
DEC C
JR Z, _iic_send_stop ; if counter = 0, exit loop
OUT (CS_I2C_SX),A ; Send byte
JR _iic_send_1 ; if counter > 0, loop again
_iic_send_stop:
LD A, 0xC3 ;STOP
OUT (CS_I2C_S1),A
CALL _slow_access
POP BC
RET
;------------------------------------------------------------------------------
; iic_read
;
; Sends data over the i2c bus
; A contains BYTE COUNTER
; B contains ADDRESS
; DE contains location of Data Buffer
;------------------------------------------------------------------------------
iic_read:
PUSH DE
PUSH BC
PUSH AF
LD A,B ;Load 'slave address' into S0 register:
OR 0x01 ;Set RW Bit for read operation
OUT (CS_I2C_SX),A
CALL _slow_access
CALL iic_bus_rdy ; Is bus ready
LD A, 0xC5 ;Load C5H into S1. 'C5H' = PCF8584 generates
;the 'START' condition and clocks out the slave
;address and the clock pulse for slave acknowledgement.
OUT (CS_I2C_S1),A
;Setup counter
POP AF
LD C,A ; Load BYTE COUNTER into C
INC C ; Offset C by 1
_iic_read_1: ;Wait for PIN = 0
IN A,(CS_I2C_S1) ; Read byte from S1 register
BIT 7,A ; S1 PIN=1?
JR NZ,_iic_read_1 ; No - loop
BIT 3,A ; S1 LRB=0? slave ACK?
JR NZ, _iic_read_error ; No ACK -> an error has occured
DEC C
LD A, C
DEC A ;If n = m 1?
JR Z, _iic_read_last
IN A,(CS_I2C_SX)
LD (DE),A
INC DE
JR _iic_read_1
_iic_read_last: ;read last byte
LD A, 0x40
OUT (CS_I2C_S1),A
CALL _slow_access
IN A,(CS_I2C_SX) ;receives the final data byte. Neg. ACK is also sent.
LD (DE),A
INC DE
_iic_read_last_1:
IN A,(CS_I2C_S1) ; Read byte from S1 register
BIT 7,A ; S1 PIN=1?
JR NZ,_iic_read_last_1 ; No - loop
_iic_read_error:
NOP
_iic_read_stop:
LD A, 0xC3
OUT (CS_I2C_S1),A
CALL _slow_access
IN A,(CS_I2C_SX) ;transfers the final data byte from the
;data buffer to accumulator.
CALL _slow_access
LD (DE),A
POP BC
POP DE
RET
;------------------------------------------------------------------------------
; iic_rdy
;
; Waits until the PCF8584 signals a byte transmission/reception is complete.
;------------------------------------------------------------------------------
iic_rdy:
PUSH AF
_iic_rdy_loop:
IN A,(CS_I2C_S1) ; Read byte from S1 register
BIT 7,A ; Is Tx/Rx complete? (S1 PIN=0?)
;call print_a_hex
JR NZ,_iic_rdy_loop ; No - loop
_iic_rdy_done:
POP AF
RET
;------------------------------------------------------------------------------
; i2c_bus_rdy
;
; Waits until the I2C bus is free before RETurning
;------------------------------------------------------------------------------
iic_bus_rdy:
PUSH AF
_iic_blp:
IN A,(CS_I2C_S1) ; Read byte from S1 register
PUSH AF
call print_a_hex
POP AF
BIT 0,A ; Is bus free? (S1 ~BB=1?)
JR Z,_iic_blp ; No - loop
POP AF
RET
;------------------------------------------------------------------------------
; _pause_loop
;
; Timer function
;
; 16-bit (BC) decrement counter, performing 4xNEG loop until BC
; reaches zero.
;
; 61 T-states in loop = 15.25uS per loop @ 4 MHz - near enough
; a second delay for 65,535 iterations.
;
; Set iteration count in BC before calling this function.
; Destroys: BC
;------------------------------------------------------------------------------
_pause_loop:
PUSH AF ; 11 T-states
_pause_loop_lp:
;NEG ; 8 T-states
;NEG ; 8 T-states
;NEG ; 8 T-states
;NEG ; 8 T-states
PUSH BC ; 11 T-states
POP BC ; 10 T-states
PUSH BC ; 11 T-states
POP BC ; 10 T-states
DEC BC ; 6 T-states
LD A,C ; 9 T-states
OR B ; 4 T-states
JP NZ,_pause_loop_lp ; 10 T-states
POP AF ; 10 T-states
RET ; Pause complete, RETurn
iic_force_stop:
IN A,(CS_I2C_S1)
BIT 0, A
RET NZ
LD A, 11000011b
OUT (CS_I2C_S1),A
NOP
NOP
JR iic_force_stop
_slow_access:
NOP
NOP
NOP
NOP
NOP
NOP
NOP
NOP
PUSH AF
POP AF
PUSH AF
POP AF
PUSH AF
POP AF
PUSH AF
POP AF
PUSH AF
POP AF
PUSH AF
POP AF
POP AF
RET

View File

@@ -0,0 +1,11 @@
;----------------------------------------------------------------
;BIOS Driver for SI5351
;by Dennis Gunia (01/2024)
;----------------------------------------------------------------
;Device address
ADDR_SI_CLK .EQU 0x00
;================================================================
; SI registers
;================================================================

View File

@@ -0,0 +1,706 @@
; TMS9918A graphics subroutines
; Copyright 2018-2020 J.B. Langston
;
; Permission is hereby granted, free of charge, to any person obtaining a
; copy of this software and associated documentation files (the "Software"),
; to deal in the Software without restriction, including without limitation
; the rights to use, copy, modify, merge, publish, distribute, sublicense,
; and/or sell copies of the Software, and to permit persons to whom the
; Software is furnished to do so, subject to the following conditions:
;
; The above copyright notice and this permission notice shall be included in
; all copies or substantial portions of the Software.
;
; THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
; IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
; FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
; AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
; LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
; FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER
; DEALINGS IN THE SOFTWARE.
; VDP Programmer's Guide: http://map.grauw.nl/resources/video/ti-vdp-programmers-guide.pdf
phase 0xE400
; ---------------------------------------------------------------------------
; configuration parameters; can be changed at runtime
TmsPort:
defb 0xE0 ; port for TMS vram (reg is 1 higher)
TmsWait:
defb 64 ; iterations to wait after ram access
TmsMode:
defw 0 ; mode registers
TmsNameAddr:
defw 3800h ; name table address (multiples of 400H)
TmsColorAddr:
defw 2000h ; color table address (multiples of 40H)
TmsPatternAddr:
defw 0 ; pattern table (multiples of 800H)
TmsSpritePatternAddr:
defw 1800h ; sprite attribute table (multiples of 80H)
TmsSpriteAttrAddr:
defw 3bc0h ; sprite pattern table (multiples of 800H)
TmsScreenColors:
defb 0 ; background (low nybble), text color (high nybble)
; ---------------------------------------------------------------------------
; register constants
dephase
setup_vars:
ld a,0xE0
ld (TmsPort),a
ld a,2
ld (TmsWait),a
ld a,0
ld (TmsMode),a
ld a,0
ld (TmsMode+1),a
ld a,0
ld (TmsNameAddr),a
ld a,38h
ld (TmsNameAddr+1),a
ld a,0
ld (TmsPatternAddr),a
ld a,0
ld (TmsPatternAddr+1),a
ld a,0
ld (TmsColorAddr),a
ld a,20h
ld (TmsColorAddr+1),a
ld a,0
ld (TmsSpritePatternAddr),a
ld a,0x18
ld (TmsSpritePatternAddr+1),a
ld a,0xc0
ld (TmsSpriteAttrAddr),a
ld a,0x3b
ld (TmsSpriteAttrAddr+1),a
ret
TmsWriteBit: equ 40h ; bit to indicate memory write
; Registers
TmsCtrl0Reg: equ 80h
TmsCtrl1Reg: equ 81h
TmsNameReg: equ 82h
TmsColorTableReg: equ 83h
TmsPatternReg: equ 84h
TmsSpriteAttrReg: equ 85h
TmsSpritePatternReg: equ 86h
TmsColorReg: equ 87h
; Control Register Bits
TmsM3: equ 200h
TmsExtVideo: equ 100h
Tms16k: equ 80h
TmsDisplayEnable: equ 40h
TmsIntEnableBit: equ 20h
TmsM1: equ 10h
TmsM2: equ 8
TmsSprite32: equ 2
TmsSpriteMag: equ 1
; ---------------------------------------------------------------------------
; table lengths
TmsTileNameLen: equ 300h
TmsTextNameLen: equ 3c0h
TmsTileColorLen: equ 20h
TmsBitmapColorLen: equ 800h
TmsTilePatternLen: equ 800h
TmsTextPatternLen: equ 800h
TmsMulticolorPatternLen: equ 600h
TmsBitmapPatternLen: equ 1800h
; ---------------------------------------------------------------------------
; color constants
TmsTransparent: equ 0
TmsBlack: equ 1
TmsMediumGreen: equ 2
TmsLightGreen: equ 3
TmsDarkBlue: equ 4
TmsLightBlue: equ 5
TmsDarkRed: equ 6
TmsCyan: equ 7
TmsMediumRed: equ 8
TmsLightRed: equ 9
TmsDarkYellow: equ 0ah
TmsLightYellow: equ 0bh
TmsDarkGreen: equ 0ch
TmsMagenta: equ 0dh
TmsGray: equ 0eh
TmsWhite: equ 0fh
; ---------------------------------------------------------------------------
; port I/O routines
; These routines access the ports configured in TmsPort.
; These memory locations can be set at runtime to support different hardware
; configurations from the same binary. TmsProbe automatically detects the
; TMS9918A on common ports.
; The TMS9918A RAM must not be accessed more than once every 8 us or display
; corruption may occur. During vblank and with the display disabled,
; accesses can be 2 us apart, but we will always use 8 us minimum delay.
; TmsRamIn/TmsRamOut include a configurable delay loop, which waits for the
; configured iterations between VRAM writes to work properly with faster CPUs
; Minimum time to execute each procedure call:
; Z80: 88 cycles, 8.8 us @ 10 MHz
; Z180: 80 cycles, 8.64 us @ 9.216 MHz, 4.32 us @ 18.432, 2.16 us @ 36.864
;
; Additional delay per djnz iteration:
; Z80: 8 cycles * (iterations - 1)
; 0.8 us @ 10 MHz
; Z180: 7 cycles * (iterations - 1)
; 0.756 us @ 9.216 MHz, 0.378 us @ 18.432, 0.189 us @ 36.864
; Delay loop iterations required for different CPU speeds:
; Z80 @ 10 MHz or less: 1
; Z180 @ 9.216 MHz or less: 1
; Z180 @ 18.432 MHz: 10
; Z180 @ 36.864 MHz: 31
TmsWaits: defb 1, 10, 31 ; wait iterations to add for different CPU speeds
; set up wait time based on clock multiplier in E
TmsSetWait:
ld a,1
ld (TmsWait), a
ret
; try to find TMS9918A on common ports
TmsProbe:
ld hl, TmsPorts
ld b, TmsNumPorts
TmsProbeNext:
ld a, (hl)
ld (TmsPort), a
call TmsRegIn ; clear vsync bit
call TmsRegIn ; check it again
jp m, TmsProbeFailed ; if still set, not a TMS9918A
ld de, 0ffffh ; long enough for another vsync
TmsProbeWait:
call TmsRegIn ; check vsync bit again
ret m ; if set, it's a TMS9918A (and Z is clear)
dec de ; otherwise, keep waiting
ld a, e
or d
jp nz, TmsProbeWait
TmsProbeFailed:
inc hl ; if still clear after this long, try next port
djnz TmsProbeNext
xor a ; set Z if we ran out of ports to check
ret
TmsPorts: ; List of ports to probe:
defb 0x80 ; ColecoVision / SG-1000
defb 98h ; MSX
defb 10h ; Sord M5 (conflicts with z80ctrl SIO port)
;defb 8 ; Tatung Einstein (conflicts with z80ctrl drive ports)
;defb 1 ; MTX (not supported by TMS9918A video card)
; add additional ports to check here
TmsNumPorts: equ $ - TmsPorts
; set a single register value
; A = register value
; E = register to set
TmsSetReg:
call TmsRegOut
ld a, e
; fallthrough to TmsRegOut
; write to configured register port
; parameters:
; A = value to write
TmsRegOut:
push bc
ld bc, (TmsPort)
inc c
out (c), a
pop bc
ret
; read from configured register port
; returns:
; A = value read
TmsRegIn:
push bc
ld bc, (TmsPort)
inc c
in a, (c)
pop bc
ret
; write to configured VRAM port
; parameters:
; A = value to write
; Z80 | Z180 cycles...
TmsRamOut: ; 17 | 16 (call)
push bc ; 11 | 11
ld bc, (TmsPort) ; 20 | 18
out (c), a ; 12 | 10
TmsRamOutDelay:
djnz TmsRamOutDelay ; 8 | 7 plus (13 | 9) * (iterations-1)
pop bc ; 10 | 9
ret ; 10 | 9
; read from configured VRAM port
; returns:
; A = value read
TmsRamIn:
push bc
ld bc, (TmsPort)
TmsRamInDelay:
djnz TmsRamInDelay
in a, (c)
ld bc, (TmsPort)
TmsRamInDelay2:
djnz TmsRamInDelay2
pop bc
ret
; ---------------------------------------------------------------------------
; register configuration routines
; set the background color
; A = requested color
TmsBackground:
and 0fh
ld b, a
ld a, (TmsScreenColors)
and 0f0h
or b
ld (TmsScreenColors), a
ld e, TmsColorReg
jp TmsSetReg
; set the sprite configuration
; A = sprite options
TmsSpriteConfig:
and TmsSprite32|TmsSpriteMag
ld b, a
ld a, (TmsMode)
and ~(TmsSprite32|TmsSpriteMag)
or b
ld (TmsMode), a
ld e, TmsCtrl1Reg
jp TmsSetReg
; enable vblank interrupts
TmsIntEnable:
ld a, (TmsMode)
or TmsIntEnableBit
ld (TmsMode), a
ld e, TmsCtrl1Reg
jp TmsSetReg
; disable vblank interrupts
TmsIntDisable:
ld a, (TmsMode)
and ~TmsIntEnableBit
ld (TmsMode), a
ld e, TmsCtrl1Reg
jp TmsSetReg
; ---------------------------------------------------------------------------
; initialization routines
TmsBlankFlags: equ Tms16k
TmsTileFlags: equ Tms16k | TmsDisplayEnable
TmsTextFlags: equ Tms16k | TmsDisplayEnable | TmsM1
TmsMulticolorFlags: equ Tms16k | TmsDisplayEnable | TmsM2
TmsBitmapFlags: equ Tms16k | TmsDisplayEnable | TmsM3
; reset registers and clear all 16KB of video memory
TmsReset:
ld hl, TmsBlankFlags ; blank the screen with 16KB enabled
ld (TmsMode), hl
ld a, l
ld e, TmsCtrl1Reg
call TmsSetReg
ld a, h
ld e, TmsCtrl0Reg
call TmsSetReg
ld a, TmsTransparent
call TmsBackground
ld a, TmsTransparent
call TmsTextColor
ld de, 0 ; clear entire VRAM
ld bc, 4000h
ld a, 0
call TmsFill
ret
; initialize for multicolor mode
TmsMulticolor:
call TmsReset
ld de, (TmsNameAddr)
call TmsWriteAddr
ld d, 6 ; name table has 6 sections
ld e, 0 ; lines in first section start at 0
TmsSectionLoop:
ld c, 4 ; each section has 4 identical lines
TmsLineLoop:
ld b, 32 ; each line is 32 bytes long
ld a, e ; same starting value for each line in section
TmsByteLoop:
call TmsRamOut
inc a ; byte value
djnz TmsByteLoop
dec c ; line counter
jp nz, TmsLineLoop
ld e, a ; next starting value = current + 32
dec d ; section counter
jp nz, TmsSectionLoop
ld hl, TmsMulticolorFlags
ld (TmsMode), hl
jp TmsInitNonBitmap
; initialize for tiled graphics
TmsTile:
call TmsReset
ld hl, TmsTileFlags
ld (TmsMode), hl
jp TmsInitNonBitmap
; initialize for text mode
; HL = address of font to load
TmsTextMode:
push hl
call TmsReset
pop hl
ld de, (TmsPatternAddr) ; load font from address in hl
ld bc, TmsTextPatternLen
call TmsWrite
ld hl, TmsTextFlags
ld (TmsMode), hl
; fallthrough to TmsInitNonBitmap
; non-bitmap color and pattern table configuration
TmsInitNonBitmap:
; set up color table address (register = address / 400H)
ld a, (TmsColorAddr)
and 0c0h
ld (TmsColorAddr), a
ld d, a
ld a, (TmsColorAddr+1)
and 3fh
ld (TmsColorAddr+1), a
rl d
rla
rl d
rla
ld e, TmsColorTableReg
call TmsSetReg
; set up pattern table address (register = address / 800H)
xor a
ld (TmsPatternAddr), a
ld a, (TmsPatternAddr+1)
and 38h
ld (TmsPatternAddr+1), a
rrca
rrca
rrca
ld e, TmsPatternReg
call TmsSetReg
jp TmsInitCommon
; initialize for bitmapped graphics
TmsBitmap:
call TmsReset
ld de, (TmsNameAddr) ; initialize name table with 3 sets
call TmsWriteAddr ; of 256 bytes ranging from 00-FF
ld b, 3
xor a
TmsBitmapLoop:
call TmsRamOut
inc a
jp nz, TmsBitmapLoop
djnz TmsBitmapLoop
ld hl, TmsBitmapFlags
ld (TmsMode), hl
; set up color table at 0H (register = 7FH) or 2000H (register = 0FFH)
xor a
ld (TmsColorAddr), a
ld (TmsPatternAddr), a
ld a, (TmsColorAddr+1)
and 20h
ld (TmsColorAddr+1), a
ld a, 0ffh ; color table at 2000H
jp nz, TmsColorTableHigh
ld a, 7fh ; color table at 0H
TmsColorTableHigh:
ld e, TmsColorTableReg
call TmsSetReg
; set up pattern table at 0H (register = 3) or 2000H (register = 7)
ld a, (TmsPatternAddr+1)
and 20h
ld (TmsPatternAddr+1), a
ld a, 7 ; pattern table at 2000H
jp nz, TmsPatternTableHigh
ld a, 3 ; pattern table at 0H
TmsPatternTableHigh:
ld e, TmsPatternReg
call TmsSetReg
; fall through to TmsInitCommon
; common initialization for all modes
TmsInitCommon:
; set up name table address (register = address / 400H)
xor a
ld (TmsNameAddr), a
ld a, (TmsNameAddr+1)
and 3ch
ld (TmsNameAddr+1), a
rrca
rrca
ld e, TmsNameReg
call TmsSetReg
; set up sprite pattern table address (register = address / 80H)
ld a, (TmsSpriteAttrAddr)
and 80h
ld (TmsSpriteAttrAddr), a
ld d, a
ld a, (TmsSpriteAttrAddr+1)
and 7fh
rl d
rla
ld e, TmsSpriteAttrReg
call TmsSetReg
; set up sprite attribute table address (register = address / 800H)
xor a
ld (TmsSpritePatternAddr), a
ld a, (TmsSpritePatternAddr+1)
and 38h
ld (TmsSpritePatternAddr+1), a
rrca
rrca
rrca
ld e, TmsSpritePatternReg
call TmsSetReg
; set up control registers
ld e, TmsCtrl1Reg
ld a, (TmsMode)
call TmsSetReg
ld a, (TmsMode+1)
ld e, TmsCtrl0Reg
jp TmsSetReg
; ---------------------------------------------------------------------------
; memory access routines
; set the next address of vram to write
; DE = address
TmsWriteAddr:
ld a, e ; send lsb
call TmsRegOut
ld a, d ; mask off msb to max of 16KB
and 3fh
or TmsWriteBit ; indicate that this is a write
call TmsRegOut
ret
; set the next address of vram to read
; DE = address
TmsReadAddr:
ld a, e ; send lsb
call TmsRegOut
ld a, d ; mask off msb to max of 16KB
and 3Fh
call TmsRegOut
ret
; copy bytes from ram to vram
; HL = ram source address
; DE = vram destination address
; BC = byte count
TmsWrite:
call TmsWriteAddr
TmsWriteLoop:
ld a, (hl)
call TmsRamOut
inc hl
dec bc
ld a, b
or c
jp nz, TmsWriteLoop
ret
; fill a section of memory with a single value
; A = value to fill
; DE = vram destination address
; BC = byte count
TmsFill:
push af
call TmsWriteAddr
pop af
TmsFillLoop:
call TmsRamOut
dec c
jp nz, TmsFillLoop
djnz TmsFillLoop
ret
; ---------------------------------------------------------------------------
; text routines
; set text color
; A = requested color
TmsTextColor:
add a, a ; text color into high nybble
add a, a
add a, a
add a, a
ld b, a ; save for later
ld a, (TmsScreenColors) ; get current colors
and 0fh ; mask off old text color
or b ; set new text color
ld (TmsScreenColors), a
ld e, TmsColorReg
jp TmsSetReg ; save it back
; set the address to place text at X/Y coordinate
; A = X
; E = Y
TmsTextPos:
ld d, 0
ld hl, 0
add hl, de ; Y x 1
add hl, hl ; Y x 2
add hl, hl ; Y x 4
add hl, de ; Y x 5
add hl, hl ; Y x 10
add hl, hl ; Y x 20
add hl, hl ; Y x 40
ld e, a
add hl, de ; add X for final address
ld de, (TmsNameAddr) ; add name table base address
add hl, de
ex de, hl
jp TmsWriteAddr
; copy a null-terminated string to VRAM
; HL = ram source address
TmsStrOut:
ld a, (hl)
cp 0 ; return when NULL is encountered
ret z
call TmsRamOut
inc hl
jp TmsStrOut
; repeat a character a certain number of times
; A = character to output
; B = count
TmsRepeat:
call TmsRamOut
djnz TmsRepeat
ret
; output a character
; A = character to output
TmsChrOut: equ TmsRamOut
; ---------------------------------------------------------------------------
; bitmap routines
TmsClearPixel: equ 0A02Fh ; cpl, and b
TmsSetPixel: equ 0B0h ; nop, or b
; set operation for TmsPlotPixel to perform
; HL = pixel operation (TmsClearPixel, TmsSetPixel)
TmsPixelOp:
ld (TmsPixelOpPlaceHolder), hl
ret
; set or clear pixel at X, Y position
; B = Y position
; C = X position
TmsPlotPixel:
ld a, b ; bail out if Y coord > 191
cp 192
ret nc
call TmsXYAddr ; get address in DE for X/Y coord in BC
ld a, c ; get lower 3 bits of X coord
and 7
ld b, 0
ld c, a
ld hl, TmsMaskLookup ; address of mask in table
add hl, bc
ld b, (hl) ; save mask in B
ld hl, (TmsPatternAddr) ; get base address for pattern table
add hl, de
ex de, hl
call TmsReadAddr ; set read within pattern table
call TmsRamIn
TmsPixelOpPlaceHolder:
or b ; mask bit in previous byte
nop ; place holder for 2 byte mask operation
push af
call TmsWriteAddr ; set write address within pattern table
pop af
jp TmsRamOut
TmsMaskLookup:
defb 80h, 40h, 20h, 10h, 8h, 4h, 2h, 1h
; set the color for a block of pixels in bitmap mode
; B = Y position
; C = X position
; A = foreground/background color to set
TmsPixelColor:
push af
ld a, b ; bail out if Y coord > 191
cp 192
ret nc
call TmsXYAddr ; get address in DE for X/Y coord in BC
ld hl, (TmsColorAddr) ; add the color table base address
add hl, de
ex de, hl
call TmsWriteAddr ; set write address within color table
pop af
jp TmsRamOut
; calculate address byte containing X/Y coordinate
; B = Y position
; C = X position
; returns address in DE
TmsXYAddr:
ld a, b ; d = (y / 8)
rrca
rrca
rrca
and 1fh
ld d, a
ld a, c ; e = (x & f8)
and 0f8h
ld e, a
ld a, b ; e += (y & 7)
and 7
or e
ld e, a
ret

File diff suppressed because it is too large Load Diff