Introduction
Following my last few posts, in this entry we’ll again work with Fire Emblem Heroes data but on the subject of Object-Oriented Programming (OOP) in R. R has been described before as being a bit awkward with respect to OOP, with 3 different types of class systems: S3, S4 and RC. In this quick post, we will focus on S4 classes and use them to build a generic character class. I’ll be more or less following the order of things displayed in this guide by Hadley Wickham.
Loading packages
library(rvest)
library(knitr)
Character structures
In Fire Emblem Heroes, characters are composed of several different attributes. As we’ve explored in my previous post, heroes possess different movement and weapon types, as well as 5 different stat attributes (Hit Points, Attack, Speed, Defense and Resistance), which determine their prowess in battle.
Additionally, the cast also possess different assist skills (abilities which help in movement, HP recovery, stat increases, etc), special attacks and three passive abilities which vary in effect. There are a few other attributes we could include, but let’s stick to these to keep things simple. The general structure of a character, then, can be thought of as follows:
- Character Name
- Movement Type
- Weapon Type
- Stats
- HP, ATK, SPD, DEF, RES
- HP, ATK, SPD, DEF, RES
- Weapon
- Assist Skill
- Special Attack
- Passives
- A Skill
- B Skill
- C Skill
- A Skill
Collecting data
First of all, we will need some data to populate the character objects we’ll create. To collect data, I’ll be using the rvest
package again as I did in my first post to get our character stats, but this time we’ll be needing to combine some information from different tables to fill all our requirements. Please refer to the first post for a bit more detail on what’s going on here. In addition to getting character stats, I’ll be separating character names into the name and their title, and their weapon type into weapon and color.
url <- "https://feheroes.gamepedia.com/Stats_Table"
webpage <- read_html(url)
max_stats <- webpage %>%
html_table()
max_stats <- as.data.frame(max_stats)
max_stats$WeaponType <- read_html(url) %>%
html_nodes("tr") %>%
html_attr("data-weapon-type")
max_stats$MoveType <- read_html(url) %>%
html_nodes("tr") %>%
html_attr("data-move-type")
max_stats <- max_stats[, -c(1, 3, 4)]
names(max_stats) <- c("FullName", "HP", "ATK", "SPD", "DEF", "RES", "BST", "WeaponType", "MoveType")
max_stats$Color <- sapply(max_stats$WeaponType, function(x) strsplit(x, split=" ")[[1]][1])
max_stats$Weapon <- sapply(max_stats$WeaponType, function(x) strsplit(x, split=" ")[[1]][2])
max_stats$Name <- sapply(max_stats$FullName, function(x) strsplit(x, split=": ")[[1]][1])
max_stats$Title <- sapply(max_stats$FullName, function(x) strsplit(x, split=": ")[[1]][2])
kable(head(max_stats))
FullName | HP | ATK | SPD | DEF | RES | BST | WeaponType | MoveType | Color | Weapon | Name | Title |
---|---|---|---|---|---|---|---|---|---|---|---|---|
Abel: The Panther | 39 | 33 | 32 | 25 | 25 | 154 | Blue Lance | Cavalry | Blue | Lance | Abel | The Panther |
Alfonse: Prince of Askr | 43 | 35 | 25 | 32 | 22 | 157 | Red Sword | Infantry | Red | Sword | Alfonse | Prince of Askr |
Alfonse: Spring Prince | 41 | 35 | 33 | 30 | 18 | 157 | Green Axe | Cavalry | Green | Axe | Alfonse | Spring Prince |
Alm: Hero of Prophecy | 45 | 33 | 30 | 28 | 22 | 158 | Red Sword | Infantry | Red | Sword | Alm | Hero of Prophecy |
Amelia: Rose of the War | 47 | 34 | 34 | 35 | 23 | 173 | Green Axe | Armored | Green | Axe | Amelia | Rose of the War |
Anna: Commander | 41 | 29 | 38 | 22 | 28 | 158 | Green Axe | Infantry | Green | Axe | Anna | Commander |
Now let’s get data about each character’s skills, which includes their weapons, assist skills, special attacks and passives. These are the skills that characters come with by default, but can be inherited from one character to another.
url <- "https://feheroes.gamepedia.com/Skills_table"
webpage <- read_html(url)
skills <- webpage %>%
html_table()
skills <- as.data.frame(skills)
skills <- skills[, -c(1, 3, 4)]
names(skills) <- c("FullName", "WeaponName", "Assist", "Special", "PassiveA", "PassiveB", "PassiveC")
skills$Name <- sapply(skills$FullName, function(x) strsplit(x, split=": ")[[1]][1])
skills$Title <- sapply(skills$FullName, function(x) strsplit(x, split=": ")[[1]][2])
kable(head(skills))
FullName | WeaponName | Assist | Special | PassiveA | PassiveB | PassiveC | Name | Title |
---|---|---|---|---|---|---|---|---|
???: Masked Knight | Valaskjálf | - | - | - | - | - | ??? | Masked Knight |
Abel: The Panther | Brave Lance+ | - | Aegis | HP +5 | Swordbreaker 3 | - | Abel | The Panther |
Alfonse: Prince of Askr | Fólkvangr | - | Sol | Death Blow 3 | - | Spur Atk 3 | Alfonse | Prince of Askr |
Alfonse: Spring Prince | Giant Spoon+ | - | Noontime | Sturdy Blow 2 | - | Def Smoke 3 | Alfonse | Spring Prince |
Alm: Hero of Prophecy | Falchion (Gaiden) | - | Draconic Aura | Attack +3 | Windsweep 3 | - | Alm | Hero of Prophecy |
Amelia: Rose of the War | Slaying Axe+ | - | Sacred Cowl | Earth Boost 3 | - | Armor March 3 | Amelia | Rose of the War |
Interestingly, when we look at the skills
data.frame, we see that it has 8 characters there that aren’t in our max_stats
data.frame. Seven of them are Non-Playable Characters (NPCs) since they are villains, but one of them, Marth: Altean Groom, as of the writing of this post is still unreleased. Let’s remove them from our skills
data.frame:
skills$FullName[!skills$FullName %in% max_stats$FullName]
## [1] "???: Masked Knight" "Helbindi: Savage Scourge"
## [3] "Laegjarn: Sheathed Steel" "Laevatein: Searing Steel"
## [5] "Loki: The Trickster" "Surtr: Ruler of Flame"
## [7] "Veronica: Emblian Princess"
skills <- skills[skills$FullName %in% max_stats$FullName, ]
S4 objects in R
In simple terms, in R, S4 objects are elements which define instances of a given class, and these instances can be given attributes in slots. Therefore, for example, an instance “dog” of a class “pet” can be given the value 4 in the “paws” slot. In our case, we’ll be using slots for each element of a character’s structure we mentioned in the first section.
setClass("hero", representation(Name = 'character',
Title = 'character',
Color = 'character',
MoveType = 'character',
WeaponType = 'character',
Stats = 'list',
Weapon = 'character',
Assist = 'character',
Special = 'character',
PassiveA = 'character',
PassiveB = 'character',
PassiveC = 'character'))
We can define an “initialize” method which can define how our objects should be initiated. In this case, I made it so that hero slots are automatically filled once the class instance is created (the for
loop). This way, we can start making modifications to the object as soon as it is created. For example, in the if
statement I’m making sure that if the object was initialized with a “full name”, that is, a name as well as a title, that these two would be separated and inserted into their own correct slots.
setMethod("initialize", signature = "hero",
function(.Object, ...){
arguments <- list(...)
for(arg_name in names(arguments)){
slot(.Object, arg_name) <- arguments[[arg_name]]
}
if(.Object@Name %in% max_stats$FullName){
name_title <- strsplit(.Object@Name, split = ": ")[[1]]
.Object@Name <- name_title[1]
.Object@Title <- name_title[2]
}
validObject(.Object)
return(.Object)
}
)
## [1] "initialize"
The validObject
function is used so we can check the validity of our object by creating a few rules inside a function which will check the contents of arguments when a hero instance is initialized. To do this, we must redefine our “hero” class and add the validity
argument.
For example, in the check_hero
function below I check whether the given character name is in either the ‘Name’ column or the ‘FullName’ column of the max_stats table. If it is present only in the ‘Name’ column and there are duplicates present, a.k.a. different versions of the same hero, then an error message is thrown, giving the full name of all of the hero’s duplicates, one of which should be inserted instead.
check_hero <- function(object){
errors <- character()
name <- object@Name
title <- object@Title
if(!(name %in% max_stats$Name) & !(name %in% max_stats$FullName)){
msg <- "Invalid character name"
errors <- c(errors, msg)
}
if(sum(max_stats$Name == name) > 1 & length(title) == 0){
dupes <- max_stats$FullName[max_stats$Name == name]
msg <- paste0("Did you mean ",
paste(c(paste0("'", dupes[1:length(dupes)-1], collapse="', "),
"' or ",
paste0("'", dupes[length(dupes)], "'?")),
collapse=""))
errors <- c(errors, msg)
}
if (length(errors) == 0) TRUE else errors
}
setClass("hero", representation(Name = 'character',
Title = 'character',
Color = 'character',
MoveType = 'character',
WeaponType = 'character',
Weapon = 'character',
Stats = 'list',
WeaponName = 'character',
Assist = 'character',
Special = 'character',
PassiveA = 'character',
PassiveB = 'character',
PassiveC = 'character'),
validity = check_hero)
All these things can be a bit daunting, so let’s check some examples:
# New instances of a class can be created with the new() function
not_a_hero <- new("hero", Name="hercule satan") # Throws an invalid character name error
## Error in validObject(.Object): invalid class "hero" object: Invalid character name
lyn <- new("hero", Name="lyn") # Also invalid, since all lowercase names weren't supported
## Error in validObject(.Object): invalid class "hero" object: Invalid character name
lyn <- new("hero", Name="Lyn") # Throws an error since there are (so many) duplicates
## Error in validObject(.Object): invalid class "hero" object: Did you mean 'Lyn: Brave Lady', 'Lyn: Bride of the Plains', 'Lyn: Lady of the Plains', 'Lyn: Lady of the Wind' or 'Lyn: Wind's Embrace'?
lyn <- new("hero", Name="Lyn: Brave Lady") # Works
lyn@Name
## [1] "Lyn"
lyn@Title
## [1] "Brave Lady"
abel <- new("hero", Name = "Abel") # Works, since there are no special hero duplicates for Abel ):
We can see that the error messages above come from the validObject
function, which called our check_hero
function to evaluate the objects we were creating. Had we not called validObject
inside our initialize
method, we could create heroes objects with whichever @Name
and @Title
slots we wanted, which could get messy and complicate things. Also, with this validity, we can add more rules to our initialize
method and automatically populate our objects with the data we obtained previously, such as stats and skills:
setMethod("initialize", signature = "hero",
function(.Object, ...){
arguments <- list(...)
# Fill slots with given info
for(arg_name in names(arguments)){
slot(.Object, arg_name) <- arguments[[arg_name]]
}
# Get name and title for full-named heroes
if(.Object@Name %in% max_stats$FullName){
name_title <- strsplit(.Object@Name, split = ": ")[[1]]
.Object@Name <- name_title[1]
.Object@Title <- name_title[2]
}
# Get title when only Name is provided
if(sum(max_stats$Name == .Object@Name) == 1){
name_title <- max_stats$FullName[max_stats$Name == .Object@Name]
.Object@Title <- strsplit(name_title, split = ": ")[[1]][2]
}
# Use name and title to get weapon type, movement type, color and weapon
slot_names <- c("WeaponType", "MoveType", "Color", "Weapon")
for(slot_name in slot_names){
slot(.Object, slot_name) <- max_stats[, slot_name][max_stats$Name == .Object@Name &
max_stats$Title == .Object@Title]
}
# Get stats
stat_names <- c("HP", "ATK", "SPD", "DEF", "RES")
stat_list <- list()
for(stat_name in stat_names){
stat_list[[stat_name]] <- max_stats[, stat_name][max_stats$Name == .Object@Name &
max_stats$Title == .Object@Title]
}
names(stat_list) <- stat_names
.Object@Stats <- stat_list
# Get skills
skill_names <- c("WeaponName", "Assist", "Special", "PassiveA", "PassiveB", "PassiveC")
for(skill_name in skill_names){
slot(.Object, skill_name) <- skills[, skill_name][max_stats$Name == .Object@Name &
max_stats$Title == .Object@Title]
}
validObject(.Object)
return(.Object)
}
)
## [1] "initialize"
We should probably add some more conditions to our check_hero
function to account for any problems in all the new rules we added to the initialize
method, but for brevity’s sake I’ll skip that.
Now we have a nifty little function for creating hero type objects with quite a bit of info in them! Let’s see it in action:
abel <- new("hero", Name = "Abel")
lyn <- new("hero", Name = "Lyn: Brave Lady")
lyn
## An object of class "hero"
## Slot "Name":
## [1] "Lyn"
##
## Slot "Title":
## [1] "Brave Lady"
##
## Slot "Color":
## [1] "Colorless"
##
## Slot "MoveType":
## [1] "Cavalry"
##
## Slot "WeaponType":
## [1] "Colorless Bow"
##
## Slot "Weapon":
## [1] "Bow"
##
## Slot "Stats":
## $HP
## [1] 35
##
## $ATK
## [1] 33
##
## $SPD
## [1] 35
##
## $DEF
## [1] 18
##
## $RES
## [1] 28
##
##
## Slot "WeaponName":
## [1] "Mulagir"
##
## Slot "Assist":
## [1] "-"
##
## Slot "Special":
## [1] "Draconic Aura"
##
## Slot "PassiveA":
## [1] "Swift Sparrow 2"
##
## Slot "PassiveB":
## [1] "Sacae's Blessing"
##
## Slot "PassiveC":
## [1] "Atk Smoke 3"
We can now easily create a simple battle simulator function to put our heroes into combat and see which one is the best! To do this, we must create a new generic function using the setGeneric
function, and its corresponding method with the setMethod
function:
setGeneric('combat', function(atk_hero, def_hero){
standardGeneric('combat')
})
## [1] "combat"
setMethod('combat', signature('hero'),
function(atk_hero, def_hero){
# Things go here!
}
)
## [1] "combat"
It’s probably worth mentioning that in Fire Emblem Heroes, combat happens between two heroes by comparing the attacking hero’s ATK stat with the defending hero’s DEF stat, and the difference is depleted from the defending hero’s HP. If the defending hero still has remaning HP, it can then counterattack in the same way. Finally, if any of the heroes have 5 or more speed than the other, that hero can then attack the opponent again. There are a few other dynamics involved as well, particularly involving heroes’ skills, but for this post let’s focus on this core mechanic.
setGeneric('combat', function(atk_hero, def_hero){
standardGeneric('combat')
})
## [1] "combat"
setMethod('combat', signature('hero'),
function(atk_hero, def_hero){
hp_atk <- atk_hero@Stats$HP
hp_def <- def_hero@Stats$HP
hp_def <- hp_def - (atk_hero@Stats$ATK - def_hero@Stats$DEF)
if(hp_def <= 0){
return(paste(def_hero@Name, "is defeated!"))
}else{
hp_atk <- hp_atk - (def_hero@Stats$ATK - atk_hero@Stats$DEF)
if(hp_atk <= 0){
return(paste(atk_hero@Name, "is defeated!"))
}
}
if(hp_atk > 0 & hp_def > 0){
if(atk_hero@Stats$SPD - def_hero@Stats$SPD >= 5){
hp_def <- hp_def - (atk_hero@Stats$ATK - def_hero@Stats$DEF)
}else if(def_hero@Stats$SPD - atk_hero@Stats$SPD >= 5){
hp_atk <- hp_atk - (def_hero@Stats$ATK - atk_hero@Stats$DEF)
}
}
if(hp_atk > 0 & hp_def > 0){
return(paste(atk_hero@Name, "survived with", hp_atk, "HP!",
def_hero@Name, "survived with", hp_def, "HP!"))
}else if(hp_atk > 0 & hp_def <= 0){
return(paste(def_hero@Name, "is defeated!"))
}else if(hp_def > 0 & hp_atk <= 0){
return(paste(atk_hero@Name, "is defeated!"))
}
}
)
## [1] "combat"
Just so I don’t have to make this function too overly complex, I’ll just hard code in the attack bonuses each unit gets from their weapons and skills. Abel gets +8 Attack and -5 Speed from his Brave Lance+, while Lyn gets +14 attack from her Mulagir bow. Abel also gets +5 HP from his HP +5 skill, while Lyn gets +4 Attack and Speed from her Swift Sparrow 2 skill.
abel@Stats$ATK <- abel@Stats$ATK + 8
abel@Stats$SPD <- abel@Stats$SPD - 5
abel@Stats$HP <- abel@Stats$HP + 5
lyn@Stats$ATK <- lyn@Stats$ATK + 14
lyn@Stats$ATK <- lyn@Stats$ATK + 4
lyn@Stats$SPD <- lyn@Stats$SPD + 4
Finally, we can test the combat simulator out:
# Abel starts the attack
combat(abel, lyn)
## [1] "Abel is defeated!"
# Lyn starts the attack
combat(lyn, abel)
## [1] "Abel is defeated!"
And the winner in both cases is Lyn! Granted, Brave Lyn is one of the best units in the game, while Abel is just lackluster at best. Nevertheless, we were able to showcase how much simpler it is to use objects for complex functions than it is to just keep querying data.frames all the time. Imagine if every time we had to do something like max_stats[max_stats$Name == "Abel", "HP"]
to get Abel’s HP value or something like that! One could save these values inside a variable, but then we’d just have another data.frame or list; the S4 objects just seem a lot cleaner to me.
We were also admitedly a bit sloppy, as most sources suggest creating functions for accessing the values of an object’s slots, instead of using the @
operator. Furthermore, we didn’t cover the full complexity of a character in the game, including its level, special and special cooldown time, IVs, Sacred Seals, merges, support, etc. However, in any case I hope this was useful as an initial guide to help understand the value and possible use cases of the S4 objects class!