3D Chess 2K18

The place for codemasters or beginners to talk about programming any language for the Spectrum.
Bizzley
Microbot
Posts: 124
Joined: Thu Nov 16, 2017 10:47 am

Re: 3D Chess 2K18

Post by Bizzley »

arkannoyed wrote: Thu Feb 07, 2019 9:11 am Proof that it does still work!

Image
Sometimes you get so wrapped up in the coding that you fail to see the bigger picture. Can you spot what's wrong here :?:
"He made eloquent speeches to an audience consisting of a few depressed daffodil roots, and sometimes the cat from next door."
User avatar
Einar Saukas
Bugaboo
Posts: 3070
Joined: Wed Nov 15, 2017 2:48 pm

Re: 3D Chess 2K18

Post by Einar Saukas »

White queen and king starting at wrong position.
User avatar
arkannoyed
Manic Miner
Posts: 435
Joined: Mon Feb 05, 2018 9:56 am
Location: Northamptonshire

Re: 3D Chess 2K18

Post by arkannoyed »

I know, work in progress, it will be sorted!!
User avatar
arkannoyed
Manic Miner
Posts: 435
Joined: Mon Feb 05, 2018 9:56 am
Location: Northamptonshire

Re: 3D Chess 2K18

Post by arkannoyed »

Fridays are always good for optimizing code!

Now 568 bytes :o
User avatar
arkannoyed
Manic Miner
Posts: 435
Joined: Mon Feb 05, 2018 9:56 am
Location: Northamptonshire

Re: 3D Chess 2K18

Post by arkannoyed »

Finally re-written the other main line building algorithm and managed to save another 4 valuable bytes.

Possibly uninteresting, but now down to 564 bytes

Technically now only -13 to go!
User avatar
Ast A. Moore
Rick Dangerous
Posts: 2640
Joined: Mon Nov 13, 2017 3:16 pm

Re: 3D Chess 2K18

Post by Ast A. Moore »

Rewrite it into checkers. :lol:
Every man should plant a tree, build a house, and write a ZX Spectrum game.

Author of A Yankee in Iraq, a 50 fps shoot-’em-up—the first game to utilize the floating bus on the +2A/+3,
and zasm Z80 Assembler syntax highlighter.
User avatar
arkannoyed
Manic Miner
Posts: 435
Joined: Mon Feb 05, 2018 9:56 am
Location: Northamptonshire

Re: 3D Chess 2K18

Post by arkannoyed »

Ast A. Moore wrote: Thu Feb 14, 2019 3:24 pm Rewrite it into checkers. :lol:
Genius! 256 bytes easy!
User avatar
arkannoyed
Manic Miner
Posts: 435
Joined: Mon Feb 05, 2018 9:56 am
Location: Northamptonshire

Re: 3D Chess 2K18

Post by arkannoyed »

...And -1 more byte 8-)

Now 563 bytes -12 to go
Bizzley
Microbot
Posts: 124
Joined: Thu Nov 16, 2017 10:47 am

Re: 3D Chess 2K18

Post by Bizzley »

arkannoyed wrote: Thu Feb 14, 2019 4:40 pm ...And -1 more byte 8-)

Now 563 bytes -12 to go
Does that include a fix for the incorrect start positions?
"He made eloquent speeches to an audience consisting of a few depressed daffodil roots, and sometimes the cat from next door."
User avatar
arkannoyed
Manic Miner
Posts: 435
Joined: Mon Feb 05, 2018 9:56 am
Location: Northamptonshire

Re: 3D Chess 2K18

Post by arkannoyed »

The positioning is merely the way the board initialising routine works, in its current state, incorrectly. The board can be set to display anything manually. Once all the other optimising is done, I’ll work on that separately. As the bytes have continued to fall away, it became apparent that to achieve the goal of sub 512 bytes, the initialisation routine can’t be counted in that, otherwise I’ve still got to shift 51 bytes, which I seriously doubt possible. Even now, to achieve it I need to make a few careful graphical tweaks, as saving another 12 bytes from the routines is highly unlikely.

