ChuckRock II
? Core Design
How to train it.

What you need:

Original/SPS release game
Tools ASMONE & Tetrapack & A1?s awesome menu code (download from link in the tutorial)
Some copy program like BurstNibbler/X-Copy
A few blank disks
AR3 cart. or ROM image

In this tutorial, we?ll create a trainer for the game, with following main functions:

– Unlimited lives
– Unlimited energy
– No collision detection
– In-game keys
– Start level selector

At the bottom of this page, a disk with needed tools, trainer source, exe & packed trainer can be downloaded.

I also included the trainer and boot block on the disk, as tracks. In the trainer code is also included a
crack for the copylock protection. This means you can very quickly install it
on a copy of the game. Here is how to do it:

copy game
Enter AR, insert downloaded disk from here and read whole track 0: RT 0 2 70000 + enter Insert copy of game and write track back: WT 0 2 70000 + enter.
Play the game with trainer!

Please note, that some addresses may differ on your computer, depending on the used memory configuration.
I have slow expansion memory at $ C00000.

Start game and enter level one. In the lower left corner of the screen, we have two lives. Lets start by having a look at this. Enter AR and start the trainer search: TS 2 + enter. When the search is over, exit to game, loose one life and enter AR again.

Continue the search with: T 1. AR will now search for addresses that are decreased from # 2 to # 1.
It returns address $ C899, this is where # of remaining lives are stored. The trick to train game, is to find and remove the instruction, that decreases life counter.

Press D + Enter. AR returns some address C11912 ? the exact is not important, but it tells us, that main program
is located in expansion memory.

Lives was stored at $ C899, and odd address. Many games uses word instead of byte instructions, so we assume game
works with address $ C898. Type FA C898 C00000, this will show how game messes with this address.

After a little searching, we get some addresses. Address C0D59E is interesting, as this instruction decreases the life value with one. How to get rid of this ? One way is to NOP out the whole instruction, but there is a sweeter way..

Notice address C0D566, which tests if the counter has reached # 0. Try compare the two instructions with each other, see above. Only difference on the TST and the SUBQ, is the first opcodes. If we insert value # 4A at address C0D59E, the decrease instruction will be changed to a TST instruction, and the life counter will never decrease.

Take note of address C0D59E and that we need to insert value # 4A there, as we need them to code the trainer.

Not important, but just want to mention.. Perhaps you noticed that address C0D59E is not doing a SUBQ.W #1,C898, but a SUBQ.W #1,26C(A5)..

This is because register A5 holds a reference value (See it with R+enter). The life counter is then ref. value + 26C.. To refresh lives, we put # 2 at $ C898.

Next up is the energy. Ensure you have fresh energy and keep walking into the first baddie on the level & count how
many times you can do this, before loosing a life. I came to five times. With fresh energy, enter AR and start hunt for energy counter; TS 5. When its done searching, exit AR and walk into the baddie ONE time. Enter AR again &
continue the search; T 4.

AR returns address C895..

Again, assuming we are working with words, see what game does with the address: FA C894 C00000.

This time AR returns a whole bunch of addresses. I?ve collected some of them in the above picture. As you can see, there are seven interesting ones, marked with RED, they all decrease the energy. Take note of these addresses.

To refresh energy, we put # 5 at C894.W
Next thing is the collision detection. This can be found in several ways. One is to trace the code back, to see what calls the energy decrease & another one is to try and eliminate all SUBQ.W instructions.

We?ll go for the last one. As we saw (no, not the movie) earlier, the SUBQ.W?s used in this game is made of the
opcodes 53 6D. Search for these; F 53 6D,C00000.

AR returns a lot of addresses. We can already exclude the one for lives & the seven ones for energy.
With the remaining ones, try change each of them to TST, by replacing 53 with 4A in the instruction. After each one,
Exit AR and collide with a baddie. You?ll discover that address C09E4A is the correct one. Again, take note.

Next up is finding the keyboard routine, so we can hook it up, and insert in-game keys. The kb address BFEC01.

Search for this; F BF EC 01,C00000. AR returns two addresses. Disassemble the first one. The raw data is put
into reg. D0 & then the key data is calculated. At address C0BF54, the calculated key is moved to a memory location.

