Background change at Raster Location

Basic and Machine Language

Moderator: Moderators

vicassembly
Vic 20 Devotee
Posts: 253
Joined: Fri Mar 19, 2010 1:40 pm

Re: Background change at Raster Location

Post by vicassembly »

Mike:

I've been able to make a bit more sense of this today and am not playing with it. I'll report back. :D :D :D
User avatar
Mike
Herr VC
Posts: 4841
Joined: Wed Dec 01, 2004 1:57 pm
Location: Munich, Germany
Occupation: electrical engineer

Re: Background change at Raster Location

Post by Mike »

Fine! :)

It was already late last evening when I posted the teaser picture. As I wrote, the code works as supposed, but I would like to refine it a bit before posting it here.
vicassembly wrote:I don't even know how to enter code in vice but that is not the issue.
In the screenshot, you see my own machine language monitor MINIMON disassembling part of the raster demo, as visual proof there's still a program running 'in the foreground', while the colour splits happen within interrupts.

The positions and colours of the regions are kept in tables, and once the main algorithm worked, I spent a good part of an hour fine-tuning the timer values kept in those tables - with the raster demo running, so I could directly see the effect of the changes!

I did the coding within VICE, with MINIMON, but it would have been even more fun doing this on the VIC-20 itself, also with MINIMON, ideally as demo party production. :mrgreen:
vicassembly
Vic 20 Devotee
Posts: 253
Joined: Fri Mar 19, 2010 1:40 pm

Re: Background change at Raster Location

Post by vicassembly »

Awesome. I can't wait to see it. This is so fun.
vicassembly
Vic 20 Devotee
Posts: 253
Joined: Fri Mar 19, 2010 1:40 pm

Re: Background change at Raster Location

Post by vicassembly »

I've spent a week off and on reading up on the timers and trying to figure this out. It is beyond me. I cannot figure out how to code Mike's idea. Can someone help me? I even looked at Raeto Collin West's VIC book and he seems to do the wait for the VIC+$04 method.


I just cannot wrap my brain around this.
tlr
Vic 20 Nerd
Posts: 567
Joined: Mon Oct 04, 2004 10:53 am

Re: Background change at Raster Location

Post by tlr »

vicassembly wrote: Tue Jun 16, 2020 4:01 pmI just cannot wrap my brain around this.
Of course you can. Admittedly it's a bit fiddly and requires certain insights about the hardware but it's not total rocket science.

What is it that is confusing you? I'll try to answer.
User avatar
chysn
Vic 20 Scientist
Posts: 1205
Joined: Tue Oct 22, 2019 12:36 pm
Website: http://www.beigemaze.com
Location: Michigan, USA
Occupation: Software Dev Manager

Re: Background change at Raster Location

Post by chysn »

tlr wrote: Wed Jun 17, 2020 3:24 am
vicassembly wrote: Tue Jun 16, 2020 4:01 pmI just cannot wrap my brain around this.
Of course you can. Admittedly it's a bit fiddly and requires certain insights about the hardware but it's not total rocket science.

What is it that is confusing you? I'll try to answer.
I'll bite, thanks!

I know that I'll have to play around with them to get them right, but what's a reasonable starting point for the timer 2 high and low values? Let's say I just want one split point, two screen colors, so I need to set two pairs of timer values, high and low for each state:
Mike wrote: Sun Jun 07, 2020 7:27 am

Code: Select all

 CPY #$01          ;  ...the number of vertical interrupts, minus 1.
 BEQ IRQ_03
 LDA Timer2Lo,Y
 STA $9128
 LDA Timer2Hi,Y
 STA $9129        ; use the interrupt "display" of STY $900F to place the next
                  ; timer 2 interrupt two (double-)lines above where the next
                  ; colour change is supposed to happen.
 
.IRQ_03
The behavior of any given set of values seems to be non-orthogonal, so I'm not sure what a reasonable starting point might be.

For reference, here's the exact code I'm using. My data table starts at line 500:

