Allow more trainer parties, with individual DVs, stat experience, nicknames, variable teams, etc - pret/pokecrystal GitHub Wiki

The NPC trainer teams in pokecrystal are fairly limited: their Pokémon can hold items and have custom movesets, but they cannot have nicknames, custom DVs (so enemy Pokémon can't be shiny or have well-typed Hidden Power), or custom stat experience. The trainer party data is also stored in a single ROM bank, which limits how many teams you can have; and the code for reading teams is repetitive and hard to edit.

This tutorial will fix all of those problems.

(The code for this feature was adapted from Pokémon Polished Crystal.)

Contents

  1. Refactor trainer types to use bit flags
  2. Add a trainer type flag for nicknames
  3. Add a trainer type flag for DVs
  4. Add a trainer type flag for stat experience
  5. Allow trainer data to be stored in multiple banks
  6. Add a trainer type flag for variable parties
  7. Add a trainer type flag for happiness
  8. Add a trainer type flag for randomized parties

1. Refactor trainer types to use bit flags

Each enemy trainer has one to six Pokémon, with individual data depending on the trainer type:

  • TRAINERTYPE_NORMAL: level, species
  • TRAINERTYPE_MOVES: level, species, four moves
  • TRAINERTYPE_ITEM: level, species, held item
  • TRAINERTYPE_ITEM_MOVES: level, species, held item, four moves

Clearly there's a lot of shared data across those four types. But if you look at ReadTrainerParty in engine/battle/read_trainer_party.asm, you'll see that each trainer type has a totally separate routine for reading their data, so there are four identical chunks of code for reading the level and species, two for the moves, and two for the items.

An alternative is to treat the trainer type byte as a set of bit flags. Without any bits set, their Pokémon will just have a level and species; but then one bit will toggle reading of held items, one for movesets, and six more bits will be available for other new kinds of data.

Edit constants/trainer_data_constants.asm:

-; TrainerTypes indexes (see engine/battle/read_trainer_party.asm)
-	const_def
-	const TRAINERTYPE_NORMAL
-	const TRAINERTYPE_MOVES
-	const TRAINERTYPE_ITEM
-	const TRAINERTYPE_ITEM_MOVES
+; TrainerTypes bits (see engine/battle/read_trainer_party.asm)
+	const_def
+	const TRAINERTYPE_MOVES_F ; 0
+	const TRAINERTYPE_ITEM_F  ; 1
+
+; Trainer party types (see data/trainers/parties.asm)
+DEF TRAINERTYPE_NORMAL     EQU 0
+DEF TRAINERTYPE_MOVES      EQU 1 << TRAINERTYPE_MOVES_F
+DEF TRAINERTYPE_ITEM       EQU 1 << TRAINERTYPE_ITEM_F
+DEF TRAINERTYPE_ITEM_MOVES EQU TRAINERTYPE_MOVES | TRAINERTYPE_ITEM

Ironically, the numeric values of the TRAINERTYPE_* constants haven't even changed. They still go from 0 to 3.

Edit ram/wram.asm:

 ...
 NEXTU
 ; catch tutorial dude pack
 wDudeNumItems:: db
 wDudeItems:: ds 2 * 4 + 1
 
 wDudeNumKeyItems:: db
 wDudeKeyItems:: ds 18 + 1

 wDudeNumBalls:: db
 wDudeBalls:: ds 2 * 4 + 1
 ENDU

-	ds 4
+wOtherTrainerType:: db
+	ds 3
 ...

The wOtherTrainerType byte will store the trainer type while their data is being read.

Edit engine/battle/read_trainer_party.asm:

 ReadTrainerParty:
 	...

 	ld a, [hli]
-	ld c, a
-	ld b, 0
+	ld [wOtherTrainerType], a
 	ld d, h
 	ld e, l
-	ld hl, TrainerTypes
-	add hl, bc
-	add hl, bc
-	ld a, [hli]
-	ld h, [hl]
-	ld l, a
-	ld bc, .done
-	push bc
-	jp hl
+	call ReadTrainerPartyPieces

 .done
 	jp ComputeTrainerReward

 .cal2
 	ld a, BANK(sMysteryGiftTrainer)
 	call OpenSRAM
+	ld a, TRAINERTYPE_MOVES
+	ld [wOtherTrainerType], a
 	ld de, sMysteryGiftTrainer
-	call TrainerType2
+	call ReadTrainerPartyPieces
 	call CloseSRAM
 	jr .done

-TrainerTypes:
-; entries correspond to TRAINERTYPE_* constants
-	dw TrainerType1 ; level, species
-	dw TrainerType2 ; level, species, moves
-	dw TrainerType3 ; level, species, item
-	dw TrainerType4 ; level, species, item, moves
-
-TrainerType1:
-; normal (level, species)
-	ld h, d
-	ld l, e
-.loop
-	...
-	jr .loop
-
-TrainerType2:
-; moves
-	ld h, d
-	ld l, e
-.loop
-	...
-	jr .loop
-
-TrainerType3:
-; item
-	ld h, d
-	ld l, e
-.loop
-	...
-	jr .loop
-
-TrainerType4:
-; item + moves
-	ld h, d
-	ld l, e
-.loop
-	...
-	jr .loop
+ReadTrainerPartyPieces:
+	ld h, d
+	ld l, e
+
+.loop
+; end?
+	ld a, [hli]
+	cp -1
+	ret z
+
+; level
+	ld [wCurPartyLevel], a
+
+; species
+	ld a, [hli]
+	ld [wCurPartySpecies], a
+
+; add to party
+	ld a, OTPARTYMON
+	ld [wMonType], a
+	push hl
+	predef TryAddMonToParty
+	pop hl
+
+; item?
+	ld a, [wOtherTrainerType]
+	bit TRAINERTYPE_ITEM_F, a
+	jr z, .no_item
+
+	push hl
+	ld a, [wOTPartyCount]
+	dec a
+	ld hl, wOTPartyMon1Item
+	call GetPartyLocation
+	ld d, h
+	ld e, l
+	pop hl
+
+	ld a, [hli]
+	ld [de], a
+.no_item
+
+; moves?
+	ld a, [wOtherTrainerType]
+	bit TRAINERTYPE_MOVES_F, a
+	jr z, .no_moves
+
+	push hl
+	ld a, [wOTPartyCount]
+	dec a
+	ld hl, wOTPartyMon1Moves
+	call GetPartyLocation
+	ld d, h
+	ld e, l
+	pop hl
+
+	ld b, NUM_MOVES
+.copy_moves
+	ld a, [hli]
+	ld [de], a
+	inc de
+	dec b
+	jr nz, .copy_moves
+
+	push hl
+
+	ld a, [wOTPartyCount]
+	dec a
+	ld hl, wOTPartyMon1
+	call GetPartyLocation
+	ld d, h
+	ld e, l
+	ld hl, MON_PP
+	add hl, de
+
+	push hl
+	ld hl, MON_MOVES
+	add hl, de
+	pop de
+
+	ld b, NUM_MOVES
+.copy_pp
+	ld a, [hli]
+	and a
+	jr z, .copied_pp
+
+	push hl
+	push bc
+	dec a
+	ld hl, Moves + MOVE_PP
+	ld bc, MOVE_LENGTH
+	call AddNTimes
+	ld a, BANK(Moves)
+	call GetFarByte
+	pop bc
+	pop hl
+
+	ld [de], a
+	inc de
+	dec b
+	jr nz, .copy_pp
+.copied_pp
+
+	pop hl
+.no_moves
+
+	jp .loop

We've replaced the four routines TrainerType1, TrainerType2, TrainerType3, and TrainerType4 with a single ReadTrainerPartyPieces routine. If you compare them all side by side, you'll notice how the chunks of ReadTrainerPartyPieces are all taken from the old routines, but now they don't need repeating.

Finally, edit engine/overworld/wildmons.asm:

 RandomPhoneMon:
 ; Get a random monster owned by the trainer who's calling.
 	...

 .skip_name
 	ld a, BANK(Trainers)
 	call GetFarByte
 	inc hl
 	cp "@"
 	jr nz, .skip_name

 	ld a, BANK(Trainers)
 	call GetFarByte
 	inc hl
-	ld bc, 2 ; level, species
-	cp TRAINERTYPE_NORMAL
-	jr z, .got_mon_length
-	ld bc, 2 + NUM_MOVES ; level, species, moves
-	cp TRAINERTYPE_MOVES
-	jr z, .got_mon_length
-	ld bc, 2 + 1 ; level, species, item
-	cp TRAINERTYPE_ITEM
-	jr z, .got_mon_length
-	; TRAINERTYPE_ITEM_MOVES
-	ld bc, 2 + 1 + NUM_MOVES ; level, species, item, moves
-.got_mon_length
+; b = trainer type
+	ld b, a
+; c = mon length
+; All trainers use 2 bytes for level and species
+	ld c, 2
+; TRAINERTYPE_ITEM uses 1 more byte
+	bit TRAINERTYPE_ITEM_F, b
+	jr z, .no_item
+	inc c
+.no_item
+; TRAINERTYPE_MOVES uses NUM_MOVES (4) more bytes
+	bit TRAINERTYPE_MOVES_F, b
+	jr z, .no_moves
+	ld a, NUM_MOVES
+	add c
+	ld c, a
+.no_moves
+; bc = mon length
+	xor a
+	ld b, a

If we stopped here, the code would be cleaner and smaller, but would not do anything new. So let's continue.

2. Add a trainer type flag for nicknames

This will allow enemy trainer parties to define nicknames for their Pokémon.

Edit constants/trainer_data_constants.asm again:

 ; TrainerTypes bits (see engine/battle/read_trainer_party.asm)
 	const_def
 	const TRAINERTYPE_MOVES_F ; 0
 	const TRAINERTYPE_ITEM_F ; 1
+	const TRAINERTYPE_NICKNAME_F ; 2

 ; Trainer party types (see data/trainers/parties.asm)
 DEF TRAINERTYPE_NORMAL     EQU 0
 DEF TRAINERTYPE_MOVES      EQU 1 << TRAINERTYPE_MOVES_F
 DEF TRAINERTYPE_ITEM       EQU 1 << TRAINERTYPE_ITEM_F
 DEF TRAINERTYPE_ITEM_MOVES EQU TRAINERTYPE_MOVES | TRAINERTYPE_ITEM
+DEF TRAINERTYPE_NICKNAME   EQU 1 << TRAINERTYPE_NICKNAME_F

I'm not bothering to define new TRAINERTYPE_* constants for every combination of {moves, item, nickname}. You can just combine flag values, like TRAINERTYPE_NICKNAME | TRAINERTYPE_ITEM for a trainer with Pokémon that have nicknames and held items.

Edit engine/battle/read_trainer_party.asm again:

 ; add to party
 	ld a, OTPARTYMON
 	ld [wMonType], a
 	push hl
 	predef TryAddMonToParty
 	pop hl
+
+; nickname?
+	ld a, [wOtherTrainerType]
+	bit TRAINERTYPE_NICKNAME_F, a
+	jr z, .no_nickname
+
+	push de
+	ld de, wStringBuffer2
+.copy_nickname
+	ld a, [hli]
+	ld [de], a
+	inc de
+	cp "@"
+	jr nz, .copy_nickname
+
+	push hl
+	ld a, [wOTPartyCount]
+	dec a
+	ld hl, wOTPartyMonNicknames
+	ld bc, MON_NAME_LENGTH
+	call AddNTimes
+	ld d, h
+	ld e, l
+	ld hl, wStringBuffer2
+	ld bc, MON_NAME_LENGTH
+	call CopyBytes
+	pop hl
+	pop de
+.no_nickname

 ; item?
 	...

Then edit engine/battle/core.asm:

LoadEnemyMon:
	...

 	ld a, [wTempEnemyMonSpecies]
 	ld [wNamedObjectIndex], a
-
-	call GetPokemonName

 ; Did we catch it?
 	ld a, [wBattleMode]
 	and a
 	ret z

 ; Update enemy nick
+	ld a, [wBattleMode]
+	dec a ; WILD_BATTLE?
+	jr z, .no_nickname
+	ld a, [wOtherTrainerType]
+	bit TRAINERTYPE_NICKNAME_F, a
+	jr z, .no_nickname
+	ld a, [wCurPartyMon]
+	ld hl, wOTPartyMonNicknames
+	ld bc, MON_NAME_LENGTH
+	call AddNTimes
+	ld a, [hl]
+	cp "@"
+	jr nz, .got_nickname
+.no_nickname
+	call GetPokemonName
 	ld hl, wStringBuffer1
+.got_nickname
 	ld de, wEnemyMonNickname
 	ld bc, MON_NAME_LENGTH
 	call CopyBytes

Finally, edit engine/overworld/wildmons.asm again:

 RandomPhoneMon:
 ; Get a random monster owned by the trainer who's calling.
 	...

 	ld a, BANK(Trainers)
 	call GetFarByte
 	inc hl
 ; b = trainer type
 	ld b, a
+; TRAINERTYPE_NICKNAME has uneven length, so always use the first mon
+	bit TRAINERTYPE_NICKNAME_F, b
+	jr nz, .got_mon
 ; c = mon length
 ; All trainers use 2 bytes for level and species
 	ld c, 2
 	...

Now you can give nicknames to enemy Pokémon. If the nickname is just "@", it will use the default species name. Be sure to keep the data in order: level, species, nickname, held item, moves.

For example, here's a party for your rival that give him nicknames, held items, and a new Pokémon:

	db "?@", TRAINERTYPE_NICKNAME | TRAINERTYPE_ITEM
	db  3, RATTATA,    "@",     NO_ITEM
	db  5, TOTODILE,   "JAWS@", BERRY
	db -1 ; end

Which successfully loads in battle:

Screenshot

Note that since −1 ($FF) is the end-of-party marker, you can't use the digit "9" in nicknames because it's equal to $FF (as seen in charmap.asm). If you really need a nickname with "9" in it, you can add a duplicate character that looks just like "9", for example by editing the "『" in gfx/font/font_battle_extra.png (since "『" is unused character $72).

3. Add a trainer type flag for DVs

This will allow enemy trainer parties to define individual DVs for their Pokémon, which not only affects their stats, but also gender, shininess, and Hidden Power type.

Edit constants/trainer_data_constants.asm again:

 ; TrainerTypes bits (see engine/battle/read_trainer_party.asm)
 	const_def
 	const TRAINERTYPE_MOVES_F ; 0
 	const TRAINERTYPE_ITEM_F ; 1
 	const TRAINERTYPE_NICKNAME_F ; 2
+	const TRAINERTYPE_DVS_F ; 3

 ; Trainer party types (see data/trainers/parties.asm)
 DEF TRAINERTYPE_NORMAL     EQU 0
 DEF TRAINERTYPE_MOVES      EQU 1 << TRAINERTYPE_MOVES_F
 DEF TRAINERTYPE_ITEM       EQU 1 << TRAINERTYPE_ITEM_F
 DEF TRAINERTYPE_ITEM_MOVES EQU TRAINERTYPE_MOVES | TRAINERTYPE_ITEM
 DEF TRAINERTYPE_NICKNAME   EQU 1 << TRAINERTYPE_NICKNAME_F
+DEF TRAINERTYPE_DVS        EQU 1 << TRAINERTYPE_DVS_F
+
+DEF PERFECT_DV EQU $11 ; treated as $FF in enemy party data

Again, I'm not bothering to define new TRAINERTYPE_* constants for every combination of {moves, item, nickname, DVs}. You can just combine individual flag values.

Edit engine/battle/read_trainer_party.asm again:

 ; add to party
 	ld a, OTPARTYMON
 	ld [wMonType], a
 	push hl
 	predef TryAddMonToParty
 	pop hl

 ; nickname?
 	ld a, [wOtherTrainerType]
 	bit TRAINERTYPE_NICKNAME_F, a
 	jr z, .no_nickname
 	...
 .no_nickname
+
+; dvs?
+	ld a, [wOtherTrainerType]
+	bit TRAINERTYPE_DVS_F, a
+	jr z, .no_dvs
+
+	push hl
+	ld a, [wOTPartyCount]
+	dec a
+	ld hl, wOTPartyMon1DVs
+	call GetPartyLocation
+	ld d, h
+	ld e, l
+	pop hl
+
+; When reading DVs, treat PERFECT_DV as $ff
+	ld a, [hli]
+	cp PERFECT_DV
+	jr nz, .atk_def_dv_nonzero
+	ld a, $ff
+.atk_def_dv_nonzero
+	ld [de], a
+	inc de
+	ld a, [hli]
+	cp PERFECT_DV
+	jr nz, .spd_spc_dv_nonzero
+	ld a, $ff
+.spd_spc_dv_nonzero
+	ld [de], a
+.no_dvs

 ; item?
 	...

 .no_moves
+
+; Custom DVs affect stats, so recalculate them after TryAddMonToParty
+	ld a, [wOtherTrainerType]
+	and TRAINERTYPE_DVS
+	jr z, .no_stat_recalc
+
+	push hl
+
+	ld a, [wOTPartyCount]
+	dec a
+	ld hl, wOTPartyMon1MaxHP
+	call GetPartyLocation
+	ld d, h
+	ld e, l
+
+	ld a, [wOTPartyCount]
+	dec a
+	ld hl, wOTPartyMon1StatExp - 1
+	call GetPartyLocation
+
+; recalculate stats
+	ld b, TRUE
+	push de
+	predef CalcMonStats
+	pop hl
+
+; copy max HP to current HP
+	inc hl
+	ld c, [hl]
+	dec hl
+	ld b, [hl]
+	dec hl
+	ld [hl], c
+	dec hl
+	ld [hl], b
+
+	pop hl
+.no_stat_recalc

 	jp .loop

Then edit engine/battle/core.asm again:

 .InitDVs:
-; Trainer DVs
-
-; All trainers have preset DVs, determined by class
-; See GetTrainerDVs for more on that
-	farcall GetTrainerDVs
-; These are the DVs we'll use if we're actually in a trainer battle
 	ld a, [wBattleMode]
 	dec a
-	jr nz, .UpdateDVs
+	jr z, .WildDVs
+
+; Trainer DVs
+	ld a, [wCurPartyMon]
+	ld hl, wOTPartyMon1DVs
+	call GetPartyLocation
+	ld b, [hl]
+	inc hl
+	ld c, [hl]
+	jr .UpdateDVs

+.WildDVs:
 ; Wild DVs
 	...

Finally, edit engine/overworld/wildmons.asm again:

 RandomPhoneMon:
 ; Get a random monster owned by the trainer who's calling.
 	...
 ; c = mon length
 ; All trainers use 2 bytes for level and species
 	ld c, 2
+; TRAINERTYPE_DVS uses 2 more bytes
+	bit TRAINERTYPE_DVS_F, b
+	jr z, .no_dvs
+	inc c
+	inc c
+.no_dvs
 ; TRAINERTYPE_ITEM uses 1 more byte
 	bit TRAINERTYPE_ITEM_F, b
 	jr z, .no_item
 	...

Now you can give custom DVs to enemy Pokémon. Be sure to keep the data in order: level, species, nickname, DVs, held item, moves.

DVs are specified as $AD, $SP, where A = attack, D = defense, S = speed, and P = special, with each one going from $0 to $F (15).

For example, here's a party with custom DVs:

	db "?@", TRAINERTYPE_DVS | TRAINERTYPE_ITEM
	db  3, RATTATA,    $87, $77, NO_ITEM
	db  5, TOTODILE,   ATKDEFDV_SHINY, SPDSPCDV_SHINY, BERRY
	db -1 ; end

Which successfully loads in battle:

Screenshot

Note that since −1 ($FF) is the end-of-party marker, you can't use $FF for any DVs. That's why PERFECT_DV gets turned into $FF, as explained in the comments. It's defined as $11 since you're unlikely to want those specific DVs, but you can use any value for it. If you want to do PERFECT_DV EQU $00, you should also replace the two cp PERFECT_DV lines with and a since that's a more efficient way to check for zero.

4. Add a trainer type flag for stat experience

This will allow enemy trainer parties to define individual stat experience for their Pokémon, which lets you increase the difficulty better than just raising levels.

Edit constants/trainer_data_constants.asm again:

 ; TrainerTypes bits (see engine/battle/read_trainer_party.asm)
 	const_def
 	const TRAINERTYPE_MOVES_F ; 0
 	const TRAINERTYPE_ITEM_F ; 1
 	const TRAINERTYPE_NICKNAME_F ; 2
 	const TRAINERTYPE_DVS_F ; 3
+	const TRAINERTYPE_STAT_EXP_F ; 4

 ; Trainer party types (see data/trainers/parties.asm)
 DEF TRAINERTYPE_NORMAL     EQU 0
 DEF TRAINERTYPE_MOVES      EQU 1 << TRAINERTYPE_MOVES_F
 DEF TRAINERTYPE_ITEM       EQU 1 << TRAINERTYPE_ITEM_F
 DEF TRAINERTYPE_ITEM_MOVES EQU TRAINERTYPE_MOVES | TRAINERTYPE_ITEM
 DEF TRAINERTYPE_NICKNAME   EQU 1 << TRAINERTYPE_NICKNAME_F
 DEF TRAINERTYPE_DVS        EQU 1 << TRAINERTYPE_DVS_F
+DEF TRAINERTYPE_STAT_EXP   EQU 1 << TRAINERTYPE_STAT_EXP_F

 DEF PERFECT_DV EQU $11 ; treated as $FF in enemy party data
+DEF PERFECT_STAT_EXP EQU $1337 ; treated as $FFFF in enemy party data

Edit engine/battle/read_trainer_party.asm again:

 ; add to party
 	ld a, OTPARTYMON
 	ld [wMonType], a
 	push hl
 	predef TryAddMonToParty
 	pop hl

 ; nickname?
 	ld a, [wOtherTrainerType]
 	bit TRAINERTYPE_NICKNAME_F, a
 	jr z, .no_nickname
 	...
 .no_nickname

 ; dvs?
 	ld a, [wOtherTrainerType]
 	bit TRAINERTYPE_DVS_F, a
 	jr z, .no_dvs
 	...
 .no_dvs
+
+; stat exp?
+	ld a, [wOtherTrainerType]
+	bit TRAINERTYPE_STAT_EXP_F, a
+	jr z, .no_stat_exp
+
+	push hl
+	ld a, [wOTPartyCount]
+	dec a
+	ld hl, wOTPartyMon1StatExp
+	call GetPartyLocation
+	ld d, h
+	ld e, l
+	pop hl
+
+	ld c, NUM_EXP_STATS
+.stat_exp_loop
+; When reading stat experience, treat PERFECT_STAT_EXP as $FFFF
+	ld a, [hl]
+	cp LOW(PERFECT_STAT_EXP)
+	jr nz, .not_perfect_stat_exp
+	inc hl
+	ld a, [hl]
+	cp HIGH(PERFECT_STAT_EXP)
+	dec hl
+	jr nz, .not_perfect_stat_exp
+	ld a, $ff
+rept 2
+	ld [de], a
+	inc de
+	inc hl
+endr
+	jr .continue_stat_exp
+
+.not_perfect_stat_exp
+rept 2
+	ld a, [hli]
+	ld [de], a
+	inc de
+endr
+.continue_stat_exp
+	dec c
+	jr nz, .stat_exp_loop
+.no_stat_exp

 ; item?
 	...

 .no_moves

-; Custom DVs affect stats, so recalculate them after TryAddMonToParty
+; Custom DVs or stat experience affect stats,
+; so recalculate them after TryAddMonToParty
 	ld a, [wOtherTrainerType]
-	and TRAINERTYPE_DVS
+	and TRAINERTYPE_DVS | TRAINERTYPE_STAT_EXP
 	jr z, .no_stat_recalc
 	...
 .no_stat_recalc

 	jp .loop

(If you're using an older version of pokecrystal where NUM_EXP_STATS is not defined, then replace ld c, NUM_EXP_STATS with ld c, 5.)

Then edit engine/battle/core.asm again:

 LoadEnemyMon:
 	...

 ; Fill stats
 	ld de, wEnemyMonMaxHP
 	ld b, FALSE
 	ld hl, wEnemyMonDVs - (MON_DVS - MON_STAT_EXP + 1)
+	ld a, [wBattleMode]
+	cp TRAINER_BATTLE
+	jr nz, .no_stat_exp
+	ld a, [wCurPartyMon]
+	ld hl, wOTPartyMon1StatExp - 1
+	call GetPartyLocation
+	ld b, TRUE
+.no_stat_exp
 	predef CalcMonStats

Finally, edit engine/overworld/wildmons.asm again:

 RandomPhoneMon:
 ; Get a random monster owned by the trainer who's calling.
 	...
 ; c = mon length
 ; All trainers use 2 bytes for level and species
 	ld c, 2
 ; TRAINERTYPE_DVS uses 2 more bytes
 	bit TRAINERTYPE_DVS_F, b
 	jr z, .no_dvs
 	inc c
 	inc c
 .no_dvs
+; TRAINERTYPE_STAT_EXP uses NUM_EXP_STATS * 2 (10) more bytes
+	bit TRAINERTYPE_STAT_EXP_F, b
+	jr z, .no_stat_exp
+	ld a, NUM_EXP_STATS * 2
+	add c
+	ld c, a
+.no_stat_exp
 ; TRAINERTYPE_ITEM uses 1 more byte
 	bit TRAINERTYPE_ITEM_F, b
 	jr z, .no_item
 	...

(Again, if you're using an older version of pokecrystal where NUM_EXP_STATS is not defined, then replace ld a, NUM_EXP_STATS * 2 with ld a, 10.)

Now you can give custom stat experience to enemy Pokémon. Be sure to keep the data in order: level, species, nickname, DVs, stat experience, held item, moves.

Stat experience is specified as five words, not bytes, because each of the five stats (HP, Attack, Defense, Speed, and Special) has two-byte experience going from $0000 to $FFFF (65,535).

For example, here's a party with custom DVs, stat experience, held items, and moves:

	db "?@", TRAINERTYPE_DVS | TRAINERTYPE_STAT_EXP | TRAINERTYPE_ITEM_MOVES
	db  3, RATTATA
		db PERFECT_DV, $de ; atk|def, spd|spc
		dw $0040, $0060, $0020, $0040, $0000 ; hp, atk, def, spd, spc
		db NO_ITEM
		db TACKLE, TAIL_WHIP, BITE, NO_MOVE ; Bite is an egg move
	db  5, TOTODILE
		db ATKDEFDV_SHINY, SPDSPCDV_SHINY ; atk|def, spd|spc
		dw $0000, PERFECT_STAT_EXP, $0000, PERFECT_STAT_EXP, $0000 ; hp, atk, def, spd, spc
		db BERRY
		db SCRATCH, LEER, NO_MOVE, NO_MOVE
	db -1 ; end

Which successfully loads in battle (no screenshot because stat experience isn't visible).

Again, since −1 ($FF) is the end-of-party marker, you can't use stat experience values with $FF in them. That's why PERFECT_STAT_EXP gets turned into $FFFF, as explained in the comments. It's defined as $1337 since you're unlikely to want that specific value, but you can use any value for it. If you want to do PERFECT_STAT_EXP EQU $0000, you should also replace the cp LOW(PERFECT_STAT_EXP) and cp HIGH(PERFECT_STAT_EXP) lines with and a since that's a more efficient way to check for zero.

5. Allow trainer data to be stored in multiple banks

If you're adding more trainers, and more data for those trainers, you'll probably run out of room in the ROM bank. The solution is to split trainer party data across multiple banks.

Edit ram/wram.asm again:

 wOtherTrainerType:: db
+wTrainerGroupBank:: db
-	ds 3
+	ds 2

The wTrainerGroupBank byte will store the trainer group's bank while a trainer's data is being read.

Edit data/trainers/party_pointers.asm:

 TrainerGroups:
 ; entries correspond to trainer classes (see constants/trainer_constants.asm)
-	table_width 2, TrainerGroups
-	dw FalknerGroup
-	...
-	dw MysticalmanGroup
+	table_width 3, TrainerGroups
+	dba FalknerGroup
+	...
+	dba MysticalmanGroup

We're just replacing dw with dba everywhere along with changing the table's length defined by the table_width macro. Each table's entry now has a third byte to declare which bank it's in, instead of expecting all the entries to be in BANK(Trainers).

Edit engine/battle/read_trainer_party.asm again:

+GetNextTrainerDataByte:
+	ld a, [wTrainerGroupBank]
+	call GetFarByte
+	inc hl
+	ret
+
 ReadTrainerParty:
 	...

 	dec a
 	ld c, a
 	ld b, 0
 	ld hl, TrainerGroups
 	add hl, bc
 	add hl, bc
+	add hl, bc
+	ld a, [hli]
+	ld [wTrainerGroupBank], a
 	ld a, [hli]
 	ld h, [hl]
 	ld l, a

 	ld a, [wOtherTrainerID]
 	ld b, a
 .skip_trainer
 	dec b
 	jr z, .got_trainer
 .loop
-	ld a, [hli]
+	call GetNextTrainerDataByte
 	cp -1
 	jr nz, .loop
 	jr .skip_trainer
 .got_trainer

 .skip_name
-	ld a, [hli]
+	call GetNextTrainerDataByte
 	cp "@"
 	jr nz, .skip_name

-	ld a, [hli]
+	call GetNextTrainerDataByte
 	ld [wOtherTrainerType], a
 	ld d, h
 	ld e, l
 	call ReadTrainerPartyPieces
 .done
 	jp ComputeTrainerReward

 .cal2
 	ld a, BANK(sMysteryGiftTrainer)
 	call OpenSRAM
 	ld a, TRAINERTYPE_MOVES
 	ld [wOtherTrainerType], a
 	ld de, sMysteryGiftTrainer
 	call ReadTrainerPartyPieces
 	call CloseSRAM
 	jr .done

 ReadTrainerPartyPieces:
 	ld h, d
 	ld l, e

 .loop
 ; end?
-	ld a, [hli]
+	call GetNextTrainerDataByte
 	cp -1
 	ret z

 ; level
 	ld [wCurPartyLevel], a

 ; species
-	ld a, [hli]
+	call GetNextTrainerDataByte
 	ld [wCurPartySpecies], a

 ; add to party
 	ld a, OTPARTYMON
 	ld [wMonType], a
 	push hl
 	predef TryAddMonToParty
 	pop hl

 ; nickname?
 	ld a, [wOtherTrainerType]
 	bit TRAINERTYPE_NICKNAME_F, a
 	jr z, .no_nickname
 
-	ld a, [hli]
+	call GetNextTrainerDataByte
 	cp "@"
 	jr z, .no_nickname
 
 	push de
 
 	ld de, wStringBuffer2
 	ld [de], a
 	inc de
 .copy_nickname
-	ld a, [hli]
+	call GetNextTrainerDataByte
 	ld [de], a
 	inc de
 	cp "@"
 	jr nz, .copy_nickname

 	push hl
 	ld a, [wOTPartyCount]
 	dec a
 	ld hl, wOTPartyMonNicknames
 	ld bc, MON_NAME_LENGTH
 	call AddNTimes
 	ld d, h
 	ld e, l
 	ld hl, wStringBuffer2
 	ld bc, MON_NAME_LENGTH
 	call CopyBytes
 	pop hl

 	pop de
 .no_nickname

 ; dvs?
 	ld a, [wOtherTrainerType]
 	bit TRAINERTYPE_DVS_F, a
 	jr z, .no_dvs

 	push hl
 	ld a, [wOTPartyCount]
 	dec a
 	ld hl, wOTPartyMon1DVs
 	call GetPartyLocation
 	ld d, h
 	ld e, l
 	pop hl

 ; When reading DVs, treat PERFECT_DV as $FF
-	ld a, [hli]
+	call GetNextTrainerDataByte
 	cp PERFECT_DV
 	jr nz, .atk_def_dv_nonzero
 	ld a, $ff
 .atk_def_dv_nonzero
 	ld [de], a
 	inc de
-	ld a, [hli]
+	call GetNextTrainerDataByte
 	cp PERFECT_DV
 	jr nz, .spd_spc_dv_nonzero
 	ld a, $ff
 .spd_spc_dv_nonzero
 	ld [de], a
 .no_dvs

 ; stat exp?
 	ld a, [wOtherTrainerType]
 	bit TRAINERTYPE_STAT_EXP_F, a
 	jr z, .no_stat_exp

 	push hl
 	ld a, [wOTPartyCount]
 	dec a
 	ld hl, wOTPartyMon1StatExp
 	call GetPartyLocation
 	ld d, h
 	ld e, l
 	pop hl

 	ld c, NUM_EXP_STATS
 .stat_exp_loop
 ; When reading stat experience, treat PERFECT_STAT_EXP as $FFFF
-	ld a, [hl]
+	call GetNextTrainerDataByte
+	dec hl
 	cp LOW(PERFECT_STAT_EXP)
 	jr nz, .not_perfect_stat_exp
 	inc hl
-	ld a, [hl]
+	call GetNextTrainerDataByte
+	dec hl
 	cp HIGH(PERFECT_STAT_EXP)
 	dec hl
 	jr nz, .not_perfect_stat_exp
 	ld a, $ff
 rept 2
 	ld [de], a
 	inc de
 	inc hl
 endr
 	jr .continue_stat_exp

 .not_perfect_stat_exp
 rept 2
-	ld a, [hli]
+	call GetNextTrainerDataByte
 	ld [de], a
 	inc de
 endr
 .continue_stat_exp
 	dec c
 	jr nz, .stat_exp_loop
 .no_stat_exp

 ; item?
 	ld a, [wOtherTrainerType]
 	bit TRAINERTYPE_ITEM_F, a
 	jr z, .no_item

 	push hl
 	ld a, [wOTPartyCount]
 	dec a
 	ld hl, wOTPartyMon1Item
 	call GetPartyLocation
 	ld d, h
 	ld e, l
 	pop hl

-	ld a, [hli]
+	call GetNextTrainerDataByte
 	ld [de], a
 .no_item

 ; moves?
 	ld a, [wOtherTrainerType]
 	bit TRAINERTYPE_MOVES_F, a
 	jr z, .no_moves

 	push hl
 	ld a, [wOTPartyCount]
 	dec a
 	ld hl, wOTPartyMon1Moves
 	call GetPartyLocation
 	ld d, h
 	ld e, l
 	pop hl

 	ld b, NUM_MOVES
 .copy_moves
-	ld a, [hli]
+	call GetNextTrainerDataByte
 	ld [de], a
 	inc de
 	dec b
 	jr nz, .copy_moves

 	...

 	jp .loop

 ...

 Battle_GetTrainerName::
 	ld a, [wInBattleTowerBattle]
 	bit 0, a
 	ld hl, wOTPlayerName
+	ld a, BANK(Battle_GetTrainerName)
+	ld [wTrainerGroupBank], a
 	jp nz, CopyTrainerName
 
 	ld a, [wOtherTrainerID]
 	ld b, a
 	ld a, [wOtherTrainerClass]
 	ld c, a

 GetTrainerName::
 	...

 .not_cal2
 	dec c
 	push bc
 	ld b, 0
 	ld hl, TrainerGroups
 	add hl, bc
 	add hl, bc
+	add hl, bc
+	ld a, [hli]
+	ld [wTrainerGroupBank], a
 	ld a, [hli]
 	ld h, [hl]
 	ld l, a
 	pop bc

 .loop
 	dec b
 	jr z, CopyTrainerName

 .skip
-	ld a, [hli]
+	call GetNextTrainerDataByte
 	cp -1
 	jr nz, .skip
 	jr .loop

 CopyTrainerName:
 	ld de, wStringBuffer1
 	push de
 	ld bc, NAME_LENGTH
-	call CopyBytes
+	ld a, [wTrainerGroupBank]
+	call FarCopyBytes
 	pop de
 	ret

 ...

-INCLUDE "data/trainers/parties.asm"
+INCLUDE "data/trainers/party_pointers.asm"

That's a long series of edits, but they're all basically the same: instead of getting data directly from [hl] in the current ROM bank (i.e. the bank that this code is in), we call GetNextTrainerDataByte to switch banks while reading party data. We also have to account for the new bank byte in each TrainerGroups table entry.

Edit engine/overworld/wildmons.asm again:

 RandomPhoneMon:
 ; Get a random monster owned by the trainer who's calling.
 	farcall GetCallerLocation
 	ld hl, TrainerGroups
 	ld a, d
 	dec a
 	ld c, a
 	ld b, 0
 	add hl, bc
 	add hl, bc
+	add hl, bc
+	ld a, BANK(TrainerGroups)
+	call GetFarByte
+	ld [wTrainerGroupBank], a
+	inc hl
 	ld a, BANK(TrainerGroups)
 	call GetFarWord

 .skip_trainer
 	dec e
 	jr z, .skipped
 .skip
-	ld a, BANK(Trainers)
+	ld a, [wTrainerGroupBank]
 	call GetFarByte
 	inc hl
 	cp -1
 	jr nz, .skip
 	jr .skip_trainer
 .skipped

 .skip_name
-	ld a, BANK(Trainers)
+	ld a, [wTrainerGroupBank]
 	call GetFarByte
 	inc hl
 	cp "@"
 	jr nz, .skip_name

-	ld a, BANK(Trainers)
+	ld a, [wTrainerGroupBank]
 	call GetFarByte
 	inc hl
 	...

 	ld e, 0
 	push hl
 .count_mon
 	inc e
 	add hl, bc
-	ld a, BANK(Trainers)
+	ld a, [wTrainerGroupBank]
 	call GetFarByte
 	cp -1
 	jr nz, .count_mon
 	pop hl

 .rand
 	call Random
 	maskbits PARTY_LENGTH
 	cp e
 	jr nc, .rand

 	inc a
 .get_mon
 	dec a
 	jr z, .got_mon
 	add hl, bc
 	jr .get_mon
 .got_mon

 	inc hl ; species
-	ld a, BANK(Trainers)
+	ld a, [wTrainerGroupBank]
 	call GetFarByte
 	ld [wNamedObjectIndex], a
 	call GetPokemonName
 	ld hl, wStringBuffer1
 	ld de, wStringBuffer4
 	ld bc, MON_NAME_LENGTH
 	jp CopyBytes

Again, we're repeating the same change in many places: replacing BANK(Trainers) with [wTrainerGroupBank], and accounting for the new bank byte in each TrainerGroups table entry.

Edit data/trainers/parties.asm:

-INCLUDE "data/trainers/party_pointers.asm"
-
-Trainers:
 ; Trainer data structure:
-; - db "NAME@", TRAINERTYPE_* constant
+; - db "NAME@", TRAINERTYPE_* constants |ed together
 ; - 1 to 6 Pokémon:
-;    * for TRAINERTYPE_NORMAL:     db level, species
-;    * for TRAINERTYPE_MOVES:      db level, species, 4 moves
-;    * for TRAINERTYPE_ITEM:       db level, species, item
-;    * for TRAINERTYPE_ITEM_MOVES: db level, species, item, 4 moves
+;    * in all cases:              db level, species
+;    * with TRAINERTYPE_NICKNAME: db "NICKNAME@"
+;    * with TRAINERTYPE_DVS:      db atk|def dv, spd|spc dv
+;    * with TRAINERTYPE_STAT_EXP: dw hp, atk, def, spd, spc
+;    * with TRAINERTYPE_ITEM:     db item
+;    * with TRAINERTYPE_MOVES:    db move 1, move 2, move 3, move 4
+;    (TRAINERTYPE_ITEM_MOVES is just TRAINERTYPE_ITEM | TRAINERTYPE_MOVES)
 ; - db -1 ; end
+
+SECTION "Enemy Trainer Parties 1", ROMX

 FalknerGroup:
 	...

BANK(Trainers) is now meaningless and unused, so we can simply remove that label.

All the parties are in the same section, "Enemy Trainer Parties 1", but of course you can now create more. Just don't split a group across multiple sections.

(I took this opportunity to also update the documentation, given our previous changes to the party data structure.)

Finally, edit main.asm:

 SECTION "Enemy Trainers", ROMX

 INCLUDE "engine/battle/ai/items.asm"
 INCLUDE "engine/battle/ai/scoring.asm"
 INCLUDE "engine/battle/read_trainer_attributes.asm"
 INCLUDE "engine/battle/read_trainer_party.asm"
+
+
+INCLUDE "data/trainers/parties.asm"

Since engine/battle/read_trainer_party.asm doesn't INCLUDE data/trainers/parties.asm any more, we have to do so here. And since data/trainers/parties.asm has its own SECTION headings, we don't need one before it in main.asm.

Anyway, we're done now. Just like step 1, the game doesn't do anything new, but the code has become more extensible.

6. Add a trainer type flag for variable parties

In this step we'll add a special flag to define variable parties for the same trainer, which will vary depending on the player's number of badges. Let's edit constants/trainer_data_constants.asm:

 ; TrainerTypes bits (see engine/battle/read_trainer_party.asm)
 	const_def
 	const TRAINERTYPE_MOVES_F ; 0
 	const TRAINERTYPE_ITEM_F ; 1
 	const TRAINERTYPE_NICKNAME_F ; 2
 	const TRAINERTYPE_DVS_F ; 3
	const TRAINERTYPE_STAT_EXP_F ; 4
+	const TRAINERTYPE_VARIABLE_F ; 5

 ; Trainer party types (see data/trainers/parties.asm)
 DEF TRAINERTYPE_NORMAL     EQU 0
 DEF TRAINERTYPE_MOVES      EQU 1 << TRAINERTYPE_MOVES_F
 DEF TRAINERTYPE_ITEM       EQU 1 << TRAINERTYPE_ITEM_F
 DEF TRAINERTYPE_ITEM_MOVES EQU TRAINERTYPE_MOVES | TRAINERTYPE_ITEM
 DEF TRAINERTYPE_NICKNAME   EQU 1 << TRAINERTYPE_NICKNAME_F
 DEF TRAINERTYPE_DVS        EQU 1 << TRAINERTYPE_DVS_F
 DEF TRAINERTYPE_STAT_EXP   EQU 1 << TRAINERTYPE_STAT_EXP_F
+DEF TRAINERTYPE_VARIABLE   EQU 1 << TRAINERTYPE_VARIABLE_F

 DEF PERFECT_DV EQU $11 ; treated as $FF in enemy party data
 DEF PERFECT_STAT_EXP EQU $1337 ; treated as $FFFF in enemy party data

And edit engine/battle/read_trainer_party.asm again:

ReadTrainerPartyPieces:
	ld h, d
	ld l, e

+; Variable?
+	bit TRAINERTYPE_VARIABLE_F, a
+	jr z, .not_variable
+	; get badge count in c
+	push hl
+	ld hl, wBadges
+	ld b, 2
+	call CountSetBits
+	pop hl
+	; Skip that many $fe delimiters
+.outerloop
+	ld a, c
+	and a
+	jr z, .continue
+.innerloop
+	call GetNextTrainerDataByte
+	cp $fe
+	jr nz, .innerloop
+	dec c
+	jr .outerloop
+
+.continue
+	; Get trainer type of variable stage
+	call GetNextTrainerDataByte
+	ld [wOtherTrainerType], a
+	; fallthrough
+.not_variable
 .loop
 ; end?
	call GetNextTrainerDataByte
	cp -1
	ret z
+	cp $fe
+	ret z

 ; level
	ld [wCurPartyLevel], a
	...

As an example, let's show how it'd work with Falkner:

 FalknerGroup:
	; FALKNER (1)
	db "Falkner@", TRAINERTYPE_VARIABLE

	; No badges 
	db TRAINERTYPE_MOVES
	db 7, PIDGEY, 		TACKLE, MUD_SLAP, NO_MOVE, NO_MOVE
	db 9, PIDGEOTTO,	TACKLE, MUD_SLAP, GUST, NO_MOVE
	db $fe ; delimiter

	...

	; Six badges
	db TRAINERTYPE_ITEM_MOVES
	db 33, PIDGEOTTO, NO_ITEM, 	MUD_SLAP, FLY, QUICK_ATTACK, WING_ATTACK
	db 35, PIDGEOT, SHARP_BEAK,	MUD_SLAP, FLY, QUICK_ATTACK, WING_ATTACK
	db $fe ; delimiter

	...

	; 16 badges
	db TRAINERTYPE_ITEM_MOVES
	db 58, PIDGEOT, NO_ITEM, 	MUD_SLAP, FLY, QUICK_ATTACK, WING_ATTACK
	db 60, PIDGEOT, SHARP_BEAK, MUD_SLAP, FLY, QUICK_ATTACK, WING_ATTACK
	db -1 ; end

Now the enemy trainer's team will vary depending on how many badges you have. A few things to note about this:

  • One trainer ID applies to all 17 parties, depending on your badge count. So you don't have to repeat the trainer's name 17 times.
  • Each party can have its own actual type (normal, item, moves, etc.).
  • Each stage ends in $fe (except the last one ends in $ff) so you cannot use it for individual DV values (unless you change the delimiter's value, of course).

If this effect is applied to a trainer that calls your on the PokeGear, it will cause them to refer to their Pokemon with inappropriate or glitched names. Depending on the variable you use, you will need to write handling in RandomPhoneMon: in engine/overworld/wildmons.asm to fix it. The following should fix the use case above.

	ld a, [wTrainerGroupBank]
	call GetFarByte
	inc hl
; b = trainer type
	ld b, a

+; TRAINERTYPE_VARIABLE increment trainer group.
+	bit TRAINERTYPE_VARIABLE_F, b
+	jr z, .no_variance
+	; get badge count in c
+	push hl
+	ld hl, wBadges
+	ld b, 2
+	call CountSetBits
+	pop hl
+	; Skip that many $fe delimiters
+.countbadges
+	ld a, c
+	and a
+	jr z, .lastincrement
+.find_delimiter ;Find delimiter then load next byte
+	ld a, [wTrainerGroupBank]
+	call GetFarByte
+	inc hl
+	cp $fe
+	jr nz, .find_delimiter
+	dec c
+	jr .countbadges
+.lastincrement
+	ld a, [wTrainerGroupBank]
+	call GetFarByte
+	inc hl
+	ld b, a
+.no_variance

; c = mon length
; All trainers use 2 bytes for level and species

[...]

.count_mon
	inc e
	add hl, bc
	ld a, [wTrainerGroupBank]
	call GetFarByte
+	cp $fe
+	jr z, .delimiter
	cp -1
	jr nz, .count_mon
+.delimiter
	pop hl

7. Add a trainer type flag for happiness

Normally all enemy Pokémon have base happiness (70), including trainers, so in this step we'll be able to give trainer parties different happiness values for each Pokémon, so that one Pokémon can have max power Return and another max power Frustration. Let's edit constants/trainer_data_constants.asm to add a new trainer type flag:

 ; TrainerTypes bits (see engine/battle/read_trainer_party.asm)
 	const_def
 	const TRAINERTYPE_MOVES_F ; 0
 	const TRAINERTYPE_ITEM_F ; 1
 	const TRAINERTYPE_NICKNAME_F ; 2
 	const TRAINERTYPE_DVS_F ; 3
	const TRAINERTYPE_STAT_EXP_F ; 4
	const TRAINERTYPE_VARIABLE_F ; 5
+	const TRAINERTYPE_HAPPINESS_F ; 6

 ; Trainer party types (see data/trainers/parties.asm)
 DEF TRAINERTYPE_NORMAL     EQU 0
 DEF TRAINERTYPE_MOVES      EQU 1 << TRAINERTYPE_MOVES_F
 DEF TRAINERTYPE_ITEM       EQU 1 << TRAINERTYPE_ITEM_F
 DEF TRAINERTYPE_ITEM_MOVES EQU TRAINERTYPE_MOVES | TRAINERTYPE_ITEM
 DEF TRAINERTYPE_NICKNAME   EQU 1 << TRAINERTYPE_NICKNAME_F
 DEF TRAINERTYPE_DVS        EQU 1 << TRAINERTYPE_DVS_F
 DEF TRAINERTYPE_STAT_EXP   EQU 1 << TRAINERTYPE_STAT_EXP_F
 DEF TRAINERTYPE_VARIABLE   EQU 1 << TRAINERTYPE_VARIABLE_F
+DEF TRAINERTYPE_HAPPINESS  EQU 1 << TRAINERTYPE_HAPPINESS_F

 DEF PERFECT_DV EQU $11 ; treated as $FF in enemy party data
 DEF PERFECT_STAT_EXP EQU $1337 ; treated as $FFFF in enemy party data
+DEF MAX_HAPPINESS EQU $42 ; treated as $FF in enemy party data

Now let's edit engine/battle/read_trainer_party.asm:

 ...
 .no_stat_exp
+; happpiness?
+	ld a, [wOtherTrainerType]
+	bit TRAINERTYPE_HAPPINESS_F, a
+	jr z, .no_happiness
+
+	push hl
+	ld a, [wOTPartyCount]
+	dec a
+	ld hl, wOTPartyMon1Happiness
+	call GetPartyLocation
+	ld d, h
+	ld e, l
+	pop hl
+
+	call GetNextTrainerDataByte
+	cp MAX_HAPPINESS
+	jr nz, .happiness_ok
+	ld a, $ff
+.happiness_ok
+	ld [de], a
+	
+.no_happiness
 ; item?
 ...

Also edit engine/battle/core.asm:

 LoadEnemyMon:
 ...
 .Happiness:
; Set happiness
+	ld a, [wBattleMode]
+	dec a
+	ld a, BASE_HAPPINESS
+	jr z, .load_happiness
+
+	ld a, [wCurPartyMon]
+	ld hl, wOTPartyMon1Happiness
+	call GetPartyLocation
+	ld a, [hl]
+.load_happiness
	ld [wEnemyMonHappiness], a
	...

And then edit engine/overworld/wildmons.asm:

RandomPhoneMon:
 ...
 .no_stat_exp
+; TRAINERTYPE_HAPPINESS uses 1 more byte
+	bit TRAINERTYPE_HAPPINESS_F, b
+	jr z, .no_happiness
+	inc c
+.no_happiness
 ; TRAINERTYPE_ITEM uses 1 more byte
 ...

We're technically done here, but it's also good to edit data/trainers/parties.asm to remember in which order to place the attributes for the TRAINERTYPE_* flags:

 ; Trainer data structure:
 ; - db "NAME@", TRAINERTYPE_* constants |ed together
 ; - 1 to 6 Pokémon:
 ;    * in all cases:              db level, species
 ;    * with TRAINERTYPE_NICKNAME: db "NICKNAME@"
 ;    * with TRAINERTYPE_DVS:      db atk|def dv, spd|spc dv
 ;    * with TRAINERTYPE_STAT_EXP: dw hp, atk, def, spd, spc
+;    * with TRAINERTYPE_HAPPINESS db happiness 
 ;    * with TRAINERTYPE_ITEM:     db item
 ;    * with TRAINERTYPE_MOVES:    db move 1, move 2, move 3, move 4
 ;    (TRAINERTYPE_ITEM_MOVES is just TRAINERTYPE_ITEM | TRAINERTYPE_MOVES)
 ; - db -1 ; end
 ...

Some important notes:

  • We created MAX_HAPPINESS since we can't directly use $ff (end-of-party marker). It's highly doubtful you're gonna use $42, but you can change it to $00 and use and a instead of cp MAX_HAPPINESS to slightly optimize your code.
  • If you're gonna give Return to a Pokémon, setting its happiness to 0–2 will give the move 0 power, dealing no damage. The same goes for Frustration with 253–255 happiness, so if you want to change this behavior you should apply this bugfix.

8. Add a trainer type flag for randomized parties

In this step we'll add a special flag to define trainers with random Pokémon from a given list, similar to Battle Tower trainers.

The team is chosen at the start of the fight, so if the player challenges the same trainer multiple times, the team will change each time.

Edit constants/trainer_data_constants.asm:

  ; TrainerTypes bits (see engine/battle/read_trainer_party.asm)
 	const_def
 	const TRAINERTYPE_MOVES_F ; 0
 	const TRAINERTYPE_ITEM_F ; 1
 	const TRAINERTYPE_NICKNAME_F ; 2
 	const TRAINERTYPE_DVS_F ; 3
	const TRAINERTYPE_STAT_EXP_F ; 4
	const TRAINERTYPE_VARIABLE_F ; 5
	const TRAINERTYPE_HAPPINESS_F ; 6
+	const TRAINERTYPE_RANDOM_F ; 7

 ; Trainer party types (see data/trainers/parties.asm)
 DEF TRAINERTYPE_NORMAL     EQU 0
 DEF TRAINERTYPE_MOVES      EQU 1 << TRAINERTYPE_MOVES_F
 DEF TRAINERTYPE_ITEM       EQU 1 << TRAINERTYPE_ITEM_F
 DEF TRAINERTYPE_ITEM_MOVES EQU TRAINERTYPE_MOVES | TRAINERTYPE_ITEM
 DEF TRAINERTYPE_NICKNAME   EQU 1 << TRAINERTYPE_NICKNAME_F
 DEF TRAINERTYPE_DVS        EQU 1 << TRAINERTYPE_DVS_F
 DEF TRAINERTYPE_STAT_EXP   EQU 1 << TRAINERTYPE_STAT_EXP_F
 DEF TRAINERTYPE_VARIABLE   EQU 1 << TRAINERTYPE_VARIABLE_F
 DEF TRAINERTYPE_HAPPINESS  EQU 1 << TRAINERTYPE_HAPPINESS_F
+DEF TRAINERTYPE_RANDOM     EQU 1 << TRAINERTYPE_RANDOM_F

 DEF PERFECT_DV EQU $11 ; treated as $FF in enemy party data
 DEF PERFECT_STAT_EXP EQU $1337 ; treated as $FFFF in enemy party data
 DEF MAX_HAPPINESS EQU $42 ; treated as $FF in enemy party data

We need to temporarily store some data in ram for this to work correctly.

  • 1 byte for the number of Pokémon in the trainer's team.
  • 1 byte for the total number of possible Pokémon we can get.
  • 6 bytes to store the index of currently chosen Pokémon, to avoid repeats.

Edit ram/wram.asm:


 wOtherTrainerType:: db
 wTrainerGroupBank:: db
+wRandomTrainerNumPokemon:: db
+wRandomTrainerTotalPokemon:: db
+wRandomTrainerRandomNumbers:: ds 6
-	ds 2

 wd430:: ; mobile
 wBattleAction:: db

 wLinkBattleSentAction:: db
 wMapStatus:: db
 wMapEventStatus:: db

 wScriptFlags::
 ; bit 3: run deferred script
 	db
-	ds 1
 wScriptFlags2::
 ; bit 0: count steps
 ; bit 1: coord events
 ; bit 2: warps and connections
 ; bit 4: wild encounters
 ; bit 5: unknown
 	db
 
 wScriptMode:: db
 wScriptRunning:: db
 wScriptBank:: db
 wScriptPos:: dw

 wScriptStackSize:: db
 wScriptStack:: ds 3 * 5
-	ds 1
 wScriptDelay:: db
 
 wDeferredScriptBank::
 wScriptTextBank::
 	db 
 wDeferredScriptAddr::
 wScriptTextAddr::
 	dw
-	ds 1
 wWildEncounterCooldown:: db
 
 wXYComparePointer:: dw
-	ds 4
+	ds 1

Edit engine/battle/read_trainer_party.asm:

 ReadTrainerPartyPieces:
     ...
 .not_variable
 
+; Random?
+	bit TRAINERTYPE_RANDOM_F, a
+	jr z, .not_random
+	call GetNextTrainerDataByte
+	ld [wRandomTrainerNumPokemon], a
+	call GetNextTrainerDataByte
+	ld b, a ; list number, skip this many $ff after bank switch
+	ld a, BANK(RandomPartyLists)
+	ld [wTrainerGroupBank], a
+	ld hl, RandomPartyLists
+.random_skiploop
+	ld a, b
+	and a
+	jr z, .skipdone
+.random_innerskiploop
+	call GetNextTrainerDataByte
+	cp -1
+	jr nz, .random_innerskiploop
+	dec b
+	jr .random_skiploop
+.skipdone
+	call GetNextTrainerDataByte
+	ld [wRandomTrainerTotalPokemon], a
+	push hl
+.start_random
+	ld hl, wRandomTrainerRandomNumbers
+	ld a, [wRandomTrainerTotalPokemon]
+	call RandomRange
+	ld b, a
+	ld a, [wOTPartyCount]
+	ld c, a
+	inc c
+.repeats_loop
+	dec c
+	jr z, .no_repeats
+	ld a, [hli]
+	cp b
+	jr z, .start_random
+	jr .repeats_loop
+.no_repeats
+	ld [hl], b
+	pop hl
+	push hl
+	; skip b $fe delimiters
+.random_skiploop2
+	ld a, b
+	and a
+	jr z, .skipdone2
+.random_innerskiploop2
+	call GetNextTrainerDataByte
+	cp $fe
+	jr nz, .random_innerskiploop2
+	dec b
+	jr .random_skiploop2
+.skipdone2
+.not_random
.loop
; end?
    ...
.no_stat_recalc
+	ld a, [wOtherTrainerType]
+	bit TRAINERTYPE_RANDOM_F, a
+	jr nz, .random_loop
	jp .loop

+.random_loop
+	ld a, [wRandomTrainerNumPokemon]
+	dec a
+	ld [wRandomTrainerNumPokemon], a
+	jp nz, .start_random
+	pop hl
+	ret
...

Since the format for this kind of trainer is completely different from the previous ones, RandomPhoneMon will simply pick the first Pokémon from the list every time.

Edit engine/overworld/wildmons.asm:

 RandomPhoneMon:
    ...
 ; b = trainer type
        ld b, a
+; TRAINERTYPE_RANDOM is a completely different format
+       bit TRAINERTYPE_RANDOM_F, b
+       jr z, .continue_checks
+       inc hl
+       ld a, [wTrainerGroupBank]
+       call GetFarByte
+       ld b, a
+       ld a, BANK(RandomPartyLists)
+       ld [wTrainerGroupBank], a
+       ld hl, RandomPartyLists
+.skip_randoms
+       inc hl
+       ld a, b
+       and a
+       jr z, .got_mon
+.skip_randoms_inner
+       ld a, [wTrainerGroupBank]
+       call GetFarByte
+       inc hl
+       cp -1
+       jr nz, .skip_randoms_inner
+       dec b
+       jr .skip_randoms
+.continue_checks
 ; TRAINERTYPE_NICKNAME has uneven length, so always use the first mon
     bit TRAINERTYPE_NICKNAME_F, b
     ...

Finally, edit data/trainers/parties.asm:

 ; Trainer data structure:
 ; - db "NAME@", TRAINERTYPE_* constants |ed together
 ; - 1 to 6 Pokémon:
 ;    * in all cases:              db level, species
 ;    * with TRAINERTYPE_NICKNAME: db "NICKNAME@"
 ;    * with TRAINERTYPE_DVS:      db atk|def dv, spd|spc dv
 ;    * with TRAINERTYPE_STAT_EXP: dw hp, atk, def, spd, spc
 ;    * with TRAINERTYPE_HAPPINESS db happiness
 ;    * with TRAINERTYPE_ITEM:     db item
 ;    * with TRAINERTYPE_MOVES:    db move 1, move 2, move 3, move 4
 ;    (TRAINERTYPE_ITEM_MOVES is just TRAINERTYPE_ITEM | TRAINERTYPE_MOVES)
 ; - db -1 ; end
+; Random Trainers:
+; - db "NAME@", TRAINERTYPE_RANDOM | other TRAINERTYPE_* constants, number of party pokémon, list constant (defined in constants/trainer_constants.asm)
+; - db -1 ; end
+; Lists of random Pokémon:
+; - db length of list
+; - Pokémon, separated by db $fe
+; - db -1 ; end

    ...
    
 MysticalmanGroup:
 	; MYSTICALMAN (1)
 	db "EUSINE@", TRAINERTYPE_MOVES
 	db 23, DROWZEE,    DREAM_EATER, HYPNOSIS, DISABLE, CONFUSION
 	db 23, HAUNTER,    LICK, HYPNOSIS, MEAN_LOOK, CURSE
 	db 25, ELECTRODE,  SCREECH, SONICBOOM, THUNDER, ROLLOUT
 	db -1 ; end

+SECTION "Random Party Lists", ROMX

+RandomPartyLists::

Lists of random Pokémon are defined in their own section, under RandomPartyLists and constants are used to define which list a trainer uses. This way, different trainers can use the same list and have different numbers of Pokémon in the party.

We can define constants for the lists at the bottom of constants/trainer_constants.asm like this:

 const_def
 const RANDOMLIST_0
 const RANDOMLIST_1
 ; and so on
 ...

Here is an example of a trainer with 3 random starters in their team:

    db "?@", TRAINERTYPE_RANDOM, 3, RANDOMLIST_0
    db -1 ; end
    
    ...
    
 RandomPartyLists::
    ; RANDOMLIST_0
    db 6
    db 10, BULBASAUR,  $fe
    db 10, CHARMANDER, $fe
    db 10, SQUIRTLE,   $fe
    db 10, CHIKORITA,  $fe
    db 10, CYNDAQUIL,  $fe
    db 10, TOTODILE,   $fe
    db -1 ; end

Some notes:

  • Defining a party size greater than the length of the list of random Pokémon will make the code in ReadTrainerPartyPieces loop infinitely, trying to generate a new random number when all options have already been rolled.

  • Since we use both -1($ff) and $fe, as separators, these values cannot be used in Pokémon data. This includes the "8" and "9" characters in nicknames.