We can hook the keyboard routine at address C0BF4E, and insert a JSR IN-GAME KEYS. Then in the trainer, we first
restore the code we changed (ROR.B #1,D0 & EORI.B #FF,D0).

To make the in-game keys, we need to know the HEX value for each key, we want to use.
I?ve decided to use following; F1, F2, F3, L, K, Q, W, E, R & HLP.

Enter AR and insert a breakpoint at address C0BF54, exit AR and press F1. AR pops up, cause the keyboard interrupt
has been executed & address C0BF54 is reached. We now have hex value for F1 in reg. D0. Press R +enter to value,
see above picture. Value is 50. Do this with rest of the keys, to find remaining values.

Next thing is finding a level skipper. Many games use ?flags? to indicate a certain state. I.E. if address 100 is set to value 2, game thinks the current level is over. Game checks this with TST.W instructions. We know from earlier, that the HEX values for these are 4A 6D. Search for them; F 4A 6D,C00000.

You?ll get a?.

This takes a little patience..
Start from an end. Stick a breakpoint to the first address & exit AR: BS C01CCA. AR pops up right away.

OK, so game seems to continually to check this address. Disassemble it: D C01CCA+enter. It checks address 1E6+A5.
Then we must know what A5 points to. See this with R+enter. A5 points to address C62C.
The instruction then checks address C62C+1E6= C812. Try inserting a value at $ C812.W, see above & exit AR.

What happens ? No level skip, but it starts to rain.. Ok, we know how to enable rain now. Do this with all the addresses and eventually you?ll find the level skipper. Here is what I found:

Rain: 1E6(A5)
Snow:1E8(A5)
Level skip:254(A5)

Next fun fun thing is the level selector. As with remaining # of lives, there is also an address which holds the level #.
How to find this ?

If you where through all the TST instructions, you noticed that the one at address C09E9E was checking address $C880,
which skips level. It would make sense, when this TST is not true and game skips level, it also adds # 1 to the address where level # is stored. Disassemble address C09E9E and hit enter a few times. Right after the TST, there is a branch to address C09EA8, if address $ C880 is #00. So, the code in-between may be interesting. Notice address C00EBE, which ADD # 1 to address C89A (26E+A5=26E+C62C=C89A). This could be the level counter.

In the above picture, I am at level 2, address C89A is = # 1. Set address C880.w (lv skipper) to # 2. After the level skip, check address C89A again. Notice it has increased with # 1. This is where the level # is stored.

Lets check what game else does with this address: FA C89A C00000.
AR returns a few addresses…

What seems interesting, is the first one. It moves value # 0 = level 1. If this is changed (before game starts, of course) to ex # 1, game will start at level 2.

In the above picture, I painted the start value # 00 red, its located at address C00143. This means we just need to put the start level here.

Another thing that needs to get worked out, is the toggle values to toggle lives/energy on & off.
This is done by shifting the decrease instruction between SUBQ & TST. To do this, the EOR instruction is perfect.

As you might remember, the decrease instructions for lives & energy all started with HEX 53 and to train it, we changed it to 4A. So, we must shift between these two values, using an EOR value. How to find this ? Easy, just EOR the train value (4A) with the SUB value (53) and you got the toggle (EOR) value.

Follow below pic:

The resulting toggle value is 19.
We now got all values needed for the trainer. But there is still some investigation..
Firstly, game uses expansion memory, so we need to find the games pointer to exp. memory, to make
trainer work with all memory configurations.
And then the main file is packed, the decrunched data must be hooked before its executed.

Are you still reading ??? I must warn you, we are far from finished yet 🙂

To find out where game loads data to, boot block is a pretty good place to start..
Insert ChuckRock II, disk 1, enter AR and read boot to address 70000: RT 0 1 70000.

Actual boot code starts at offset $ C (before is header+checksum). Disassemble : D 70000+enter.
First part is copying boot block to address 78000 and executing it. Second part of boot, is the part copied to 78000, which is just a track loader. The ? MOVE.L #70000,28(A1), tells us, the data is loaded to address 70000.
Also the JMP 70000 gives an idea about it.
Exit AR and boot game. Enter AR when screen turns black and lets see what is loaded to address 70000:

Hmm, not much interesting.
Oki, the game code was located in expansion memory. A logically way to execute it, would be to make ex. A0 point to exp. memory and then do a JMP (A0), of course this could also be A1,etc.

Try search for the opcodes for JMP (A0); F 4E D0,70000. (How to find opcodes ? Assemble JMP (A0) and seem them)

From above, you can see address 76328 makes a JMP (A0). Address 76322 moves pointer to expansion memory into A0. This address must be taken, and our trainer patch called, in order to train game before its run.
Insert a breakpoint to address 76328 & exit AR. When it pops up, game is unpacked & ready to run. You can also see
the contents of A0 now.

You can see, that game is located right from beginning of expansion memory, which is good news for us.
This means when we train ex. lives, where the instruction is located at C0D59E, we add value #D59E to A0 and then
move train value # 4A into (A0)..

If you want to, try and enter a value at address C00143, ex 01. Then game should start at level two, remember ?
Also, try to disassemble start of game code and follow it:

What you see above at address 19712 is the copy protection. It is a copylock (WOW, big supprise), and we?ll also crack this in our trainer patch, by hardwire new encrypted opcodes into it. I won?t go into details with this, as it is a trainer tutorial. Just don?t worry about the copy protection.

Next question is where to locate the trainer in memory ? Usually real low chip is good. Lets say address 100.
But is game using this area ? Fill memory with ?n??s and boot game, upon start of level 1, check if our ?n??s has
been overwritten:

As you can see above, game is overwriting address $ 100 with a longword value, so $ 100 is no good place for trainer, lets choose address 140 instead. The value at 100 is the copylock key, returned from the protection.

The actual trainer can now be coded:

CRACK:
           

           MOVE.L #$ 150,$78078       ;hook jmp 70000 and make it jmp 150
           JMP $ 78030                ;execute what we took over from boot block
           MOVE.L #$ 4EF80160,$76322  ;hook jmp (a0) and make it jmp 160
           JMP $ 70000                ;execute jmp we took over
           MOVEA.L $ 76342,A0         ;execute code where we inserted jmp 160

LEVELSELC:
           SUBQ.B #$ 1,$C4.W          ;decrease level # with 1
           MOVE.B $ C4.W,$143(A0)     ;insert start level in game code

COPYLOCK:
           MOVE.L #$ A9E4F576,$ 19B3A ;hardwire copylock protection
           MOVE.L #$ 54A9534,$ 19B3E  ;hardwire copylock protection

           
TRAINER:   

LIVES:     CMPI.B #$ 01,$ C0.W        ;check if unlimited lives has been chosen
           BNE.B ENERGY               ;if not, branch to energy
           ADDA.L #$ D59E,A0          ;if chosen,add d59e to a0,point to live decrease ins.
           MOVE.B #$ 4A,(A0)          ;move train value into game
           SUBA.L #$ D59E,A0          ;subtract d59e from a0, to rest. it to original value

ENERGY:

           CMPI.B #$ 01,$ C1.W        ;check if unlimited energy has been chosen
           BNE.B COL                  ; if not, branch to collision detection
           MOVEM.L D0-A0,(A7)         ;save regs.
           MOVEQ #$ 4A,D0             ;move train value # 4a into d0
           ADDA.L #$ C2D2,A0          ;add c2d2,a0 point to first energy decrease inst.
           MOVE.B D0,(A0)             ;move train value into game
           LEA $ B0(A0),A0            ;add # b0 to a0, a0 point to next eng. decrease ins.
           MOVE.B D0,(A0)             ;move train value into game
           LEA $ 908(A0),A0           ;etc.      
           MOVE.B D0,(A0)             ;etc.
           LEA $ 705E(A0),A0          ;etc.
           MOVE.B D0,(A0)             ;etc.
           LEA $ 22(A0),A0            ;etc.
           MOVE.B D0,(A0)             ;etc
           LEA $ 7BE(A0),A0           ;etc.
           MOVE.B D0,(A0)             ;etc       
           LEA $ 2250(A0),A0          ;etc.
           MOVE.B D0,(A0)             ;etc.
           MOVEM.L (A7)+,D0-A0        ;restore regs.

COL:

           CMPI.B #$01,$ C2.W         ;check if no collision detection has been chosen
           BNE.B KEY                  ;if not, branch to in game keys
           ADDA.L #$ 9E4A,A0          ;add 9e4a to a0,make it point to collision instruction
           MOVE.B #$ 4A,(A0)          ;move train value into game
           SUBA.L #$ 9E4A,A0          ;subtract 9e4a from a0, rest. it to its original value

KEY:

           CMPI.B #$01,$ C3.W         ;check if in game keys has been chosen
           BNE.B GAME                 ;if not, execute game
           MOVE.L A0,$ D0.            ;save value of a0 at address d0, for use in in-game keys
           ADDA.L #$ BF4E,A0          ;add bf4e to a0, make it point to kb instruction
           MOVE.L #$ 4EB90000,(A0)    ;hook keyboard instruction with jsr                              
           MOVE.W #$ 218,$ 4(A0)      ;218
           SUBA.L #$ BF4E,A0          ;subtract bf4e from a0, rest. to its original value            

          

GAME:

           JMP (A0)                   ;execute jmp we took over with jmp 160, start game

 

 

TOG:

           MOVEM.L D1,$ F0.W          ;save reg. d1 at address f0
           ROR.B #$ 1,D0              ;restore code we have overwritten in the keyboard routine
           EORI.B #$ FF,D0            ;etc.
           MOVEQ #$ 19,D1             ;move toggle value into d1

TOG_LIVES: 

           CMPI.B #$ 50,D0            ;check if f1 is pressed
           BNE.B TOG_ENG              ;if not, branch to toggle energy
           MOVE.L A0,$ E0.W           ;save reg. a0 in game at address a0
           MOVE.L $ D0.W,A0           ;get saved a0 value (start of exp. memory)move into a0
           ADDA.L #$ D59E,A0          ;add d59e to a0, make it point to lives decrease instruction
           EOR.B D1,(A0)              ;toggle subq & tst
           MOVEA.L $ E0.W,A0          ;restore a0

TOG_ENG:

           CMPI.B #$ 51,D0            ;check if f2 is pressed
           BNE.B TOG_COL              ;if not, branch to toggle collision
           MOVE.L A0,$ E0.W           ;save reg. a0 in game at address e0
           MOVEA.L $ D0.W,A0          ;get saved a0 val. (start of exp. memory)move into a0
           ADDA.L #$ C2D2,A0          ;add c2d2 to a0, point to first energy decrease ins.
           EOR.B D1,(A0)              ;toggle subq & tst
           LEA $ B0(A0),A0            ;add b0 to a0, point to second energy decrease ins.
           EOR.B D1,(A0)              ;tuggle second energy decrease instruction
           LEA $ 908(A0),A0           ;etc.
           EOR.B D1,(A0)              ;etc.
           LEA $ 705E(A0),A0          ;etc.
           EOR.B D1,(A0)              ;etc.
           LEA $ 22(A0),A0            ;etc.
           EOR.B D1,(A0)              ;etc.
           LEA $ 7BE(A0),A0           ;etc.
           EOR.B D1,(A0)              ;etc.
           LEA $ 2250(A0),A0          ;etc.
           EOR.B D1,(A0)              ;etc.
           MOVEA.L $ E0.W,A0          ;restore a0 value in game

TOG_COL:

           CMPI.B #$ 52,D0            ;check if f3 is prsessed
           BNE.B REFLIV               ;if not, branch to refresh lives
           MOVE.L A0,$ E0.W           ;save reg. a0 in game at address e0            
           MOVEA.L $ D0.W,A0          ;get saved a0 val. (start exp. memory) move it into a0
           ADDA.L #$ 9E4A,A0          ;add 9e4a to a0, make it point to collision det. value
           EOR.B D1,(A0)              ;toggle subq & tst 
           MOVEA.L $ E0.W,A0          ;restore a0 value in game           

REFLIV:

           CMPI.B #$ 28,D0            ;check if l is pressed
           BNE.B REFENG               ;if not, branch to refresh energy
           MOVE.W #$ 02,$ 26C(A5)     ;move value 2 into lives counter

REFENG:    

           CMPI.B #$ 27,D0            ;check if k is pressed
           BNE.B RAINON               ;if not, branch to rain on
           MOVE.W #$ 07,$ 268(A5)     ;refresh energy

RAINON:

           CMPI.B #$ 10,D0            ;check if q is pressed
           BNE.B RAINOFF              ; if not, branch to rain off
           MOVE.W #$FF,$ 1E6(A5)      ;enable rain

RAINOFF:

           CMPI.B #$ 11,D0            ;check if w is pressed
           BNE.B SNOWON               ;if not, branch to snow on
           MOVE.W #$ 00,$ 1E6(A5)     ;disable rain

SNOWON:

           CMPI.B #$ 12,D0            ;check if e is pressed
           BNE.B SNOWOFF              ; if not, branch to snow off
           MOVE.W #$ FF,$ 1E8(A5)     ; enable rain

SNOWOFF:

           CMPI.B #$ 13,D0            ;check if r is pressed
           BNE.B SKIPLV               ;if not, branch to skip lv
           MOVE.W #$00,$ 1E8(A5)      ;disable snow

SKIPLV:

           CMPI.B #$ 5F,D0            ;check if hlp is pressed
           BNE.B RETURN               ;if not, branch to return to game
           MOVE.W #$ 02,$ 254(A5)

 

RETURN:

           MOVEM.L $ F0.W,D1          ;restore d1
        RTS                           ;return to game

Open the trainer menu in your favourite TXT editor and set up functions marked with red (they are self-explained):

And then the actual trainer comes: (I haven?t shown all pics)

Then there is the TXT presented to the user. A list of option
s and list of in-game keys:

Save the completed source and start up ASMONE & fill in the options: (explained in picture)

Ok, we now got the trainer menu as a RELOC EXE file. Which is not helping us much, as the game is using trackloading..
Next is packing & relocating the trainer, so it can be track loaded. For this, we use Tetrapack.

Fill in the options:

A quick explanation.

First we choose which memory area the decruncher should reserve. Then how effective to crunch the file.

Then press enter to start the cruncher, screen flashes for a while & cruncher returns. Then we choose the JMP address (start address of trainer menu), set no decrunch color or choose $ 00 for flashing screen when decrunching.

At last we save our packed file as packed. When the file is executed, the trainer menu will be located in memory from address 30000. I just chose this address, 40000 will also do.

Next step is writing trainer to disk & making a track loader for it.
Start by making a copy of original disks. You?ll see that track 1 is faulty. This is because of the copylock protection, cause the MFM data is located here. This is excellent news. Because we included a crack for the game, this track is no longer used & can be used to fit our trainer menu instead.
Lets start by writing the trainer to disk. Enter AR, insert copy of disk 1 & read out track 1 to address 60000: RT 1 1 60000. The non-used copylock track is now in memory. Insert disk with packed trainer, and load it to address 60000: LM packed,60000. Insert copy of disk 1 again & write track back:
WT 1 1 60000. Trainer menu is now on disk.
Next up, is making a track loader. Read boot block into memory, starting at address 70000: RT 0 1 70000.
Disassemble boot: D 7000C +enter

From offset $ 40 we all ready got a track loader, so we can just copy this. The easiest thing, is to copy whole boot block temp. to address 50000, copy the track loader to start of boot, insert a JSR to trainer, and then copy boot block back after our track loader:

We start by saving all the regs., copy the track loader to offset $ 10, insert a JSR 60020, restore regs. And then copy Boot block back to offset $ 40. Then we need to modify the new track loader, to laod our menu from offset $ 1600 on disk, load it to address $ 60000 (track load address must NOT be the same as depack address (30000) as file would overwrite itself then). JSR address is set to 60020, as first 20 bytes of the file is EXE header.
The original copy routine must also be changed, so points to the correct data again:

Finally, correct boot block checksum & write boot block back, see above picture.

0

Publication author

offline 20 years

Rob

0
Comments: 103Publics: 79Registration: 20-07-2004

Subscribe
Notify of
guest

0 Comments
Inline Feedbacks
View all comments
TheSpecialist
TheSpecialist
8 years ago

Nice tutorial ! That level skipping based on looking for TST opcode, lol, too funny 🙂

0
sim
sim
8 years ago

Niiiice, but! Some things I find completely unclear.. For ex. Once you are talking about “a sweeter way” (using EOR.B) and in the source you use “MOVE.B #$4A,(A0)”. But still you use EOR in TOG routine(s)… What was not too clear neither, was all the “HOOKing” JMP stuff (i.e. MOVE.L #$ 4EF80160,$76322). Not properly, in my opinion, described. All the CRACK routine is quite unclear too (image25.png and $76322 issues). The $78078, $76342 both show all of the sudden, with not being previously mentionned nor disassembled. But anyway, I learnt some stuff, found out what I did not know back… Read more »

WayneK
17 years ago

Nice work -Rob-, very good tutorial!

0
DLFRSILVER
17 years ago

Yippe you strike aggainnn ^^

0
Flasher
17 years ago

Great tutorial, excellent!

0
Authorization
*
*

This site is protected by reCAPTCHA and the Google Privacy Policy and Terms of Service apply.

Registration
*
*
*

This site is protected by reCAPTCHA and the Google Privacy Policy and Terms of Service apply.

Password generation

This site is protected by reCAPTCHA and the Google Privacy Policy and Terms of Service apply.

0
Would love your thoughts, please comment.x
()
x