News:

Printed Amstrad Addict magazine announced, check it out here!

Main Menu
avatar_fgbrain

Fast Line Draw in assembly (Bresenham algorithm)

Started by fgbrain, 19:08, 27 August 16

Previous topic - Next topic

0 Members and 1 Guest are viewing this topic.

fgbrain

I'm talking about the Breseham's  line algorithm...
I wont bore you with maths, you can find such analysis in other sites and videos!


In Locomotive basic, this is a proper implementation (posted here in another thread) that works on all 8 octants :

10 REM === DRAW a LINE. Bresenham algorithm from (x1,y1) to (x2,y2)
20 DX = ABS(X2 - X1) :SX = -1 :IF X1 - x2 < 0 THEN SX = 1
30 DY = ABS(Y2 - Y1) :SY = -1 :IF Y1 - y2 < 0 THEN SY = 1
40 ER = -DY : IF DX - dy > 0 THEN ER = DX
50 ER = INT(ER / 2)
60 PLOT X1,Y1
70 IF X1 = X2 AND Y1 = Y2 THEN RETURN
80 E2 = ER
90 IF E2 +dx > 0 THEN ER = ER - DY:X1 = X1 + SX
100 IF E2 -dy < 0 THEN ER = ER + DX:Y1 = Y1 + SY
110 GOTO 60



Besides, this routine is useful for calculating points between two positions on screen. (e,g: path of sprite)


I've been looking allover the sites and forums... but it seems nobody has shared this for CPC in Z80 assembler.

Therefore, I tried myself to translate this code into Z80 assembler for ultra fast execution but faced some bugs..
For the PLOT routine I used Executioner 's excellent code:
Programming:Fast plot - CPCWiki

To avoid large post, I will share my source next..

_____

6128 (UK keyboard, Crtc type 0/2), 6128+ (UK keyboard), 3.5" and 5.25" drives, Reset switch and Digiblaster (selfmade), Inicron Romram box, Bryce Megaflash, SVideo & PS/2 mouse, , Magnum Lightgun, X-MEM, X4 Board, C4CPC, Multiface2 X4, RTC X4 and Gotek USB Floppy emulator.

fgbrain

#1
Here's my code (WinAPE compatible, works for MODE 0):




CMASK    equ &B6A3 ;EQU &B338  ;Address for colormask

org &7000 : RUN $ :nolist

ld hl,(y2)      ; y2
ld de,(y1+1)    ; y1
or a:sbc hl,de    ;  hl=y2-y1   
bit 7,h:jr z,gnp0:xor a:sub l:ld l,a:sbc a,a:sub h:ld h,a     ;  ABS hl
gnp0 ld (dy),hl      ; =ABS(DY)
LD A,H:    CPL:LD H,A:LD A,L:CPL:LD L,A:INC HL ; neg hl = -DY
ld(er),hl    ; er=-DY

ex de,hl:ld de,(y2)
or a:sbc hl,de   ; hl=y1-y2
ld a,&23:jr c,$+4:ld a,&2b  ; sy=-1 / if y1 - y2 <0  sy=1
ld (sy),a


ld de,(x1+1)
ld hl,(x2)
or a:sbc hl,de ; hl=x2-x1
bit 7,h:jr z,gnp1:xor a:sub l:ld l,a:sbc a,a:sub h:ld h,a     ;  ABS hl
gnp1 ld(dx),hl   ; =ABS(DX)

ex de,hl:ld de,(x2)
or a:sbc hl,de ; HL=x1-x2
ld a,&23:jr c,$+4:ld a,&2b  ; sx=-1 / if x1 - x2 <0  sx=1
ld (sx),a

ld hl,(dx):ld de,(dy)
or a:sbc hl,de    ;hl=dx-dy
jr c,nex0    ;if dx-dy>0 (dx>dy)
ld hl,(dx):ld (er),hl ; then er=dx

