Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Optimizing a bit-manipulating algorithm in GameBoy Z80

This is not a homework problem, it's for a game I'm developing.

I have two 16-bit RGB colors, and would like to vary their six channels according to six other four-bit quantities. The algorithm is simple but tedious; I'm looking for a way to optimize it by doing more useful work at once.

The high-level overview:

  • hl points to the four color bytes. [hl] = %gggrrrrr, [hl+1] = %0bbbbbgg, [hl+2] = %GGGRRRRR, and [hl+3] = %0BBBBBGG. (That's two colors, rgb and RGB.)
  • bc points to the three delta bytes. [bc] = %hhhhaaaa, [bc+1] = %ddddssss, and [bc+2] = %ppppqqqq. (That's six delta values, h, a, d, s, p, and q.)
  • So there are six 5-bit color channel values, and six 4-bit delta values. I want to pair each color channel C with a delta value D, and vary C like so: C' = C + (D & %11) − ((D & %1100) >> 2), but keeping C within its 5-bit bounds [0, 31]. I don't actually care how they're paired: any convenient one-to-one pairing is fine. And if C + ((D & %1100) >> 2) − (D & %11) allows a more elegant algorithm somehow, I'd be okay with that.

If I isolate a color channel C in register d and a delta value D in register e, then this routine will do the variation for that pair:

VaryColorChannelByDV:
; d = color, e = DV
; a <- d + (e & %11) - (e >> 2), clamped to [0, 31]
    ld a, e
    and %11   ; a <- (e & %11)
    add d   ; a <- d + (e & %11)
    srl e
    srl e   ; e <- e >> 2
    sub e   ; a <- d + (e & %11) - (e >> 2)
    jr c, .zero   ; a < 0, clamp to 0
    cp 32
    ret c   ; 0 <= a < 32
    ld a, 31   ; a >= 32, clamp to 31
    ret
.zero
    xor a
    ret

So far I have a generic routine that applies any DV to any color channel; then three routines that isolate the red, green, or blue channels and apply a given DV to them; and finally a main routine that picks out the six DVs and calls the appropriate channel-modifying routine with them. This is "good enough", but I'm certain there's room for improvement. Execution speed doesn't seem to be a problem, but I'd like to reduce the code size (and of course removing redundant instructions will also improve speed a bit). Are there any asm bit-manipulation tricks that would help?

Here's the full code:

GetColorChannelVariedByDV:
; d = color, e = DV
; a <- d + (e & %11) - (e & %1100 >> 2), clamped to [0, 31]
    ld a, e
    and %11
    add d
    srl e
    srl e
    sub e
    jr c, .zero
    cp 32
    ret c
    ld a, 31
    ret
.zero
    xor a
    ret

VaryRedByDV:
;;; e = DV
;;; [hl+0] = gggr:rrrr
;;; [hl+1] = 0bbb:bbgg
; store red in d
    ld a, [hl]
    and %00011111
    ld d, a
; vary d according to e
    call GetColorChannelVariedByDV
; store a back in red
    ld d, a
    ld a, [hl]
    and %11100000
    or d
    ld [hl], a
    ret

VaryGreenByDV:
;;; e = DV
;;; [hl+0] = gggr:rrrr
;;; [hl+1] = 0bbb:bbgg
; store green in d
    ld a, [hli]
    and %11100000
    srl a
    swap a
    ld d, a ; d = 00000ggg
    ld a, [hld]
    and %00000011
    swap a
    srl a
    or d
    ld d, a
; vary d according to e
    call GetColorChannelVariedByDV
; store a back in green
    sla a
    swap a
    ld d, a
    and %11100000
    ld e, a
    ld a, d
    and %00000011
    ld d, a
    ld a, [hl]
    and %00011111
    or e
    ld [hli], a
    ld a, [hl]
    and %11111100
    or d
    ld [hld], a
    ret

VaryBlueByDV:
;;; e = DV
;;; [hl+0] = gggr:rrrr
;;; [hl+1] = 0bbb:bbgg
; store blue in d
    inc hl
    ld a, [hl]
    and %01111100
    srl a
    srl a
    ld d, a
; vary d according to e
    call GetColorChannelVariedByDV
; store a back in blue
    ld d, a
    sla d
    sla d
    ld a, [hl]
    and %10000011
    or d
    ld [hl], a
    dec hl
    ret

VaryColorsByDVs::
; hl = colors
; [hl+0] = gggr:rrrr
; [hl+1] = 0bbb:bbgg
; [hl+2] = GGGR:RRRR
; [hl+3] = 0BBB:BBGG
; bc = DVs
; [bc+0] = hhhh:aaaa
; [bc+1] = dddd:ssss
; [bc+2] = pppp:qqqq

;;; LiteRed ~ hDV, aka, rrrrr ~ hhhh
; store hDV in e
    ld a, [bc]
    swap a
    and %1111
    ld e, a
; vary LiteRed by e
    call VaryRedByDV

;;; LiteGrn ~ aDV, aka, ggggg ~ aaaa
; store aDV in e
    ld a, [bc]
    and %1111
    ld e, a
; vary LiteGrn by e
    call VaryGreenByDV

;;; move from h/a DV to d/s DV
    inc bc

;;; LiteBlu ~ dDV, aka, bbbbb ~ dddd
; store dDV in e
    ld a, [bc]
    swap a
    and %1111
    ld e, a
; vary LiteBlu by e
    call VaryBlueByDV

;;; Move from Lite color to Dark color
    inc hl
    inc hl

;;; DarkRed ~ sDV, aka, RRRRR ~ ssss
; store sDV in e
    ld a, [bc]
    and %1111
    ld e, a
; vary DarkRed by e
    call VaryRedByDV

;;; move from d/s DV to p/q DV
    inc bc

;;; DarkGrn ~ pDV, aka, GGGGG ~ pppp
; store pDV in e
    ld a, [bc]
    swap a
    and %1111
    ld e, a
; vary DarkGrn by e
    call VaryGreenByDV

;;; DarkBlu ~ qDV, aka, BBBBB ~ qqqq
; store qDV in e
    ld a, [bc]
    and %1111
    ld e, a
; vary DarkBlu by e
    call VaryBlueByDV

    ret
like image 878
Remy Avatar asked May 15 '17 14:05

Remy


1 Answers

The smallest I can come up with right now is 57 bytes:

VaryColorsByDVs::
; hl = colors
; [hl+0] = gggr:rrrr
; [hl+1] = 0bbb:bbgg
; [hl+2] = GGGR:RRRR
; [hl+3] = 0BBB:BBGG
; bc = DVs
; [bc+0] = hhhh:aaaa
; [bc+1] = dddd:ssss
; [bc+2] = pppp:qqqq
    ld a, 2 ; -floor($100/3)*6 mod $100
.next:
    sla [hl]
    inc hl
    rl [hl]
.loop:
    push af
    rrca
    ld a, [bc]
    jr nc, .skip
    swap a
    inc bc
.skip:
    rlca
    ld d, a
    and %00011000
    ld e, a
    ld a, d
    rlca
    rlca
    and %00011000
    add a, [hl]
    jr nc, .noOverflow
    or %11111000
.noOverflow:
    sub e
    jr nc, .noUnderflow
    and %00000111
.noUnderflow:
    dec hl
    ld de, 5
.rotate:
    add a, a
    rl [hl]
    adc a, d
    dec e
    jr nz, .rotate
    inc hl
    ld [hl], a
    pop af
    add a, 85 ; floor($100/3)
    jr nc, .loop
    ret z
    inc hl
    jr .next

Fixing Ped7g's comment only costs 4 bytes for a total of 61 bytes:

VaryColorsByDVs::
; hl = colors
; [hl+0] = gggr:rrrr
; [hl+1] = 0bbb:bbgg
; [hl+2] = GGGR:RRRR
; [hl+3] = 0BBB:BBGG
; bc = DVs
; [bc+0] = hhhh:aaaa
; [bc+1] = dddd:ssss
; [bc+2] = pppp:qqqq
    ld a, 2 ; -floor($100/3)*6 mod $100
.next:
    sla [hl]
    inc hl
    rl [hl]
.loop:
    push af
    rrca
    ld a, [bc]
    jr nc, .skip
    swap a
    inc bc
.skip:
    ld d, a
    and %00001100
    ld e, a
    ld a, d
    rlca
    rlca
    and %00001100
    sub e
    add a, a
    jr nc, .positive
.negative:
    add a, [hl]
    jr c, .continue
    and %00000111
    db $38 ; jr c,
.positive:
    add a, [hl]
    jr nc, .continue
    or %11111000
.continue:
    dec hl
    ld de, 5
.rotate:
    add a, a
    rl [hl]
    adc a, d
    dec e
    jr nz, .rotate
    inc hl
    ld [hl], a
    pop af
    add a, 85 ; floor($100/3)
    jr nc, .loop
    ret z
    inc hl
    jr .next
like image 101
jacobly Avatar answered Oct 01 '22 19:10

jacobly