Code: Select all

  100 *A000 ;CODE START
  105 @*    SEI
  110 @*    LDA #-IL
  115 @*    STA $0314
  120 @*    LDA #-IH
  125 @*    STA $0315
  126 @*    LDY #$A0
  127 @*    STY $9128
  128 @*    STY $9129
  129 @*    LDA #$F0
  130 @*    STA $912E
  131 @*    CLI
  135 @*    RTS
  140 @* -I ;ISR
  145 @*    LDA $912D
  150 @*    AND #$40
  155 @*    BEQ -0
  160 @*    LDA #$00
  165 @*    STA -S
  170 @* -0 LDY -S
  175 @*    INC -S
  180 @*    ;STY $900F
  185 @*    LDA -R,Y
  190 @* -1 CMP $9004
  195 @*    BNE -1
  200 @*    LDX -W,Y
  205 @* -2 DEX
  210 @*    BNE -2
  215 @*    LDA -C,Y
  220 @*    STA $900F
  225 @*    CPY #$01
  230 @*    BEQ -3
  235 @*    LDA -T,Y
  240 @*    STA $9128
  245 @*    LDA -U,Y
  250 @*    STA $9129
  255 @* -3 CPY #$00
  260 @*    BEQ -4
  265 @*    JMP $EB18
  270 @* -4 JMP $EABF
  280 @;
  500 *033C ;DATA TABLE
  505 @; STATE
  510 @*-S:00
  511 @;
  515 @; RASTER
  520 @*-R:40 00
  521 @;
  525 @; WAIT
  530 @*-W:03 03
  531 @;
  535 @; COLORS
  540 @*-C:08 3B
  541 @;
  545 @; TIMER 2 LOW
  550 @*-T:10 10
  551 @;
  555 @; TIMER 2 HIGH
  560 @*-U:24 24
Edit: If I change line 225 to CPY #$00, then things get a little better. I have a nice, stable split about 5/6 of the time. But every few seconds, the display flashes rapidly for about 1/3 of a second. The computer is always sluggish, though, with LIST frequently grinding to a halt.
VIC-20 Projects: wAx Assembler, TRBo: Turtle RescueBot, Helix Colony, Sub Med, Trolley Problem, Dungeon of Dance, ZEPTOPOLIS, MIDI KERNAL, The Archivist, Ed for Prophet-5

WIP: MIDIcast BASIC extension

he/him/his
User avatar
beamrider
Vic 20 Scientist
Posts: 1452
Joined: Sun Oct 17, 2010 2:28 pm
Location: UK

Re: Background change at Raster Location

Post by beamrider »

Here's my attempt for what it's worth.

I've tried to strip it down to the bare minimum code, a single band, with hard coded values.

I get the black bar as expected, but occasionally it isn't stable and the first few pixels of the top row are missing. As mentioned before adjustment of the timings etc seems to yield chaotic changes.

Critique welcome in the meantime, I'll stick with Markos routine black-box style.

CC65

Code: Select all

.segment "CODE"

VIC = $9000
LINES = 312 ; PAL
CYCLES_PER_LINE = 71 ; PAL
FIRST_SPLIT_LINE = 119 
TIMER_FREQ = (LINES * CYCLES_PER_LINE) - 2
SPLIT_HEIGHT = 20
SECOND_SPLIT_OFFSET = CYCLES_PER_LINE * SPLIT_HEIGHT - 7
 
		jsr IRQInstall

MainLoop:

		jmp MainLoop ; Program loop here....
		
		rts

		
; Install Timer1 IRQ Handler		
IRQInstall:		
	
		sei
		ldx #<TIMER_FREQ
		stx $9126
		ldx	#>TIMER_FREQ	
		lda #FIRST_SPLIT_LINE  - 2
		stx $9127

IrqSync1:
		
		cmp VIC+$04
		bne IrqSync1
		stx $9125

		ldx #<IrqHandler                 
		ldy #>IrqHandler
		stx $0314
		sty $0315
		cli
		rts
 
IrqHandler:

		lda $912D
		and #(1<<6)
		beq Timer2	