I do have a final idea waiting in the wings to try out, and if I can make it work, and if the decoding isn’t too heavy, then it could save probably -40 bytes from the graphics data. That’s still in the planning stage, but fortunately the code structure would allow for it to integrate without too much hassle.

When I rewrite the board initialiser it will hopefully be no more than the 39 bytes it is now. One reason for leaving it be for the moment is that other factors elsewhere might affect how it needs to operate. Once they’re finalised, then it can have some attention.

I promise I’ll post some properly commented source soon too!
User avatar
arkannoyed
Manic Miner
Posts: 435
Joined: Mon Feb 05, 2018 9:56 am
Location: Northamptonshire

Re: 3D Chess 2K18

Post by arkannoyed »

Ast A. Moore wrote: Thu Feb 14, 2019 3:24 pm Rewrite it into checkers. :lol:
On a serious note, it could be done easily, just new gfx data and a suitable board initialising routine. Graphics currently 256 bytes, so probably possible in around 45-50 bytes max, total size no more than 350!
User avatar
Ast A. Moore
Rick Dangerous
Posts: 2640
Joined: Mon Nov 13, 2017 3:16 pm

Re: 3D Chess 2K18

Post by Ast A. Moore »

arkannoyed wrote: Thu Feb 14, 2019 6:30 pm
Ast A. Moore wrote: Thu Feb 14, 2019 3:24 pm Rewrite it into checkers. :lol:
On a serious note, it could be done easily, just new gfx data and a suitable board initialising routine. Graphics currently 256 bytes, so probably possible in around 45-50 bytes max, total size no more than 350!
Are you willing to put your bytes where your mouth is? ;)
Every man should plant a tree, build a house, and write a ZX Spectrum game.

Author of A Yankee in Iraq, a 50 fps shoot-’em-up—the first game to utilize the floating bus on the +2A/+3,
and zasm Z80 Assembler syntax highlighter.
User avatar
arkannoyed
Manic Miner
Posts: 435
Joined: Mon Feb 05, 2018 9:56 am
Location: Northamptonshire

Re: 3D Chess 2K18

Post by arkannoyed »

You design the gfx then?! No more than 22 bits wide though! Then I’ll encode it.
Last edited by arkannoyed on Thu Feb 14, 2019 7:04 pm, edited 1 time in total.
User avatar
arkannoyed
Manic Miner
Posts: 435
Joined: Mon Feb 05, 2018 9:56 am
Location: Northamptonshire

Re: 3D Chess 2K18

Post by arkannoyed »

Or rip off the ones from draughts genius, even easier!
User avatar
Ast A. Moore
Rick Dangerous
Posts: 2640
Joined: Mon Nov 13, 2017 3:16 pm

Re: 3D Chess 2K18

Post by Ast A. Moore »

arkannoyed wrote: Thu Feb 14, 2019 7:04 pm Or rip off the ones from draughts genius, even easier!
I have a better idea: to rip off the base of your chess pieces.
Every man should plant a tree, build a house, and write a ZX Spectrum game.

Author of A Yankee in Iraq, a 50 fps shoot-’em-up—the first game to utilize the floating bus on the +2A/+3,
and zasm Z80 Assembler syntax highlighter.
User avatar
arkannoyed
Manic Miner
Posts: 435
Joined: Mon Feb 05, 2018 9:56 am
Location: Northamptonshire

Re: 3D Chess 2K18

Post by arkannoyed »

Could do, but they’d still need alteration and encoding properly. I’ll demonstrate perhaps tomorrow the encoded graphics format.
User avatar
arkannoyed
Manic Miner
Posts: 435
Joined: Mon Feb 05, 2018 9:56 am
Location: Northamptonshire

Re: 3D Chess 2K18

Post by arkannoyed »

Obsessive or what!

I woke up in the night and suddenly thought of a way to save another byte in the Standard line routine, which now stands at only 28 bytes.

Now at 562 bytes with only -11 to go!
User avatar
Ersh
Manic Miner
Posts: 480
Joined: Mon Nov 13, 2017 1:06 pm

Re: 3D Chess 2K18

Post by Ersh »

