Show Posts

This section allows you to view all posts made by this member. Note that you can only see posts made in areas you currently have access to.


Messages - Iambian

Pages: 1 ... 13 14 [15] 16 17 ... 52
211
CaDan SHMUP / Re: Yet another shooter
« on: September 23, 2011, 11:13:10 pm »
Nowhere near done with the bullet engine. Instead, I'm working on the script system. Just enough so that I can get use it to run full tests on the bullet engine that I'm gonna be making. I have a specification of what I want of it so far, but at the moment, I suppose I could poll the people here to see if there's anything I might be missing with respect to the general purpose commands. Yes, the stage itself can shoot at you. And yes, this is what I'm going to be doing to test out the bullet engine. Bullets flying in from NOWHERE! Mwahahaha*COUGH*... Yeah...

Code: [Select]
Script system outline:

Internal notes:
Warning: Do not use the following for names of a script system command
"db", "dw", "end", "org", "byte", "word", "fill", "block", "addinstr",
"echo", "error", "list", "nolist", "equ", "show", "option", "seek"
These are reserved by SPASM

Naming conventions:
 rx = virtual register 0-7
 nn = 1 byte value
 ww = 2 byte value
 b  = Some value between 0-7
 s  = Some value between 0-15
 
Some names will have a more descriptive label for its use. If one is used,
read the description to determine the data's size.
 
VERY IMPORTANT NOTE: ALL SCRIPT NAMES HAVE A PERIOD (.) PRECEDING THE NAMES
EVEN THOUGH THEY DO NOT SHOW IN THIS LIST. ALWAYS REMEMBER.

COMMANDSET AND NAME
==============================================================================
------------------------------------------------------------------------------
- NORMAL EVERYDAY USE --------------------------------------------------------
------------------------------------------------------------------------------
000             | No operation. The script system halts on encountering this.
 NOP            | Used for filler or something.
------------------------------------------------------------------------------
001-008         | LOAD(rx,nn)
 LOAD           | Stores a constant (1 byte) into a register.
 2 bytes        |
------------------------------------------------------------------------------
009-016         | ADD(rx,nn)
 ADD            | Adds a constant (1 byte) with a register, then stores the
 2 bytes        | results back to the register. Affects zero and carry flags.
                | There's no subtract operand for this mode. Use a negative
                | constant for doing that. There is no add with carry.
------------------------------------------------------------------------------
017-024         | CLEAR(rx)
 CLEAR          | Sets a register to zero.
 1 byte         |
------------------------------------------------------------------------------
025-032         | AND(rx,nn)
 AND            | Do a bitwise AND operation between a register and a constant
 2 bytes        | and store the result back into the register.
                | Affects the zero flag. Does not affect the carry flag.
------------------------------------------------------------------------------
033-040         | XOR(rx,nn)
 XOR            | Do a bitwise XOR operation between a register and a constant
 2 bytes        | and store the result back into the register.
                | Affects the zero flag. Does not affect the carry flag.
------------------------------------------------------------------------------
041-048         | OR(rx,nn)
 OR             | Do a bitwise OR operation between a register and a constant
 2 bytes        | and store the result back into the register.
                | Affects the zero flag. Does not affect the carry flag.
------------------------------------------------------------------------------
049-056         | CPL(rx)
 CPL            | Inverts all bits in a register.
 1 byte         | Affects the zero flag.
                | If you want to do NEG instead, just CPL, then INC it.
------------------------------------------------------------------------------
057-064         | WAIT(rx)
 WAIT           | Makes the script system wait for the number of game cycles
 1 byte         | that is stored in a register. Remember that 24 cycles is
                | about one second's worth of time in normal gameplay mode.
                | You should be setting that register to some known value
                | before using this instruction. Feeding in 0 is using 256.
------------------------------------------------------------------------------
065-072         | CMP(rx,nn)
 CMP            | Performs subtraction between a register and a constant in
 2 bytes        | the form: register-constant. The result is NOT stored back,
                | but instead, used to affect the zero and carry flags.     
                | Good for use with conditional jumps.
------------------------------------------------------------------------------
073-080         | TEST(rx,nn)
 TEST           | Performs a bitwise AND operation between a register and a
 2 bytes        | constant, but does NOT store the results back to the
                | register. Instead, it's used to affect the zero flag.
                | Used when you need to figure out which bits are set in a
                | register, perhaps for conditional jumps?
