Thread Rating:
  • 0 Vote(s) - 0 Average
  • 1
  • 2
  • 3
  • 4
  • 5
COCHES & CICLOPES (Y SATURNO)
#6
Here goes the sprite routine. You have to name it sprite3.bas (or change the incluide statement in the main program listing)

Code:
'XOR SPRITE SUBROUTINE. HERE WE JUST POKE THE COORDINATES IN THE FORM (X COORD,Y COORD,GFX ADDRESS,PREVIOUS X COORD, PREVIOUS Y COORD, PREVIOUS GFX ADDRESS)
SUB xorsprite (xd as ubyte,yd as ubyte, gfx as uinteger, xda as ubyte, yda as ubyte, gfxa as uinteger)
POKE @esprite,xd: POKE @esprite+1,yd: POKE Uinteger (@esprite+2),gfx
POKE @esprite+4,xda: POKE @esprite+5,yda: POKE Uinteger (@esprite+6),gfxa
gosub printsprite
END SUB

'SUBROUTINE TO SELECT THE HEIGHT OF THE SPRITE (TO SKIP SOME CYCLES IF WE DON'T NEED TO PRINT 16 LINES)
SUB spriteh (h as ubyte)
POKE @altura+1,h-1
END SUB

'MEMORY LOCATIONS WHERE WE KEEP THE COORDINATES AND THE GRAPHICS ADDRESSES
esprite:
ASM
xp: defb 0
yp: defb 0
gfxdir: defw 0
xpa: defb 0
ypa: defb 0
gfxant: defw 0
END ASM


'XORing ROUTINE. IT'S A VERY SIMPLE AND STRIGHTFORWARD ROUTINE WITH NO OPTIMIZATION, BUT I'M VERY HAPPY WITH THE RESULT BEING IT MY FIRST ATTEMP AT M/C
'IT MAKES USE OF TWO ROUTINES: SCADD TO CALCULATE THE SCREEN ADDRESS GIVEN THE X AND Y COORDINATES. THIS IS BORROWED FROM J.CAULDWELL'S "HOW TO WRITE
'ZX SPECTRUM GAMES" TUTORIAL. AND UPHL, A LITTLE ROUTINE TO CALCULATE THE SCREEN ADDRESS OF THE LINE BELLOW THE CURRENT ADDRESS. I HAVE CHANGED IT FOR
'CONVENIENCE TO UPDE. I CAN'T REMEMBER WHERE I TOOK IT FROM, PROBABLY SOME POST IN WOS.
'HOW THE ROUTINE WORKS IS EASY. WE NEED THE SPRITE ADDRESS IN HL AND THE SCREEN ADDRESS IN DE (WE PUT THE CORRDINATES IN BC AND CALL THE SCADD ROUTINE THAT
'RETURNS THE ADRESS IN DE)
'THEN WE SWAP REGISTERS AND MAKE THE SAME OPERATION WITH THE PREVIOUS SPRITE ADRRESS AND THE PREVIOUS COORDINATES.
'FROM NOW ON IT'S VERY EASY, WE JUST CLEAR (XOR) THE CONTENT OF THE PREVIOUS SCREEN POSITION, SWAP REGISTERS AND THEN PRINT THE NEW SPRITE BYTE IN THE NEW
'ADDRESS. WE DO THIS 3 TIMES (AS THE SPRITES ARE IN FACT 3 CHARACTERS WIDE, BECAUSE THEY ARE 16 PIXEL WIDE BUT PRESHIFTED TO THE RIGHT 8 TIMES)
'NOW WE CALL DE UPDE ROUTINE, DECREASE DE AND HL IN 3 (SO WE ARE IN THE CORRECT COLUMN) AND THEN REPEAT IT 15 TIMES MORE.
printsprite:
ASM
sprite:

       ld hl,(gfxdir)
       ld bc,(xp)
       call scadd          ; calculate screen address.
       exx
       ld hl,(gfxant)
       ld bc,(xpa)
       call scadd         ;ahora tenemos en los dos sets de registros alternativos(actual y anterior): direccion del grafico en hl, dirección de pantalla en de

       ld a,(de)
       ld c,a
       ld a,(hl)
       xor c
       ld (de),a
       exx
       ld a,(de)
       ld c,a
       ld a,(hl)
       xor c
       ld (de),a           ;pintamos el primer byte, primero el anterior (alternativo) y luego el actual

       inc hl
       inc de
       exx
       inc hl
       inc de

       ld a,(de)
       ld c,a
       ld a,(hl)
       xor c
       ld (de),a
       exx
       ld a,(de)
       ld c,a
       ld a,(hl)
       xor c
       ld (de),a          ;pintamos el segundo byte

       inc hl
       inc de
       exx
       inc hl
       inc de

       ld a,(de)
       ld c,a
       ld a,(hl)
       xor c
       ld (de),a
       exx
       ld a,(de)
       ld c,a
       ld a,(hl)
       xor c
       ld (de),a          ;pintamos el tercer byte