Timer1:
		
 		lda #FIRST_SPLIT_LINE 
@loop:
		cmp VIC+$04
		bne @loop
		lda #8
		sta $900F
		lda #$A0
		sta $912E	
 		ldx #<SECOND_SPLIT_OFFSET                
		ldy #>SECOND_SPLIT_OFFSET
		stx $9128
		sty $9129
		jmp $EB15	
		
Timer2:
 		
  		lda #25
		sta $900F	
		JMP $EB18	
tlr
Vic 20 Nerd
Posts: 567
Joined: Mon Oct 04, 2004 10:53 am

Re: Background change at Raster Location

Post by tlr »

Here's my take on the problem, using a single timer this time: vicrast.prg

The idea is that as you can load the T1 latches through $9126/$9127, I just preload those on each interrupt and then automatically get cycle exact reload of the timer. Then it's just a matter of making the sum of the splits equal to the number of cycles in a frame, i.e by adding a last split with the "rest". One really nice things of using the same timer is that you won't get any cascading error setting up each next time interval. This means I can just use a straight interrupt handler without any raster line waiting, making the overhead much less.

I've chosen not to use any "stable" code when setting up the initial timer for simplicity. This will yield a somewhat differing starting point but it shouldn't be visible normally anyway.

Code below:
The code could be optimized by separating the tables into three but I kept it in one to keep it readable (thus the 3 * INX).

Code: Select all

;**************************************************************************
;*
;* FILE  vicrast.asm
;* Copyright (c) 2020 Daniel Kahlin <daniel@kahlin.net>
;* Written by Daniel Kahlin <daniel@kahlin.net>
;*
;* DESCRIPTION
;*   VIC20 simple single timer splits
;*
;******
	processor 6502

;**************************************************************************
;*
;* Constants PAL
;*
;******
;the length of a row in cycles
LINETIME	equ	71
;the number of raster lines
NUMLINES	equ	312
;the length of a screen in cycles
SCREENTIME	equ	22152


	seg.u	zp
;**************************************************************************
;*
;* SECTION  zero page
;*
;******
	org	$fb
pos_zp:
	ds.b	1
last_pos_zp:
	ds.b	1
col_zp:
	ds.b	1


	seg	code
	org	$1201
;**************************************************************************
;*
;* Basic line!
;*
;******
start_of_line:
	dc.w	end_line
	dc.w	0
	dc.b	$9e,"4629 /T.L.R/",0
;	        0 SYS4629 /T.L.R/
end_line:
	dc.w	0

;**************************************************************************
;*
;* NAME  startofcode
;*
;******
startofcode:
	sei

; install split code in the tape buffer
	ldx	#SPLIT_CODE_LEN
soc_lp1:
	lda	split_code_st-1,x
	sta	split_code-1,x
	dex
	bne	soc_lp1

; setup interrupts
	lda	#%01111111
	sta	$912e
	sta	$912d
	lda	#%11000000
	sta	$912e
	lda	#%01000000
	sta	$912b
	lda	#<irq_server
	sta	$0314
	lda	#>irq_server
	sta	$0315

INITIAL_ADJ	equ	LINETIME-16
	ldx	#<[SCREENTIME-INITIAL_ADJ-2]
	ldy	#>[SCREENTIME-INITIAL_ADJ-2]
;--- wait until the first raster line until starting timer
soc_lp2:
	lda	$9004
	beq	soc_lp2
soc_lp3:
	lda	$9004
	bne	soc_lp3
;--- at the first raster line
	stx	$9124
	sty	$9125	;load T1

	jsr	setup_first

	cli
	jmp	$c474		; return to basic


split_code_st:
	rorg	$033c
split_code:
;**************************************************************************
;*
;* interrupt handler
;*
;******
irq_server:
	lda	col_zp
	sta	$900f

	jsr	setup_next

	lda	last_pos_zp
	beq	is_full_irq
	jmp	$eb15
is_full_irq:
	jmp	$eabf

