Skip to content

Commit

Permalink
implemented get_news()
Browse files Browse the repository at this point in the history
  • Loading branch information
msperlin committed Sep 3, 2024
1 parent ed8a70d commit 207f24e
Show file tree
Hide file tree
Showing 7 changed files with 217 additions and 3 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
Package: eodhdR2
Type: Package
Title: Official R API for Fetching Data from 'EODHD'
Version: 0.5.0
Version: 0.5.1
Authors@R: c(
person(given = c("Marcelo", "S."),
family = "Perlin",
Expand Down
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ export(get_demo_token)
export(get_dividends)
export(get_exchanges)
export(get_fundamentals)
export(get_news)
export(get_prices)
export(get_splits)
export(get_tickers)
Expand Down
6 changes: 5 additions & 1 deletion NEWS.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
## Version 0.5 (2024-08-08)
## Version 0.5.1 (2024-09-03)

- implemented `get_news()`

## Version 0.5.0 (2024-08-08)

- first version on CRAN
2 changes: 1 addition & 1 deletion R/cache.R
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@ write_cache <- function(x, f_out) {

readr::write_rds(x, f_out)

cli::cli_alert_info("cache file {f_out} saved")
cli::cli_alert_info("cache file {basename(f_out)} saved")

return(invisible(TRUE))

Expand Down
133 changes: 133 additions & 0 deletions R/news.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,133 @@
#' Retrieves news for a given ticker and exchange
#'
#' This function will query the news point of eodhd and return all news for a user
#' supplied time period.
#'
#' @inheritParams get_fundamentals
#' @param first_date the first date to fetch news. The function will keep querying the api
#' until this date is reached. Default is previous three months.
#' @param last_date the last date to fetch news. Default is today.
#' @param offset_delta how much to change offset in each iterations (higher values will result
#' in more query time, but less queries). Default is 500.
#'
#' @return A dataframe with news events and sentiments
#' @export
#'
#' @examples
#' \dontrun{
#' set_token(get_demo_token())
#' df_news <- get_news(ticker = "AAPL", exchange = "US")
#' }
get_news <- function(ticker = "AAPL",
exchange = "US",
first_date = Sys.Date() - 3*30,
last_date = Sys.Date(),
offset_delta = 500,
cache_folder = get_default_cache(),
check_quota = TRUE) {

cli::cli_h1("retrieving news data for ticker {ticker}|{exchange}")

if (check_quota) {
get_quota_status()
}

token <- get_token()

first_date <- as.Date(first_date)
last_date <- as.Date(last_date)

f_out <-get_cache_file(ticker, exchange, cache_folder,
paste0("news_",
first_date, '_',
last_date))

if (fs::file_exists(f_out)) {

df_out <- read_cache(f_out)

return(df_out)
}

i_query <- 1
this_offset <- 0
l_news <- list()
while (TRUE) {
cli::cli_alert_info("query #{i_query} | offset = {this_offset}")

url <- glue::glue(
paste0('{get_base_url()}/news?s=',
'{ticker}.{exchange}&',
'from={as.character(first_date)}&',
'to={as.character(last_date)}&',
'offset={this_offset}&',
'limit={offset_delta}&',
'api_token={token}&fmt=json'
)
)

content <- query_api(url)

if (content == "[]") {
cli::cli_alert_warning("cant find any more data..")
break()
}

this_news <- jsonlite::fromJSON(content) |>
dplyr::mutate(
ticker = ticker,
exchange = exchange
)

vec_symbols <- this_news$symbols |>
purrr::map_chr(paste0, collapse = ", ")

vec_tags <- this_news$tags |>
purrr::map_chr(paste0, collapse = ", ")

sentiment <- this_news$sentiment
names(sentiment) <- paste0("sentiment_", names(sentiment) )

this_news <- jsonlite::fromJSON(content) |>
dplyr::select(-sentiment) |>
dplyr::mutate(
date = as.POSIXct(date),
ticker = ticker,
exchange = exchange,
symbols = vec_symbols,
tags = vec_tags
) |>
dplyr::bind_cols(sentiment)

query_last_date <- max(this_news$date)
n_rows <- nrow(this_news)

cli::cli_alert_success(
"\tgot {n_rows} news | last date: {query_last_date}"
)

i_query <- i_query + 1
this_offset <- this_offset + offset_delta

l_news[[i_query]] <- this_news

if (query_last_date <= first_date) {
cli::cli_alert_warning("current date is lower than first date.. exiting loop.")

break()

}

}

df_news <- l_news |>
purrr::list_rbind()

write_cache(df_news, f_out)

cli::cli_alert_success("got {nrow(df_news)} rows of news from {min(df_news$date)} to {max(df_news$date)}")

return(df_news)

}

49 changes: 49 additions & 0 deletions man/get_news.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

27 changes: 27 additions & 0 deletions tests/testthat/test-news.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,27 @@
test_that("news", {

# test relies on calling api (we skip it on cran to save network bandwith)
skip_if_offline()
skip_on_cran() # too heavy for cran

suppressMessages({
set_token()

df_news1 <- get_news(
ticker = "AAPL",
exchange = "US"
)

expect_true(nrow(df_news1) > 0)

# run it again for testing local cache
df_news2 <- get_news(
ticker = "AAPL",
exchange = "US"
)

expect_true(identical(df_news1, df_news2))


})
})

0 comments on commit 207f24e

Please sign in to comment.