Re: A86: Sprite demo


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

Re: A86: Sprite demo



I really should pay attention and attach the file.

At 07:07 PM 8/31/98 -0500, you wrote:
>
>Due to everyone new trying to learn asm, I took couple of hours and wrote a
; SPRMOVE -- sprite moving demo for TI-86 in Z80 assembler
; by David Phillips <electrum@tfs.net>   08/31/98
;
; This is just a simple example of graphics and other stuff in assembler.
; I tried to include elements important to writting a game such as reading
; keys using ports, drawing masked sprites, saving and restoring the
; background, and displaying intro/splatch screens.
;
; Note:  The picture was created with Windows Paintbrush, converted to an
;        asm file using Trent Lillehaugen's BMP2ASM utility, compiled to
;		 an .86p file, then finally compressed using my PIC2RLE utility.
;        PIC2RLE includes BMP2ASM and is available at www.ticalc.org.
;		 The bitmap files must be saved as monochrome to work correctly.
;
; Note2: The ASCR routines originally clipped at the 15th column (8x8 sprites),
; 	     but I changed it to clip at the entire screen.  This is because
;		 they were used by Mardell in Sqrxz, and the 16th column was
; 		 used for the status bars.

#include "ti86asm.inc"

.org _asm_exec_ram


clipmask 	= _textShadow		; [1] used by ASCR
rows2put 	= _textShadow + 1	; [1] ...
bitmask  	= _textShadow + 2	; [1] ...
currspr	 	= _textShadow + 3	; [2] current sprite to draw
background 	= _textShadow + 5	; [8] background behind the sprite 


 call _flushallmenus			; close any open menus
 res indicRun,(iy+indicflags)	; turn off the run indicator
 ld hl,Pic						; we will display the RLE at Pic
 ld de,$fc00					; we will decompress it to video memory
 call DispRLE					; show our cool picture

 ld b,57						; set starting X coord
 ld c,53						; set starting Y coord
 ld hl,SprRight					; the first time the right sprite is drawn
 ld (currspr),hl				; set starting sprite
 ld de,background				; we will save the background at this address
 call PutSprite_MSB				; draw the sprite for the first time

Loop:
 halt				; wait for the interrupt
 ld a,%01111110		; load the row for the arrow keys (bit 0 is 0)
 out (1),a			; tell the port to check
 nop \ nop			; give the port time to check the hardware
 in a,(1)			; read the key status
 rra				; move last bit to carry flag
 jr nc,Down			; bit 0 is for down
 rra				; check the next key
 jr nc,Left			; bit 1 is for left
 rra				; check the next key
 jr nc,Right		; bit 2 is for right
 rra				; check the last key
 jr nc,Up			; bit 3 is for up
 ld a,%00111111		; load the row for exit (bit 6 is 0)
 out (1),a			; tell the port to check
 nop \ nop			; give the port time to check the hardware
 in a,(1)			; read the key status
 bit 6,a			; test the bit for the exit key
 jr nz,Loop			; if it's not set, we can loop
 call _clrLCD		; clear the screen
 ret				; return to the TI-OS or shell

Up:
 ld a,c				; load the coord for check
 or a				; is it 0?
 jr z,Loop			; then we don't want to move
 call Erase			; erase the old sprite
 dec c				; decrease Y coord
 jr Draw			; draw sprite

Down:
 ld a,c				; load the coord for check
 cp 56				; is it 56?
 jr z,Loop			; then we don't want to move
 call Erase			; erase the old sprite
 inc c				; increase Y coord
 jr Draw			; draw sprite

Left:
 ld a,b				; load the coord for check
 or a				; is it 0?
 jr z,Loop			; then we don't want to move
 call Erase			; erase the old sprite
 dec b				; decrease X coord
 ld hl,SprLeft		; point to sprite for left direction
 ld (currspr),hl	; save new sprite
 jr Draw			; draw sprite

Right:
 ld a,b				; load the coord for check
 cp 120				; is it 120?
 jr z,Loop			; then we don't want to move
 call Erase			; erase the old sprite
 inc b				; increase X coord
 ld hl,SprRight		; point to sprite for right direction
 ld (currspr),hl	; save new sprite
					; a JR DRAW is not needed, we fall through...				

Draw:
 push bc			; save coords
 ld hl,(currspr)	; load the pointer of the sprite to draw
 ld de,background	; we will save the background at this address
 call PutSprite_MSB	; draw the masked sprite and save the background
 pop bc				; restore coords
 jr Loop			; loop through the program

Erase:
 push bc			; save coords
 ld hl,background	; we need to redraw the background
 call PutSprite		; erase by redrawing the background
 pop bc				; restore coords
 ret				; return to what called us