; load up the latches with the next timer value and collect the pending color.
setup_first:
	ldx	#0
	dc.b	$2c	; skip
setup_next:
	ldx	pos_zp
	ldy	time_list,x
	lda	time_list+1,x
	bmi	setup_first
	sty	$9126
	sta	$9127
	lda	time_list+2,x
	sta	col_zp
	stx	last_pos_zp
	inx
	inx
	inx
	stx	pos_zp
	rts


; table of splits
CYCLE_COUNT	set	0

	mac	SPLIT
CYCLE_COUNT	set	CYCLE_COUNT+{1}
	dc.w	{1}-2
	dc.b	{2}
	endm

time_list:
	SPLIT	76*LINETIME,$1b
	SPLIT	5*8*LINETIME,$1a
	SPLIT	7*8*LINETIME,$1d
	SPLIT	1*8*LINETIME,$1e
	SPLIT	8*8*LINETIME,$1f
	SPLIT	2*8*LINETIME,$1c
tmp	set	CYCLE_COUNT
	SPLIT	SCREENTIME-tmp,$1b
	dc.w	-1

	rend
SPLIT_CODE_LEN	equ	. - split_code_st

; eof
User avatar
chysn
Vic 20 Scientist
Posts: 1205
Joined: Tue Oct 22, 2019 12:36 pm
Website: http://www.beigemaze.com
Location: Michigan, USA
Occupation: Software Dev Manager

Re: Background change at Raster Location

Post by chysn »

How is this:

Code: Select all

;--- wait until the first raster line until starting timer
soc_lp2:
	lda	$9004
	beq	soc_lp2
soc_lp3:
	lda	$9004
	bne	soc_lp3
materially different than just this?

Code: Select all

;--- wait until the first raster line until starting timer
soc_lp3:
	lda	$9004
	bne	soc_lp3
VIC-20 Projects: wAx Assembler, TRBo: Turtle RescueBot, Helix Colony, Sub Med, Trolley Problem, Dungeon of Dance, ZEPTOPOLIS, MIDI KERNAL, The Archivist, Ed for Prophet-5

WIP: MIDIcast BASIC extension

he/him/his
tlr
Vic 20 Nerd
Posts: 567
Joined: Mon Oct 04, 2004 10:53 am

Re: Background change at Raster Location

Post by tlr »

chysn wrote: Thu Jun 18, 2020 12:42 pm

Code: Select all

;--- wait until the first raster line until starting timer
soc_lp3:
	lda	$9004
	bne	soc_lp3
This code has a race condition in that, if it happens to start in any cycle during the two first raster lines the timing will be misaligned. The first loop I have will ensure we are not on any of the first two raster lines when entering the second loop.
User avatar
beamrider
Vic 20 Scientist
Posts: 1452
Joined: Sun Oct 17, 2010 2:28 pm
Location: UK

Re: Background change at Raster Location

Post by beamrider »

@tlr Thanks for that.

Works a treat and fairly easy to understand as well.
Last edited by beamrider on Thu Jun 18, 2020 3:30 pm, edited 1 time in total.
User avatar
chysn
Vic 20 Scientist
Posts: 1205
Joined: Tue Oct 22, 2019 12:36 pm
Website: http://www.beigemaze.com
Location: Michigan, USA
Occupation: Software Dev Manager

Re: Background change at Raster Location

Post by chysn »

tlr wrote: Thu Jun 18, 2020 1:04 pm
chysn wrote: Thu Jun 18, 2020 12:42 pm

Code: Select all

;--- wait until the first raster line until starting timer
soc_lp3:
	lda	$9004
	bne	soc_lp3
This code has a race condition in that, if it happens to start in any cycle during the two first raster lines the timing will be misaligned. The first loop I have will ensure we are not on any of the first two raster lines when entering the second loop.
Gotcha, I see how that makes a difference now.
beamrider wrote: Thu Jun 18, 2020 9:34 am Here's my attempt for what it's worth.
Beamrider, I get the bar with yours (after converting to NTSC), but I get no cursor. If I go back to $EABF on Timer 2, the cursor is super-fast, but the machine is otherwise super-slow...
VIC-20 Projects: wAx Assembler, TRBo: Turtle RescueBot, Helix Colony, Sub Med, Trolley Problem, Dungeon of Dance, ZEPTOPOLIS, MIDI KERNAL, The Archivist, Ed for Prophet-5