arkannoyed wrote: Fri Feb 15, 2019 9:14 am I woke up in the night and suddenly thought of a way to save another byte in the Standard line routine, which now stands at only 28 bytes.
Love when that happens. :) Great work mate!
User avatar
arkannoyed
Manic Miner
Posts: 435
Joined: Mon Feb 05, 2018 9:56 am
Location: Northamptonshire

Re: 3D Chess 2K18

Post by arkannoyed »

So, as mentioned in the long boring bit yesterday, that meant very little to anyone I'm sure, I'd decided that the only possible way left to achieve the goal was to tweak the graphics carefully to lose the bytes. So I've managed to get down to 559 without too much alteration. Just a very minor change to the head of the Pawn so far.

As promised, the source so far;

Code: Select all

;Chess 2K19 Version 3 012
;
;July 2018 to February 2019. (c)Arkannoyed
;
;Significant changes to the way the data is constructed have allowed the
;code to become much faster and more efficient, also allowing the gfx
;data to vastly reduce in size.
;
;Standard lines consist of 4 bits of data and a length of (Black or White) infill.
;
;Data lines consist of 4 types
;1. long lines. These are lines of 18, 20 or 22 bits length, where the additional 6 bits over 16
;are stored within the index (first) byte, followed by 4 bytes of (W W XorB XorB) arranged data
;2. mini lines. Lines of 8 bits length or less, where left and right bytes are mirrored, so the
;4 bits are stored in the low 4 bits of the index byte.
;3. BLR-WLR lines. The Black and White versions of the line are different, but their Right and Left sides
;are mirrored versions of each other, where the low 5 bits of the index byte hold a XOR overlay to create
; the Black version from the White data. If the XOR ooverlay is 00000 then there is no change applied.
;4. BWR-BWL lines. These lines are non-mirrored, but Black and White are the same, so the low 5 bits in the
;index are ADDed to the Left side to create the Right.
;
;the line Buffers are HL and DE where the MSB is the innermost in the line and they are written outwards
;right for DE and left for HL.
;The last bit in the buffer is always '1' and is inverted to '0' and written, then the printing ends.
;
;559 bytes
;520 minus the board initialiser
;
org 0fd57h

init_board:
           ld de,0ffc0h
           ld b,d
           ld c,d
           ld hl,data_17
ib_loop1:  
           ld a,(hl)
           dec a
           ld (bc),a
           ldi
           jr nz,ib_loop1
           dec e
           ld b,20h
ib_loop2:
           ld (de),a
           inc e
           djnz ib_loop2

           ret                   ;23 bytes


data_17:
           db 15h,1fh,29h,33h,3dh,29h,1fh,15h
           db 0bh,0bh,0bh,0bh,0bh,0bh,0bh,0bh


chess_build:
           ld bc,00c0h                    ;start address of board
main_loop:                                
           ld ix,gfx_data_2               ;IX reset address
           ld d,b                         ;D=00h
           dec b                          ;B=FFh
calc_square:
           ld a,c                         ;C=board square 00-3f
           ld hl,0c811h                    ;HL=square 00 address 4830h
           ld e,l                         ;DE=0011h
csa_lp1:
           add hl,de                      ;
csa_ovr:
           sla e                          ;E x 2
           jr nc,csa_lp2                  ;
           ld e,1eh                       ;2nd part E value
csa_lp2:
           srl a                          ;test the next bit in BIT 0
           jr c,csa_lp1                   ;if '1' then add DE to HL
           jr nz,csa_ovr                  ;if '0' and A=00 then end
csa_lp3:
           sla h                          ;H x 8
           jr c,csa_lp3                  ;

           push hl
get_height:
           ld h,0feh                      ;H=Hi-byte of size/jump table address
           ld a,(bc)                      ;get the current piece occupying the square
           ld e,a                         ;save in E
           rra                            ;x1
           ld l,a                         ;
           ld b,(hl)                      ;B=piece height
           dec l                          ;next table item - switch 1

get_len:
           ex (sp),hl                     ;swap table position with SCReen address on stack
           push de                        ;line number (D) and piece (E) onto stack
           push bc                        ;height counter (B) and current square (C) onto stack