;===========================================================
; RLE picture displayer
; Decodes a RLE picture made by RLE2PIC
;
; written by David Phillips <electrum@tfs.net>
; started: 8/19/98
; last update: 8/31/98
;
; input: HL = RLE encoded picture, DE = where to display
; output: 1024 byte decoded picture
; destroys: AF, BC, DE, HL
; current size: 32 bytes
;===========================================================
DispRLE:
 ld bc,1024			; we need to copy 
DispRLEL:
 ld a,(hl)			; get the next byte
 cp $80				; is it a run?
 jr z,DispRLERun	; then we need to decode the run
 ldi				; copy the byte, and update counters
DispRLEC:
 ld a,b				; load in the high byte
 or c				; check both both bytes for zero
 jr nz,DispRLEL		; if not, then we're not done either
 ret				; if it's zero, we're done
DispRLERun:
 inc hl				; move to the run value
 ld a,(hl)			; get the run value
 inc hl				; move to the run count
 push hl			; save source pointer
 ld h,(hl)			; get the run count
 ex de,hl			; swap source and destination pointers
DispRLERunL:
 ld (hl),a			; copy the byte
 inc hl				; increase destination pointer
 dec bc				; decrease byte count
 dec d				; decrease run count
 jr nz,DispRLERunL	; if we're not done, then loop
 ex de,hl			; swap pointers back
 pop hl				; recover source pointer
 inc hl				; advance the source pointer
 jr DispRLEC		; check to see if we should loop

; ASCR	- Advanced Sprite Clipping Routines
;
; 	by Jimmy M†rdell	970304	 Last update 970803
;
; Temporary variables needed:
;  clipmask  : Byte
;  rows2put  : Byte
;  bitmask	 : Byte
;
;
; PutSprite_MSB:
;  Puts an 8x8 sprite at coordinates B,C. HL should point to a bitmapped
;  sprite followed by a bitmapped mask, total 16 bytes. DE should point
;  to an a memory location where the background will be stored as a
;  bitmap (8 bytes). The sprite will be clipped.
;
; PutSprite:
;  Puts an 8x8 sprite at B,C. HL = pointer to sprite. No mask and no
;  background storage, just clipping.


PutSprite_MSB:		; BC = x,y	DE = background storage  HL = sprite + mask
 ld a,c
 cp 150
 jr nc,PMSB_NoBotClip
 cp 64
 ret nc
PMSB_NoBotClip:
 push bc
 push de
 push hl
 push ix
 ld a,$FF
 ld (clipmask),a
 bit 7,b
 jr z,PMSB_CheckRightClip
 ld a,b
 cp 249
 jr c,EndPMSB
 neg
 push bc
 ld b,a
 ld a,$FF
PMSB_LeftClip:
 srl a
 djnz PMSB_LeftClip
 pop bc
 res 7,b
 dec c
 ld (clipmask),a
 jr PMSB_CheckBotClip
PMSB_CheckRightClip
 ld a,b
 sub 121
 jr c,PMSB_CheckBotClip
 push bc
 ld b,a
 inc b
 ld a,$FF
PMSB_RightClip:
 add a,a
 djnz PMSB_RightClip
 ld (clipmask),a
 pop bc
PMSB_CheckBotClip:
 ld a,8
 ld (rows2put),a
 bit 7,c
 jr nz,PMSB_CheckTopClip
 bit 6,c
 jp nz,EndMSB
 ld a,64
 sub c
 cp 8
 jr nc,PMSB_ClippingDone
 ld (rows2put),a
 jr PMSB_ClippingDone
PMSB_CheckTopClip:
 ld a,c
 cp 249
EndPMSB:
 jr c,EndMSB
 ret c
 push bc
 neg
 ld b,a
 sub 8
 neg
 ld (rows2put),a
PMSB_TopClip:
 inc hl
 inc de
 djnz PMSB_TopClip
 pop bc
 ld c,0
PMSB_ClippingDone:
 di
 push iy
 push hl
 pop iy
 push de
 pop ix
 ld a,(rows2put)
 push af
 call FIND_PIXEL
Modify_5:
 ld de,$FC00
 add hl,de
 ld (bitmask),a
 pop bc
PMSB_PutRow:
 push bc
 push hl
 ld a,(clipmask)
 ld e,a
 ld a,(iy+8)
 and e
 ld e,a 	 ; e = mask for this row
 ld d,0 	 ; d = background for this row
 ld b,8 	 ; b = pixels left to put
 ld c,(iy) ; c = sprite row
 inc iy
PMSB_PutCol:
 push bc
 sla d
 ld a,(bitmask)
 and (hl)
 jr z,PMSB_NPH
 inc d
