0 Members and 1 Guest are viewing this topic.
; divide HL by C (HL is signed, C is not); output: HL = quotient, A = remainderdivHLbyCs: bit 7,h push af jr z,divHLbyCsStart xor a \ sub l \ ld l,a sbc a,a \ sub h \ ld h,adivHLbyCsStart: xor a ld b,16divHLbyCsLoop: add hl,hl rla cp c jp c,divHLbyCsNext sub c inc ldivHLbyCsNext: djnz divHLbyCLoop ld b,a pop af ld a,b ret z xor a \ sub l \ ld l,a sbc a,a \ sub h \ ld h,a ld a,c sub b ret
pushpop:;26 bytes, adds 229cc to the calling routine ex (sp),hl push de push bc push af push hl ld hl,pushpopret ex (sp),hl push hl push af ld hl,12 add hl,sp ld a,(hl) inc hl ld h,(hl) ld l,a pop af retpushpopret: pop af pop bc pop de pop hl ret
diRestore: ex (sp),hl push hl push af ld hl,restoreei ld a,r jp pe,+_ dec hl dec hl_: di inc sp inc sp inc sp inc sp ex (sp),hl dec sp dec sp dec sp dec sp pop af retrestoredi: di retrestoreei: ei ret
endianswap32: push hl ld h,e ld e,l inc sp push hl inc sp pop hl inc sp ret
atan8:;computes 256*atan(A/256)->A;56 bytes including the LUT;min: 246cc;max: 271cc;avg: 258.5cc rlca rlca rlca ld d,a and 7 ld hl,atan8LUT add a,l ld l,a#if (atan8LUT&255)>248 ;this section not included in size/speed totals jr nc,$+3 ;can add three bytes, 12cc to max, 11cc to min, and 11.5cc to avg inc h#endif ld c,(hl) inc hl ld a,(hl) sub c ld e,0 ex de,hl ld d,l ld e,a sla h \ jr nc,$+3 \ ld l,e add hl,hl \ jr nc,$+3 \ add hl,de add hl,hl \ jr nc,$+3 \ add hl,de add hl,hl \ jr nc,$+3 \ add hl,de add hl,hl \ jr nc,$+3 \ add hl,de add hl,hl add hl,hl add hl,hl; add hl,hl ;used in rounding... ld a,h; rra ;but doesn't seem to improve the error adc a,c retatan8LUT: .db 0,32,63,92,119,143,165,184,201
sqrtHLIX:;Input: HLIX;Output: DE is the sqrt, AHL is the remainder;speed: 751+6{0,6}+{0,3+{0,18}}+{0,38}+sqrtHL;min: 1103;max: 1237;avg: 1165.5;166 bytes call sqrtHL ;expects returns A as sqrt, HL as remainder, D = 0 add a,a ld e,a rl d ld a,ixh sll e \ rl d add a,a \ adc hl,hl add a,a \ adc hl,hl sbc hl,de jr nc,+_ add hl,de dec e .db $FE ;start of `cp *`_: inc e sll e \ rl d add a,a \ adc hl,hl add a,a \ adc hl,hl sbc hl,de jr nc,+_ add hl,de dec e .db $FE ;start of `cp *`_: inc e sll e \ rl d add a,a \ adc hl,hl add a,a \ adc hl,hl sbc hl,de jr nc,+_ add hl,de dec e .db $FE ;start of `cp *`_: inc e sll e \ rl d add a,a \ adc hl,hl add a,a \ adc hl,hl sbc hl,de jr nc,+_ add hl,de dec e .db $FE ;start of `cp *`_: inc e;Now we have four more iterations;The first two are no problem ld a,ixl sll e \ rl d add a,a \ adc hl,hl add a,a \ adc hl,hl sbc hl,de jr nc,+_ add hl,de dec e .db $FE ;start of `cp *`_: inc e sll e \ rl d add a,a \ adc hl,hl add a,a \ adc hl,hl sbc hl,de jr nc,+_ add hl,de dec e .db $FE ;start of `cp *`_: inc esqrt32_iter15:;On the next iteration, HL might temporarily overflow by 1 bit sll e \ rl d ;sla e \ rl d \ inc e add a,a adc hl,hl add a,a adc hl,hl ;This might overflow! jr c,sqrt32_iter15_br0; sbc hl,de jr nc,+_ add hl,de dec e jr sqrt32_iter16sqrt32_iter15_br0: or a sbc hl,de_: inc e;On the next iteration, HL is allowed to overflow, DE could overflow with our current routine, but it needs to be shifted right at the end, anywayssqrt32_iter16: add a,a ld b,a ;either 0x00 or 0x80 adc hl,hl rla adc hl,hl rla;AHL - (DE+DE+1) sbc hl,de \ sbc a,b inc e or a sbc hl,de \ sbc a,b ret p add hl,de adc a,b dec e add hl,de adc a,b ret
;written by ZedasqrtHL:;returns A as the sqrt, HL as the remainder, D = 0;min: 352cc;max: 391cc;avg: 371.5cc ld de,05040h ; 10 ld a,h ; 4 sub e ; 4 jr nc,sq7 ;\ add a,e ; | branch 1: 12cc ld d,16 ; | branch 2: 18ccsq7: ;/; ---------- cp d ; 4 jr c,sq6 ;\ sub d ; | branch 1: 12cc set 5,d ; | branch 2: 19ccsq6: ;/; ---------- res 4,d ; 8 srl d ; 8 set 2,d ; 8 cp d ; 4 jr c,sq5 ;\ sub d ; | branch 1: 12cc set 3,d ; | branch 2: 19ccsq5: ;/ srl d ; 8; ---------- inc a ; 4 sub d ; 4 jr nc,sq4 ;\ dec d ; | branch 1: 12cc add a,d ; | branch 2: 19cc dec d ; | <-- this resets the low bit of D, so `srl d` resets carry.sq4: ;/ srl d ; 8 ld h,a ; 4; ---------- ld a,e ; 4 sbc hl,de ; 15 jr nc,sq3 ;\ add hl,de ; | 12cc or 18ccsq3: ;/ ccf ; 4 rra ; 4 srl d ; 8 rra ; 4; ---------- ld e,a ; 4 sbc hl,de ; 15 jr c,sq2 ;\ or 20h ; | branch 1: 23cc db 254 ; | <-- start of `cp *` which is 7cc to skip the next byte.sq2: ; | branch 2: 21cc add hl,de ;/ xor 18h ; 7 srl d ; 8 rra ; 4; ---------- ld e,a ; 4 sbc hl,de ; 15 jr c,sq1 ;\ or 8 ; | branch 1: 23cc db 254 ; | <-- start of `cp *` which is 7cc to skip the next byte.sq1: ; | branch 2: 21cc add hl,de ;/ xor 6 ; 7 srl d ; 8 rra ; 4; ---------- ld e,a ; 4 sbc hl,de ; 15 jr nc,+_ ; \ add hl,de ; 15 | srl d ; 8 | rra ; 4 | branch 1: 38cc ret ; 10 | branch 2: 40cc_: ; | inc a ; 4 | srl d ; 8 | rra ; 4 | ret ; 10 /
;Converts an 8-bit signed integer to a stringitoa_8:;Input:; A is a signed integer; HL points to where the null-terminated ASCII string is stored (needs at most 5 bytes);Output:; The number is converted to a null-terminated string at HL;Destroys:; Up to five bytes at HL; All registers preserved.;on 0 to 9: 252 D=0;on 10 to 99: 258+20D D=0 to 9;on 100 to 127: 277+20D D=0 to 2;on -1 to -9: 276 D=0;on -10 to -99: 282+20D D=0 to 9;on -100 to -128: 301+20D D=0 to 2;min: 252cc (+23cc over original);max: 462cc (-49cc over original);avg: 343.74609375cc = 87999/256;54 bytes push hl push de push bc push af or a jp p,itoa_pos neg ld (hl),$1A ;start if neg char on TI-OS inc hlitoa_pos:;A is on [0,128];calculate 100s place, plus 1 for a future calculation ld b,'0' cp 100 \ jr c,$+5 \ sub 100 \ inc b;calculate 10s place digit, +1 for future calculation ld de,$0A2F inc e \ sub d \ jr nc,$-2 ld c,a;Digits are now in D, C, A; strip leading zeros! ld a,'0' cp b \ jr z,$+5 \ ld (hl),b \ inc hl \ .db $FE ; start of `cp *` to skip the next byte, turns into `cp $BB` which will always return nz and nc cp e \ jr z,$+4 \ ld (hl),e \ inc hl add a,c add a,d ld (hl),a inc hl ld (hl),0 pop af pop bc pop de pop hl ret
;This converts a fixed-point number to a string.;It displays up to 3 digits after the decimal.fixed88_to_str:;Inputs:; D.E is the fixed-point number; HL points to where the string gets output.; Needs at most 9 bytes.;Outputs:; HL is preserved;Destroys:; AF,DE,BC;First check if the input is negative.;If so, write a negative sign and negate push hl ld a,d or a jp p,+_ ld (hl),$1A ;negative sign on TI-OS inc hl xor a sub e ld e,a sbc a,a sub d_:;Our adjusted number is in A.E;Now we can print the integer part call itoa_8;Check if we need to print the fractional part xor a cp e jr z,fixed88_to_str_end;We need to write the fractional part, so seek the end of the string;Search for the null byte. A is already 0 cpir;Write a decimal dec hl ld (hl),'.' ld b,3_:;Multiply E by 10, converting overflow to an ASCII digit call fixed88_to_str_e_times_10 inc hl ld (hl),a djnz -_;Strip the ending zeros ld a,'0'_: cp (hl) dec hl jr z,-_;write a null byte inc hl inc hl ld (hl),0fixed88_to_str_end:;restore HL pop hl retfixed88_to_str_e_times_10: ld a,e ld d,0 add a,a \ rl d add a,a \ rl d add a,e \ jr nc,$+3 \ inc d add a,a ld e,a ld a,d rla add a,'0' ret
sqrtA:;Input: A;Output: D is the square root, A is the remainder (input-D^2);Destroys: BC;speed: 161+{0,6}+{0,1}+{0,1}+{0,3};min: 161cc;max: 172cc;avg: 166.5cc;45 bytes ld d,$40 sub d jr nc,+_ add a,d ld d,0_: set 4,d sub d jr nc,+_ add a,d .db $01 ;start of ld bc,** which is 10cc to skip the next two bytes._: set 5,d res 4,d srl d set 2,d sub d jr nc,+_ add a,d .db $01 ;start of ld bc,** which is 10cc to skip the next two bytes._: set 3,d res 2,d srl d inc d sub d jr nc,+_ add a,d dec d_: inc d srl d ret
sqrtfixed_88:;Input: A.E ==> D.E;Output: DE is the sqrt, AHL is the remainder;Speed: 690+6{0,13}+{0,3+{0,18}}+{0,38}+sqrtA;min: 855cc;max: 1003cc;avg: 924.5cc;152 bytes call sqrtA ld l,a ld a,e ld h,0 ld e,d ld d,h sla e rl d sll e \ rl d add a,a \ adc hl,hl add a,a \ adc hl,hl sbc hl,de jr nc,+_ add hl,de dec e .db $FE ;start of `cp *`_: inc e sll e \ rl d add a,a \ adc hl,hl add a,a \ adc hl,hl sbc hl,de jr nc,+_ add hl,de dec e .db $FE ;start of `cp *`_: inc e sll e \ rl d add a,a \ adc hl,hl add a,a \ adc hl,hl sbc hl,de jr nc,+_ add hl,de dec e .db $FE ;start of `cp *`_: inc e sll e \ rl d add a,a \ adc hl,hl add a,a \ adc hl,hl sbc hl,de jr nc,+_ add hl,de dec e .db $FE ;start of `cp *`_: inc e;Now we have four more iterations;The first two are no problem sll e \ rl d add hl,hl add hl,hl sbc hl,de jr nc,+_ add hl,de dec e .db $FE ;start of `cp *`_: inc e sll e \ rl d add hl,hl add hl,hl sbc hl,de jr nc,+_ add hl,de dec e .db $FE ;start of `cp *`_: inc esqrtfixed_88_iter11:;On the next iteration, HL might temporarily overflow by 1 bit sll e \ rl d ;sla e \ rl d \ inc e add hl,hl add hl,hl jr c,sqrtfixed_88_iter11_br0; sbc hl,de jr nc,+_ add hl,de dec e jr sqrtfixed_88_iter12sqrtfixed_88_iter11_br0: or a sbc hl,de_: inc e;On the next iteration, HL is allowed to overflow, DE could overflow with our current routine, but it needs to be shifted right at the end, anywayssqrtfixed_88_iter12: ld b,a ;A is 0, so B is 0 add hl,hl add hl,hl rla;AHL - (DE+DE+1) sbc hl,de \ sbc a,b inc e or a sbc hl,de \ sbc a,b ret p add hl,de adc a,b dec e add hl,de adc a,b ret
; Requires; mul16 ;BC*DE ==> DEHL; DEHL_Div_BC ;DEHL/BC ==> DEHLncr_HL_DE:;"n choose r", defined as n!/(r!(n-r)!);Computes "HL choose DE";Inputs: HL,DE;Outputs:; HL is the result; "HL choose DE"; carry flag reset means overflow;Destroys:; A,BC,DE,IX;Notes:; Overflow is returned as 0; Overflow happens if HL choose DE exceeds 65535; This algorithm is constructed in such a way that intermediate; operations won't erroneously trigger overflow.;66 bytes ld bc,1 or a sbc hl,de jr c,ncr_oob jr z,ncr_exit sbc hl,de add hl,de jr c,$+3 ex de,hl ld a,h or l push hl pop ixncr_exit: ld h,b ld l,c scf ret zncr_loop: push bc \ push de push hl \ push bc ld b,h ld c,l call mul16 ;BC*DE ==> DEHL pop bc call DEHL_Div_BC ;result in DEHL ld a,d or e pop bc pop de jr nz,ncr_overflow add hl,bc jr c,ncr_overflow pop bc inc bc ld a,b cp ixh jr c,ncr_loop ld a,ixl cp c jr nc,ncr_loop retncr_overflow: pop bc xor a ld b,ancr_oob: ld h,b ld l,b ret
;Converts an 8-bit unsigned integer to a stringuitoa_8:;Input:; A is a signed integer; HL points to where the null-terminated ASCII string is stored (needs at most 5 bytes);Output:; The number is converted to a null-terminated string at HL;Destroys:; Up to four bytes at HL; All registers preserved.;on 0 to 9: 238 D=0;on 10 to 99: 244+20D D=0 to 9;on 100 to 255: 257+2{0,6}+20D D=0 to 5;min: 238cc;max: 424cc;avg: 317.453125cc = 81268/256 = (238*10 + 334*90+313*156)/256;52 bytes push hl push de push bc push af;A is on [0,255];calculate 100s place, plus 1 for a future calculation ld b,'0' cp 100 \ jr c,$+5 \ sub 100 \ inc b cp 100 \ jr c,$+5 \ sub 100 \ inc b;calculate 10s place digit, +1 for future calculation ld de,$0A2F inc e \ sub d \ jr nc,$-2 ld c,a;Digits are now in D, C, A; strip leading zeros! ld a,'0' cp b \ jr z,$+5 \ ld (hl),b \ inc hl \ .db $FE ; start of `cp *` to skip the next byte, turns into `cp $BB` which will always return nz and nc cp e \ jr z,$+4 \ ld (hl),e \ inc hl add a,c add a,d ld (hl),a inc hl ld (hl),0 pop af pop bc pop de pop hl ret
;Converts a 16-bit signed integer to an ASCII string.itoa_16:;Input:; DE is the number to convert; HL points to where to write the ASCII string (up to 7 bytes needed).;Output:; HL points to the null-terminated ASCII string; NOTE: This isn't necessarily the same as the input HL. push de push bc push af push hl bit 7,d jr z,+_ xor a sub e ld e,a sbc a,a sub d ld d,a ld (hl),$1A ;negative char on TI-OS inc hl_: ex de,hl ld bc,-10000 ld a,'0'-1 inc a \ add hl,bc \ jr c,$-2 ld (de),a inc de ld bc,1000 ld a,'9'+1 dec a \ add hl,bc \ jr nc,$-2 ld (de),a inc de ld bc,-100 ld a,'0'-1 inc a \ add hl,bc \ jr c,$-2 ld (de),a inc de ld a,l ld h,'9'+1 dec h \ add a,10 \ jr nc,$-3 add a,'0' ex de,hl ld (hl),d inc hl ld (hl),a inc hl ld (hl),0;No strip the leading zeros pop hl;If the first char is a negative sign, skip it ld a,(hl) cp $1A push af ld a,'0' jr nz,$+3 inc hl cp (hl) jr z,$-2;Check if we need to re-write the negative sign pop af jr nz,+_ dec hl ld (hl),a_: pop af pop bc pop de ret
;Converts a 16-bit unsigned integer to an ASCII string.uitoa_16:;Input:; DE is the number to convert; HL points to where to write the ASCII string (up to 6 bytes needed).;Output:; HL points to the null-terminated ASCII string; NOTE: This isn't necessarily the same as the input HL. push de push bc push af ex de,hl ld bc,-10000 ld a,'0'-1 inc a \ add hl,bc \ jr c,$-2 ld (de),a inc de ld bc,1000 ld a,'9'+1 dec a \ add hl,bc \ jr nc,$-2 ld (de),a inc de ld bc,-100 ld a,'0'-1 inc a \ add hl,bc \ jr c,$-2 ld (de),a inc de ld a,l ld h,'9'+1 dec h \ add a,10 \ jr nc,$-3 add a,'0' ex de,hl ld (hl),d inc hl ld (hl),a inc hl ld (hl),0;No strip the leading zeros ld c,-6 add hl,bc ld a,'0' inc hl \ cp (hl) \ jr z,$-2 pop af pop bc pop de ret
;Masked Sprite routineputsprite_masked:;Inputs:; (A,L) = (x,y); B is height; IX points to the sprite data; first byte is the data; second byte is mask; continues, alternating like this.;;Outputs:; Mask is ANDed to the buffer, then data is ORed on top of that.;;Destroys:; AF, BC, DE, HL, IX;;Notes:; To set a pixel...; black: mask is any, data is 1; white: mask is 0, data is 0; clear: mask is 1, data is 0 (keeps the data from the buffer);;This routine is free to use :);65 bytes (or 66 bytes if gbuf is not located at 0x**40 ld e,l ld h,0 ld d,h add hl,hl add hl,de add hl,hl add hl,hl ld e,a and 7 ld c,a xor e ;essentially gets E with the bottom 3 bits reset#if (plotSScreen&255) = 64 inc a rra rra rra ld e,a ld d,plotSScreen>>8#else rra rra rra ld e,a add hl,de ld de,plotSScreen#endif add hl,deputsprite_masked_loop: push bc xor a ld d,(ix) ld e,a sub c ld b,c ld c,$FF inc ix ld a,(ix) jr z,putsprite_masked_rotdoneputsprite_masked_rot: scf rra rr c srl d rr e djnz putsprite_masked_rotputsprite_masked_rotdone: and (hl) or d ld (hl),a inc hl ld a,(hl) and c or e ld (hl),a ld c,11 add hl,bc inc ix pop bc djnz putsprite_masked_loop ret
;Masked Sprite routineputsprite_masked:;Inputs:; (A,L) = (x,y); B is height; IX points to the sprite data; first byte is the data; second byte is mask; continues, alternating like this.;;Outputs:; Mask is ORed to the buffer, then data is XORed on top of that.;;Destroys:; AF, BC, DE, HL, IX;;Notes:; To set a pixel...; black: mask is 1, data is 0; white: mask is 1, data is 1; clear: mask is 0, data is 0 (keeps the data from the buffer); invert: mask is 0, data is 1 (inverts the data from the buffer);;This routine is free to use :);63 bytes (or 64 bytes if gbuf is not located at 0x**40 ld e,l ld h,0 ld d,h add hl,hl add hl,de add hl,hl add hl,hl ld e,a and 7 ld c,a xor e ;essentially gets E with the bottom 3 bits reset#if (plotSScreen&255) = 64 inc a rra rra rra ld e,a ld d,plotSScreen>>8#else rra rra rra ld e,a add hl,de ld de,plotSScreen#endif add hl,deputsprite_masked_loop: push bc xor a ld d,(ix) ld e,a or c ld b,c ld c,e inc ix ld a,(ix) jr z,putsprite_masked_rotdoneputsprite_masked_rot: rra rr c srl d rr e djnz putsprite_masked_rotputsprite_masked_rotdone: or (hl) xor d ld (hl),a inc hl ld a,(hl) or c xor e ld (hl),a ld c,11 add hl,bc inc ix pop bc djnz putsprite_masked_loop ret
;133 bytes total;This is made by Zeda, feel free to use it for whatever.;Takes inputs for a big sprite and sets up masks and clipping;requires 4 bytes of temporary RAM, but doesn't use SMCspritetmp = 8000h ;relocate this as needed! Just need 4 bytes.sprite_width = spritetmp+0sprite_x = spritetmp+1sprite_mask0 = spritetmp+2sprite_mask1 = spritetmp+3bigsprite_subroutine:;Inputs:; B is the X-coordinate; C is the Y-Coordinate; DE points to the sprite; H is the height; L is the width in bytes;Outputs:; carry flag is set if okay to draw, nc if out-of-bounds.; B is height.; C is width.; HL points to the byte to start drawing at.; DE points to where to start sourcing the sprite data; (sprite_width) is the width of the sprite in bytes; (sprite_x) is the intitial x coordinate to begin drawing at; (sprite_mask0) is the left mask; (sprite_mask1) is the right mask;92 bytes;First check if the sprite is on-screen in the horizontal direction ld a,c cp 64 jr c,+_ add a,h ret nc ld h,a push hl xor a ld h,a sub c ex de,hl add hl,de dec a jr nz,$-2 ex de,hl pop hl xor a ld c,a_:;Next check h+c<=64 ld a,64 sub c cp h jr nc,+_ ld h,a_:;Make sure the height is not now 0 ld a,h or a ret z;Save the width and height of the sprite push hl ;height,width ld h,b ld (sprite_width),hl ;x,width push de ;sprite pointer;Set up a pointer to the routine for shifting the routine for shifting the sprite data ld ixh,rshiftHA_7>>8 ld a,h cpl and 7 ld l,a add a,a add a,l add a,rshiftHA_7&255 ld ixl,a#if (rshiftHA_7&255)>234 jr nc,$+4 inc ixh#endif ld a,b and 7 ld de,spritemask add a,e ld e,a#if spritemask&255>248 jr nc,$+3 inc d#endif ld a,(de) ld (sprite_mask0),a cpl ld (sprite_mask1),a;; ld a,c add a,a sbc a,a ld h,a ld a,b ld b,h ld l,c add hl,hl add hl,bc add hl,hl add hl,hl ld c,a add a,a sbc a,a ld b,a ld a,c sra c sra c sra c add hl,bc ld bc,plotSScreen add hl,bc pop de pop bc ;B is height ;C is width ex de,hl scf retrshiftHA_7: rr h \ rra rr h \ rra rr h \ rra rr h \ rra rr h \ rra rr h \ rra rr h \ rra ex de,hl ld e,a retspritemask: .db $00,$80,$C0,$E0,$F0,$F8,$FC,$FEcall_ix: jp (ix)
bigsprite_OR:;Inputs:; B is the X-coordinate; C is the Y-Coordinate; DE points to the sprite; H is the height; L is the width in bytes;68 bytes;Set up the clipping call bigsprite_subroutine ret ncbigsprite_OR_loop: push bc ;height,width push de ;gbuf ptr push hl ;sprite data pointer ld a,(sprite_x) ld c,a add a,8 ld (sprite_x),aspriteloop_OR: push bc push hl ld h,(hl) xor a call call_ix ld a,c cp 96 jr nc,+_ ld a,(hl) or d ld (hl),a ld a,c_: inc hl add a,8 cp 96 jr nc,+_ ld a,(sprite_mask1) ld a,(hl) or e ld (hl),a_: ld bc,11 add hl,bc ex de,hl pop hl ld a,(sprite_width) ld c,a add hl,bc pop bc djnz spriteloop_OR pop hl inc hl pop de inc de pop bc dec c jr nz,bigsprite_OR_loop ret
bigsprite_XOR:;Inputs:; B is the X-coordinate; C is the Y-Coordinate; DE points to the sprite; H is the height; L is the width in bytes;68 bytes;Set up the clipping call bigsprite_subroutine ret ncbigsprite_XOR_loop: push bc ;height,width push de ;gbuf ptr push hl ;sprite data pointer ld a,(sprite_x) ld c,a add a,8 ld (sprite_x),aspriteloop_XOR: push bc push hl ld h,(hl) xor a call call_ix ld a,c cp 96 jr nc,+_ ld a,(hl) xor d ld (hl),a ld a,c_: inc hl add a,8 cp 96 jr nc,+_ ld a,(sprite_mask1) ld a,(hl) xor e ld (hl),a_: ld bc,11 add hl,bc ex de,hl pop hl ld a,(sprite_width) ld c,a add hl,bc pop bc djnz spriteloop_XOR pop hl inc hl pop de inc de pop bc dec c jr nz,bigsprite_XOR_loop ret
bigsprite_AND:;Inputs:; B is the X-coordinate; C is the Y-Coordinate; DE points to the sprite; H is the height; L is the width in bytes;69 bytes;Set up the clipping call bigsprite_subroutine ret ncbigsprite_AND_loop: push bc ;height,width push de ;gbuf ptr push hl ;sprite data pointer ld a,(sprite_x) ld c,a add a,8 ld (sprite_x),aspriteloop_AND: push bc push hl ld h,(hl) scf \ sbc a,a call call_ix ld a,c cp 96 jr nc,+_ ld a,(hl) and d ld (hl),a ld a,c_: inc hl add a,8 cp 96 jr nc,+_ ld a,(sprite_mask1) ld a,(hl) and e ld (hl),a_: ld bc,11 add hl,bc ex de,hl pop hl ld a,(sprite_width) ld c,a add hl,bc pop bc djnz spriteloop_AND pop hl inc hl pop de inc de pop bc dec c jr nz,bigsprite_AND_loop ret
bigsprite_Erase:;Inputs:; B is the X-coordinate; C is the Y-Coordinate; DE points to the sprite; H is the height; L is the width in bytes;67 bytes;Set up the clipping call bigsprite_subroutine ret ncbigsprite_Erase_loop: push bc ;height,width push de ;gbuf ptr push hl ;sprite data pointer ld a,(sprite_x) ld c,a add a,8 ld (sprite_x),aspriteloop_Erase: push bc push hl ld h,(hl) xor a call call_ix ld a,c cp 96 jr nc,+_ ld a,d cpl and (hl) ld (hl),a ld a,c_: inc hl add a,8 cp 96 jr nc,+_ ld a,e cpl and (hl) ld (hl),a_: ld bc,11 add hl,bc ex de,hl pop hl ld a,(sprite_width) ld c,a add hl,bc pop bc djnz spriteloop_Erase pop hl inc hl pop de inc de pop bc dec c jr nz,bigsprite_Erase_loop ret
bigsprite_Overwrite:;Inputs:; B is the X-coordinate; C is the Y-Coordinate; DE points to the sprite; H is the height; L is the width in bytes;71 bytes;Set up the clipping call bigsprite_subroutine ret ncbigsprite_Overwrite_loop: push bc ;height,width push de ;gbuf ptr push hl ;sprite data pointer ld a,(sprite_x) ld c,a add a,8 ld (sprite_x),aspriteloop_Overwrite: push bc push hl ld h,(hl) xor a call call_ix ld a,c cp 96 jr nc,+_ ld a,(sprite_mask0) and (hl) or d ld (hl),a ld a,c_: inc hl add a,8 cp 96 jr nc,+_ ld a,(sprite_mask1) and (hl) or e ld (hl),a_: ld bc,11 add hl,bc ex de,hl pop hl ld a,(sprite_width) ld c,a add hl,bc pop bc djnz spriteloop_Overwrite pop hl inc hl pop de inc de pop bc dec c jr nz,bigsprite_Overwrite_loop ret
@Zeda: Nice performance aware exercise! (Except for the many push and pop which look a bit dated to me).I wonder how many are really interested in speeding up the calculations these days.It seems all they care about is python, java and what-have-you-funky-high-level-language .
;Written by Zeda Thomas, free to use.;This draws a circle centered at 8-bit coordinates and with radius up to 127.;IX points to a `plot` routine that takes (B,C)=(x,y) as input and does something;with it, like plot the pixel a certain color, or plot a "big" pixel, or whatever.; plot; Takes coordinates, (B,C) = (x,y) and plots the point.;;For example, on the TI-83+/84+/SE the plot routine might look like:; plot:; call getpixelloc; ret nc ;Exit if the coordinates are out-of-bounds; or (hl); ld (hl),a; ret;;; Required subroutines:; call_ix:; jp (ix)circle:;Input:; (B,C) is the center (x,y); D is the radius, unsigned, less than 128 (0 or greater than 128 just quits).; IX points to a `plot` routine that takes (B,C)=(x,y) as input. ld a,d add a,a ret c ret z ld l,d dec a ld e,a dec a ;if the pixel is only 1 wide, just plot the point jp z,call_ix ;Jump to the plot routine xor a ld h,-1 ld d,1 scf ;skip the first plotcircleloop: call nc,plot4 inc h sub d inc d inc d jr nc,circleloop_: dec l call plot4 add a,e dec e ret z dec e jr nc,-_ jp circleloopplot4:;BC is center;HL is x,y push de push af push hl push bc;If H is 0, or L is 0, we need to draw only half push hl ld a,b sub h ld b,a add a,h add a,h ld h,a ld a,c sub l ld c,a add a,l add a,l ld l,a;B is x0-x;C is y0-y;H is x0+x;L is y0+y;plot(x0-x,y0-y);plot(x0+x,y0+y) push bc push hl call call_ix ;call the plot routine pop bc push bc call call_ix ;call the plot routine;now swap the y coords pop hl pop bc ld a,l ld l,c ld c,a pop de xor a cp d jr z,+_ cp e jr z,+_;plot(x0-x,y0+y);plot(x0+x,y0-y) push hl call call_ix ;call the plot routine pop bc call call_ix ;call the plot routine_: pop bc pop hl pop af pop de ret
;calling with `ld ix,pixelOn_2x2`pixelOn_2x2: sla b ret c sla c ret c push bc call pixelOn pop bc inc b push bc call pixelOn pop bc inc c push bc call pixelOn pop bc dec b jp pixelOn
;calling with `ld ix,pixelOn_circle`pixelOn_circle: ld a,b cp 32 ret nc add a,a add a,a ld b,a ld a,c cp 32 ret nc add a,a add a,a ld c,a ld d,4 push ix ;need to save IX! ld ix,pixelOn call circle pop ix ret
;Written by Zeda Thomas, free to use.;This draws the fill of a circle centered at 8-bit coordinates and with radius;up to 127.;IX points to a `horizontal line` routine that takes E=x, A=y, D=width as input;and does something with it, like plot a horizontal line.;; For example, on the ti-83+/84+/SE calculators, you might have:; horizontal_line:; ld b,e; ld c,a; ld e,1; ld hl,gbuf; jp rectOR; Required subroutines:; call_ix:; jp (ix)filledcircle:;Input:; (B,C) is the center (x,y); D is the radius, unsigned, less than 128 (0 or greater than 128 just quits).; IX points to a `plot` routine that takes (B,C)=(x,y) as input. ld a,d add a,a ret c ret z ld l,d dec a ld e,a xor a ld h,-1 ld d,1filledcircleloop: ; call c,fillcircle_plot inc h sub d inc d inc d jr nc,filledcircleloop_: dec l call fillcircle_plot add a,e dec e ret z dec e jr nc,-_ jp filledcircleloopfillcircle_plot: inc h dec h ret z push hl push de push bc push af dec h ld a,b sub h ld e,a ld d,h sll d ;aka `slia`, undocumented ld a,l or a ld h,c jr z,+_ add a,h push de push hl call nz,call_ix pop hl pop de_: ld a,h sub l call call_ix pop af pop bc pop de pop hl ret
;Requires `call_ix` routine that looks like:; call_ix:; jp (ix);;IX points to a comparison routine that takes as input:; HL points to the input element to find; DE is the element to compare to;Outputs are:; carry set if the HL element is less than the DE element; carry reset if the HL element is greater than or equal to the DE element; z set if the HL element is equal to the DE element; nz set if the HL element is not equal to the DE element;;This is useful if you have a table of pointers to strings, and want to find a;string in the array. See the end of this file for an example.;binarysearch:;This is a general-purpose binary search routine.;;Inputs:; BC is the element to find; HL is the number of elements; IX points to a callback routine that compares the input element;Outputs:; DE is the matching element index; z means match found; nz means no match; In this case, DE is interpreted as where the match should have been;Destroys:; AF, DE;RAM needed:; 10 bytes of stack space (4 pushes and a call); ld de,-1binarysearch_loop_inc_lower: inc debinarysearch_loop: push hl push de or a sbc hl,de jr z,binarysearch_nomatch rr h rr l add hl,de ld d,h ld e,l push hl ;test index push bc ;input ld h,b ld l,c call call_ix pop bc ;input jr nc,binarysearch_input_bigger_or_equal pop hl ;test index is the new upper index pop de ;restore the lower index pop af ;dummy pop jr binarysearch_loopbinarysearch_input_bigger_or_equal: pop de ;test index +1 is the new lower index pop hl ;dummy pop pop hl ;restore upper index jr nz,binarysearch_loop_inc_lower ;a match was found ;DE is left as the index retbinarysearch_nomatch: pop de ;lower index pop hl ;upper index (also lower index and test index) or 1 ret
; This routine requires the following subroutine:; call_ix:; jp (ix);; To use SMC, define SMC.; #define SMC;; If you are not using SMC, you'll need to define `arraylen` to point;to 2 bytes of scrap RAMheapsort:;Inputs:; BC is the size of the array.; IX points to the routine that compares or swpas two entries; HL is the index of the first element; DE is the index of the second element; c means swap; nc means compare HL to DE; Should return:; z if they are equal; nc if HL>=DE; c if HL<DE;Outputs:; The data is sorted.;Destroys:; All;Notes:; You can make the comparison routine work any way that you want :); For example, you can invert the carry flag output to sort descending.;If the array is size 0 or 1, then it is sorted inc b dec b jr nz,heapsort_heapify dec c ret z inc c ret zheapsort_heapify: call heapify ld hl,(arraylen)heapsort_loop: dec hl ld (arraylen),hl push hl;HL is the last element ld de,0 call heapsort_swap ld bc,1 call propogate pop hl ld a,h or l jr nz,heapsort_loop retheapify:;Inputs:; HL points to the array data; BC is the size of the array. NOT GREATER THAN 32767; IX points to the routine that compares the values ld (arraylen),bc srl b rr c_: push bc call propogate pop bc dec bc ld a,b or c jr nz,-_ retpropogate:;BC-1 is the parent index;2BC-1 is the child0 index;2BC is the child1 index sla c rl b ld d,b ld e,c#ifdef SMCarraylen=$+1 ld hl,0#else ld hl,(arraylen)#endif sbc hl,de add hl,de ret c ;no children;z means one child;compare the two children ld h,b ld l,c dec hl;HL is the child0 index;DE is the child1 index call nz,heapsort_cmp jr nc,+_ ex de,hl_:;parent is (HL+1)>>1;child is HL ld d,h ld e,l inc hl srl h rr l dec hl call heapsort_cmp ret nc call heapsort_swap;values heapsort_swapped, now set parent=child+1 ld b,d ld c,e inc bc jr propogateheapsort_swap:;HL and DE are the indices of the elements to heapsort_swap push hl push de scf call call_ix pop de pop hl retheapsort_cmp: push hl push de or a call call_ix pop de pop hl ret
;HL must be non-zero add hl,hl sbc a,a and %00101101 xor l ld l,a ld a,r add a,a ;Because R is a 7-bit register add a,h;HL is the new seed;A is the output, or AL for 16 bits.
;HL must be non-zero add hl,hl sbc a,a and %10000111 xor l ld l,a ld a,r add a,a ;Because R is a 7-bit register add a,h;HL is the new seed;A is the output, or AL for 16 bits.
;E must be non-zero;10 bytes, 39cc;min period: 255;max period: 32640;avg period: 21760 sla e sbc a,a and %01011111 xor e ld e,a ld a,r add a,e;E is the new seed, non-zero so long as the input was non-zero;A is the output
mul_hl_1337: ; size optimized;17 bytes, 173cc ld b,h ld c,l add hl,hl add hl,hl add hl,bc add hl,hl add hl,hl add hl,hl add hl,bc add hl,hl add hl,bc add hl,hl add hl,bc add hl,hl add hl,hl add hl,hl add hl,bc
mul_hl_1337: ; speed optimized;25 bytes, 148cc ld b,h ld c,l add hl,hl add hl,bc add hl,hl add hl,bc ld b,h ld c,l add hl,hl add hl,bc ld a,h ld h,l rra rr h rra rr h rra and 11000000b ld l,a or a sbc hl,bc