nex0
ld hl,(er):srl h:rr l:ld (er),hl  ;er/2

DRLOOP
x1 ld de,1:
y1 ld hl,1
call fplot

ld hl,(x1+1):ld de,(x2):or a:sbc hl,de:jr nz,nex1  ;
ld hl,(y1+1):ld de,(y2):or a:sbc hl,de:jr z,exith  ; if x1=x2 and y1=y2 then exit!!

nex1 ld hl,(er):ld(e2),hl ;e2=er
ld de,(dx):add hl,de ;IF  E2+DX > 0  THEN ER = ER - DY ;X1 = X1 + SX
jr c,nex2
ld hl,(er):ld de,(dy):or a:sbc hl,de:ld(er),hl ;er = er -dy
ld hl,(x1+1):sx db 0:ld(x1+1),hl

nex2
ld hl,(e2):ld de,(dy)
or a:sbc hl,de
jr nc,nex3 ;IF E2 - DY < 0 THEN ER = ER + DX ;Y1 = Y1 + SY
ld hl,(er):ld de,(dx):add hl,de:ld(er),hl ;er = er+dx
ld hl,(y1+1):sy db 0:ld(y1+1),hl

nex3 JP DRLOOP
exith ret

dx dw 0
dy dw 0
er dw 0
e2 dw 0
x2 dw 0
y2 dw 0


;Fast plotting routine for MODE 0
;Input DE = X (0..159), HL = Y (0..199)
FPLOT    LD A, L            ;A = Lowbyte Y
    AND %00000111        ;isolate Bit 0..2
    LD H, A            ;= y MOD 8 to H
    XOR L            ;A = Bit 3..7 of Y
    LD L, A            ;= (Y\*8 to L
    LD C, A            ;store in C
    LD B, &60        ;B = &C0\2 = Highbyte Screenstart\2
    ADD HL, HL        ;HL * 2
    ADD HL, HL        ;HL * 4
    ADD HL, BC        ;+ BC = Startaddress
    ADD HL, HL        ;of the raster line
    SRL E            ;calculate X\2, because 2 pixel per byte, Carry is X MOD 2
    LD C, %10101010            ;Bitmask for MODE 0
    JR NC, NSHIFT        ;-> = 0, no shift
SHIFT     LD C, %01010101            ;other bitmask for right pixel
NSHIFT    ADD HL, DE        ;+ HL = Screenaddress
        LD A, (CMASK)        ;get color mask
    XOR (HL)        ;XOR screenbyte
    AND C            ;AND bitmask
    XOR (HL)        ;XOR screenbyte
    LD (HL), a        ;new screenbyte
    RET            ;done



I have documented this code to my best.
My problem is that the code doesnt work when Y2>X2 or  E2<0  (produces wrong screen addresses)!!
I use 16 bit arithmetic but of course for a byte plot routine we can optimize it with 8 bit registers only..
I would be happy if it worked for 80x256 because I prepare this for byte per byte movement.

Any help - fixes & optimizations are welcomed!!
_____

6128 (UK keyboard, Crtc type 0/2), 6128+ (UK keyboard), 3.5" and 5.25" drives, Reset switch and Digiblaster (selfmade), Inicron Romram box, Bryce Megaflash, SVideo & PS/2 mouse, , Magnum Lightgun, X-MEM, X4 Board, C4CPC, Multiface2 X4, RTC X4 and Gotek USB Floppy emulator.

SRS

You can check with this: drawing lines with cpcTelera / SDCC

And there should be an implementation in Z88DK library source.

fgbrain

@SRS

As I wrote, I have searched in every relevant cpc site. My routine is 100% assembly, a lot faster and much smaller. Crappy C is not enough for me sorry!
I know its easy to optimize - this is very basic interpretation of the Basic code...
But cannot fix the bugs I mentioned yet!!
_____

6128 (UK keyboard, Crtc type 0/2), 6128+ (UK keyboard), 3.5" and 5.25" drives, Reset switch and Digiblaster (selfmade), Inicron Romram box, Bryce Megaflash, SVideo & PS/2 mouse, , Magnum Lightgun, X-MEM, X4 Board, C4CPC, Multiface2 X4, RTC X4 and Gotek USB Floppy emulator.

AMSDOS

@ervin shared a workable Breseham Line Drawing Algorithm last year, which is in the CPC BASIC 3 thread. Because that works in CPC BASIC 3, it's possible to translate it to Assembly.
* Using the old Amstrad Languages :D   * with the Firmware :P
* I also like to problem solve code in BASIC :)   * And type-in Type-Ins! :D

