Skip to content

Commit

Permalink
Merge branch 'main' into main
Browse files Browse the repository at this point in the history
  • Loading branch information
JaseZiv committed Nov 12, 2023
2 parents 8b5e30d + 62ce06f commit 6f89f4d
Show file tree
Hide file tree
Showing 2 changed files with 4 additions and 4 deletions.
2 changes: 1 addition & 1 deletion R/get_match_results.R
Original file line number Diff line number Diff line change
Expand Up @@ -83,7 +83,7 @@
suppressWarnings(
season_summary <- season_summary %>%
dplyr::filter(is.na(.data[["Time"]]) | .data[["Time"]] != "Time") %>%
dplyr::mutate(Score = iconv(.data[["Score"]], 'utf-8', 'ascii', sub=' ') %>% stringr::str_squish()) %>%
dplyr::mutate(Score = gsub("\u2013", " ", .data[["Score"]]) %>% stringr::str_squish()) %>%
tidyr::separate(.data[["Score"]], into = c("HomeGoals", "AwayGoals"), sep = " ") %>%
dplyr::mutate(HomeGoals = as.numeric(.data[["HomeGoals"]]),
AwayGoals = as.numeric(.data[["AwayGoals"]]),
Expand Down
6 changes: 3 additions & 3 deletions R/player_market_values.R
Original file line number Diff line number Diff line change
Expand Up @@ -107,12 +107,12 @@ tm_player_market_values <- function(country_name, start_year, league_url = NA) {
player_num <- NA_character_
}
# player names
player_name <- team_data %>% rvest::html_nodes(".hauptlink a") %>% rvest::html_text() %>% stringr::str_squish()
player_name <- team_data %>% rvest::html_nodes(".inline-table a") %>% rvest::html_text() %>% stringr::str_squish()
if(length(player_name) == 0) {
player_name <- NA_character_
}
# player_url
player_url <- team_data %>% rvest::html_nodes(".hauptlink a") %>% rvest::html_attr("href") %>%
player_url <- team_data %>% rvest::html_nodes(".inline-table a") %>% rvest::html_attr("href") %>%
paste0(main_url, .)
if(length(player_url) == 0) {
player_url <- NA_character_
Expand Down Expand Up @@ -225,7 +225,7 @@ tm_player_market_values <- function(country_name, start_year, league_url = NA) {
dplyr::mutate(date_joined = .tm_fix_dates(.data[["date_joined"]]),
contract_expiry = .tm_fix_dates(.data[["contract_expiry"]])) %>%
tidyr::separate(., player_birthday, into = c("Month", "Day", "Year"), sep = " ", remove = F) %>%
dplyr::mutate(player_age = sub(".*(?:\\((.*)\\)).*|.*", "\\1", .data[["Year"]]),
dplyr::mutate(player_age = gsub(".*\\(", "", .data[["player_birthday"]]) %>% gsub("\\)", "", .),
Day = gsub(",", "", .data[["Day"]]) %>% as.numeric(),
Year = as.numeric(gsub("\\(.*", "", .data[["Year"]])),
Month = match(.data[["Month"]], month.abb),
Expand Down

0 comments on commit 6f89f4d

Please sign in to comment.