PMSB_NPH:
 rlc e
 jr nc,PMSB_NextBit
 ld a,(bitmask)
 rlc c
 jr c,PMSB_BitOn
 cpl
 and (hl)
 ld (hl),a
 jr PMSB_NextBit
PMSB_BitOn:
 or (hl)
 ld (hl),a
PMSB_NextBit:
 ld a,(bitmask)
 rrca
 ld (bitmask),a
 jr nc,PMSB_SSB
 inc hl
PMSB_SSB:
 pop bc
 rlc c
 djnz PMSB_PutCol
 ld (ix),d
 inc ix
 pop hl
 ld de,16
 add hl,de
 pop bc
 djnz PMSB_PutRow
 pop iy
 ei
EndMSB:
 pop ix
 pop hl
 pop de
 pop bc
 ret

PutSprite:		 ; BC = x,y  HL = sprite
 push bc
 push de
 push hl
 push ix
 ld a,$FF
 ld (clipmask),a
 bit 7,b
 jr z,PSC_CheckRightClip
 ld a,b
 cp 249
 jr c,EndPPS
 neg
 push bc
 ld b,a
 ld a,$FF
PSC_LeftClip:
 srl a
 djnz PSC_LeftClip
 pop bc
 res 7,b
 dec c
 ld (clipmask),a
 jr PSC_CheckBotClip
PSC_CheckRightClip
 ld a,b
 sub 121
 jr c,PSC_CheckBotClip
 push bc
 ld b,a
 inc b
 ld a,$FF
PSC_RightClip:
 add a,a
 djnz PSC_RightClip
 ld (clipmask),a
 pop bc
PSC_CheckBotClip:
 ld a,8
 ld (rows2put),a
 bit 7,c
 jr nz,PSC_CheckTopClip
 bit 6,c
 jr nz,EndPS
 ld a,64
 sub c
 cp 8
 jr nc,PSC_ClippingDone
 ld (rows2put),a
 jr PSC_ClippingDone
PSC_CheckTopClip:
 ld a,c
 cp 249
EndPPS:
 jr c,EndPS
 push bc
 neg
 ld b,a
 sub 8
 neg
 ld (rows2put),a
PSC_TopClip:
 inc hl
 inc de
 djnz PSC_TopClip
 pop bc
 ld c,0
PSC_ClippingDone:
 push hl
 pop ix
 ld a,(rows2put)
 push af
 call FIND_PIXEL
Modify_6:
 ld de,$FC00
 add hl,de
 ld d,a
 pop bc
PSC_PutRow:
 push bc
 push hl
 ld a,(clipmask)
 ld e,a
 ld b,8
 ld c,(ix)
 inc ix
PSC_PutCol:
 push bc
 rlc e
 jr nc,PSC_NextBit
 ld a,d
 rlc c
 jr c,PSC_BitOn
 cpl
 and (hl)
 ld (hl),a
 jr PSC_NextBit
PSC_BitOn:
 or (hl)
 ld (hl),a
PSC_NextBit:
 rrc d
 jr nc,PSC_SSB
 inc hl
PSC_SSB:
 pop bc
 rlc c
 djnz PSC_PutCol
 pop hl
 ld bc,16
 add hl,bc
 pop bc
 djnz PSC_PutRow
EndPS:
 pop ix
 pop hl
 pop de
 pop bc
 ret

FIND_PIXEL:
 push bc
 push de
 ld hl,ExpTable+1
 ld d,0
 ld a,b
 and $07
 ld e,a
 add hl,de
 ld e,(hl)
 ld h,d
 srl b
 srl b
 srl b
 ld a,c
 add a,a
 add a,a
 ld l,a
 add hl,hl
 add hl,hl
 ld a,e
 ld e,b
 add hl,de
 pop de
 pop bc
 ret

ExpTable:
 .db $01,$80,$40,$20,$10,$08,$04,$02,$01

SprLeft:
	.db %00111000
	.db %01111100
	.db %11100110
	.db %01111111
	.db %00000111
	.db %00001111
	.db %01111110
	.db %00111100
	.db %00111000
	.db %01111100
	.db %11111110
	.db %01111111
	.db %00000111
	.db %00001111
	.db %01111110
	.db %00111100

SprRight:
	.db %00011100
	.db %00111110
	.db %01110011
	.db %11111110
	.db %11100000
	.db %11110000
	.db %01111110
	.db %00111100
	.db %00011100
	.db %00111110
	.db %01111111
	.db %11111110
	.db %11100000
	.db %11110000
	.db %01111110
	.db %00111100