current_sq:
           ld a,c                         ;c=curent square
           and 09h                        ;
           jp pe,main_call                ;if white square, jump to main call
                                          ;change to JP PO to effectively rotate the board
                                          ;90 degrees.
calc_line:
           ld a,d                         ;D=current line
           sub 11h                        ;are we above the height of the board square?
           jr nc,main_call                ;if so, skip drawing the line part of the square

           adc a,d                        ;add back 1 + D (line number)
           jr nc,ovr_e                    ;if we don't go above 00 then don't DEC or INVERT
           jr z,skp1                      ;
           dec a
skp1:
           cpl                            ;
ovr_e:
           and 0fh                        ;

           inc a                          ;
           ld b,a                         ;line length /2 in B
           ld c,80h                       ;C=bit mask
add_line:
           push hl                        ;save HL position
addl_lp1:
           rlc c                          ;next bit left
           jr nc,addl_ovr1                ;
           dec l                          ;update HL if theres a carry
addl_ovr1:
           djnz addl_lp1                  ;loop
draw_line:
           add a,a                        ;x2 to get line length
           ld b,a                         ;into B again
addl_lp2:
           ld a,(hl)                      ;
           or c                           ;
           ld (hl),a                      ;merge bit with screen content
           xor a
           rrc c
           adc a,l
           ld l,a
addl_ovr2:
           djnz addl_lp2                  ;

           pop hl                         ;restore HL
           
main_call:
           push hl                        ;Push HL SCReen address
           sra e                          ;test E - piece no to see if a piece occupies the square.
           call nz,chess_2019             ;call main build routine if a piece occupies the square

           pop hl                         ;HL=SCReen address
           pop bc                         ;B=height C=current square
           pop de                         ;D=current line E=piece no.
           inc d                          ;next line up counter increment

nxt_line_up:
           ld a,h                         ;fairly standard stuff
           dec h                          ;I'm sure we're all
           and 07h                        ;familiar with!
           jr nz,sw2                      ;
           ld a,l                         ;
           add a,0e0h                     ;
           ld l,a                         ;
           sbc a,a                        ;
           and 08h                        ;
           add a,h                        ;
           ld h,a                         ;
sw2:
           ex (sp),hl                     ;place SCR addr. on stack, get pieces table position address
           ld a,b                         ;check the switch byte against the current value in the counter B
           cp (hl)                        ;test against current in table
           jr nz,piece_loop               ;if no match, then skip
jmp2:
           dec l                          ;point to Jump byte
           ld a,(hl)                      ;get jump byte
           ld ixl,a                       ;into IX
           dec l                          ;DEC for next
piece_loop:
           djnz get_len                   ;inner loop for pieces
end_check:
           pop af                         ;retrieve and discard pieces table addr. so stack is correct + clear carry.
           inc c                          ;next square
           jr nz,main_loop                ;repeat if needed

           ret                            ;ret

;data at 0FE00h
pieces:
             ;JL2 SW2 JL1 SW1 HT
           db                 11h                 ;00/00 square only - won't use 4 previous bytes - unimportant.
           db 1fh,0ch,6ch,16h,24h                 ;0a/0b pawn
           db 2ch,0dh,72h,12h,29h                 ;14/15 castle
           db 0a8h,17h,71h,1dh,2dh                ;1e/1f knight
           db 98h,0ah,6fh,16h,2fh                 ;28/29 bishop
           db 8dh,08h,6fh,16h,2fh                 ;32/33 queen
           db 80h,0ah,6fh,18h,31h                 ;3c/3d king

gfx_data_1:

           db 9ch,0eeh ;1f                                  ;pawn j2

           db 57h
           db 2fh
           db 2eh
           db 1eh
           db 2eh
           db 1eh
           db 1fh
           db 0a0h,38h
           db 8dh
           db 84h

           db 98h,1ch ;2c                                       ;csl j2
           db 5dh
           db 5ch
           db 2ch
           db 5ch
           db 2ch
           db 5ch
           db 0a0h,67h
           db 0a0h,0a7h
           db 0a0h,9bh
           db 0a0h,92h                                          ;uses 1st line of base as last top line of csl
