.include "tgi-kernel.inc"
+ .include "tgi-vectorfont.inc"
+ .include "zeropage.inc"
.import popax, negax
- .importzp ptr3
+
+
+;----------------------------------------------------------------------------
+; Data
+
+text := regbank
+
+;----------------------------------------------------------------------------
+;
.proc _tgi_outtext
+ ldy _tgi_font ; Bit or vectorfont?
+ bne VectorFont
+
+; Handle bitmapped font output
+
sta ptr3
stx ptr3+1 ; Pass s in ptr3 to driver
pha
sta _tgi_curx+1,y
rts
+; Handle vector font output
+
+VectorFont:
+ tay
+ lda _tgi_vectorfont ; Do we have a vector font?
+ ora _tgi_vectorfont+1
+ beq Done ; Bail out if not
+
+ lda text ; Save zero page variable on stack
+ pha
+ lda text+1
+ pha
+
+ sty text
+ stx text+1 ; Store pointer to string
+
+; Output the text string
+
+@L1: ldy #0
+ lda (text),y ; Get next character from string
+ beq EndOfText
+ jsr _tgi_vectorchar ; Output it
+ inc text
+ bne @L1
+ inc text+1
+ bne @L1
+
+; Done. Restore registers and return
+
+EndOfText:
+ pla
+ sta text+1
+ pla
+ sta text
+Done: rts
+
.endproc
.include "tgi-kernel.inc"
.include "tgi-vectorfont.inc"
.include "zeropage.inc"
-
+
.macpack longbranch
;----------------------------------------------------------------------------
Y1: .res 2
X2: .res 2
Y2: .res 2
+BaseX: .res 2
+BaseY: .res 2
+Char: .res 1
+
+;----------------------------------------------------------------------------
+; Get the next operation from the Ops pointer, remove the flag bit and sign
+; extend the 8 bit value. On return, the flags are set for the value in A.
+
+.code
+.proc GetOp
+
+; Load delta value
+
+ ldy #0
+ lda (Ops),y
+ inc Ops
+ bne :+
+ inc Ops+1
+
+; Move bit 7 into Flag, then sign extend the value in A
+
+: asl a ; Flag into carry
+ ror Flag
+ cmp #$80 ; Sign bit into carry
+ ror a ; Sign extend the value
+
+; Done
+ rts
+
+.endproc
+
+
+;----------------------------------------------------------------------------
+; Round a 16.8 fixed point value in eax
+
+.code
+.proc RoundFix
+
+ cmp #$80 ; frac(val) >= 0.5?
+ txa
+ ldx sreg
+ adc #$00
+ bcc @L1
+ inx
+@L1: rts
+
+.endproc
+
+;----------------------------------------------------------------------------
+; Get and process one coordinate value. The scale factor is passed in a/x
+
+.code
+.proc GetProcessedCoord
+
+; Save scale factor as left operand for multiplication
+
+ sta ptr1
+ stx ptr1+1
+
+; Load next operation value. This will set the flags for the value in A.
+
+ jsr GetOp
+
+; Since we know that the scale factor is always positive, we will remember
+; the sign of the coordinate offset, make it positive, do an unsigned mul
+; and negate the result if the vector was negative. This is faster than
+; relying on the signed multiplication, which will do the same, but for
+; both operands.
+
+ sta tmp1 ; Remember sign of vector offset
+ bpl :+
+ eor #$FF
+ clc
+ adc #$01 ; Negate
+: ldx #$00 ; High byte is always zero
+
+; Multiplicate with the scale factor.
+
+ jsr umul16x16r32 ; Multiplicate
+
+; The result is a 16.8 fixed point value. Round it.
+
+ jsr RoundFix
+
+; Check the sign and negate if necessary
+
+ bit tmp1 ; Check sign
+ bpl :+
+ jmp negax ; Negate result if necessary
+: rts
+
+.endproc
;----------------------------------------------------------------------------
;
lda Flag
pha
-; Calculate a pointer to the vector ops for the given char (now in Y).
+; Get the width of the char in question
+ lda _tgi_vectorfont
+ clc
+ adc #<(TGI_VECTORFONT::WIDTHS - TGI_VF_FIRSTCHAR)
+ sta Ops
lda _tgi_vectorfont+1
- tax
- ora _tgi_vectorfont
- jeq Done ; Bail out if no font installed
+ adc #>(TGI_VECTORFONT::WIDTHS - TGI_VF_FIRSTCHAR)
+ sta Ops+1
+ lda (Ops),y
+
+; Save the character
+
+ sty Char
+
+; Calculate the width of the character by multiplying with the scale
+; factor for the width
+
+ sta ptr1
+ lda #0
+ sta ptr1+1
+
+ lda _tgi_textscalew
+ ldx _tgi_textscalew+1
+ jsr umul16x16r32
+ jsr RoundFix
+
+; Store the current value of the graphics cursor into BaseX/BaseY, then
+; move it to the next character position
+
+ pha
+ ldy #3
+: lda _tgi_curx,y
+ sta BaseX,y
+ dey
+ bpl :-
+ pla
+
+ ldy _tgi_textdir
+ beq :+ ; Jump if horizontal text
+
+ jsr negax
+ ldy #2 ; Offset of tgi_cury
+
+; Advance graphics cursor
+
+: clc
+ adc _tgi_curx,y
+ sta _tgi_curx,y
+ txa
+ adc _tgi_curx+1,y
+ sta _tgi_curx+1,y
+
+; Calculate a pointer to the vector ops for the given char (now in Y). We
+; definitely expect a font here, that has to be checked by the caller.
+
lda _tgi_vectorfont
clc
adc #<(TGI_VECTORFONT::CHARS - 2*TGI_VF_FIRSTCHAR)
adc #>(TGI_VECTORFONT::CHARS - 2*TGI_VF_FIRSTCHAR)
sta Ops+1
+ ldy Char
iny
lda (Ops),y
tax
Loop: lda _tgi_textscalew+0
ldx _tgi_textscalew+1
- jsr GetProcessedCoord
+ jsr GetProcessedCoord ; Get X vector
-; X2 = tgi_curx + XMag * XDelta.
+; X2 = BaseX + XMag * XDelta.
clc
- adc _tgi_curx+0
+ adc BaseX+0
sta X2+0
txa
- adc _tgi_curx+1
+ adc BaseX+1
sta X2+1
; Process the Y value
ldx _tgi_textscaleh+1
jsr GetProcessedCoord
-; Y2 = tgi_cury - YMag * YDelta;
-; Y2 = tgi_cury + (~(YMag * YDelta) + 1);
+; Y2 = BaseY - YMag * YDelta;
+; Y2 = BaseY + (~(YMag * YDelta) + 1);
eor #$FF
sec ; + 1
- adc _tgi_cury+0
+ adc BaseY+0
sta Y2+0
txa
eor #$FF
- adc _tgi_cury+1
+ adc BaseY+1
sta Y2+1
; Draw, then move - or just move
.endproc
-;----------------------------------------------------------------------------
-; Get and process one coordinate value. The scale factor is passed in a/x
-
-.proc GetProcessedCoord
-
-; Save scale factor as left operand for multiplication
-
- sta ptr1
- stx ptr1+1
-
-; Load delta value
-
- ldy #0
- lda (Ops),y
- inc Ops
- bne :+
- inc Ops+1
-
-; Move bit 7 into Flag
-
-: asl a ; Flag into carry
- ror Flag
-
-; Since we know that the scale factor is always positive, we will remember
-; the sign of the coordinate offset, make it positive, do an unsigned mul
-; and negate the result if the vector was negative. This is faster than
-; relying on the signed multiplication, which will do the same, but for
-; both operands.
-
- sta tmp1 ; Remember sign of vector offset
- cmp #$80 ; Sign bit into carry
- ror a ; Sign extend the value
- bpl :+
- eor #$FF
- clc
- adc #$01 ; Negate
-: ldx #$00 ; High byte is always zero
-
-; Multiplicate with the scale factor.
-
- jsr umul16x16r32 ; Multiplicate
-
-; The result is a 16.8 fixed point value. Round it.
-
- cmp #$80 ; frac(val) >= 0.5?
- txa
- adc #$00
- tay
- lda sreg
- adc #$00
- tax
- tya
- bit tmp1 ; Check sign
- bpl :+
- jmp negax ; Negate result if necessary
-: rts
-
-.endproc
-