Home Computing Weekly Programs
Popular Computing Weekly Programs
Your Computer Programs
Updated Other Program Links on Profile Page (Update April 16/15 phew!)
Programs for Turbo Pascal 3

fgbrain

Im aware of this one as well.. It is not  any better than mine above I guess..
Thanks anyway
_____

6128 (UK keyboard, Crtc type 0/2), 6128+ (UK keyboard), 3.5" and 5.25" drives, Reset switch and Digiblaster (selfmade), Inicron Romram box, Bryce Megaflash, SVideo & PS/2 mouse, , Magnum Lightgun, X-MEM, X4 Board, C4CPC, Multiface2 X4, RTC X4 and Gotek USB Floppy emulator.

ervin

Quote from: fgbrain on 07:19, 28 August 16
@SRS

As I wrote, I have searched in every relevant cpc site. My routine is 100% assembly, a lot faster and much smaller. Crappy C is not enough for me sorry!
I know its easy to optimize - this is very basic interpretation of the Basic code...
But cannot fix the bugs I mentioned yet!!

Regarding drawing lines with cpcTelera / SDCC
The bresenham bits of the project I'm working on are indeed 100% assembly, and it is definitely fast.
8)

HAL6128

I didn't have a deeper look in your BASIC code above for comparison. Is this one different to yours?
Maybe mine below could also help for another translation into assembler / MC?
Cheers,
HAL6128

10 REM
20 REM Bresenham algorithm (3) - only Integer
30 REM
40 REM * initialize
50 REM
60 MODE 2
70 ORIGIN 0,0
80 INK 1,26:INK 0,0:BORDER 13
90 DEFINT a-z
110 REM
120 REM * input
130 REM
140 LOCATE 2,2:PRINT"Line from ... until .."
150 LOCATE 2,4:INPUT"x1:",x1
160 LOCATE 2,5:INPUT"x2:",x2
170 LOCATE 2,7:INPUT"y1:",y1
180 LOCATE 2,8:INPUT"y2:",y2
190 REM
200 REM * calculation
210 REM
220 t1!=TIME
240 dx=x2-x1:dy=y2-y1
250 e=2*dy-dx
255 incrE=2*dy:incrNE=2*(dy-dx)
256 x=x1:y=y1
260 REM
270 REM * output
280 REM
290 FOR i=x TO x2 STEP 1
300 IF e>0 THEN y=y+1:e=e+incrNE ELSE e=e+incrE
310 PLOT i,y
330 NEXT i
340 t2!=TIME
350 LOCATE 50,24:PRINT"time:";:PRINT USING "##.#";(t2!-t1!)/300;:PRINT " seconds"
360 CALL &BB18
...proudly supported Schnapps Demo, Pentomino and NQ-Music-Disc with GFX

krusty_benediction

Hello,

I won't help a lot...

I have not written a Breseham implementation since years, so I can't verify your code (btw, compressed code like that is quite hard to read in a forum message).
However:
- As you use winape to assemble, have you tried to launch step by step your algorithm to detect at which position it fails ?
- You talk of wrong screen addresses, but maybe it does not come from your code, but from the fast plot routine