gfx_data_2:
           db 81h ;3c                                          ;base
           db 0a0h,0f2h
           db 0e4h,0eh,0eh,0f0h,0f0h
           db 0f6h,05h,01h,0fah,0f8h
           db 39h
           db 59h
           db 39h
           db 59h
           db 0fbh,0e3h,0e0h,0fch,0fch
           db 0fbh,1dh,1ch,0feh,0feh
           db 0f6h,0bh,03h,0f7h,0f6h
           db 0e4h,0eh,02h,0f0h,0e8h

           db 5ch ;61                                          ;pwn sw1
           db 5dh

           db 2dh ;63                                          ;knt sw1
           db 5dh
           db 2dh
           db 2eh
           db 5eh
           db 2eh
           db 5eh

           db 1fh ;6a                                           ;csl sw1
           db 2fh

           db 2dh ;6c                                           ;pwn j1, kng sw1, qn sw1, bsp sw1
           db 2eh
           db 5eh

           db 1fh ;6f                                           ;kng j1, qn j1, bsp j1
           db 2fh

           db 1fh ;71                                           ;knt j1

           db 9fh,0ech ;72                                      ;csl j1
           db 1dh
           db 1ch
           db 1ch

           db 9fh,0c6h ;77                                      ;pwn sw2

           db 9eh,3ch ;79                                      ;csl sw2, knt sw2
           db 17h
           db 1eh
           db 2eh

           db 16h ;7e                                          ;bsp sw2
           db 5dh

           db 0a0h,1eh ;80                                      ;kng sw2/j2, qn sw2
           db 0a0h,0e3h
           db 0a0h,7eh
           db 0a0h,0b4h
           db 89h
           db 8fh
           db 8fh
           db 8ah
           db 88h

           db 0a0h,0b6h ;8d                                    ;qn j2
           db 0a0h,57h
           db 0a0h,6bh
           db 0a0h,0b2h
           db 8dh
           db 8ch
           db 88h

           db 0c0h,0ech,0ch,10h,0c0h   ;98                       ;bsp j2

           db 0aah,0bch
           db 0b0h,98h
           db 0aah,48h
           db 83h
           db 8bh
           db 86h
           db 8ch
           db 88h

           db 16h ;a8                                           ;knight j2
           db 0c0h,5ch,06h,0a0h,0a0h
           db 0c0h,2eh,03h,0d0h,0d0h
           db 3ch
           db 5ch
           db 0e0h,17h,03h,0e8h,0a0h
           db 0e0h,0bh,06h,0f4h,40h
           db 0e0h,17h,0ch,68h,80h
           db 0e0h,0bh,31h,0b4h,00h
           db 0e4h,07h,43h,78h,00h
           db 0e6h,0bh,9dh,34h,00h
           db 0e3h,85h,61h,1ah,1ch
           db 0c3h,8bh,82h,34h,7ch
           db 0c6h,17h,00h,68h,0fdh
           db 0c4h,0eh,03h,0f0h,0f8h
           db 0c0h,2eh,65h,0d0h,0f8h
           db 0c0h,5ch,0dch,0a0h,0e0h
           db 0c0h,38h,68h,0c0h,80h
           db 0aeh,70h
           db 0ach,60h
           db 0b8h,0c0h
           db 88h

           ;221 bytes 109 lines
           ;total data 253 bytes

chess_2019:
           sbc a,a                           ;set B/W component according to BIT 0 of E
           ld c,a                            ;set B/W component in C, Black=FF, White=00
           
           ld b,03h
           ld a,d                            ;test current line no.
           cp b                              ;if 00-02 then RET, as we've not reached printing
           ret c                             ;of the base yet.
continue:
           ld a,(ix+00h)                     ;get gfx byte
           inc ixl                           ;
test_line:
           add a,a                           ;test BIT 7 to determine whether its a Standard or Data line type

           push hl                           ;save the screen address for printing.

           ld hl,0fc00h                      ;initialise HL
           ld e,l                            ;E=00h

           jr c,data_line                    ;if type '1' line then jump to Data_Line builder