------------------------------------------------------------------------------
081-088         | TRACK(rx)
 TRACK          | Output-only. Sets the given register to an angle that would,
 1 byte         | when used with the SHOOT command, fire a bullet directly
                | toward the player.
------------------------------------------------------------------------------
089-096         | SHOOT(rx)
 SHOOT          | Fires a shot at the angle given in a register. 'nuff said.
 1 byte         |
------------------------------------------------------------------------------
097-104         | SETSTATS(rx,nn)
 SETSTATS       | Stores rx to an external variable. If you need to define
 2 bytes        | your own variables, look in the code developer's guide for
                | more information.
------------------------------------------------------------------------------
105-112         | GETSTATS(rx,nn)
 GETSTATS       | Retrieves rx from an external variable. Again, if you need
 2 bytes        | to define your own variables, look in the code developer's
                | guide for more information.
------------------------------------------------------------------------------
113-120         | MULT(rx,nn)
 MULT           | Multiplies a register by a constant, then stores the least
 2 bytes        | significant byte (LSB) of the result back into the register.
                | NOTE: If it's possible, try to use the rotate/shift
                |       commands if you're dividing or multiplying by
                |       multiples of 2. It's much friendlier that way.
                | The most significant byte (MSB) is stored in "sta.overflow"
                | be accessed by the getstats command. Flags are affected as
                | follows: Carry is set if the MSB is not zero. Zero is set if
                | the result in the LSB was zero (even if the whole isn't)
------------------------------------------------------------------------------
121-128         | DIVIDE(rx,nn)
 DIVIDE         | Dividend (rx) / Divisor (nn) -> Quotient to (rx)
 2 bytes        | This is a slow operation. See if you can't use right shifts
                | instead.
                | The remainder is stored in "sta.overflow", which is accessed
                | via getstats command. Flags are affected as follows:
                | Carry is set if there is a remainder. Zero is set if the
                | quotient is zero (does not check remainder).
                |
------------------------------------------------------------------------------
129-136         | INC(rx)
 INC            | Increments rx by one. Same as ADD(rx,1) but much faster and
 1 byte         | uses less memory. Affects only the zero flag, to remain
                | consistent with how the Z80 does things.
------------------------------------------------------------------------------
137-144         | DEC(rx)
 DEC            | Decrements rx by one. Same as ADD(rx,-1) but much faster and
 1 byte         | uses less memory. Affects only the zero flag, to remain
                | consistent with how the Z80 does things.
------------------------------------------------------------------------------
145-152         | DJNZ(rx,label)
 DJNZ           | Automatically decrements the given register and takes the
 2 bytes        | specified relative jump while the register does not become
                | zero that cycle. Just like Z80's djnz instruction, except
                | you can use any register.
------------------------------------------------------------------------------
------------------------------------------------------------------------------
153             | MOVE(rxa,rxb)
 MOVE           | Copies the contents of register B over to register A.
 2 bytes        | Register A is overwritten with B and B stays the same.
------------------------------------------------------------------------------
154             | SWAP(rxa,rxb)
 SWAP           | The values in register A and register B are swapped.
 2 bytes        | Nothing is destroyed in this operation.
------------------------------------------------------------------------------
155             | ADDRX(rxa,rxb)
 ADDRX          | Adds register A and register B, then stores the result
 2 bytes        | back into register A. Affects only the carry flag.
------------------------------------------------------------------------------
156             | SUBRX(rxa,rxb)
 SUBRX          | Subtracts register B from register A in the form of
 2 bytes        | rxa-rxb, then stores the result back into register A.
                | Affects
                |
                |
------------------------------------------------------------------------------
157             | ROTR(rx,b) / ROTL(rx,b)
 ROTR/ROTL      | Rotates a given register a number of bits right or left
 2 bytes        | (respectively). All bits that leave one side of the register
                | Immediately appears on the other side of the register.
                | Flags are NOT affected.
                | INTERNAL NOTE: Distinguishing between ROTR and ROTL is done
                |                with bit 7 of the data byte. (1=ROTL)
------------------------------------------------------------------------------
158             | SHIFTR(rx,b) / SHIFTL(rx,b)
 SHIFTR/SHIFTL  | Shifts a given register a number of bits right or left
 2 bytes        | (respectively. All bits that leave are gone forever. Bits
                | shifted in will always be zero.
| Flags are NOT affected.
                | INTERNAL NOTE: Distinguishing between ROTR and ROTL is done
                |                with bit 7 of the data byte. (1=SHIFTL)
------------------------------------------------------------------------------
159             | MULTRX(rxa,rxb)
 MULTRX         | Multiplies register A with register B, then stores the
 2 bytes        | LSB of the result back to register A.
------------------------------------------------------------------------------
160             | DIVIDERX(rxa,rxb)
 DIVIDERX       | Divides register A with register B in the form of rxa/rxb,
 2 bytes        | then stores the quotient to register A.
------------------------------------------------------------------------------
161             | ANDRX(rxa,rxb)
 ANDRX          | Performs the bitwise AND function between register A and
 2 bytes        | register B, then stores the result to register A. Affects
                | the zero flag.
------------------------------------------------------------------------------
162             | ORRX(rxa,rxb)
 ORRX           | Performs the bitwise OR function between register A and
 2 bytes        | register B, then stores the result to register A. Affects
                | the zero flag.
------------------------------------------------------------------------------
163             | XORX(rxa,rxb)
 XORRX          | Performs the bitwise XOR function between register A and
 2 bytes        | register B, then stores the result to register A. Affects
                | the zero flag.
------------------------------------------------------------------------------
164             | CMPRX(rxa,rxb)
 CMPRX          | Performs virtual subtraction between register A and register
 2 bytes        | B. Does NOT store the result anywhere, but the carry and
                | zero flags are affected as though subtraction took place.
                | Useful for testing conditions.
------------------------------------------------------------------------------
165             | TEXTRX(rxa,rxb)
 TESTRX         | Performs a virtual AND function between register A and
 2 bytes        | register B. Does NOT store the result anywhere, but the
                | zero flag is affected as though an AND function was done.
                | Useful for testing bits to see if they're set.
------------------------------------------------------------------------------
166             | JUMPNC(label) [+ or - 127 bytes in either direction]
 JUMPNC         | Sets the script's execution pointer to wherever you defined
 2 bytes        | the label only if the result of flag altering command prior
                | to this instruction stayed between 0 and 255 (carry flag
                | reset)
------------------------------------------------------------------------------
167             | JUMPC(label) [+ or - 127 bytes in either direction]
 JUMPC          | Sets the script's execution pointer to wherever you defined
 2 bytes        | the label only if the result of flag altering command prior
                | to this instruction crossed zero. (Carry flag set)
------------------------------------------------------------------------------
168             | JUMPNZ(label) [+ or - 127 bytes in either direction]
 JUMPNZ         | Sets the script's execution pointer to wherever you defined
 2 bytes        | the label only if the result of flag altering command prior
                | to this instruction was NOT zero. (Zero flag reset)
------------------------------------------------------------------------------
169             | JUMPZ(label) [+ or - 127 bytes in either direction]
 JUMPZ          | Sets the script's execution pointer to wherever you defined
 2 bytes        | the label only if the result of flag altering command prior
                | to this instruction was zero. (Zero flag set)
------------------------------------------------------------------------------
170             | JUMP(label) [+ or - 127 bytes in either direction]
 JUMP           | Unconditionally sets the script's execution pointer to
 2 bytes        | wherever the label is defined. Just like Z80's JR.
------------------------------------------------------------------------------
171             | NEWPOSRT(rx_angle,rx_radius)
 NEWPOSRT       | Changes the firing position from the center of the enemy to
 3 bytes        | radius away from that center at some angle, both of which
                | are stored in registers. ANGLE is between 0 and 255, and
                | RADIUS can be anything, just note that 90 is the length of
                | the longest possible line on the screen. Keep that in mind
                | so you don't clip.
                | NOTE: Position is reset to center after a pause, or another
                |       use of the NEWPOSRT command.
------------------------------------------------------------------------------
172             | NEWPOSXY(rx_x,rx_y)
 NEWPOSXY       | Changes the firing position from the center of the enemy to
 3 bytes        | some offset X,Y away from the enemy. You MUST understand
                | that Y is reversed (positive values move down, negative
                | moves upward). To obtain negative values of a certain number
                | you should CPL/INC it. Or store a negative number to the
                | register to begin with. The screen is 64 by 64 pixels.
                | NOTE: Position is reset to center after a pause, or another
                |       use of the NEWPOSRT command.
------------------------------------------------------------------------------
173             | USESPRITE(rx_resourceID,rx_locationID)
 SETSPRITE      | Sets a sprite found in resourceID to an active enemy sprite
 3 bytes        | found in locationID. resourceID refers to a place on the
                | current script's resource table, which should be set at
                | "codegen"-time. locationID refers to a number 0-3, which
                | refers to which sprite slot to use (there are four).
------------------------------------------------------------------------------
174             | JUMPTABLE(rx_offset,nn_table_length) \.db label1,label2,...
 JUMPTABLE      | Allows you branch to different routines depending on what
 3+n bytes      | is in a register. You MUST put the table immediately after
                | this instruction. Example:
                |
                | LOAD(r1,0)      ;sets r1 to zero
                | JUMPTABLE(r1,4) ;r1 is the offset, 4 is the number of labels
                | .db Label_0     ;<-- Will be chosen, since it's the 0th one.
                | .db Label_1     ;Next label. If r1=1, then this is taken.
                | .db Label_2     ;Same, except if r1=2...
                | .db Label_3     ;And again... If r1=3...
                |
                | Note: If r1 is a value outside the bounds, the table is
                |       skipped over and code beneath is will run.
                | Note: The labels are relative addresses, + or - 127 bytes
                |       in either direction. This makes it prohibitive to use
                |       very large tables. If you need to make tables that
                |       large, use jump nodes as intermediaries.
                | IMPORTANT NOTE: THE TABLE CANNOT BE LARGER THAN 16 LABELS!
                |                 If you try to make it larger anyway, garden
                |                 gnomes will (likely) invade your home.
                | A typical use for this routine is retrieving the built-in
                | difficulty level, and then branching to different attacks
                | based on the difficulty, so one script does many things.
                | See how *you* can abuse this sucker. I won't be stopping you
------------------------------------------------------------------------------
175             | CALL(ww_relativelabel)
 CALL           | Lets you run a subroutine so you can save precious space by
 3 bytes        | not having to replicate redudnant code. The spacing for this
                | label is double-wide, so it can reach anywhere you need it
                | to. DO NOT TRY TO CALL ANYTHING WHILE IN A SUBROUTINE.
                | Endless loops and never getting back to the main code will
                | result. It's safe this time around to do a PAUSE or a WAIT
                | while you're in a subroutine, however. It's safe this time
                | around to do a PAUSE/WAIT combination while in a subroutine.
------------------------------------------------------------------------------
176             | RETURN   
 RETURN         | Exits a subroutine. Don't try to use this if you're not in
 1 byte         | a subroutine. Main script code all have exit points, and
                | using this command is NOT one of them. You might end up
                | crashing your calc or something.
------------------------------------------------------------------------------
177             | XYTORT(rxa_x,rxb_y,rxc_r,rxd_t)
 XYTORT         | Takes of the x,y coordinates found in registers A and B
 3 bytes        | (respectively), then uses the position given by the center
                | of the enemy in use (or whereever newposxy/newposrt has
                | changed it to) to output a distance and an angle in
                | registers C and D, respectively.
------------------------------------------------------------------------------
178             | RTTOXY(rxa_r,rxb_t,rxc_x,rxd_y)
 RTTOXY         | Similar to above, except it takes a distance and an angle,
 3 bytes        | then converts it to its corresponding x,y coordinates,
                | outputting to registers C and D, respectively.
                | The starting position is the center of the enemy in use or
                | wherever you changed it to via newposxy/newposrt.
                |
------------------------------------------------------------------------------
179             | GETPLAYERXY(rxa_x,rxb_y)
 GETPLAYERXY    | Outputs the player's X,Y coordinates to registers A and B,
 2 bytes        | respectively. If you only need an angle, you should be using
                | the TRACK command instead. Much faster that way.

212
CaDan SHMUP / Re: Yet another shooter
« on: September 20, 2011, 03:59:01 am »
To make a long story short, I spent all this time slacking off, working on a Celtic 2 rewrite, fighting with Vista until I decided it's time for Win7, pining over the loss of Celtic II due to missing the file while backing up, and reading the Temeraire series. If you haven't read that series, you ought to. Nothing's more awesome than re-envisioning the Napoleonic wars with dragons, but don't blame me if you start slacking on your projects because you're reading such awesome (okay, you *can* but only if you get the following line and find it hilarious: "Temerer! Cow?") But now that I'm done with the 6th book with the next one not due to be released for almost another year, I'm back to working on CaDan.

Save for a few things that I'm probably not going to miss until I cross that bridge, the side bar is just about done, so I'm off to deal with the bullet engine. Everything except for the line routine (since it's pretty much self-contained) has to be written from scratch since I'm going to use a different coordinate scheme to move and render the bullets. I am doing it this way so I can have myself the option of allowing bullets to properly clip, which solves a problem with respect to using bullets larger than 2x2 squares. This will also allow me to have bullets originate and fly off-screen and at my option, still allow bullets to bounce off the sides of the screen. I also plan on having varying velocities for bullets (not by much but still present) so you can fire off stuff at different speeds. Previously, there was only full speed and half speed (which was never really used). The whole velocity thing is only going to be done if I have enough clock cycles left over to do something like that. While I'm making these upgrades to the bullet system, I also plan on filling out the various bullet types, so you will have a bit more variety than the one pixel and 2x2 pixel blocks. I might also go with some graphical frills like having a bullet creation animation. That would be cool.

Certain details have yet to be worked out, but that's pretty much the plan of attack. The next screen shot I will post (which may take a while) is going to demonstrate what the new bullet engine can do. Since scripting won't be available yet, the patterns you see will be hardcoded into the engine for testing purposes.



213
ASM / Re: Constructive and Creative uses of IX and IY
« on: August 20, 2011, 12:21:45 am »
Here's a strip of code that uses IX/IY in a manner more consistent with how a person might use HL. Except IX. This is an example where I pretty much run out of registers. I could probably have used DE' in place of IY, though. And SP was out of the question. Maybe I could've used register I for storage.

The trick to using IY lies in not using any romcalls or allowing any TI-OS interrupts while you're (ab)using it. All bets are off if you are writing your own OS, but still. Restoring IY is even easier. "ld iy,flags"

Code: [Select]
workonthisrow:
 call leftiter
 call centeriter
 call fourthiter
 ld a,10
Workonthisrowsub:
 push af
  call firstiter
  call centeriter
  call fourthiter
 pop af
 dec a
 jr nz,Workonthisrowsub
 call firstiter
 call centeriter
 call rightiter
 ret

;External setup:
;HL = LUT for bit comparison
;HL'= LUT for result testing
; Two LUTs are indexed by HL by incrementing and decrementing H (256 byte wide tables)
;IX = pointer to buffer 1 (reading)
;IY = pointer to buffer 2 (writing)
;
;Internal setup:
;D= row above
;E= row below
;C= current position
;B= temporary variable
;B'=center byte storage
;
;Registers used so far:
; AF, BC, DE, HL, AF', BC', HL', IX, IY
;
;Free registers:
; DE'
;
firstiter:
 ld d,(ix-12)
 ld e,(ix+12)
 ld c,(ix+00)
 ld a,(ix-13)
 rrca
 ld a,d
 rra
 and 11101110b
 ld l,a
 ld b,(hl)
 ld a,(ix+11)
 rrca
 ld a,e
 rra
 and 11101110b
 ld l,a
 ld a,(hl)
 ex af,af'
 ld a,(ix-01)
 rrca
 ld a,c
 rra
 and 10101010b
 ld l,a
 ld a,c
 ex af,af'
 add a,(hl)
 add a,b
 exx
 ld l,a
 ex af,af'
 ld b,a
 and (hl) \ dec h
 or (hl)  \ inc h
 and 10001000b
 ld c,a
 exx
 ret
 
centeriter:
 ld a,d
 and 11101110b
 ld l,a
 ld b,(hl)
 ld a,e
 and 11101110b
 ld l,a
 ld a,(hl)
 ex af,af'
 ld a,c
 and 10101010b
 ld l,a
 ex af,af'
 add a,(hl)
 add a,b
 exx
 ld l,a
 ld a,b
 and (hl) \ dec h
 or (hl)  \ inc h
 and 01000100b
 or c
 ld c,a
 exx
 ld a,d
 and 01110111b
 ld l,a
 ld b,(hl)
 ld a,e
 and 01110111b
 ld l,a
 ld a,(hl)
 ex af,af'
 ld a,c
 and 01010101b
 ld l,a
 ex af,af'
 add a,(hl)
 add a,b
 exx
 ld l,a
 ld a,b
 and (hl) \ dec h
 or (hl)  \ inc h
 and 00100010b
 or c
 ld c,a
 exx
 ret

fourthiter:
 ld a,(ix-11)
 rlca
 ld a,d
 rla
 and 01110111b
 ld l,a
 ld d,(hl)
 ld a,(ix+13)
 rlca
 ld a,e
 rla
 and 01110111b
 ld l,a
 ld e,(hl)
 ld a,(ix+01)
 rlca
 ld a,c
 rla
 and 01010101b
 ld l,a
 ld a,(hl)
 add a,e
 add a,d
 exx
 ld l,a
 ld a,b
 and (hl) \ dec h
 or (hl)  \ inc h
 and 00010001b
 or c
 ld (iy+0),a
 exx
 inc ix
 inc iy
 ret
;=============== side of screen routines
leftiter:
 ld d,(ix-12)
 ld e,(ix+12)
 ld c,(ix+00)
 ld a,(ix-01)
 rrca
 ld a,d
 rra
 and 11101110b
 ld l,a
 ld b,(hl)
 ld a,(ix+23)
 rrca
 ld a,e
 rra
 and 11101110b
 ld l,a
 ld a,(hl)
 ex af,af'
 ld a,(ix+11)
 rrca
 ld a,c
 rra
 and 10101010b
 ld l,a
 ld a,c
 ex af,af'
 add a,(hl)
 add a,b
 exx
 ld l,a
 ex af,af'
 ld b,a
 and (hl) \ dec h
 or (hl)  \ inc h
 and 10001000b
 ld c,a
 exx
 ret

rightiter:
 ld a,(ix-23)
 rlca
 ld a,d
 rla
 and 01110111b
 ld l,a
 ld d,(hl)
 ld a,(ix+01)
 rlca
 ld a,e
 rla
 and 01110111b
 ld l,a
 ld e,(hl)
 ld a,(ix-11)
 rlca
 ld a,c
 rla
 and 01010101b
 ld l,a
 ld a,(hl)
 add a,e
 add a,d
 exx
 ld l,a
 ld a,b
 and (hl) \ dec h
 or (hl)  \ inc h
 and 00010001b
 or c
 ld (iy+0),a
 exx
 inc ix
 inc iy
 ret

;
;Subroutine code end
;======================================

This code can be found in my earlier 2D Cellular automata project, which is table-based to allow rulesets other than Conway's Game of Life.

My problem these days with IX and IY isn't exactly the fact that they're slow(er) and large(r) (than HL). They're okay to use when you really need them, but my beef is that you can't use IXL and IXH operations and expect them to work on the Nspire. There was ONE instance in which I did that stunt in CaDan (somewhere in the enemy data reading routine I think) and people complained they couldn't play the demo on their Nspire.

214
ASM / Re: Constructive and Creative uses of IX and IY
« on: August 19, 2011, 11:50:10 pm »
Not entirely sure this counts as "just an extra HL" but I do recall using IX in a 32-bit scoreboard, where IX couldn't be used in an ADC instruction. The input was basically IX:HL. IY's role? Pointing to a table of bytes that need to be output to the screen in the meantime. SP at the time was pointing to a table of 32 bit values that corresponded to alternating pairs of negative and positive powers of tens, starting at one billion.

I've got to think of other ways I've used and abused the index registers, but I do recall other instances in my other projects. Gotta dig 'em up.
Code: [Select]
ld a,10           ;48 ten digits to look after. 1.000.000.000
DSBDECSCOLP:
 ex af,af'         ;52 62
 pop bc            ;62 72
 pop de            ;72 82
 ld a,(iy+0)       ;91 101
 out ($11),a       ;11
 ld a,$FF          ;18
 inc a             ;22
 add ix,bc         ;37
 adc hl,de         ;52
 jr c,$-5          ;59
 ld c,a            ;63
 ld a,(iy+1)       ;82
 out ($11),a       ;11
 pop de            ;21
 add ix,de         ;36
 pop de            ;46
 ld a,(iy+2)       ;65 arghamahblabbles!
 nop               ;69 BAD CODE! WORST ENEMY! *rolls newspaper* WHAP WHAP WHAP
 out ($11),a       ;11
 adc hl,de         ;26
 ld a,c            ;30
 add a,a           ;34
 add a,a           ;38
 ld c,a            ;42
 ld b,0            ;49
 ld a,(iy+3)       ;68
 out ($11),a       ;11
 ld iy,NumberTable ;25
 add iy,bc         ;40
 ex af,af'         ;44
 dec a             ;48
 jp nz,DSBDECSCOLP ;58
 ld sp,(itemp1)
 ld iy,myflags
 jp DSBSCORCOLL
Nevermind the comments. It was a late night with no caffeine.

EDIT: The scoreboard routine is written inline with the LCD update routine for the scoreboard. This is CaDan, so... yeah. I kinda needed the speed where it was available but I had to make sure that no timings were violated for even the fastest condition. That's the timings that was listed.

EDIT2: An almost identical run of code which sets up IY for the first run is not shown. That initializing code was used to render parts of the sprite above the score.

215
CaDan SHMUP / Re: Yet another shooter
« on: August 12, 2011, 01:52:29 pm »
Added in the score counter as long as an (unused at the moment) kills counter. The player is able to move around on the field. There is a single black line in the middle of the field to serve as a test for collision detection, which works, but I have not yet removed that.

Also, the score display will display in hexadecimal (zero-padded to maintain length) if set from the menu options. This was originally designed to help me debug the game since the score counter is a perfect way to output values as the game runs. It's also a good way for the user to see through the cheap methods that I'll employ to make the score counter count upward at regular intervals.

Next on the todo list: Resource allocation for additional menus and backgrounds. Also have to do some sort of scripting and I've also got to reconstruct the bullet engine.

In the following screenshot, the scoring, hex mode, and movement is demonstrated. The score panel is not actually tied to the score, but is instead tied to the some of the internal game timer. This "some" part is seen clearly when the score is viewed under hex mode.


216
CaDan SHMUP / Re: Yet another shooter
« on: July 09, 2011, 03:51:50 am »
Recreating the status bar is going to take... quite a while. To give the basic rundown of what is holding me up on that, I'm just gonna say that the entire status bar is directly drawn to the LCD; it's not buffered anywhere. And while I'm drawing it to the LCD, I'm using some of the spare cycles to perform these tasks:

* Character sprite rendering (done)
* Character / enemy bullet collision detection
* Character movement (done)
* Anything else I can think of stuffing inside the LCD's wait states while handling the elements I need to draw to the screen, really.

It's using these spare cycles that's eating up all my time, but I really want this thing to work right the first time around.

I would copy and paste the stuff found in the old iteration, but there's just stuff I simply won't or can't (without some effort) copy. If you took a good look at the code found in _drawlcd.z80 in the S2 folder of my old project (released as open source in this post) starting at around line 202, you'll sort of understand why I don't want to mess with it.

217
ASM / Re: Checking the amount of set bits.
« on: July 07, 2011, 11:01:35 pm »
Code: [Select]
;Input: A=byteToCheck
;Destroys B.
CheckOneBitUnset:
 cpl
 ld b,8
 rlca
 jr c,$+6
 djnz $-3
 scf
 ret  ;returns with a carry if no bits are set
 and %11111110
 ret  ;zero if only one bit is unset, nonzero if others are set. No carry regardless.
Check to see if that actually works. Just made it up on the spot.

218
CaDan SHMUP / Re: Yet another shooter
« on: June 28, 2011, 01:54:12 pm »
The menu's look great, but on all of the screenshots i see only the menu's. How is the game itself going?
The actual game play has not yet been recoded. I want to verify that all the data that is being passed to the main game engine is accurate given the selections from the menus that is depicted on the screen shots.

If you want to learn about the progress that happened on this project prior to the reboot, check out this post, which is a summary of all that went on before.

Coding the main game engine should progress a fair bit faster than the previous iteration, since I have a reference for how it is supposed to go, and I also have tons of working code that I can copy and paste.

The next screenshot that I'm going to put up will be the main game screen with some random shots being fired from nowhere, akin to how the early stages of the initial game's progress was. This is because I want to know that the bullet engine works before I build a script system that relies on it. The prior script system could not be used since it was broken beyond repair.

Just so you know, once I get the script system working again, I'm going to lock down this thread and create a new one to show the progress of this recent iteration of CaDan.

219
CaDan SHMUP / Re: Yet another shooter
« on: June 27, 2011, 02:31:06 am »
Finished up most of the menus, at least the ones I'm going to be supporting right now. There are placeholders for the Replay and External levels sections. I still need to write something for the Extra option and get the character select screen to figure out what was selected from the main menu so I can collect all the information needed to start the main engine.

A screenshot of what I have so far. Enabling external levels changes the function of "Start" if you haven't noticed.

220
CaDan SHMUP / Re: Yet another shooter
« on: June 15, 2011, 02:29:22 am »
Changes made: Shuffled around resources to allow compression of menu text and image files. Saved around 2KB so far. "Practice" is changed to "Extra" and the ability to practice the game is now found in the settings menu, which I am working on.

Plans: Additional stage selection is planned after the character selection is complete from the main menu. You will not be able to practice the extra stage (sorry guys). I also plan on providing a simple layout for the visual replays, but none will be enabled until I get the file structures encoded. Additional juggling of some data will happen shortly after I get the menus hashed out, and then I will start working on the "battle" system (main game play area).

Screenshots will be available once all that is done.

221
Escheron: Shadow over Ragnoth / Re: Escheron: Shadow over Ragnoth
« on: June 08, 2011, 03:53:57 pm »
Just to let you know, I'm going to hash out some sort of schedule so I can work on both CaDan and E:SoR simultaneously. I'll let ya guys know how well that's working out by the end of the month.

222
CaDan SHMUP / Re: Yet another shooter
« on: May 31, 2011, 05:36:15 pm »
Just so you know, I'm not dead, and neither is the project. I've just been a little busy with other things, like work and coding a website related to said work.

What I've got to do with CaDan is to redo the resource tables (which shouldn't take too long) and fully figure out how resource management is going to take place. Until I can get those things down, I won't be able to work on the battle engine. I just wanna be able to do things right this time around.

223
CaDan SHMUP / Re: Yet another shooter
« on: May 20, 2011, 06:20:24 pm »
A screenshot that demonstrates the completed (excepting for additional character slots) character select screen, a completed high score screen, and a mostly filled out general statistics screen. I access the gen stats screen twice to show that "game uptime" is actually being kept in the background. The "game uptime" keeps track of the number of frames the game has gone through (which is roughly 24-32 frames a second).

None of the scores are real; they were created by the script to demonstrate that the score entries can be accessed in a manner that conforms to the spec sheet. I also noted one bug with respect to the small sprite display in the character select menu, regarding what is in the gray layer. I'm going to explore that routine to figure out what is up with that. If you don't know what I'm talking about, look carefully at those 8x8 sprites at the right when it changes between the normal character set and the secret character set, then back again. You'll see it. It should either be all black or all gray, but not both.

EDIT: Nevermind about that bug that I just mentioned. It was being caused by me not clearing off the gray buffer between frames.

224
CaDan SHMUP / Re: Yet another shooter
« on: May 17, 2011, 02:42:41 am »
Change: Added character sprites before name, which was the original reason why the space was there. Tell me whether or not it looks better this way, or if you want it name only. Screenshot animated to demonstrate alignment.

Still need to put in code to read out the scores.

EDIT: Think it might be better to put the sprite into the gray layer?

225
CaDan SHMUP / Re: Yet another shooter
« on: May 17, 2011, 02:28:02 am »
Added to the Results menu, showing what I have so far of the high score menu. You can already guess where the scores are gonna be.

Note: Up to three high scores in each category are going to be kept at a time.
EDIT: Four high scores. Just re-read my spec sheet.

Pages: 1 ... 13 14 [15] 16 17 ... 52