0 Members and 1 Guest are viewing this topic.
.addinstr add ahl,de 00CE19 3 NOP 1 ;add hl,de \ adc a,0.addinstr add ahl,cde 8919 2 NOP 1 ;add hl,de \ adc a,c
.addinstr <instruction> <asm code for the instruction, written in hex> <amounth of bytes of asm code> NOP 1
EXAMPLE EXAMPLEINSTRUCTION DEFINITION SOURCE OBJECT-------------------------------------------------------------------XYZ * FF 3 NOTOUCH 1 xyz 1234h FF 34 12XYZ * FF 2 NOTOUCH 1 xyz 1234h FF 34ZYX * FE 3 SWAP 1 zyx 1234h FE 12 34ZYX * FE 3 R2 1 zyx $+4 FE 01 00ABC *,* FD 3 COMBINE 1 abc 45h,67h FD 45 67ABC *,* FD 3 CSWAP 1 abc 45h,67h FD 67 45ADD A,#* FC 2 NOTOUCH 1 add A,#'B' FC 42RET "" FB 1 NOTOUCH 1 ret FBLD IX,* 21DD 4 NOTOUCH 1 ld IX,1234h DD 21 34 12LD IX,* 21DD 4 NOTOUCH 1 1 0 ld IX,1234h DD 21 68 24LD IX,* 21DD 4 NOTOUCH 1 0 1 ld IX,1234h DD 21 35 12LD IX,* 21DD 4 NOTOUCH 1 1 1 ld IX,1234h DD 21 69 24LD IX,* 21DD 4 NOTOUCH 1 8 12 ld IX,34h DD 21 12 34
#ifdef TI83PGBUF_LSB = $40GBUF_MSB = $93#elseGBUF_LSB = $29GBUF_MSB = $8E#endif;b = # columns;c = # rows;d = starting x;e = starting yrectangle_filled_xor: ld a,$AE ;xor (hl) jr rectangle_filled2rectangle_filled_solid: ld a,$B6 ;or (hl)rectangle_filled2: push de push bc ld (or_xor),a ;use smc for xor/solid fill ld a,d ;starting x and $7 ;what bit do we start on? ex af,af' ld a,d ;starting x ld l,e ;ld hl,e ld h,0 ; .. ld d,h ;set d = 0 add hl,de ;starting y * 12 add hl,de ;x3 add hl,hl ;x6 add hl,hl ;x12 rra ;a = x coord / 8 rra ; rra ; and %00011111 ;starting x/8 (starting byte in gbuf) add a,GBUF_LSB ld e,a ; ld d,GBUF_MSB ; add hl,de ;hl = offset in gbuf ex af,af' ;carry should be reset and z affected from and $7 ld e,a ld a,%10000000 jr z,$+6 rra dec e jr nz,$-2 ld d,a ;starting bit to drawrectangle_loop_y: push bc push hlrectangle_loop_x: ld e,a ;save a (overwritten with or (hl))or_xor = $ or (hl) ;smc will modify this to or/xor ld (hl),a ld a,e ;recall a rrca ;rotate a to draw the next bit jr nc,$+3 inc hl djnz rectangle_loop_x pop hl ;hl = first column in gbuf row ld c,12 ;b = 0, bc = 12 add hl,bc ;move down to next row pop bc ;restore b (# columns) ld a,d ;restore a (starting bit to draw) dec c jr nz,rectangle_loop_yrectangle_end: pop bc pop de ret
start: ld de,$041B ld bc,$1103 call draw_box2 call ionFastCopy bcall _getkey ret draw_box2: call rectangle_filled_solid inc d inc e dec b dec b dec c dec c call rectangle_filled_xor ret
ld hl,or_xor ld (hl),a ;use smc for xor/solid fill
ld (or_xor),a
rra ;a = x coord / 8 rra ; rra ; and %00011111 ;starting x/8 (starting byte in gbuf) ld e,a ; add hl,de ;add x ld de,gbuf ; add hl,de ;hl = offset in gbuf
rra ;a = x coord / 8 rra ; rra ; and %00011111 ;starting x/8 (starting byte in gbuf) or 40h ;gbuf=9340h, 40h = %01000000, so this won't cause problems ld e,a ; ld d,93h add hl,de ;add x
pop hl pop bc ;restore b (# columns) pop af ld de,12 add hl,de ;move down to next row
pop hl ld c,12 add hl,bc pop bc ;restore b (# columns) pop af
ld d,arectangle_loop_y: push bc push hl rectangle_loop_x: ld e,a or_xor = $ or (hl) ;smc will modify this to or/xor ld (hl),a ld a,e rrca jr nc,$+3 inc hl djnz rectangle_loop_x pop hl ld c,12 add hl,bc pop bc ld a,d dec c jr nz,rectangle_loop_y
;D is the x coordinate, here;HL points to the pattern buffer (12 bytes) ld a,d and 7 ld a,80h ld b,a jr z,$+5 rrca djnz $-1;A is the mask if it were for a pixel;B is 0 add a,a dec a ld (hl),a
;b = # columns ;c = # rows ;d = starting x ;e = starting y rectangle_filled2: ld a,d ;a = starting x coord ld l,e ;ld hl,e ld h,0 ; .. ld d,h ;set d = 0 add hl,de ;starting y * 12 add hl,de ;x3 add hl,hl ;x6 add hl,hl ;x12 rra ;a = x coord / 8 rra ; rra ; and %00011111 ;starting x/8 ld e,a ; add hl,de ;add x ld de,gbuf add hl,de ;offset in gbuf ld a,b ;b = no columns rra rra rra and %00011111 ;no. columns / 8 ld b,a ld a,12 sub b ld e,a ld d,0 rectangle_loop_y: push bc rectangle_loop_x: ld (hl),$FF inc hl djnz rectangle_loop_x pop bc ;restore c (# columns) add hl,de ;move down to next row dec c jr nz,rectangle_loop_y rectangle_end: ret
#ifdef TI83PGBUF_LSB = $40GBUF_MSB = $93 .org progstart-2 .db $bb,$6d#else GBUF_LSB = $29GBUF_MSB = $8E .org progstart#endif;... rra ;a = x coord / 8 rra ; rra ; and %00011111 ;starting x/8 (starting byte in gbuf) add a,GBUF_LSB ld e,a ; ld d,GBUF_MSB ; add hl,de ;hl = offset in gbuf
#ifdef TI83PGBUF_LSB = $40GBUF_MSB = $93#elseGBUF_LSB = $29GBUF_MSB = $8E#endif;b = # rows;c = # columns;d = starting x;e = starting yrectangle_filled_xor: ld a,$AE ;xor (hl) jr rectangle_filled2rectangle_filled_solid: ld a,$B6 ;or (hl)rectangle_filled2: push de push bc ld (or_xor),a ;use smc for xor/solid fill ld a,d ;starting x and $7 ;what bit do we start on? ex af,af' ld a,d ;starting x ld l,e ;ld hl,e ld h,0 ; .. ld d,h ;set d = 0 add hl,de ;starting y * 12 add hl,de ;x3 add hl,hl ;x6 add hl,hl ;x12 rra ;a = x coord / 8 rra ; rra ; and %00011111 ;starting x/8 (starting byte in gbuf) add a,GBUF_LSB ld e,a ; ld d,GBUF_MSB ; add hl,de ;hl = offset in gbuf ex af,af' ;carry should be reset and z affected from and $7 ld d,a ld a,%10000000 jr z,$+6 rra dec d jr nz,$-2 ld e,12rectangle_loop_x: push af push bc push hl ld c,arectangle_loop_y:or_xor = $ or (hl) ;smc will modify this to or/xor ld (hl),a ld a,c add hl,de djnz rectangle_loop_y pop hl pop bc pop af rrca jr nc,$+3 inc hl dec c jr nz,rectangle_loop_xrectangle_end: pop bc pop de ret
start: ld de,$0204 ld bc,$2121 call draw_box2 call ionFastCopy bcall _getkey retdraw_box2: call rectangle_filled_solid inc d inc e dec b dec b dec c dec c call rectangle_filled_xor ret
;b = # rows;c = # columns;d = starting x;e = starting yrectangle: push de push bc ld a,d ;starting x and $7 ;what bit do we start on? ex af,af' ld a,d ;starting x ld l,e ;ld hl,e ld h,0 ; .. ld d,h ;set d = 0 add hl,de ;starting y * 12 add hl,de ;x3 add hl,hl ;x6 add hl,hl ;x12 rra ;a = x coord / 8 rra ; rra ; and %00011111 ;starting x/8 (starting byte in gbuf) add a,GBUF_LSB ld e,a ; ld d,GBUF_MSB ; add hl,de ;hl = offset in gbuf ex af,af' ;carry should be reset and z affected from and $7 ld e,a ld a,%10000000 jr z,$+6 rra dec e jr nz,$-2 dec b ;you could adjust your input to take care of this, ie b = width-2, c = height-1 and save 3 bytes here dec b ;we draw the ends separately dec c ;we'll draw the last line at the end ld d,a ;starting bit to draw;d = starting bitrectangle_loop_y: push bc push hl call rectangle_loop_x pop hl ;hl = first column in gbuf row ld c,12 ;b = 0, bc = 12 add hl,b ;move down to next row pop bc ;restore b (# columns) xor a; cp c ; # UNCOMMENT TO ALLOW LINES WITH A HEIGHT OF 1 PIXEL; jr z,rectangle_end ; # ld (ld_hl),a ;change ld (hl),a to nop ld a,d ;restore a (starting bit to draw) dec c jr nz,rectangle_loop_y ld a,$77 ;ld (hl),a ld (ld_hl),a ;return nop to ld (hl),a ld a,d call rectangle_loop_xrectangle_end: pop bc pop de retrectangle_loop_x: or (hl) ;first bit ld (hl),a; inc b ; # UNCOMMENT TO ALLOW LINES WITH A WIDTH OF 1 PIXEL; ret z ; # ; dec b ; # ; jr z,rectangle_loop_x_end ; # ld a,drectangle_loop_x_inner: rrca ;rotate a to draw the next bit jr nc,$+3 inc hl ld e,a ;save a (overwritten with or (hl)) or (hl) ;smc will modify this to or/xorld_hl = $ ld (hl),a ld a,e ;recall a djnz rectangle_loop_x_innerrectangle_loop_x_end: rrca ;rotate a to draw the next bit jr nc,$+3 inc hl or (hl) ;last bit ld (hl),a ret
Rectangle_or: ld a,$B6 jr RectangleRectangle_xor: ld a,$AERectangle:; DE = (x,y); BC = (height,width) ld (smc_logic1),a ld (smc_logic0),a push de push bc push bc ld a,d call ComputeByte ld (smc_FirstByte),a ex (sp),hl ld a,d neg and 7 ld b,a ld a,l sub b ex (sp),hl ld c,a call ComputeByte cpl ld (smc_LastByte),a ld b,a sra c \ sra c \ sra c inc c; ld a,c; and %11111000; rra \ rra \ rra; inc a; ld c,a ld a,d ld d,0 ld h,d ld l,e add hl,hl add hl,de add hl,hl add hl,hl and %11111000 rra \ rra \ rra add a,GBUF_LSB ld e,a ld d,GBUF_MSB add hl,de;HL points to the first byte pop de;D is the height;E is the number of bytes wide inc c dec c jr nz,RectOverLoop-1 ld a,(smc_FirstByte) and b ld c,a ;value ld b,d ;height ld de,12 ld a,csmc_logic1: or (hl) ld (hl),a add hl,de djnz $-4 pop bc pop de ret ld e,cRectOverLoop: ld b,e ld c,12 .db 3Eh ;start of ld a,*smc_FirstByte: .db 0RectLoop:smc_logic0: or (hl) ld (hl),a inc hl dec c jr z,ExitLoop ld a,-1 djnz RectLoop; jp p,$+4; dec b .db 3Eh ;start of ld a,*smc_LastByte: .db 0 or (hl) ld (hl),a add hl,bcExitLoop: dec d jr nz,RectOverLoop pop bc pop de retComputeByte: and 7 ld b,a ld a,80h jr z,$+5 rrca djnz $-1 add a,a dec a ret
;;;;rectXOR;;rectOR;;rectErase;; (B,C) = (x,y) signed;; (D,E) = (w,h) unsigned;; HL points to bufrectXOR: push hl call rectSub pop ix ret nc ex de,hl add ix,de ex de,hl push ix pop hl dec b jp m,xorrect0 inc bxor_rect_loop: push bc push hl ld a,(hl) \ xor d \ ld (hl),a \ inc hl dec b jr z,$+8 ld a,(hl) \ cpl \ ld (hl),a \ inc hl \ djnz $-4 ld a,(hl) \ xor e \ ld (hl),a ld bc,12 pop hl add hl,bc pop bc dec c jr nz,xor_rect_loop retxorrect0: ld a,d and e ld b,c ld c,a ld de,12 ld a,c xor (hl) ld (hl),a add hl,de djnz $-4 retrectErase: push hl call rectSub pop ix ret nc ex de,hl add ix,de ex de,hl push ix pop hl ld a,d cpl ld d,a ld a,e cpl ld e,a dec b jp m,eraserect0 inc berase_rect_loop: push bc push hl ld a,(hl) \ and d \ ld (hl),a \ inc hl dec b jr z,$+7 xor a ld (hl),a \ inc hl \ djnz $-2 ld a,(hl) \ and e \ ld (hl),a ld bc,12 pop hl add hl,bc pop bc dec c jr nz,erase_rect_loop reteraserect0: ld a,d xor e ld b,c ld c,a ld de,12 ld a,c and (hl) ld (hl),a add hl,de djnz $-4 retrectOR: push hl call rectSub pop ix ret nc ex de,hl add ix,de ex de,hl push ix pop hl dec b jp m,orrect0 inc bor_rect_loop: push bc push hl ld a,(hl) \ or d \ ld (hl),a \ inc hl dec b jr z,$+8 ld c,-1 ld (hl),c \ inc hl \ djnz $-2 ld a,(hl) \ or e \ ld (hl),a ld bc,12 pop hl add hl,bc pop bc dec c jr nz,or_rect_loop retorrect0: ld a,d and e ld b,c ld c,a ld de,12 ld a,c or (hl) ld (hl),a add hl,de djnz $-4 retrectsub:;(B,C) = (x,y) signed;(D,E) = (w,h) unsigned;Output:; Start Mask D; End Mask E; Byte width B; Height C; buf offset HL bit 7,b jr z,+_ ;Here, b is negative, so we have to add width to x. ;If the result is still negative, the entire box is out of bounds, so return ;otherwise, set width=newvalue,b=0 ld a,d add a,b ret nc ld d,a ld b,0_: bit 7,c jr z,+_ ld a,e add a,c ret nc ld e,a ld c,0_:;We have clipped all negative areas.;Now we need to verify that (x,y) are on the screen.;If they aren't, then the whole rectangle is off-screen so no need to draw. ld a,b cp 96 ret nc ld a,c cp 64 ret nc;Let's also verfiy that height and width are non-zero: ld a,d or a ret z ld a,e or a ret z;Now we need to clip the width and height to be in-bounds add a,c cp 65 jr c,+_ ;Here we need to set e=64-c ld a,64 sub c ld e,a_: ld a,d add a,b cp 97 jr c,+_ ;Here we need to set d=96-b ld a,96 sub b ld d,a_:;B is starting X;C is starting Y;D is width;E is height push bc ld a,b and 7 ld b,a ld a,-1 jr z,+_ rra \ djnz $-1_: inc a cpl ld h,a ;start mask ld a,b add a,d and 7 ld b,a ld a,-1 jr z,+_ rra \ djnz $-1_: inc a ld l,a ;end mask ex (sp),hl ;stack now holds DE ;HL is now the coordinates ;B=0, C=height ;A,BC are free to destroy ld a,h ld h,b add hl,hl add hl,bc add hl,hl add hl,hl ld b,a rrca rrca rrca and 31 add a,l ld l,a jr nc,$+3 inc h;B is the starting x, D is width;Only A,B,D,E are available ld a,b add a,d and $F8 ld d,a ld a,b and $F8 ld b,a ld a,d sub b rrca rrca rrca ld b,a ld c,e pop de scf ret
ComputeByte: and 7 ld b,a ld a,$FF ret z srl a ;or or a \ rra djnz $-2 ret
It's interesting to see how our syntax/style differs even on bits of code that do exactly the same thing
And if you don't mind sacrificing just a few clocks (altogether maybe between 8-64), maybe you could try this and save 2 bytes:
ComputeByte: neg ; or 'cpl \ inc a and 7 ld b,a ld a,FFh ret z add a,a djnz $-1 ret
GCDDE_HL:;Inputs:; HL,DE are the two values;Outputs:; B is 0; DE is 0; HL is the GCD; C is not changed;Destroys:; A xor a ;AF 4 ld b,a ;47 4CheckMax: ; sbc hl,de ;ED52 15n jr z,AdjustGCD ;28** 12n-5 jr nc,ParityCheck ;30** 12n-5 xor a ;AF 4(n-a) sub l ;95 4(n-a) ld l,a ;6F 4(n-a) sbc a,a ;9F 4(n-a) sub h ;94 4(n-a) ld h,a ;67 4(n-a) ex de,hl jp CheckMax ;C3**** 10(n-a)ParityCheck: ; bit 0,e ;CB** 8a jr nz,DE_Odd ;20** 12a-5b bit 0,l ;CB** 8b jr z,BothEven ;28** 12b-5c rr d ;CB** 8(n-a-b-c) rr e ;CB** 8(n-a-b-c) jp CheckMax ;C3**** 10(n-a-b-c)BothEven: ; inc b ;04 4c rr d \ rr e ; 16c rr h \ rr l ; 16c jp CheckMax ; 10cDE_Odd: ; bit 0,l ; 8b jr nz,BothOdd ; 12b-5d rr h \ rr l ; 16(n-a-b-d) jp CheckMax ; 10(n-a-b-d)BothOdd: ; sbc hl,de ; 15d rr h \ rr l ; 16d jp CheckMax ; 10dAdjustGCD: ; ex de,hl ; 4 inc b ; 4 dec b ; 4 ret z ; 11+4(k>0) add hl,hl ; 11k djnz $-1 ; 13k-5 ret ; --
GCD_A_C:;Outputs:; A is the GCD; C should be the smallest odd number that divides both inputs; B is 0;Destroys:; D ld b,1CheckMax: sub c jr z,AdjustGCD jr nc,ParityCheck neg ld d,a ld a,c ld c,a jr CheckMaxParityCheck: rrc c jr c,c_Odd inc b rrca jr nc,CheckMax rlca djnz CheckMaxc_Odd: rlc c rrca jr nc,CheckMax rlca jr CheckMaxAdjustGCD: ld a,c dec b ret z add a,a djnz $-1 ret
GCDDE_HL:;Inputs:; HL,DE are the two values;Outputs:; B is 0; DE is 0; HL is the GCD; C is not changed; A is not changed ld b,1 or aCheckMax: ; sbc hl,de ;ED52 15n jr z,AdjustGCD ;28** 12n-5 jr nc,ParityCheck ;30** 12n-5 add hl,de or a ex de,hlParityCheck: ; bit 0,e ;CB** 8a jr nz,DE_Odd ;20** 12a-5b bit 0,l ;CB** 8b jr z,BothEven ;28** 12b-5c rr d ;CB** 8(n-a-b-c) rr e ;CB** 8(n-a-b-c) jp CheckMax ;C3**** 10(n-a-b-c)BothEven: ; inc b ;04 4c rr d \ rr e ; 16cHL_Even: rr h \ rr l ; 16c jp CheckMax ; 10cDE_Odd: ; bit 0,l ; 8b jr z,HL_Even ; 12b-5d sbc hl,de ; 15d rr h \ rr l ; 16d jp nz,CheckMax ; 10dAdjustGCD: ; ex de,hl ; 4 dec b ; 4 ret z ; 11+4(k>0) add hl,hl ; 11k djnz $-1 ; 13k-5 ret ; --
Code: [Select]SignedDivision: ld a,h xor d push af bit 7,h jr z,$+8 xor a sub l ld l,a sbc a,a sub h ld h,a bit 7,d jr z,$+8 xor a sub e ld e,a sbc a,a sub d ld d,a call RegularDivision pop af add a,a ret nc xor a sub l ld l,a sbc a,a sub h ld h,a ret
SignedDivision: ld a,h xor d push af bit 7,h jr z,$+8 xor a sub l ld l,a sbc a,a sub h ld h,a bit 7,d jr z,$+8 xor a sub e ld e,a sbc a,a sub d ld d,a call RegularDivision pop af add a,a ret nc xor a sub l ld l,a sbc a,a sub h ld h,a ret
SignedDivision: ld a,h xor d push af xor d jp p,$+9 xor a sub l ld l,a sbc a,a sub h ld h,a bit 7,d jr z,$+8 xor a sub e ld e,a sbc a,a sub d ld d,a call RegularDivision pop af ret p xor a sub l ld l,a sbc a,a sub h ld h,a ret
SqrtL:;Inputs:; L is the value to find the square root of;Outputs:; C is the result; B,L are 0; DE is not changed; H is how far away it is from the next smallest perfect square; L is 0; z flag set if it was a perfect square;Destroyed:; A ld bc,400h ; 10 10 ld h,c ; 4 4sqrt8Loop: ; add hl,hl ;11 44 add hl,hl ;11 44 rl c ; 8 32 ld a,c ; 4 16 rla ; 4 16 sub a,h ; 4 16 jr nc,$+5 ;12|19 48+7x inc c cpl ld h,a djnz sqrt8Loop ;13|8 47 ret ;10 10;287+7x, x is the number of bits in the result;min: 287;max: 315;19 bytes
GCDHL_DE:;Outputs:; DE is the GCDGCDLoop: or a sbc hl,de ret z jr nc,$-3 add hl,de ex de,hl jp GCDLoop
HL_mod_3:;Outputs:; Preserves HL; A is the remainder; destroys DE,BC; z flag if divisible by 3, else nz ld bc,030Fh ld a,h add a,l sbc a,0 ;conditional decrement;Now we need to add the upper and lower nibble in a ld d,a and c ld e,a ld a,d rlca rlca rlca rlca and c add a,e sub c jr nc,$+3 add a,c;add the lower half nibbles ld d,a sra d sra d and b add a,d sub b ret nc add a,b ret;at most 132 cycles, at least 123