Quote from: fgbrain on 19:15, 27 August 16
Here's my code (WinAPE compatible, works for MODE 0):




CMASK    equ &B6A3 ;EQU &B338  ;Address for colormask

org &7000 : RUN $ :nolist

ld hl,(y2)      ; y2
ld de,(y1+1)    ; y1
or a:sbc hl,de    ;  hl=y2-y1   
bit 7,h:jr z,gnp0:xor a:sub l:ld l,a:sbc a,a:sub h:ld h,a     ;  ABS hl
gnp0 ld (dy),hl      ; =ABS(DY)
LD A,H:    CPL:LD H,A:LD A,L:CPL:LD L,A:INC HL ; neg hl = -DY
ld(er),hl    ; er=-DY

ex de,hl:ld de,(y2)
or a:sbc hl,de   ; hl=y1-y2
ld a,&23:jr c,$+4:ld a,&2b  ; sy=-1 / if y1 - y2 <0  sy=1
ld (sy),a


ld de,(x1+1)
ld hl,(x2)
or a:sbc hl,de ; hl=x2-x1
bit 7,h:jr z,gnp1:xor a:sub l:ld l,a:sbc a,a:sub h:ld h,a     ;  ABS hl
gnp1 ld(dx),hl   ; =ABS(DX)

ex de,hl:ld de,(x2)
or a:sbc hl,de ; HL=x1-x2
ld a,&23:jr c,$+4:ld a,&2b  ; sx=-1 / if x1 - x2 <0  sx=1
ld (sx),a

ld hl,(dx):ld de,(dy)
or a:sbc hl,de    ;hl=dx-dy
jr c,nex0    ;if dx-dy>0 (dx>dy)
ld hl,(dx):ld (er),hl ; then er=dx

nex0
ld hl,(er):srl h:rr l:ld (er),hl  ;er/2

DRLOOP
x1 ld de,1:
y1 ld hl,1
call fplot

ld hl,(x1+1):ld de,(x2):or a:sbc hl,de:jr nz,nex1  ;
ld hl,(y1+1):ld de,(y2):or a:sbc hl,de:jr z,exith  ; if x1=x2 and y1=y2 then exit!!

nex1 ld hl,(er):ld(e2),hl ;e2=er
ld de,(dx):add hl,de ;IF  E2+DX > 0  THEN ER = ER - DY ;X1 = X1 + SX
jr c,nex2
ld hl,(er):ld de,(dy):or a:sbc hl,de:ld(er),hl ;er = er -dy
ld hl,(x1+1):sx db 0:ld(x1+1),hl

nex2
ld hl,(e2):ld de,(dy)
or a:sbc hl,de
jr nc,nex3 ;IF E2 - DY < 0 THEN ER = ER + DX ;Y1 = Y1 + SY
ld hl,(er):ld de,(dx):add hl,de:ld(er),hl ;er = er+dx
ld hl,(y1+1):sy db 0:ld(y1+1),hl

nex3 JP DRLOOP
exith ret

dx dw 0
dy dw 0
er dw 0
e2 dw 0
x2 dw 0
y2 dw 0