WIP: MIDIcast BASIC extension

he/him/his
User avatar
beamrider
Vic 20 Scientist
Posts: 1452
Joined: Sun Oct 17, 2010 2:28 pm
Location: UK

Re: Background change at Raster Location

Post by beamrider »

chysn wrote: Thu Jun 18, 2020 2:33 pm
beamrider wrote: Thu Jun 18, 2020 9:34 am Here's my attempt for what it's worth.
Beamrider, I get the bar with yours (after converting to NTSC), but I get no cursor. If I go back to $EABF on Timer 2, the cursor is super-fast, but the machine is otherwise super-slow...
It's probably spending all its time polling I guess. I'm as new to this as you, so I probably got some things wrong.

I'll likely go with TLRs routine if/when I swap over.
vicassembly
Vic 20 Devotee
Posts: 253
Joined: Fri Mar 19, 2010 1:40 pm

Re: Background change at Raster Location

Post by vicassembly »

chysn.... Your code was so similar to what I was doing before coming back here to ask for help.

My code below simply blinks and doesn't do any raster timing at all. Anyone see anything I am missing in the code?

I have so many questions. I've documented the code the best I can and have questions in there. I will also bring them out here.

1. I assume the first entry into the IRQ is when timer 1 (bit 6 in VIA2IFR) is on.
2. At that point timer 2 will fire. I don't understand the numbers stored in VIA2T2CH. My little understanding tells me that this fires timer 2 after counting down the number in VIA2T2CL.
3. Could timer 1 fire before timer 2 in number 2?

I'm really missing how the timers relate and if one steps on the other.

4. I intuit that EABF is just doing the normal IRQ. What does EB18 do? Rate Collin West used EB15. What is the difference?

I guess that's enough for this moment. Let's see if I can learn this part and see what other questions come about.

Code: Select all

; pertinent VIC20 symbols
TIMEH  		= $A0
TIMEM	  	= $A1
TIMEL 		= $A2		  ; jiffy-clock low byte value
COLORPAGE	= $F4		  ; high order byte of screen color page
SCRNPAGE	= $0288		; screen memory page (unexpanded = 1E)
CINVL     = $0314   ; Vector to Interrupt routine
CINVH     = $0315
VIC			  = $9000		; start of video interface chip registers

CHARDATA  = $1C00		; character definitions
SCREEN    = $1E00   ; Top left of Screen (unexpanded)
COLOR     = $9600   ; Color for top left of screen (unexpanded)

; VIA2 addresses
VIA2T1CL  = $9124   ; Timer 1 low order LSB
VIA2T1CH  = $9125   ; Timer 1 high order MSB
VIA2T2CL  = $9128   ; Timer 2 low order LSB counter and LSB latch
VIA2T2CH  = $9129   ; Timer 2 high order MSB and MSB latch
VIA2ACR   = $912B   ; Auxiliary control register
VIA2IFR   = $912D   ; Interupt flag register
VIA2IER   = $912E   ; Interrupt enable register

; joystick storage
VIA1DDRA	= $9113		; Joystick registers
VIA2DDRB	= $9122		;
VIA1PA1		= $9111		;
VIA2PB		= $9120		;


; kernel rom routines
CHROUT		= $FFD2		; routine to print a character
GETIN		  = $FFE4		; routine to get a character

; zero page variables
FLAG  		= $FC		  ; 0 or 1 to track state of interrupts

.segment "BASIC"

.word	RUN		; load address
RUN:	.word	END		; next line link
.word	2020	; line number
.byte	$9E		; BASIC token: SYSHI
.byte	<(MAIN / 1000 .mod 10) + $30
.byte	<(MAIN / 100 .mod 10) + $30
.byte	<(MAIN / 10 .mod 10) + $30
.byte	<(MAIN / 1 .mod 10) + $30
.byte	0		; end of line
END:	.word	0		; end of program