Pic:
; compressed picture made with RLE2PIC
; RLE2PIC by David Phillips <electrum@tfs.net>

 .db $80,$00,$b2,$03,$80,$80,$01,$80,$00,$0e,$1f,$e0
 .db $80,$00,$03,$ff,$3f,$c0,$80,$00,$08,$7f,$f0,$80
 .db $00,$03,$fe,$3f,$80,$80,$01,$80,$00,$08,$ff,$f0
 .db $80,$00,$02,$01,$fe,$7f,$80,$80,$01,$80,$00,$08
 .db $f9,$f0,$80,$00,$02,$01,$fe,$7f,$80,$80,$01,$80
 .db $00,$07,$01,$f9,$f3,$ef,$87,$d9,$fe,$ff,$87,$f8
 .db $80,$f1,$02,$fe,$80,$00,$03,$01,$f3,$f7,$ff,$cf
 .db $fb,$fe,$ff,$1f,$fd,$f1,$e7,$fe,$80,$00,$03,$01
 .db $f3,$e7,$ff,$cf,$fb,$fe,$ff,$3f,$fd,$f3,$ef,$ff
 .db $80,$00,$03,$03,$f8,$07,$cf,$8f,$f3,$fd,$df,$3e
 .db $7d,$f3,$ef,$9f,$80,$00,$03,$03,$fc,$0f,$cf,$9f
 .db $f7,$fd,$fe,$7e,$fd,$f7,$df,$bf,$80,$00,$03,$01
 .db $ff,$0f,$df,$9f,$f7,$df,$fe,$7c,$f9,$e7,$df,$3e
 .db $80,$00,$03,$01,$ff,$0f,$9f,$1f,$87,$ff,$be,$7c
 .db $f9,$e7,$9f,$fe,$80,$00,$04,$ff,$80,$9f,$02,$3f
 .db $07,$ff,$fc,$fd,$fb,$ef,$bf,$fe,$80,$00,$04,$7f
 .db $9f,$bf,$3f,$0f,$bf,$7c,$f9,$fb,$ef,$3f,$fe,$80
 .db $00,$04,$1f,$9f,$80,$3e,$02,$0f,$bf,$7c,$f9,$f3
 .db $ff,$3e,$80,$00,$04,$0f,$df,$bf,$3e,$7e,$0f,$be
 .db $f9,$fb,$f3,$de,$7e,$7c,$80,$00,$03,$0f,$9f,$bf
 .db $80,$7e,$02,$1f,$7e,$f9,$80,$f3,$02,$de,$7c,$fc
 .db $80,$00,$03,$0f,$9f,$be,$80,$7c,$02,$1f,$7c,$f9
 .db $f3,$e3,$fc,$7c,$f8,$80,$00,$03,$1f,$9f,$7e,$7c
 .db $fc,$1f,$7d,$f3,$f7,$e7,$80,$fc,$02,$f8,$80,$00
 .db $03,$1f,$bf,$7e,$80,$fc,$02,$3e,$79,$f3,$f7,$c7
 .db $f8,$fd,$f0,$80,$00,$03,$1f,$fe,$7f,$80,$f8,$02
 .db $3e,$79,$f3,$ff,$c7,$f8,$ff,$f0,$80,$00,$03,$0f
 .db $fc,$ff,$f9,$f8,$3e,$7b,$e3,$ff,$87,$f8,$7f,$e0
 .db $80,$00,$03,$0f,$f8,$fd,$f1,$f8,$7c,$f3,$e1,$fe
 .db $07,$f0,$3f,$80,$80,$01,$80,$00,$05,$f8,$80,$00
 .db $0f,$f8,$80,$00,$0e,$01,$f8,$80,$00,$3d,$20,$00
 .db $0f,$80,$00,$02,$80,$80,$02,$f2,$02,$18,$60,$80
 .db $80,$01,$80,$00,$04,$20,$00,$08,$80,$80,$01,$80
 .db $00,$02,$80,$80,$01,$8a,$00,$08,$20,$80,$00,$05
 .db $2c,$88,$08,$9c,$89,$86,$80,$80,$01,$8a,$c6,$08
 .db $21,$8f,$1c,$80,$00,$03,$32,$88,$08,$82,$88,$89
 .db $80,$80,$01,$f3,$22,$08,$20,$88,$a0,$80,$00,$03
 .db $22,$78,$08,$9e,$80,$88,$02,$80,$80,$01,$82,$22
 .db $08,$20,$8f,$1c,$80,$00,$03,$22,$80,$08,$02,$a2
 .db $50,$88,$80,$80,$01,$82,$22,$08,$20,$88,$02,$80
 .db $00,$03,$3c,$70,$0f,$1e,$21,$c7,$80,$80,$01,$82
 .db $27,$1c,$71,$c8,$3c,$80,$00,$ff,$80,$00,$13

; 1024 bytes compressed to 503 -- 49% of original.

.end


--
David Phillips
mailto:electrum@tfs.net
ICQ: 13811951
AOL/AIM: Electrum32

References: