Skip to content

Commit

Permalink
US data
Browse files Browse the repository at this point in the history
  • Loading branch information
emanuele-guidotti committed Apr 9, 2020
1 parent 3db7562 commit 7588bcc
Show file tree
Hide file tree
Showing 8 changed files with 192 additions and 14 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
Package: COVID19
Type: Package
Title: Coronavirus COVID-19 (2019-nCoV) Data Acquisition and Visualization
Version: 0.2.3.2
Version: 0.2.3.3
Authors@R: person(given = "Emanuele", family = "Guidotti", email = "[email protected]", role = c("aut", "cre"), comment = c(ORCID = "0000-0002-8961-6623"))
Description: Collects unified and curated datasets of the 2019 Novel Coronavirus COVID-19 (2019-nCoV) epidemic across several trusted sources. The latest data are downloaded in real-time, processed and merged with demographic indicators. The package implements advanced data visualization across the space and the time dimensions by means of animated mapping. Besides worldwide data, the package includes granular data for Italy, Switzerland and the Diamond Princess.
License: GPL-3
Expand Down
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ export(geomap)
export(italy)
export(liechtenstein)
export(switzerland)
export(us)
export(world)
import(ggplot2)
importFrom(dplyr,"%>%")
5 changes: 4 additions & 1 deletion R/diamond.R
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,10 @@
diamond <- function(){

# download
x <- jhuCSSE()
x <- jhuCSSE("global")

# bindings
country <- state <- NULL

# subset
x <- x[x$country=="Diamond Princess",]
Expand Down
43 changes: 32 additions & 11 deletions R/jhuCSSE.R
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
jhuCSSE <- function(){
jhuCSSE <- function(type = "global"){

# data source
repo <- "https://raw.githubusercontent.com/CSSEGISandData/COVID-19/master/csse_covid_19_data/"
Expand All @@ -17,17 +17,28 @@ jhuCSSE <- function(){
colnames(x)[cn %in% c("Longitude", "Long")] <- "lng"
colnames(x)[cn=="Province_State"] <- "state"
colnames(x)[cn=="Country_Region"] <- "country"
colnames(x)[cn=="Population"] <- "pop"

return(x)

}

# files
files = c(
"confirmed" = "time_series_covid19_confirmed_global.csv",
"deaths" = "time_series_covid19_deaths_global.csv",
"tests" = "time_series_covid19_testing_global.csv"
)
# global
if(type=="global"){
files = c(
"confirmed" = "time_series_covid19_confirmed_global.csv",
"deaths" = "time_series_covid19_deaths_global.csv"
)
}

# US
if(type=="US"){
files = c(
"confirmed" = "time_series_covid19_confirmed_US.csv",
"deaths" = "time_series_covid19_deaths_US.csv"
)
}


# download data
data <- NULL
Expand All @@ -40,13 +51,23 @@ jhuCSSE <- function(){
next

x <- clean_colnames(x)
x <- reshape2::melt(x, id = c("state", "country", "lat", "lng"), value.name = names(files[i]), variable.name = "date")
cn <- colnames(x)
id <- c("Combined_Key", "state", "country", "lat", "lng", "pop")
id <- id[id %in% cn]
cn <- (cn %in% id) | !is.na(as.Date(cn, format = "X%m_%d_%y"))

x <- reshape2::melt(x[,cn], id = id, value.name = names(files[i]), variable.name = "date")
x$date <- as.Date(x$date, format = "X%m_%d_%y")

if(!is.null(data))
data <- merge(data, x, all = TRUE, by = c("state", "country", "lat", "lng", "date"))
else
if(!is.null(data)){
if(type=="global")
data <- merge(data, x, all = TRUE, by = c("state", "country", "date"), suffixes = c("",".y"))
if(type=="US")
data <- merge(data, x, all = TRUE, by = c("Combined_Key", "date"), suffixes = c("",".y"))
}
else {
data <- x
}

}

Expand Down
93 changes: 93 additions & 0 deletions R/us.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,93 @@
#' Coronavirus COVID-19 data - United States
#'
#' Tidy format dataset of the 2019 Novel Coronavirus COVID-19 (2019-nCoV) epidemic.
#' US data by state.
#' The data are downloaded in real-time.
#'
#' @seealso \code{\link{world}}, \code{\link{diamond}}, \code{\link{italy}}, \code{\link{switzerland}}, \code{\link{liechtenstein}}
#'
#' @param type one of \code{country} (data by country) or \code{state} (data by state). Default \code{state}, data by state.
#'
#' @details
#' Data pulled from the repository for the 2019 Novel Coronavirus
#' Visual Dashboard operated by the Johns Hopkins University Center for Systems
#' Science and Engineering (JHU CSSE). Also, Supported by ESRI Living Atlas Team
#' and the Johns Hopkins University Applied Physics Lab (JHU APL).
#' This \href{https://github.com/CSSEGISandData/COVID-19}{repository} and its contents herein, including all data, mapping, and analysis,
#' copyright 2020 Johns Hopkins University, all rights reserved, is provided to the
#' public strictly for educational and academic research purposes.
#' The Website relies upon publicly available data from multiple sources,
#' that do not always agree. The Johns Hopkins University hereby disclaims any and
#' all representations and warranties with respect to the Website, including accuracy,
#' fitness for use, and merchantability. Reliance on the Website for medical guidance or
#' use of the Website in commerce is strictly prohibited. Data Sources:
#' \itemize{
#' \item \href{https://www.who.int/}{World Health Organization (WHO)}
#' \item \href{http://3g.dxy.cn/newh5/view/pneumonia}{DXY.cn. Pneumonia. 2020}
#' \item \href{https://bnonews.com/index.php/2020/02/the-latest-coronavirus-cases/}{BNO News}
#' \item \href{http://www.nhc.gov.cn/xcs/yqtb/list_gzbd.shtml}{National Health Commission of the People’s Republic of China (NHC)}
#' \item \href{http://weekly.chinacdc.cn/news/TrackingtheEpidemic.htm}{China CDC (CCDC)}
#' \item \href{https://www.chp.gov.hk/en/features/102465.html}{Hong Kong Department of Health}
#' \item \href{https://www.ssm.gov.mo/portal/}{Macau Government}
#' \item \href{https://sites.google.com/cdc.gov.tw/2019ncov/taiwan?authuser=0}{Taiwan CDC}
#' \item \href{https://www.cdc.gov/coronavirus/2019-ncov/index.html}{US CDC}
#' \item \href{https://www.canada.ca/en/public-health/services/diseases/coronavirus.html}{Government of Canada}
#' \item \href{https://www.health.gov.au/news/coronavirus-update-at-a-glance}{Australia Government Department of Health}
#' \item \href{https://www.ecdc.europa.eu/en/geographical-distribution-2019-ncov-cases}{European Centre for Disease Prevention and Control (ECDC)}
#' \item \href{https://www.moh.gov.sg/covid-19}{Ministry of Health Singapore (MOH)}
#' \item \href{http://www.salute.gov.it/nuovocoronavirus}{Italy Ministry of Health}
#' }
#'
#' @return Return of the internal function \code{\link{covid19}}
#'
#' @examples
#' # data by country
#' x <- us("country")
#'
#' # data by state
#' x <- us("state")
#'
#' @export
#'
us <- function(type = "state"){

# check
if(!(type %in% c("country","state")))
stop("type must be one of 'country', 'state'")

# download data
x <- jhuCSSE("US")

# drop "Grand Princess" and "Diamond Princess"
x <- x[!(x$state %in% c("Grand Princess","Diamond Princess")),]

# bindings
Combined_Key <- country <- state <- date <- lat <- lng <- confirmed <- deaths <- tests <- pop <- NULL

# group by
if(type=="country"){
x <- x %>%
dplyr::group_by(country, date)
}
if(type=="state"){
x <- x %>%
dplyr::group_by(Combined_Key, state, country, date)
}

# aggregate
x <- x %>%
dplyr::summarize(lat = mean(lat, na.rm = TRUE),
lng = mean(lng, na.rm = TRUE),
confirmed = sum(confirmed, na.rm = TRUE),
deaths = sum(deaths, na.rm = TRUE),
tests = sum(tests, na.rm = TRUE),
pop = sum(pop, na.rm = TRUE))


# population info
# x <- merge(x, COVID19::US, by.x = "country", by.y = "id", all.x = TRUE)

# return
return(covid19(x))

}
2 changes: 1 addition & 1 deletion R/world.R
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,7 @@ world <- function(type = "state"){
stop("type must be one of 'country', 'state'")

# download data
x <- jhuCSSE()
x <- jhuCSSE("global")

# drop "Taiwan*" and "Holy See"
x <- x[!(x$country %in% c("Taiwan*","Holy See")),]
Expand Down
Binary file modified data/IT.rda
Binary file not shown.
60 changes: 60 additions & 0 deletions man/us.Rd

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

0 comments on commit 7588bcc

Please sign in to comment.