END ASM
altura:
ASM
       ld b,15

repeticiones:
       dec de
       dec de
       call upde
       inc hl
       exx
       dec de
       dec de
       call upde
       inc hl

       ld a,(de)
       ld c,a
       ld a,(hl)
       xor c
       ld (de),a
       exx
       ld a,(de)
       ld c,a
       ld a,(hl)
       xor c
       ld (de),a           ;pintamos el primer byte, primero el anterior (alternativo) y luego el actual

       inc hl
       inc de
       exx
       inc hl
       inc de

       ld a,(de)
       ld c,a
       ld a,(hl)
       xor c
       ld (de),a
       exx
       ld a,(de)
       ld c,a
       ld a,(hl)
       xor c
       ld (de),a          ;pintamos el segundo byte

       inc hl
       inc de
       exx
       inc hl
       inc de
      
       ld a,(de)
       ld c,a
       ld a,(hl)
       xor c
       ld (de),a
       exx
       ld a,(de)
       ld c,a
       ld a,(hl)
       xor c
       ld (de),a          ;pintamos el tercer byte

       djnz repeticiones

END ASM


ASM
; This routine returns a screen address for (c, b) in de.

scadd:  ld a,c              ; get vertical position.
       and 7               ; line 0-7 within character square.
       add a,64            ; 64 * 256 = 16384 (Start of screen display)
       ld d,a              ; line * 256.
       ld a,c              ; get vertical again.
       rrca                ; multiply by 32.
       rrca
       rrca
       and 24              ; high byte of segment displacement.
       add a,d             ; add to existing screen high byte.
       ld d,a              ; that's the high byte sorted.
       ld a,c              ; 8 character squares per segment.
       rlca                ; 8 pixels per cell, mulplied by 4 = 32.
       rlca                ; cell x 32 gives position within segment.
       and 224             ; make sure it's a multiple of 32.
       ld e,a              ; vertical coordinate calculation done.
       ld a,b              ; y coordinate.
       rrca                ; only need to divide by 8.
       rrca
       rrca
       and 31              ; squares 0 - 31 across screen.
       add a,e             ; add to total so far.
       ld e,a              ; hl = address of screen.
       ret


dispx: defb 0        ; general-use coordinates.
dispy: defb 0
dispxa: defb 0
dispya: defb 0
sprtmp: defw 0          ; sprite temporary address.

;uphl:
;    inc h
;    ld a,h
;    and 7
;    ret nz
;    ld a,l
;    add a,32
;    ld l,a
;    ret c
;    ld a,h
;    sub 8
;    ld h,a
;    ret

upde:
    inc d
    ld a,d
    and 7
    ret nz
    ld a,e
    add a,32
    ld e,a
    ret c
    ld a,d
    sub 8
    ld d,a
    ret
    
END ASM


If you look at the code for this routine or the main program you will see that I'll never become another Peter Moligneux. But if you check my earlier posts in this fórum you'll probably get to the conclussion that it's posible with ZxBC to transit from zero knowledge in programming to a point where you can do some cool things and get a lot of fun trying. That's what I love about this compiler, it makes things possbile.


If anyone need any further explanation, just ask here and I'll see if I can help.


P.S. Later in the day I'll try to post the code for the cyclops game. Or better still, instead of posting the code as is I'll do a Little tweak to show just the bouncing saturn and a moving cyclop for better readability.
Reply


Messages In This Thread

Forum Jump:


Users browsing this thread: 1 Guest(s)