commit 5ab9b4821580694d9c5d459c801d5646f85d79e6
parent c52ab117f08872f658ce0b25ed828b6e51137297
Author: JayVii <jayvii[AT]posteo[DOT]de>
Date: Fri, 10 May 2024 16:19:24 +0200
cleanup script
Diffstat:
M | yt.R | | | 109 | +++++++++++++------------------------------------------------------------------ |
1 file changed, 18 insertions(+), 91 deletions(-)
diff --git a/yt.R b/yt.R
@@ -14,7 +14,15 @@ if (!require("rjson")) { install.packages("rjson"); library("rjson") }
channels <- as.character(
read.csv(file = "./url.csv", header = TRUE, sep = ",")$url
)
-data <- matrix(data = NA, nrow = 1, ncol = 7, dimnames = list(NULL, c("title", "url", "author", "date", "time", "vid", "img")))
+data <- matrix(
+ data = NA,
+ nrow = 1,
+ ncol = 7,
+ dimnames = list(
+ NULL,
+ c("title", "url", "author", "date", "time", "vid", "img")
+ )
+)
# functions --------------------------------------------------------------------
@@ -49,92 +57,14 @@ fetch.yt <- function(channel) {
return(video_dat)
}
-fetch.tw <- function(channel) {
-
- channel_data <- tidyfeed(
- channel,
- clean_tags = TRUE,
- list = TRUE,
- parse_dates = FALSE
- )
-
- video_dat <- data.frame(
- title = channel_data$entries$item_title,
- author = channel_data$meta$feed_title,
- url = channel_data$entries$item_link,
- date = channel_data$entries$item_pub_date %>%
- as.Date(format = "%a, %d %b %Y %H:%M:%S") %>%
- as.character(),
- time = channel_data$entries$item_pub_date %>%
- gsub(pattern = "^.*\\d{4} ", replacement = ""),
- vid = NA,
- img = paste0(
- "https://static-cdn.jtvnw.net/previews-ttv/live_user_",
- channel_data$meta$feed_title,
- "-853x480.jpg"
- )
- )
-
- return(video_dat)
-}
-
-# fetch data -------------------------------------------------------------------
-#invdata <- fromJSON(file = "https://api.invidious.io/instances.json?sort_by=type,health") %>%
-# lapply(X = ., FUN = function(x) {
-# c(url = x[[1]], health = x[[2]]$monitor$statusClass)
-# })
-#invdomains <- character(0)
-#for (i in seq_along(invdata)) {
-# if (!is.null(invdata[[i]]["health"])) {
-# invdomains[i] <- ifelse(invdata[[i]]["health"] == "success", invdata[[i]]["url"], NA)
-# }
-#}
-#invdomains <- as.character(na.omit(invdomains))
-#invspeed <- sapply(X = invdomains, FUN = function(x) {
-# cat("Test Speed of", x, "\n")
-# tryCatch(
-# mean(ping(x, count = 3, timeout = 1)),
-# error = function(e) NA
-# )
-#})
-#
-#invweight <- 1 - (invspeed / (max(invspeed, na.rm = TRUE) + 1))
-#invweight[is.na(invweight)] <- 0
-
-cat("DONE!\n")
-
for (i in seq_along(channels)) {
channel <- channels[i]
- cat(paste("Fetching:", as.character(channel), "\n"))
+ cat(paste("Fetching:", as.character(channel)))
video_dat <- NULL
-
- if (length(grep(x = channel, pattern = "youtube\\.com|youtu\\.be")) > 0) {
- #domain <- sample(x = invdomains, size = 1, prob = invweight)
- #channel <- sub(
- # x = channel,
- # pattern = "^.*channel_id=",
- # replacement = paste0("https://", domain, "/feed/channel/")
- #)
- video_dat <- tryCatch(fetch.yt(channel), error = function(e) NULL)
- #if (!is.null(video_dat$url)) {
- # video_dat$url <- paste0(
- # video_dat$url,
- # paste0(
- # "&autoplay=1",
- # "&quality=hd720",
- # "&dark_mode=true",
- # "&thin_mode=false",
- # "&continue=1"
- # )
- # )
- #}
- } else
- if (length(grep(x = channel, pattern = "twitchrss.appspot.com")) > 0) {
- video_dat <- tryCatch(fetch.tw(channel), error = function(e) NULL)
- }
+ video_dat <- tryCatch(fetch.yt(channel), error = function(e) NULL)
failed <- TRUE
if (!is.null(video_dat)) {
@@ -143,7 +73,11 @@ for (i in seq_along(channels)) {
failed <- FALSE
}
}
- if (failed) { cat("FAILED!\n") }
+ if (failed) {
+ cat("FAILED!\n")
+ } else {
+ cat("OK!\n")
+ }
}
# edit data --------------------------------------------------------------------
@@ -162,13 +96,6 @@ dates <- gsub(x = data[, 4], pattern = "-", replacement = "") %>% as.numeric()
times <- gsub(x = data[, 5], pattern = ":", replacement = "") %>% as.numeric()
data <- data[rev(order(dates, times, na.last = FALSE)), ]
-# setting platform
-# yt_icon <- "<svg style='width:1em;' viewBox='0 0 24 24'><path fill='currentColor' d='M10,15L15.19,12L10,9V15M21.56,7.17C21.69,7.64 21.78,8.27 21.84,9.07C21.91,9.87 21.94,10.56 21.94,11.16L22,12C22,14.19 21.84,15.8 21.56,16.83C21.31,17.73 20.73,18.31 19.83,18.56C19.36,18.69 18.5,18.78 17.18,18.84C15.88,18.91 14.69,18.94 13.59,18.94L12,19C7.81,19 5.2,18.84 4.17,18.56C3.27,18.31 2.69,17.73 2.44,16.83C2.31,16.36 2.22,15.73 2.16,14.93C2.09,14.13 2.06,13.44 2.06,12.84L2,12C2,9.81 2.16,8.2 2.44,7.17C2.69,6.27 3.27,5.69 4.17,5.44C4.64,5.31 5.5,5.22 6.82,5.16C8.12,5.09 9.31,5.06 10.41,5.06L12,5C16.19,5 18.8,5.16 19.83,5.44C20.73,5.69 21.31,6.27 21.56,7.17Z' /></svg>"
-# tw_icon <- "<svg style='width:1em;' viewBox='0 0 24 24'><path fill='currentColor' d='M11.64 5.93H13.07V10.21H11.64M15.57 5.93H17V10.21H15.57M7 2L3.43 5.57V18.43H7.71V22L11.29 18.43H14.14L20.57 12V2M19.14 11.29L16.29 14.14H13.43L10.93 16.64V14.14H7.71V3.43H19.14Z' /></svg>"
-# platform <- rep(x = "unknown", times = nrow(data))
-# platform[grep(x = data[, "url"], pattern = "youtube")] <- yt_icon
-# platform[grep(x = data[, "url"], pattern = "twitch")] <- tw_icon
-
# construct per user HTML -----------------------------------------------------
channels <- na.omit(data[, "author"]) %>%
@@ -241,7 +168,7 @@ top_mainfeed <- paste0("<details>\n<summary class=\"button\">Channel List</summa
bottom <- paste0("</main>\n</body>\n</html>")
# print files -------------------------------------------------------------------
-sink("/var/www/video.jayvii.de/index.html")
+sink("index.html")
cat(
template, "\n",
top, "\n",
@@ -252,7 +179,7 @@ cat(
sink()
for (i in 1:length(entry_pc)) {
- sink(paste0("/var/www/video.jayvii.de/videos_", i, ".html"))
+ sink(paste0("videos_", i, ".html"))
cat(
template, "\n",
top, "\n",