;Fast plotting routine for MODE 0
;Input DE = X (0..159), HL = Y (0..199)
FPLOT    LD A, L            ;A = Lowbyte Y
    AND %00000111        ;isolate Bit 0..2
    LD H, A            ;= y MOD 8 to H
    XOR L            ;A = Bit 3..7 of Y
    LD L, A            ;= (Y\*8 to L
    LD C, A            ;store in C
    LD B, &60        ;B = &C0\2 = Highbyte Screenstart\2
    ADD HL, HL        ;HL * 2
    ADD HL, HL        ;HL * 4
    ADD HL, BC        ;+ BC = Startaddress
    ADD HL, HL        ;of the raster line
    SRL E            ;calculate X\2, because 2 pixel per byte, Carry is X MOD 2
    LD C, %10101010            ;Bitmask for MODE 0
    JR NC, NSHIFT        ;-> = 0, no shift
SHIFT     LD C, %01010101            ;other bitmask for right pixel
NSHIFT    ADD HL, DE        ;+ HL = Screenaddress
        LD A, (CMASK)        ;get color mask
    XOR (HL)        ;XOR screenbyte
    AND C            ;AND bitmask
    XOR (HL)        ;XOR screenbyte
    LD (HL), a        ;new screenbyte
    RET            ;done



I have documented this code to my best.
My problem is that the code doesnt work when Y2>X2 or  E2<0  (produces wrong screen addresses)!!
I use 16 bit arithmetic but of course for a byte plot routine we can optimize it with 8 bit registers only..
I would be happy if it worked for 80x256 because I prepare this for byte per byte movement.

Any help - fixes & optimizations are welcomed!!

madram


There does is a routine : http://cpcrulez.fr/coding_amslive08-3D.htm


Optimization tip: do not use a plot routine, which does a lot of work at each pixel, but maintain the current screen pos and mask (e.g. %10001000 for mode 1, %10101010 for mode 0, RRC will switch to right neighbourg, with Carry if you need to INC screen pos).

fgbrain

#10
@hal6128


your code does not seem to work on all octants like the one in the first post.. will test asap!




@krusty
Quote- As you use winape to assemble, have you tried to launch step by step your algorithm to detect at which position it fails ?


I said when it fails:  code doesnt work when Y2>X2 or  E2<0  (produces wrong screen addresses)!!


Quote- You talk of wrong screen addresses, but maybe it does not come from your code, but from the fast plot routine
the routine is great but if its input is out of range..GIGO!




@madram

Thanks for the link & tips. It was not possible to find unless you searched for "Bresen" Will test asap!

Actually, I will use this algorithm for sprite movement between 2 points so its not vital to plot points very fast.

EDIT:
Your code doesnt assemble!! Missing labels and errors.... Please fix it!!!


Again this works only by INCrementing (from left to right or downwards movement). One octant only..
_____

6128 (UK keyboard, Crtc type 0/2), 6128+ (UK keyboard), 3.5" and 5.25" drives, Reset switch and Digiblaster (selfmade), Inicron Romram box, Bryce Megaflash, SVideo & PS/2 mouse, , Magnum Lightgun, X-MEM, X4 Board, C4CPC, Multiface2 X4, RTC X4 and Gotek USB Floppy emulator.

fgbrain

Seems nobody saw latest edit in previous post ..
sorry for  double posts!
_____

6128 (UK keyboard, Crtc type 0/2), 6128+ (UK keyboard), 3.5" and 5.25" drives, Reset switch and Digiblaster (selfmade), Inicron Romram box, Bryce Megaflash, SVideo & PS/2 mouse, , Magnum Lightgun, X-MEM, X4 Board, C4CPC, Multiface2 X4, RTC X4 and Gotek USB Floppy emulator.

fgbrain

#12
GREAT NEWS!!

I finally completed this routine (see 1st post) in asm...
Now works in all octants as it meant to do!!

There were 2 bugs in my code:  :-[

1) Division by 2 but maintain the sign (signed division). Fixed by keeping the 7th bit.
2) Carry check was not enough to test for positive/negative 16bits. Fixed with BIT 7,H.

I can share the final code if there's enough interest!!


PS: I am still surprised that with so many better coders than me in here, noone found the bugs earlier!! Almost a month gone...
_____

6128 (UK keyboard, Crtc type 0/2), 6128+ (UK keyboard), 3.5" and 5.25" drives, Reset switch and Digiblaster (selfmade), Inicron Romram box, Bryce Megaflash, SVideo & PS/2 mouse, , Magnum Lightgun, X-MEM, X4 Board, C4CPC, Multiface2 X4, RTC X4 and Gotek USB Floppy emulator.

ervin


fgbrain