standard_line:
           ld l,a                            ;save source
           and 0f0h                          ;mask Data part
           ld d,a                            ;save in D
           xor l                             ;inverse mask - 0Fh to get counter
           sub h                             ;ADD +04h - same as -0FCh
           ld b,a                            ;counter into B
           ld a,c                            ;B/W component into A
           or 0ch                            ;overlay add-in outer bits
           and h                             ;mask 0FCh
           ld e,a                            ;into E
           xor d                             ;apply Data
           ld l,a                            ;into L
           ld d,c                            ;B/W component into D
           ld h,c                            ;B/W component into H
           inc c                             ;test C (00-01=W/FF-00=B)
           jr nz,st_lp1                      ;skip over swap if Black
st_lp0:
           ex de,hl                          ;swap buffers Left-Right
st_lp1:
           add hl,hl                         ;propagate the unwanted bits out of HL
           djnz st_lp0                       ;loop

           ld a,h                            ;replace BIT 7 of H
           rla                               ;with the last BIT carried
           rrca                              ;out of D

           jr bit4_res+1                     ;jump to printing line

data_line:

           ld d,(ix+00h)                     ;pre load D
           cp 1fh                            ;test for line type where only 1 byte
           jr c,bit6_test                    ;
           inc ixl                            ;inc IX if 2 bytes+
bit6_test:
           add a,a                           ;test BIT 6
           jr c,long_line                    ;next if '0'
bit5_test:
           add a,a
           jr nc,bit4_test-1
bit5_set:
           add a,d
           jr bit4_res+1
long_line:
           ld l,a                            ;remainder of A into L - 6 bits
           and 0e0h                          ;mask upper 3 bits E0h
           ld e,a
lllp_00:
           ld a,(ix+00h)
           and c
           xor (ix+0feh)
           ld d,h
           add hl,hl
           ld h,a
           inc ixl
           djnz lllp_00
           jr print_line                     ;second byte here is 07=RLCA
bit4_test:
           jr nc,bit4_res                    ;if bit ='0' then the data for BWRL is in the 4 bits remaining in A
bit4_set:
           rra                               ;re-use bit to fill BIT 7, creating a left orientated mask
           and c                             ;mask with C BW byte to create 5 bit overlay mask of ccccc000
           xor d                             ;create the Black or White Left and Right buffer bytes
bit4_res:
           ld d,a                            ;load Right buffer
           ld h,a                            ;load Left buffer

print_line:
           ex (sp),hl                        ;put HL Left buffer on stack and retrieve screen address
           ex de,hl                          ;swap register pair, DE=screen address, HL=buffer
           dec e                             ;adjust screen position to Left Hand Side
           ld c,01h                          ;bit mask Right initial
right:
           xor a
           rrc c
           adc a,e
           ld e,a
ovr21:
           call place_bit                    ;
           jr nz,right                       ;rpt if HL not 0000

           ld a,(de)
           xor c
           ld (de),a
reset_scr1:
           res 0,e                           ;restore SCReen address
get_lhs:
           pop hl                            ;LHS data retrieve
set_mask_l:
           ld c,80h                          ;reset bit mask for Right side so that we automatically move screen addr left.
left:
           rlc c                             ;next left bit
           sbc a,a
           add a,e
           ld e,a
ovr22:
           call place_bit                    ;
           jr nz,left                        ;repeat if HL not 0000

place_bit:
           ld a,(de)
           ld b,a
           add hl,hl
           sbc a,a
           xor b
           and c
           xor b
           ld (de),a
           ld a,h
           or l
           ret
Sorry, it looks big here! :lol:
User avatar
arkannoyed
Manic Miner
Posts: 435
Joined: Mon Feb 05, 2018 9:56 am
Location: Northamptonshire

Re: 3D Chess 2K18

Post by arkannoyed »

*******Fanfare********

512 bytes alert!!!!!!!!!!!!!!!

With a barely noticeable alteration to the Knight sprite data, I've only gone and done it!!!!!