; ------------------------------------------------------------------------------------------------
; Main entry point of routine
; ------------------------------------------------------------------------------------------------

.segment "STARTUP"

MAIN:

SEI
        LDA #$01              ; 2 (n-1) colors
        STA FLAG
        LDA #<BACKGROUND      ; enable my IRQ vector jump
        STA CINVL
        LDA #>BACKGROUND
        STA CINVH
        LDY #$A0              ; 10100000
        STY VIA2T2CL          ; Initializes latch component.
        STY VIA2T2CH          ; Bit 5 initializes the latch component.
                              ; Neither of the two above means anything to me.
        LDA #$F0              ; 11110000
        STA VIA2IER           ; Enable timer 1 (bit 6), timer 2 (bit 5), and CB1 (bit 4) interrupt.
                              ; Is there a reason CB1 is enabled?
        CLI
        RTS

RASTER:    .byte	$20, $00    ; raster refresh points
WAIT:      .byte $03, $03     ; how long to delay
COLORS:    .byte $08, $3B     ; colors to display
TIML:      .byte $24, $44     ; timer low
TIMH:      .byte $2A, $2A     ; timer high
STATE:     .byte $00          ; number of color counter


BACKGROUND:
        LDA VIA2IFR
        AND #$40      ; Check If bit 6 is 1 that means timer 1 expired
        BEQ @bg1      ; if not timer expired (bit 6 set) jump ahead
        LDA #$00
        STA STATE     ; clear state flag
@bg1:
        LDY STATE     ; current state
        INC STATE     ; set to next (highest will be in FLAG. 2 colors is value of 1, 3 .. 2, etc.)
        LDA RASTER,y  ; raster line to wait for
@bg2:
        CMP VIC+$04   ; sit and spin until raster line reached.
        BNE @bg2
        LDX WAIT,y    ; load some defined number of beats to skip
@bg3:
        DEX
        BNE @bg3
        LDA COLOR,y   ; get the current color and set it
        STA VIC+$0F
        CPY FLAG      ; have we reached max colors?
        BEQ @bg4      ; Yes... do not set timer 2
        LDA TIML,y    ;
        STA VIA2T2CL  ; Putting any value in low order latch initializes the latch component
                      ; I have no idea what that means.
        LDA TIMH,y
        STA VIA2T2CH  ; By default this is a Single Interval Timer (VIA2ACR bit 5 containing 0)
                      ; Putting a value here initializes the latch component, stores the LSB latch
                      ; into the LSB counter component, clears the interrupt flag in VIA2IFR,
                      ; resets the IRQ line, and starts the timer. This happens whether timer 2 is
                      ; active or not and thus can trigger it.
@bg4:
        CPY #$00      ; if entered via timer1 then continue with EABF
        BEQ @bg5
        JMP $EB18     ; otherwise continue with EB18.
                      ; i've seem people use EB15 as well.  What is the significance of these two locations?
@bg5:
        JMP $EABF

vicassembly
Vic 20 Devotee
Posts: 253
Joined: Fri Mar 19, 2010 1:40 pm

Re: Background change at Raster Location

Post by vicassembly »

I just loved this into vice and it didn't do anything. I'm not sure what happened. I tried PAL and NTSC

tlr wrote: Thu Jun 18, 2020 11:43 am Here's my take on the problem, using a single timer this time: vicrast.prg

The idea is that as you can load the T1 latches through $9126/$9127, I just preload those on each interrupt and then automatically get cycle exact reload of the timer. Then it's just a matter of making the sum of the splits equal to the number of cycles in a frame, i.e by adding a last split with the "rest". One really nice things of using the same timer is that you won't get any cascading error setting up each next time interval. This means I can just use a straight interrupt handler without any raster line waiting, making the overhead much less.