#14
The main code is there in the second post...  and I told you the bugs in order to fix!!

Today I optimized it using all registers..
I cant think of any faster code now as it uses 16bit numbers and negatives..
(it is pixel perfect not byte based and can work in all modes)

Adding special code for horizontal and vertical lines is special case to optimize.
_____

6128 (UK keyboard, Crtc type 0/2), 6128+ (UK keyboard), 3.5" and 5.25" drives, Reset switch and Digiblaster (selfmade), Inicron Romram box, Bryce Megaflash, SVideo & PS/2 mouse, , Magnum Lightgun, X-MEM, X4 Board, C4CPC, Multiface2 X4, RTC X4 and Gotek USB Floppy emulator.

ervin

#15
Quote from: fgbrain on 21:03, 27 September 16
The main code is there in the second post...  and I told you the bugs in order to fix!!

Erm... alrighty then.

Can you post the code which sets up the screen, variables etc?

fgbrain

#16
OK... I post here completed version


; faster version 27.9.2016

CMASK    equ &B6A3 ;EQU &B338  change address for colormask in 464
org &7000 : RUN $ :nolist
cp 4:jr z,okk:ret  ; 4 parameters ONLY
okk 
di:ld(exith+1),sp  ; save SP to restore at exit..

ld l,(ix+6):ld h,(ix+7):ld(x1+1),hl  ;x1
ld e,(ix+4):ld d,(ix+5):ld(y1+1),de  ;y1
ld l,(ix+2):ld h,(ix+3):ld(x2+1),hl  ;x2
ld l,(ix+0):ld h,(ix+1):ld(y2+1),hl  ;y2
;   x1, y1 start point   0<x<159
;   x2, y2  end point    0<y<199


or a:sbc hl,de    ;  hl=y2-y1   
bit 7,h:jr z,gnp0:xor a:sub l:ld l,a:sbc a,a:sub h:ld h,a     ;  ABS hl
gnp0 ld (dy+1),hl      ; =ABS(DY)
LD A,H:    CPL:LD H,A:LD A,L:CPL:LD L,A:INC HL ; neg hl = -DY
srl h:rr l:set 7,h ; keep negative HL
ld(er+1),hl    ;  ER = -DY/2

ex de,hl: ld de,(y2+1) : or a:sbc hl,de   ; hl=y1-y2
ld a,&34:jr c,$+4:ld a,&35  ; sy= DEC (HL) / if y1 - y2 <0  sy= INC (HL)
ld (sy),a

ld de,(x1+1) : ld hl,(x2+1) : or a:sbc hl,de     ; hl=x2-x1
bit 7,h:jr z,gnp1:xor a:sub l:ld l,a:sbc a,a:sub h:ld h,a     ;  ABS hl
gnp1 ld sp,hl:ld b,h:ld c,l ; =ABS(DX) = BC = SP stack pointer !!!!!!

ex de,hl : ld de,(x2+1) : or a : sbc hl,de ;  HL=x1-x2
ld a,&34:jr c,$+4:ld a,&35  ; sx= DEC (HL) / if x1 - x2 <0  sx= INC (HL)
ld (sx),a

ld h,b:ld l,c ;  HL=dx
ld de,(dy+1) : or a : sbc hl,de    ; hl=dx-dy
jr c,nex0    ; if dx-dy>0 (dx>dy)  [when nc]
ld h,b:ld l,c ; HL=dx
srl h:rr l : ld (er+1),hl ; then er=dx/2



nex0

DRLOOP  ; main DRAWING loop
x1 ld de,1
y1 ld hl,1