So, as it stands, the full routine, including the board initialising routine is 551 bytes

If we subtract that 39 bytes from the total we get the almost magical figure of 512 bytes

I never thought it possible, but I've done it.

New Knight graphics data;

Code: Select all

           db 16h ;a8                                           ;knight j2
           db 5dh
           db 5ch
           db 3ch
           db 5ch
           db 0e0h,17h,03h,0e8h,0a0h
           db 0e0h,0bh,06h,0f4h,40h
           db 0e0h,17h,0ch,68h,80h
           db 0e0h,0bh,31h,0b4h,00h
           db 0e4h,07h,43h,78h,00h
           db 0e6h,0bh,9dh,34h,00h
           db 0e3h,85h,61h,1ah,1ch
           db 0c3h,8bh,82h,34h,7ch
           db 0c6h,17h,00h,68h,0fdh
           db 0c4h,0eh,03h,0f0h,0f8h
           db 0c0h,2eh,65h,0d0h,0f8h
           db 0c0h,5ch,0dch,0a0h,0e0h
           db 0c0h,38h,68h,0c0h,80h
           db 0aeh,70h
           db 0ach,60h
           db 0b8h,0c0h
           db 88h
I think I need a rest now before I set about re-writing the initialiser to make it work properly.

Then I suppose I should consider the hard part of actually making it playable :?

Image
Last edited by arkannoyed on Fri Feb 15, 2019 3:29 pm, edited 1 time in total.
User avatar
arkannoyed
Manic Miner
Posts: 435
Joined: Mon Feb 05, 2018 9:56 am
Location: Northamptonshire

Re: 3D Chess 2K18

Post by arkannoyed »

No rest....another -4 bytes this time shaved off the base part, and surprisingly, well in my opinion anyway, makes it look better.

Now at 547 bytes = 508

Image
User avatar
arkannoyed
Manic Miner
Posts: 435
Joined: Mon Feb 05, 2018 9:56 am
Location: Northamptonshire

Re: 3D Chess 2K18

Post by arkannoyed »

I am interested to know if the source makes an sense to anyone perhaps more familiar with source code listings?

I generally comment mine extremely badly or not at all. I'm probably not alone in the fact that when you write something, it reads just fine to you without lengthy explanations. I do appreciate however, that the older I get, the more helpful the comments are when I revisit some past projects.

If any parts do need further explanation, then I will oblige of course.
User avatar
arkannoyed
Manic Miner
Posts: 435
Joined: Mon Feb 05, 2018 9:56 am
Location: Northamptonshire

Re: 3D Chess 2K18

Post by arkannoyed »

.TAP file to load and mess with.

https://dl.dropbox.com/s/ud9urfxww0giq7 ... a.tap?dl=1

Small 'cheat' added in the basic loader to swap the White king and queen for now. Will be fixed very soon, promise! :D
User avatar
Ast A. Moore
Rick Dangerous
Posts: 2640
Joined: Mon Nov 13, 2017 3:16 pm

Re: 3D Chess 2K18

Post by Ast A. Moore »

arkannoyed wrote: Fri Feb 15, 2019 3:17 pm when you write something, it reads just fine to you without lengthy explanations. I do appreciate however, that the older I get, the more helpful the comments are when I revisit some past projects.
In my case, if I don’t comment everything like I’m explaining to a child, I tend to forget what I do in about a week if I’m lucky. Usually, though, I can’t recognize my own routines and optimizations about two days later, if I don’t comment them.
Every man should plant a tree, build a house, and write a ZX Spectrum game.

Author of A Yankee in Iraq, a 50 fps shoot-’em-up—the first game to utilize the floating bus on the +2A/+3,
and zasm Z80 Assembler syntax highlighter.
KayBee
Drutt
Posts: 17
Joined: Thu May 31, 2018 3:14 pm

Re: 3D Chess 2K18

Post by KayBee »

This is stunning arkannoyed. If I could have two wishes, they would be:
1. Tie Peter Jennings 1k MicroChess to this beautiful interface.
2. tie the infamous 1k ZX chess to this beautiful interface.

I wish I wish.

KB
Post Reply