A86: Grayscale Sprites


[Prev][Next][Index][Thread]

A86: Grayscale Sprites




I'm working on an RPG for the Ti86.  It will feature grayscale sprites,
maps, and Joltima (FF) style fighting (insted of real-time).  I have a
moving engine done, maps done, sprites, and some other things.  I need help
on grayscaling a sprite though.  I have the routines to use a grayscale
sprite, but i doin't know how to use it.  I know i have to make (masked) one
sprite for dark blocks & one for light blocks, but how would it look in asm?
Here's the routines for sprite placement;

;=========================================================================
; Sprite routines by David Phillips <david@acz.org>    http://www.acz.org/
;=========================================================================
; All sprites are 8x8 masked sprites
;
;  PutSprite      -- black/white         (sprite, mask)
;  PutSpriteClip  -- black/white with clipping   (sprite, mask)
;  GraySprite     -- grayscale          (dark, light, mask)
;  GraySpriteClip -- grayscale with clipping   (dark, light, mask)
;
; in:   hl = pointer to sprite, bc = x,y location
; out:  af, bc, de, hl, ix = trash
; size: 250 bytes
;=========================================================================
VideoDraw = VirtScr     ; [1024] virtual screen or video ram
GrayDraw1 = GrayMem1    ; [1024] dark grayscale plane
GrayDraw2 = GrayMem2    ; [1024] light grayscale plane
;=========================================================================
; in: hl = 8x8 masked sprite, bc = x,y location
PutSpriteClip:
 ex de,hl       ; save pointer in de
 ld hl,PutSpriteE     ; need to call putsprite
 ld (ClipSpriteE),hl    ; modify call address
 jr ClipSprite      ; jump to clipsprite

; in: hl = 8x8 masked grayscale sprite, bc = x,y location
GraySpriteClip:
 ex de,hl       ; save pointer in de
 ld hl,GraySpriteE     ; need to call graysprite
 ld (ClipSpriteE),hl    ; modify call address

; in: de = sprite pointer, bc = x,y location
ClipSprite:
 ld a,b        ; get x coord
 cp 249        ; hanging off left edge?
 jr nc,ClipSpriteL     ; then clip left edge
 cp 128        ; completely off right edge?
 ret nc        ; then don't draw it
 jr ClipSpriteR      ; clip right edge
ClipSpriteL:
 res 7,b       ; draw on right edge
 dec c        ; move up a row (left clipping)
 bit 7,c       ; are we on the top edge?
 jr z,ClipSpriteA     ; if not, skip top fix
 ld hl,RenderSpriteCV    ; point to rows to draw
 inc (hl)       ; increase it (decreased later)
 dec de        ; decrease sprite pointer
 ld hl,-16       ; need to draw up a row
 ld (ClipSpriteX),hl    ; modify top row fix value
ClipSpriteA:
 ld hl,$0218      ; change instruction to <jr 2>
 ld (RenderSpriteCL),hl    ; modify to skip drawing left byte
 jr ClipSpriteH      ; done clipping horizontal
ClipSpriteR:
 cp 120        ; hanging off right edge?
 jr c,ClipSpriteH     ; if not, don't clip
 ld hl,$0218      ; change instruction to <jr 2>
 ld (RenderSpriteCR),hl    ; modify to skip drawing right byte
ClipSpriteH:
 ld a,c        ; get y coord
 cp 249        ; hanging off top?
 jr nc,ClipSpriteT     ; then clip the top
 cp 64        ; completely off the bottom?
 jr nc,ClipSpriteF     ; then don't draw, but fix everything
 jr ClipSpriteB      ; clip the bottom
ClipSpriteT:
 xor a        ; clear for subtract
 ld h,a        ; clear high byte
 sub c        ; calc bytes above screen
 ld c,h        ; set y coord to 0
 ld l,a        ; set low byte to bytes above screen
 add hl,de       ; advance sprite pointer
 ex de,hl       ; swap back into de
 jr ClipSpriteV      ; finish vertical clipping
ClipSpriteB:
 sub 57        ; calc bytes below screen
 jr c,ClipSpriteD     ; don't clip if not below screen
 inc a        ; increase bytes below screen
ClipSpriteV:
 neg        ; negate so it can be subtracted