I've chosen not to use any "stable" code when setting up the initial timer for simplicity. This will yield a somewhat differing starting point but it shouldn't be visible normally anyway.

Code below:
The code could be optimized by separating the tables into three but I kept it in one to keep it readable (thus the 3 * INX).

Code: Select all

;**************************************************************************
;*
;* FILE  vicrast.asm
;* Copyright (c) 2020 Daniel Kahlin <daniel@kahlin.net>
;* Written by Daniel Kahlin <daniel@kahlin.net>
;*
;* DESCRIPTION
;*   VIC20 simple single timer splits
;*
;******
	processor 6502

;**************************************************************************
;*
;* Constants PAL
;*
;******
;the length of a row in cycles
LINETIME	equ	71
;the number of raster lines
NUMLINES	equ	312
;the length of a screen in cycles
SCREENTIME	equ	22152


	seg.u	zp
;**************************************************************************
;*
;* SECTION  zero page
;*
;******
	org	$fb
pos_zp:
	ds.b	1
last_pos_zp:
	ds.b	1
col_zp:
	ds.b	1


	seg	code
	org	$1201
;**************************************************************************
;*
;* Basic line!
;*
;******
start_of_line:
	dc.w	end_line
	dc.w	0
	dc.b	$9e,"4629 /T.L.R/",0
;	        0 SYS4629 /T.L.R/
end_line:
	dc.w	0

;**************************************************************************
;*
;* NAME  startofcode
;*
;******
startofcode:
	sei

; install split code in the tape buffer
	ldx	#SPLIT_CODE_LEN
soc_lp1:
	lda	split_code_st-1,x
	sta	split_code-1,x
	dex
	bne	soc_lp1

; setup interrupts
	lda	#%01111111
	sta	$912e
	sta	$912d
	lda	#%11000000
	sta	$912e
	lda	#%01000000
	sta	$912b
	lda	#<irq_server
	sta	$0314
	lda	#>irq_server
	sta	$0315

INITIAL_ADJ	equ	LINETIME-16
	ldx	#<[SCREENTIME-INITIAL_ADJ-2]
	ldy	#>[SCREENTIME-INITIAL_ADJ-2]
;--- wait until the first raster line until starting timer
soc_lp2:
	lda	$9004
	beq	soc_lp2
soc_lp3:
	lda	$9004
	bne	soc_lp3
;--- at the first raster line
	stx	$9124
	sty	$9125	;load T1

	jsr	setup_first

	cli
	jmp	$c474		; return to basic


split_code_st:
	rorg	$033c
split_code:
;**************************************************************************
;*
;* interrupt handler
;*
;******
irq_server:
	lda	col_zp
	sta	$900f

	jsr	setup_next

	lda	last_pos_zp
	beq	is_full_irq
	jmp	$eb15
is_full_irq:
	jmp	$eabf

; load up the latches with the next timer value and collect the pending color.
setup_first:
	ldx	#0
	dc.b	$2c	; skip
setup_next:
	ldx	pos_zp
	ldy	time_list,x
	lda	time_list+1,x
	bmi	setup_first
	sty	$9126
	sta	$9127
	lda	time_list+2,x
	sta	col_zp
	stx	last_pos_zp
	inx
	inx
	inx
	stx	pos_zp
	rts


; table of splits
CYCLE_COUNT	set	0

	mac	SPLIT
CYCLE_COUNT	set	CYCLE_COUNT+{1}
	dc.w	{1}-2
	dc.b	{2}
	endm

time_list:
	SPLIT	76*LINETIME,$1b
	SPLIT	5*8*LINETIME,$1a
	SPLIT	7*8*LINETIME,$1d
	SPLIT	1*8*LINETIME,$1e
	SPLIT	8*8*LINETIME,$1f
	SPLIT	2*8*LINETIME,$1c
tmp	set	CYCLE_COUNT
	SPLIT	SCREENTIME-tmp,$1b
	dc.w	-1

	rend
SPLIT_CODE_LEN	equ	. - split_code_st

; eof
Post Reply