; Fast Plot for MODE 0 by Executioner follows...
FPLOT    LD A, L            ;A = Lowbyte Y
    AND %00000111        ;isolate Bit 0..2
    LD H, A            ;= y MOD 8 to H
    XOR L            ;A = Bit 3..7 of Y
    LD L, A            ;= (Y\*8 to L
    LD C, A            ;store in C
    LD B, &60        ;B = &C0\2 = Highbyte Screenstart\2
    ADD HL, HL        ;HL * 2
    ADD HL, HL        ;HL * 4
    ADD HL, BC        ;+ BC = Startaddress
    ADD HL, HL        ;of the raster line
    SRL E            ;calculate X\2, because 2 pixel per byte, Carry is X MOD 2
    LD C, %10101010            ;Bitmask for MODE 0
    JR NC, NSHIFT        ;-> = 0, no shift
SHIFT     LD C, %01010101            ;other bitmask for right pixel
NSHIFT    ADD HL, DE        ;+ HL = Screenaddress
        LD A, (CMASK)        ;get color mask
    XOR (HL)        ;XOR screenbyte
    AND C            ;AND bitmask
    XOR (HL)        ;XOR screenbyte
    LD (HL), a        ;new screenbyte


ld hl,(x1+1):x2 ld de,0:or a:sbc hl,de:jr nz,nex1  ; CHECK if we reach the end???
ld hl,(y1+1):y2 ld de,0:or a:sbc hl,de:jr z,exith  ; if x1=x2 and y1=y2 then exit!!

nex1

er ld hl,0 :ld b,h:ld c,l     ; HL=ER=E2=BC
dy ld de,0   ; DE= DY
add hl,sp    ; SP=DX
bit 7,h:jr nz,nex2    ; IF  E2+DX > 0  THEN ER = ER - DY
ld h,b:ld l,c:or a:sbc hl,de:ld(er+1),hl  ; er = er -dy
ld hl,x1+1:sx db 0        ; X1 = X1 + SX

nex2
ld h,b:ld l,c  ; HL=E2   DE=dy
or a:sbc hl,de      ; IF E2 - DY < 0 THEN ER = ER + DX
bit 7,h:jr z,nex3
ld hl,(er+1)  :add hl,sp    ; SP=DX
ld(er+1),hl         ; er = er+dx
ld hl,y1+1:sy db 0             ; Y1 = Y1 + SY

nex3 JP DRLOOP

exith
ld sp,0:ei:ret  ; finished OK




USAGE from BASIC:

CALL &7000,X1%,Y1%,X2%,Y2%
where  x1, y1= Start point   0<x<159
and  x2, y2=End point     0<y<199
% means integer only

Remember this works in all octants. Line is drawn FROM x1,y1 TO x2,y2 depending to their position (INC or DEC using both directions)

It uses all main registers (SP too).. I cant think of any way to make faster. Ideas anyone??
_____

6128 (UK keyboard, Crtc type 0/2), 6128+ (UK keyboard), 3.5" and 5.25" drives, Reset switch and Digiblaster (selfmade), Inicron Romram box, Bryce Megaflash, SVideo & PS/2 mouse, , Magnum Lightgun, X-MEM, X4 Board, C4CPC, Multiface2 X4, RTC X4 and Gotek USB Floppy emulator.

fgbrain

OK, since nobody noticed it...

A tiny optimization again.. We can gain 1 byte (!) by using the SIGN flag of Z80.
Warning:
1) JR works only with ZERO flag so we must use JP only
2) ADD wont work as well, so we change this to ADC (or SBC).

Therefore, we can replace :
bit 7,h
jr nz,NNNN


with

jp M,NNNN


and of course:

bit 7,h
jr z,NNNN

with

jp P,NNNN

_____

6128 (UK keyboard, Crtc type 0/2), 6128+ (UK keyboard), 3.5" and 5.25" drives, Reset switch and Digiblaster (selfmade), Inicron Romram box, Bryce Megaflash, SVideo & PS/2 mouse, , Magnum Lightgun, X-MEM, X4 Board, C4CPC, Multiface2 X4, RTC X4 and Gotek USB Floppy emulator.

Powered by SMFPacks Menu Editor Mod