ClipSpriteZ =$+1
 ld hl,RenderSpriteCV    ; point to rows to draw
 add a,(hl)       ; add (subtract) from current value
 ld (hl),a       ; save new value
ClipSpriteD:
 push de       ; push sprite pointer
 pop ix        ; pop sprite pointer in ix
 call FindAddress     ; calc address and offset of sprite
ClipSpriteX =$+1
 ld de,0       ; load address fix for top row
 add hl,de       ; add the fix value
ClipSpriteE =$+1
 call $ffff       ; call the correct sprite routine
ClipSpriteF:
 ld a,8        ; normally 8 rows are drawn
 ld (RenderSpriteCV),a    ; set rows to draw back
 ld hl,$a678      ; normal opcode is <ld a,b \ and (hl)>
 ld (RenderSpriteCL),hl    ; set instructions back
 inc l        ; change <ld a,b> to <ld a,c>
 ld (RenderSpriteCR),hl    ; set instructions back
 ld hl,0       ; normally top row fix is 0
 ld (ClipSpriteX),hl    ; set rox fix back
 ret        ; return from clipping

; in: hl = 8x8 masked sprite, bc = x,y location
PutSprite:
 push hl       ; push sprite pointer
 pop ix        ; pop in ix
 call FindAddress     ; calc address and offset
PutSpriteE:
 ld de,VideoDraw     ; draw sprite to video memory
 add hl,de       ; add offset to buffer start
 jr RenderSprite     ; actually draw the sprite

; in: hl = 8x8 masked grayscale sprite, bc = x,y location
GraySprite:
 push hl       ; push sprite pointer
 pop ix        ; pop in ix
 call FindAddress     ; calc address and offset
GraySpriteE:
 push hl       ; save address offset
 push ix       ; save sprite pointer
 ld de,GrayDraw1     ; draw to first gray buffer
 add hl,de       ; add offset to buffer start
 ld a,16       ; grayscale sprites are 16 bytes
 ld (RenderSpriteM),a    ; adjust sprite load instruction
 call RenderSprite     ; draw the sprite
 ld a,8        ; second sprite is 8 bytes from mask
 ld (RenderSpriteM),a    ; adjust sprite load instruction back
 pop ix        ; restore sprite pointer
 pop hl        ; restore address offset
 ld de,GrayDraw2     ; now draw to second gray buffer
 add hl,de       ; add offset to second buffer start
 ld de,$0008      ; sprites are 8 bytes
 add ix,de       ; advance sprite pointer

; in: hl = address in buffer, c = offset, ix = sprite
RenderSprite:
RenderSpriteCV =$+1
 ld b,8        ; set row counter to 8 bytes
RenderSpriteL:
 push bc       ; save row counter and sprite offset
 ld a,(ix+8)      ; load mask for this row
RenderSpriteM =$-1
 cpl        ; invert the mask
 ld b,a        ; save inverted mask
 ld d,(ix)       ; load sprite byte for this row
 inc ix        ; advance sprite pointer
 ld a,c        ; set shift counter to sprite offset
 ld c,$ff       ; set all bits of right mask byte
 ld e,0        ; clear right byte of sprite
 or a        ; is the sprite aligned?
 jr z,RenderSpriteD     ; then skip shifting it
RenderSpriteS:
 srl d        ; shift left sprite byte
 rr e        ; into the right sprite byte
 scf        ; set carry
 rr b         ; shift left mask byte
 rr c        ; into the right mask byte
 dec a        ; decrease shift counter
 jr nz,RenderSpriteS    ; loop until counter is 0
RenderSpriteD:
RenderSpriteCL =$
 ld a,b        ; load the left sprite byte
 and (hl)       ; and it with the screen
 or d        ; or it with the mask
 ld (hl),a       ; set screen memory to left byte
 inc hl        ; increase screen pointer
RenderSpriteCR =$
 ld a,c        ; load the right sprite byte
 and (hl)       ; and it with the screen
 or e        ; or it with the mask
 ld (hl),a       ; set screen memory to left byte
 ld de,15       ; next row is 15 bytes ahead
 add hl,de       ; move screen pointer to next row
 pop bc        ; restore loop counter and shift mask
 djnz RenderSpriteL     ; loop for all bytes in sprite
 ret        ; done drawing the sprite




Follow-Ups: