From a4bcf1c5150d7909191cf1f59775109049716bc5 Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Tue, 7 May 2024 11:51:31 -0400 Subject: [PATCH 01/30] add R script for updating fields in signal spreadsheet --- scripts/signal_spreadsheet_updater.R | 805 +++++++++++++++++++++++++++ 1 file changed, 805 insertions(+) create mode 100644 scripts/signal_spreadsheet_updater.R diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R new file mode 100644 index 000000000..45ef5fa61 --- /dev/null +++ b/scripts/signal_spreadsheet_updater.R @@ -0,0 +1,805 @@ +# Load packages +suppressPackageStartupMessages({ + library(epidatr) # Access Delphi API + library(dplyr) # Data handling + library(readr) # Import csv sheet + library(pipeR) # special pipe %>>% + library(glue) # f-string formatting +}) + +options(warn = 1) + + +# COVIDcast metadata +# Metadata documentation: https://cmu-delphi.github.io/delphi-epidata/api/covidcast_meta.html + +metadata <- pub_covidcast_meta() +# Convert `last_update` into a datetime. +# metadata$last_update <- as.POSIXct(metadata$last_update, origin = "1970-01-01") +## If don't want the hours, etc, truncate with `as.Date` +metadata$last_update <- as.Date(as.POSIXct(metadata$last_update, origin = "1970-01-01")) + + +#Patch NCHS-mortality max_time data into metadata, and min_time +source_name = "nchs-mortality" #optional to use this variable +nchs_row_nums = which(metadata$data_source == source_name) + +metadata$min_time <- as.character(metadata$min_time) +metadata$max_time <- as.character(metadata$max_time) +metadata$max_issue <- as.character(metadata$max_issue) + +for (index in nchs_row_nums) { + row = metadata[index, ] + epidata <- pub_covidcast( # epidata is corresponding data set, ie) all counties and dates between min max + source = source_name, + signals = row$signal, + time_type = as.character(row$time_type), + geo_type = as.character(row$geo_type), + geo_values = "*", + time_values = epirange(199001, 203001) + ) + column = epidata$time_value #col variable is optional, helps minimize typing + metadata[index, "min_time"] = epidatr:::date_to_epiweek(min(column)) %>% + as.character() %>>% + { paste0(substr(., 1, 4), "-", substr(., 5, 6)) } + metadata[index, "max_time"] = epidatr:::date_to_epiweek(max(column)) %>% + as.character() %>>% + { paste0(substr(., 1, 4), "-", substr(., 5, 6)) } + metadata[index, "max_issue"] = epidatr:::date_to_epiweek(max(epidata$issue)) %>% + as.character() %>>% + { paste0(substr(., 1, 4), "-", substr(., 5, 6)) } +} + +# keep only unique rows [dplyr::distinct] +# only keeps listed columns....does select as well +metadata_subset <- distinct( + metadata, + data_source, + signal, + min_time, + max_time +) + +# check that geo_types for a given signal have the same start/end dates +# counts number of rows with unique data_source-signal combination [base::anyDuplicated] for duplicates +# warning [stop] will indicate manual correction is required + +if (anyDuplicated(select(metadata_subset, data_source, signal)) != 0){ + warning( + "discovered geos for the same signal with different metadata values. ", + "Currently, we are keeping the earliest min_time and the lastest max_time. ", + "We also create a note column where dates differ by geo and list all geos ", + "and all scope start/end dates" + ) +} + +metadata_subset <- group_by( + metadata, + data_source, + signal +) %>% + summarize( + min_time_notes = paste0("Start dates vary by geo: ", paste(geo_type, min_time, collapse = ", ")), + n_unique_min_time = length(unique(min_time)), + min_time = min(min_time), + max_time_notes = paste0("End dates vary by geo: ", paste(geo_type, max_time, collapse = ", ")), + n_unique_max_time = length(unique(max_time)), + max_time = max(max_time), + .groups = "keep" + ) %>% + ungroup() + +metadata_subset[metadata_subset$n_unique_min_time <= 1, "min_time_notes"] <- NA_character_ +metadata_subset[metadata_subset$n_unique_max_time <= 1, "max_time_notes"] <- NA_character_ + + +# read in SIGNALS table as csv from https://docs.google.com/spreadsheets/d/1zb7ItJzY5oq1n-2xtvnPBiJu2L3AqmCKubrLkKJZVHs/edit#gid=329338228 +# source subdivision is in "source_sub" col +# data signal is in "signal" col +# start date is in "temp_start" col +# end date is in "temp_end" col +signal_sheet <- suppressMessages(read_csv("delphi-eng-covidcast-data-sources-signals_Signals.csv")) %>% + # Drop empty rows + filter(!is.na(`Source Subdivision`) & !is.na(Signal)) # (Signa) makes extra certain data is missing + +# Fields we want to add. +new_fields <- c( + "Geographic Scope", + "Temporal Scope Start", + "Temporal Scope End", + "Reporting Cadence", + "Reporting Lag", + "Revision Cadence", + "Demographic Scope", + "Demographic Disaggregation", ###Change to "Demographic Breakdowns" when granted sheet access + "Severity Pyramid Rungs", + "Data Censoring", + "Missingness", + "Who may Access this signal?", + "Who may be told about this signal?", + "Use Restrictions", + "Link to DUA" +) +names(new_fields) <- new_fields + +# Which ones have missing values and need to be filled in? +new_fields_with_missings <- lapply(new_fields, function(col) { + any(is.na(signal_sheet[, col])) +}) +new_fields_with_missings <- names(new_fields_with_missings[unlist(new_fields_with_missings)]) + +message( + paste(new_fields_with_missings, collapse = ", "), + " columns contain missing values and need to be filled in programmatically" +) + + +# read in SOURCES table as csv from https://docs.google.com/spreadsheets/d/1zb7ItJzY5oq1n-2xtvnPBiJu2L3AqmCKubrLkKJZVHs/edit#gid=0 +# shows how real data source names map to "source subdivisions" +# data source is in "DB Source" col +# source subdivision is in "source_sub" col +source_map <- suppressMessages(read_csv("delphi-eng-covidcast-data-sources-signals_Sources.csv")) %>% + # Drop empty rows + filter(!is.na(`Source Subdivision`) & !is.na(`DB Source`)) %>% + rename(data_source =`DB Source`) %>% + select(data_source, "Source Subdivision") + +# left join metadata_subset with source_map +source2 <- left_join( + signal_sheet, + source_map, + by = "Source Subdivision" +) + +# left join signal_sheet with source2 +# result: table with source subdivision, signal, scope start, scope end, min date, max date +source3 <- left_join( + source2, + metadata_subset, + by = c("Signal" = "signal", "data_source") +) + +# select: source subdivision, signal, scope start, scope end, min_time, max_time +# first reformat max_time col to character for compatibility +# also convert min_time col to character (easier to move times over to google spreadsheet without corrupting) +# *only in dplyr can you use col names without quotations, as.character is base function +# *min_time, we can just use the earliest date available and not specify each geo's different dates +source4 <- mutate( + source3, + `Temporal Scope Start Note` = min_time_notes, + `Temporal Scope End Note` = max_time_notes, + max_time = as.character(max_time), + min_time = as.character(min_time) +) + + +# overwrite scope start with min_time [dplyr::mutate]. Set all scope end values +# to "Ongoing" as default. Make copies of manually-filled in columns so we can +# compare our programmatic results. +source5 <- source4 %>% + mutate( + `Temporal Scope Start manual` = `Temporal Scope Start`, + `Temporal Scope End manual` = `Temporal Scope End`, + `Temporal Scope Start` = min_time, + `Temporal Scope End` = max_time + ) + + +# Inactive data_sources list +inactive_sources <- c( + "jhu-csse", "dsew-cpr", "fb-survey", "covid-act-now", "ght", "google-survey", + "indicator-combination", "safegraph", "usa-facts" +) + +# Inactive signals list, where some signals for a given data source are active +# and some are inactive. +inactive_signals <- tibble::tribble( + ~data_source, ~signal, + + "quidel", "raw_pct_negative", + "quidel", "smoothed_pct_negative", + "quidel", "raw_tests_per_device", + "quidel", "smoothed_tests_per_device", + + "hospital-admissions", "smoothed_covid19", + "hospital-admissions", "smoothed_adj_covid19", + + "google-symptoms", "anosmia_raw_search", + "google-symptoms", "anosmia_smoothed_search", + "google-symptoms", "ageusia_raw_search", + "google-symptoms", "ageusia_smoothed_search", + "google-symptoms", "sum_anosmia_ageusia_raw_search", + "google-symptoms", "sum_anosmia_ageusia_smoothed_search" +) +inactive_signals$active <- FALSE + +source55 <- left_join( + source5, inactive_signals, + by = c("Signal" = "signal", "data_source") +) %>% + mutate(active = coalesce(active, !(data_source %in% inactive_sources))) + +if (filter(source55, data_source %in% inactive_sources) %>% pull(active) %>% any()) { + stop("Some data sources that should be fully inactive list active signals", + "Data handling above probably has a bug.") +} + +# overwrite scope end with max_time where signal/data source is active [dplyr::mutate] +active_mask <- source55$active +source55$`Temporal Scope End`[active_mask] <- "Ongoing" + + +# delete helper columns (min and max_time, active) [dplyr::select] +source6 <- select( + source55, + -min_time, + -max_time, + -active +) + +# # Check that our programmatically-derived and manually-filled temporal scope columns match +# compare_start_dates <- filter(source6, !is.na(`Temporal Scope Start manual`)) %>% +# mutate(compare = `Temporal Scope Start manual` == `Temporal Scope Start`) +# if (!all(compare_start_dates$compare)) { +# warning("Not all start dates match between programmatic and manual versions. ", +# "See rows ", paste(which(!compare_start_dates$compare), collapse = ", ")) +# } +# # Examine the ones that don't match +# # These differences are acceptable +# source6[which(!compare_start_dates$compare), c("data_source", "Signal", "Temporal Scope Start manual", "Temporal Scope Start", "Temporal Scope Start Note")] + +# compare_end_dates <- filter(source6, !is.na(`Temporal Scope End manual`)) %>% +# mutate(compare = `Temporal Scope End manual` == `Temporal Scope End`) +# if (!all(compare_end_dates$compare)) { +# warning("Not all end dates match between programmatic and manual versions. ", +# "See rows ", paste(which(!compare_end_dates$compare), collapse = ", ")) +# } +# # Examine the ones that don't match +# # These differences are acceptable +# source6[which(!compare_end_dates$compare), c("data_source", "Signal", "Temporal Scope End manual", "Temporal Scope End", "Temporal Scope End Note")] + +# our new df MUST have the same row order as the signal spreadsheet +sort_order_is_the_same <- identical( + select(source6, `Source Subdivision`, Signal), + select(signal_sheet, `Source Subdivision`, Signal) +) + +if (!sort_order_is_the_same) { + stop("new signal fields are sorted differently than signal spreadsheet. ", + "Columns cannot be pasted in as-is") +} + +source_updated <- select( + source6, + -`Temporal Scope Start manual`, + -`Temporal Scope End manual`, + -min_time_notes, + -max_time_notes, + -n_unique_min_time, + -n_unique_max_time +) + + + +col <- "Geographic Scope" +# List all the highest-level locations for which the signal is available. +# Each location should b fully disambiguated as in the examples below. +# Muliple locations, if any, should be separated by a semicolon. +# E.g.: +# If it's available for all (or almost all) of the US (whether by county, by state or only nationally), enter "USA". +# If it's available only for the state of PA (whether by county, or only for the whole state), enter, "Pennsylvania, USA". +# If it's available only for the states of PA and OH, enter, "Pennsylvania, USA; Ohio, USA" +# If it's available only for Allegheny County, PA, enter "Allegheny, Pennsylvania, USA" +# etc. +geo_scope <- c( + "chng" = "USA", + "covid-act-now" = "USA", + "doctor-visits" = "USA", + "dsew-cpr" = "USA", + "fb-survey" = "USA", + "ght" = "USA", + "google-survey" = "USA", + "google-symptoms" = "USA", + "hhs" = "USA", + "hospital-admissions" = "USA", + "indicator-combination" = "USA", + "jhu-csse" = "USA", + "nchs-mortality" = "USA", + "quidel" = "USA", + "safegraph" = "USA", + "usa-facts" = "USA" +) +source_updated[, col] <- geo_scope[source_updated$data_source] + + +col <- "Available Geography" +# List all available geo-levels. If a geo-level was created by Delphi +# aggregation (as opposed to being ingested directly from the data source), +# indicate this as per this example: county, state (by Delphi), National +# (by Delphi). + +# Tool: Create lists of geos for each data source-signal combo based on what is reported in metadata (does not include quidel, at least with). +metadata_factorgeo <- metadata +metadata_factorgeo$geo_type <- factor(metadata_factorgeo$geo_type, levels = c("county", "hrr", "msa", "dma", "state", "hhs", "nation")) +auto_geo_list_by_signal <- arrange( + metadata_factorgeo, + geo_type +) %>% + group_by( + data_source, + signal + ) %>% + summarize( + geos_list = paste(geo_type, collapse = ", "), + .groups = "keep" + ) %>% + ungroup() + +# Tool: Are there any data sources where geos_list is different for different signal? +different_geos_by_signal <- count(auto_geo_list_by_signal, data_source, geos_list, name = "n_signals") +different_geos_by_signal +# which(duplicated(select(different_geos_by_signal, data_source))) +# # [1] 2 6 8 9 15 17 + +# Keep most common geos_list for each data source. +most_common_geos_list <- group_by(different_geos_by_signal, data_source) %>% + slice_max(n_signals, with_ties = FALSE) +# most_common_geos_list +leftover_datasource_geos <- anti_join(different_geos_by_signal, most_common_geos_list) +# leftover_datasource_geos +leftover_signal_geos <- semi_join(auto_geo_list_by_signal, leftover_datasource_geos) +# leftover_signal_geos + +delphi_agg_text <- " (by Delphi)" + +# These values are applied first. They are the default (most common) geos for each data source. +avail_geos <- c( + "chng" = glue("county, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), + "covid-act-now" = glue("county, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), + "doctor-visits" = glue("county, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), + "dsew-cpr" = glue("county, msa, state, hhs, nation{delphi_agg_text}"), + "fb-survey" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, nation{delphi_agg_text}"), + "ght" = glue("hrr{delphi_agg_text}, msa{delphi_agg_text}, dma, state"), + "google-survey" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}"), + "google-symptoms" = glue("county, hrr{delphi_agg_text}, msa{delphi_agg_text}, state, hhs{delphi_agg_text}, nation{delphi_agg_text}"), + "hhs" = glue("state, hhs{delphi_agg_text}, nation{delphi_agg_text}"), + "hospital-admissions" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), + "indicator-combination" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), + "jhu-csse" = glue("county, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), + "nchs-mortality" = glue("state, nation"), + # TODO check against actual data. Or maybe there's an internal/private version of metadata that includes Quidel stats? + "quidel" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), + "safegraph" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), + "usa-facts" = glue("county, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), + "youtube-survey" = "state{delphi_agg_text}" +) + +# These are signal-specific geo lists. These are less common and are applied as a patch. +dsew_geos <- glue("state, hhs, nation{delphi_agg_text}") +fb_geos1 <- glue("county{delphi_agg_text}, state{delphi_agg_text}, nation{delphi_agg_text}") +fb_geos2 <- glue("county{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, nation{delphi_agg_text}") +hosp_geos <- glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}") +combo_geos <- glue("county{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}") +quidel_geos <- glue("msa{delphi_agg_text}, state{delphi_agg_text}") +leftover_signal_geos_manual <- tibble::tribble( + ~data_source, ~signal, ~geos_list, + "chng", "7dav_inpatient_covid", "state", + "chng", "7dav_outpatient_covid", "state", + + "dsew-cpr", "booster_doses_admin_7dav", dsew_geos, + "dsew-cpr", "doses_admin_7dav", dsew_geos, + "dsew-cpr", "people_booster_doses", dsew_geos, + + "fb-survey", "smoothed_vaccine_barrier_appointment_location_tried", fb_geos1, + "fb-survey", "smoothed_vaccine_barrier_other_tried", fb_geos1, + "fb-survey", "smoothed_wvaccine_barrier_appointment_location_tried", fb_geos1, + "fb-survey", "smoothed_wvaccine_barrier_other_tried", fb_geos1, + + "fb-survey", "smoothed_vaccine_barrier_appointment_time_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_childcare_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_document_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_eligible_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_language_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_no_appointments_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_none_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_technical_difficulties_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_technology_access_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_time_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_travel_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_type_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_appointment_time_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_childcare_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_document_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_eligible_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_language_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_no_appointments_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_none_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_technical_difficulties_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_technology_access_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_time_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_travel_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_type_tried", fb_geos2, + + "hospital-admissions", "smoothed_adj_covid19", hosp_geos, + "hospital-admissions", "smoothed_covid19", hosp_geos, + + "indicator-combination", "nmf_day_doc_fbc_fbs_ght", combo_geos, + "indicator-combination", "nmf_day_doc_fbs_ght", combo_geos, + + # Quidel flu signals + # TODO check against actual data. Or maybe there's an internal/private version of metadata that includes Quidel stats? + "quidel", "raw_pct_negative", quidel_geos, + "quidel", "smoothed_pct_negative", quidel_geos, + "quidel", "raw_tests_per_device", quidel_geos, + "quidel", "smoothed_tests_per_device", quidel_geos +) + +source_updated[, col] <- coalesce(avail_geos[source_updated$data_source], source_updated[[col]]) + +source_updated <- left_join( + source_updated, leftover_signal_geos_manual, + by = c("Signal" = "signal", "data_source") +) %>% + mutate(`Available Geography` = coalesce(geos_list, `Available Geography`)) %>% + select(-geos_list) + + +# Temporal Scope Start +# Above. YYYY-MM-DD, with epiweeks as YYYY-WW. Formatted as a string + +# Temporal Scope End +# Above. YYYY-MM-DD, with epiweeks as YYYY-WW, or "Ongoing" if still ongoing. +# Formatted as a string + + +col <- "Reporting Cadence" +# E.g. daily, weekly, etc. Might not be the same as Temporal Granularity +avail_geos <- c( + "chng" = "daily", + "covid-act-now" = "daily", + "doctor-visits" = "daily", + "dsew-cpr" = "daily", + "fb-survey" = "daily", + "ght" = "daily", + "google-survey" = "daily", + "google-symptoms" = "daily", + "hhs" = "weekly", + "hospital-admissions" = "daily", + "indicator-combination" = "daily", + "jhu-csse" = "daily", + "nchs-mortality" = "weekly", + "quidel" = "daily", + "safegraph" = "weekly", + "usa-facts" = "weekly" +) + +# TOOD to be renamed to "Typical Reporting Lag" @Carlyn +col <- "Typical Reporting Lag" +# The number of days as an unstructured field, e.g. "3-5 days", from the last +# day of a reported period until the first reported value for that period is +# usually available in Epidata. E.g. if reporting U.S. epiweeks +# (Sunday through Saturday), and the first report is usually available in +# Epidata on the following Friday, enter 6. +# +# By "usually available" we mean when it's "supposed to be" available based on +# our current understanding of the data provider's operations and Delphi's +# ingestion pipeline. That would be the date on which we think of the data +# as showing up "on time", and relative to which we will track unusual +# delays. +# +# values are from production params files, e.g. +# https://github.com/cmu-delphi/covidcast-indicators/blob/d36352b/ansible/templates/changehc-params-prod.json.j2#L42-L43, +# and sirCAL params +# https://github.com/cmu-delphi/covidcast-indicators/blob/main/ansible/templates/sir_complainsalot-params-prod.json.j2#L16 + +# Make a map between each data source (or source subdivision) and value. The +# value can be numeric, string, etc. +reporting_lag <- c( + "chng" = "4-5 days", + "covid-act-now" = "2-9 days", + "doctor-visits" = "3-6 days", + "dsew-cpr" = "3-9 days", + "fb-survey" = "1 day", + "ght" = "4-5 days", + "google-survey" = "1-2 days", + "google-symptoms" = "4-7 days", + "hhs" = "5-11 days", + "hospital-admissions" = "3-4 days", + "indicator-combination" = "1-3 days", + "jhu-csse" = "1 day", + "nchs-mortality" = "11-17 days", + "quidel" = "5-6 days", + "safegraph" = "3-11 days", + "usa-facts" = "2-8 days" +) +# Index (using `[]`) into the map using the data_source (or source division) +# column and save to the relevant field. +# Using the data_source to index into the map puts the output into the same +# order as the dataframe. +source_updated[, col] <- reporting_lag[source_updated$data_source] + +# TOOD to be renamed to "Typical Revision Cadence" @Carlyn +col <- "Typical Revision Cadence" +# How frequently are revised values (AKA backfill) usually made available as +# an unstructured field, e.g. "Weekly (usually Fridays)", "daily", etc. If +# there are no reporting revisions, enter "None". +revision_cadence <- c( + "chng" = "Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 4-6 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 45 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.", + "covid-act-now" = "Daily. Most recent test positivity rates do not change substantially (having a median delta of close to 0). However, most recent total tests performed are expected to increase in later data revisions (having a median increase of 7%). Values more than 5 days in the past are expected to remain fairly static (with total tests performed having a median increase of 1% of less), as most major revisions have already occurred.", + "doctor-visits" = "Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 5-7 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 50 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.", + "dsew-cpr" = "Daily. This data source is susceptible to large corrections that can create strange data effects such as negative counts and sudden changes of 1M+ counts from one day to the next.", + "fb-survey" = "Daily, for 5 consecutive issues for each report date", + "ght" = "None", + "google-survey" = "Daily, for 3 consecutive issues for each report date", + "google-symptoms" = "None", + "hhs" = "Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.", + "hospital-admissions" = "Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 7-13 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 57 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.", + "indicator-combination" = "Daily", + "jhu-csse" = "None. The raw data reports cumulative cases and deaths, which + Delphi diffs to compute incidence. Raw cumulative figures are sometimes + corrected by adjusting the reported value for a single day, but revisions + do not affect past report dates.", + "nchs-mortality" = "Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7)", + "quidel" = NA_character_, # Happens, up to 6+ weeks after the report date. # TODO + "safegraph" = "None", + "usa-facts" = "None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates." +) +source_updated[, col] <- revision_cadence[source_updated$data_source] + +col <- "Demographic Scope" +# The demographic group covered by the report. +# E.g. "all", "Pediatric", "Adult", "Women", "adult facebook +# users", "MSM", "Google search users", "VA Health system +# members", "smartphone users", … +demo_scope <- c( + "chng" = "Nationwide Change Healthcare network", + "covid-act-now" = "Hospital patients", + "doctor-visits" = "Nationwide Optum network", + "dsew-cpr" = "All", + "fb-survey" = "Adult Facebook users", + "ght" = "Google search users", + "google-survey" = "Google ad publisher website, Google's Opinions Reward app, and similar application users", + "google-symptoms" = "Google search users", + "hhs" = "All", + "hospital-admissions" = "Nationwide Optum network", + "indicator-combination" = "This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group", + "jhu-csse" = "All", + "nchs-mortality" = "All", + "quidel" = "Nationwide Quidel testing equipment network", + "safegraph" = "Safegraph panel members who use mobile devices", + "usa-facts" = "All" +) +source_updated[, col] <- demo_scope[source_updated$data_source] + +# TODO rename to "Demographic Breakdowns" @Carlyn +col <- "Demographic Breakdowns" +# What demographic breakdowns are available, e.g. "by age groups 0-17, +# 18-64, 65+", "by race/ethnicity", "by gender". +# +# These might be used in filters, so the values need to be structured. E.g. +# it could be a list of all available breakdowns, e.g. "gender, race", +# or "age bands(0-17,18-64,65+)", or "None" if no breakdown. If it's easier, +# we can separate it into three different columns: "Gender Breakdown" +# (yes/no), "Race Breakdown" (yes/no), and "Age breakdown" (list of age +# bands, or "none") +demo_breakdowns <- c( + "chng" = "None", + "covid-act-now" = "None", + "doctor-visits" = "None", + "dsew-cpr" = "None", + "fb-survey" = "None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).", + "ght" = "None", + "google-survey" = "None", + "google-symptoms" = "None", + "hhs" = "None", + "hospital-admissions" = "None", + "indicator-combination" = "None", + "jhu-csse" = "None", + "nchs-mortality" = "None", + "quidel" = "age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)", + "safegraph" = "None", + "usa-facts" = "None" +) +source_updated[, col] <- demo_breakdowns[source_updated$data_source] +# Quidel covid has age bands, but quidel flu doesn't. +source_updated[source_update$`Source Subdivision` == "quidel-flu", col] <- "None" + +# TODO name in spreadsheet ends with a space -- remove @Carlyn +col <- "Severity Pyramid Rungs" +# One or more rungs to which this signal best relates: +# https://docs.google.com/presentation/d/1K458kZsncwwjNMOnlkaqHA_0Vm7PEz6g43fYy4GII10/edit#slide=id.g10e023ed748_0_163 + + +# TODO +col <- "Data Censoring" +# Has any of the data been censored (e.g. small counts)? +# +# TODO: If so how, and how much impact does it have (e.g. approximate fraction of +# counts affected). +# +# This is an unstructured text field. +data_censoring <- c( + "chng" = "Discarded if over a given 7-day period an estimate is computed with 100 or fewer observations", + "covid-act-now" = "Discarded if sample size (total tests performed) is 0. It is unknown what, if any, censoring the data source performs", + "doctor-visits" = "Discarded if over a given 7-day period an estimate is computed with 500 or fewer observations", + "dsew-cpr" = "It is unknown what, if any, censoring the data source performs", + "fb-survey" = "Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.", + "ght" = NA_character_, + "google-survey" = NA_character_, + "google-symptoms" = "Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the raw datasets", + "hhs" = NA_character_, # TODO + "hospital-admissions" = "Discarded if over a given 7-day period an estimate is computed with 500 or fewer observations", + "indicator-combination" = NA_character_, + "jhu-csse" = NA_character_, # TODO + "nchs-mortality" = "Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading", + "quidel" = "Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests", + "safegraph" = NA_character_, + "usa-facts" = NA_character_ +) +signal_specific_censoring <- tibble::tribble( + ~data_source, ~signal, ~note, + "dsew-cpr", "covid_naat_pct_positive_7dav", "Discarded when the 7dav NAAT test volume provided in the same originating + spreadsheet, corresponding to a period ~4 days earlier, is 5 or fewer. This removes 10-20% of counties (https://github.com/cmu-delphi/covidcast-indicators/issues/1513). It is unknown what, if any, censoring the data source performs", +) +source_updated[, col] <- data_censoring[source_updated$data_source] + +# TODO +col <- "Missingness" +# How much missingness is there, and for what reasons? Is it possible to +# distinguish a missing value from a true zero? This is an unstructured text +# field. +# +# E.g. in a signal that's available at county level, how many of the US's +# 3000+ counties are usually reported on? Not filter-related, so can be +# unstructured text. The problem is that these numbers can change +# dramatically over time, as has happened e.g. for the Facebook survey. I'm +# not sure what to do. Maybe just summarize the current state, e.g. "85% +# counties available in mid 2020, then gradually declined to 8% of counties +# by April 2024", and leave it at that. We could occasionally update it. +missingness <- c( + "chng" = NA_character_, + "covid-act-now" = "A few counties, most notably in California, are not covered by this data source", + "doctor-visits" = NA_character_, + "dsew-cpr" = NA_character_, + "fb-survey" = "A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)", + "ght" = NA_character_, + "google-survey" = NA_character_, + "google-symptoms" = NA_character_, + "hhs" = NA_character_, + "hospital-admissions" = NA_character_, + "indicator-combination" = NA_character_, + "jhu-csse" = NA_character_, + "nchs-mortality" = NA_character_, + "quidel" = NA_character_, + "safegraph" = NA_character_, + "usa-facts" = NA_character_ +) +source_updated[, col] <- missingness[source_updated$data_source] + + +# TODO best guess, should check +# TODO fix capitalization in name @Carlyn +col <- "Who may access this signal?" +# Who has the right to access this signal? E.g. "Delphi, CDC" or "Delphi, +# ACHD, PADOH", or "public". Separate different orgs by comma. +orgs_allowed_access <- c( + "chng" = "public", + "covid-act-now" = "public", + "doctor-visits" = "public", + "dsew-cpr" = "public", + "fb-survey" = "public", + "ght" = "public", + "google-survey" = "public", + "google-symptoms" = "public", + "hhs" = "public", + "hospital-admissions" = "public", + "indicator-combination" = "public", + "jhu-csse" = "public", + "nchs-mortality" = "public", + "quidel" = "Delphi", + "safegraph" = "public", + "usa-facts" = "public" +) +source_updated[, col] <- orgs_allowed_access[source_updated$data_source] + +# TODO best guess, should check +col <- "Who may be told about this signal?" +orgs_allowed_know <- c( + "chng" = "public", + "covid-act-now" = "public", + "doctor-visits" = "public", + "dsew-cpr" = "public", + "fb-survey" = "public", + "ght" = "public", + "google-survey" = "public", + "google-symptoms" = "public", + "hhs" = "public", + "hospital-admissions" = "public", + "indicator-combination" = "public", + "jhu-csse" = "public", + "nchs-mortality" = "public", + "quidel" = "public", + "safegraph" = "public", + "usa-facts" = "public" +) +source_updated[, col] <- orgs_allowed_know[source_updated$data_source] + + +# TODO add column to spreadsheet @Carlyn +col <- "License" +license <- c( + "chng" = "CC BY-NC", + "covid-act-now" = "CC BY-NC", + "doctor-visits" = "CC BY-NC", + "dsew-cpr" = "Public Domain US Government (https://www.usa.gov/government-works)", + "fb-survey" = "CC BY", + "ght" = "Google Terms of Service (https://policies.google.com/terms)", + "google-survey" = "CC BY", + "google-symptoms" = "Google Terms of Service (https://policies.google.com/terms)", + "hhs" = "Public Domain US Government (https://www.usa.gov/government-works)", + "hospital-admissions" = "CC BY", + "indicator-combination" = "CC BY", + "jhu-csse" = "CC BY", + "nchs-mortality" = "NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm)", + "quidel" = "CC BY", + "safegraph" = "CC BY", + "usa-facts" = "CC BY" +) +source_updated[, col] <- license[source_updated$data_source] + +# TODO +col <- "Use Restrictions" +# Any important DUA restrictions on use, publication, sharing, linkage, etc.? +use_restrictions <- c( + "chng" = NA_character_, + "covid-act-now" = NA_character_, + "doctor-visits" = NA_character_, + "dsew-cpr" = NA_character_, + "fb-survey" = NA_character_, + "ght" = NA_character_, + "google-survey" = NA_character_, + "google-symptoms" = NA_character_, + "hhs" = NA_character_, + "hospital-admissions" = NA_character_, + "indicator-combination" = NA_character_, + "jhu-csse" = NA_character_, + "nchs-mortality" = NA_character_, + "quidel" = NA_character_, + "safegraph" = NA_character_, + "usa-facts" = NA_character_ +) +source_updated[, col] <- use_restrictions[source_updated$data_source] + +# TODO +col <- "Link to DUA" +dua_link <- c( + "chng" = "https://cmu.box.com/s/cto4to822zecr3oyq1kkk9xmzhtq9tl2", + "covid-act-now" = NA_character_, # contract? + "doctor-visits" = "https://cmu.box.com/s/l2tz6kmiws6jyty2azwb43poiepz0565", + "dsew-cpr" = NA_character_, + "fb-survey" = "https://cmu.box.com/s/qfxplcdrcn9retfzx4zniyugbd9h3bos", + "ght" = NA_character_, + "google-survey" = NA_character_, # contract? + "google-symptoms" = NA_character_, + "hhs" = NA_character_, + "hospital-admissions" = "https://cmu.box.com/s/l2tz6kmiws6jyty2azwb43poiepz0565", + "indicator-combination" = NA_character_, + "jhu-csse" = NA_character_, + "nchs-mortality" = NA_character_, + "quidel" = NA_character_, + "safegraph" = "https://cmu.box.com/s/m0p1wpet4vuvey7od83n70h0e97ky2kg", + "usa-facts" = NA_character_, + "youtube-survey" = NA_character_ # contract? +) +source_updated[, col] <- dua_link[source_updated$data_source] + + +source_updated + +# TODO: save updated signals table to CSV [readr::read_csv] + + +# Final manual steps: +# open CSV in a GUI editor (excel or google sheets). copy scope date columns and paste into original spreadsheet online [manual] \ No newline at end of file From 72b7c3dd47d240b9e5855e99a8732c2c4d944c0b Mon Sep 17 00:00:00 2001 From: Tina Townes Date: Tue, 7 May 2024 12:29:48 -0400 Subject: [PATCH 02/30] Update signal_spreadsheet_updater.R Manual merge --- scripts/signal_spreadsheet_updater.R | 113 +++++++++++++++++---------- 1 file changed, 72 insertions(+), 41 deletions(-) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index 45ef5fa61..d9b33983d 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -203,7 +203,7 @@ inactive_signals <- tibble::tribble( "hospital-admissions", "smoothed_covid19", "hospital-admissions", "smoothed_adj_covid19", - + "google-symptoms", "anosmia_raw_search", "google-symptoms", "anosmia_smoothed_search", "google-symptoms", "ageusia_raw_search", @@ -307,7 +307,8 @@ geo_scope <- c( "nchs-mortality" = "USA", "quidel" = "USA", "safegraph" = "USA", - "usa-facts" = "USA" + "usa-facts" = "USA", + "youtube-survey" = NA_character_ ) source_updated[, col] <- geo_scope[source_updated$data_source] @@ -367,7 +368,10 @@ avail_geos <- c( "indicator-combination" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), "jhu-csse" = glue("county, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), "nchs-mortality" = glue("state, nation"), - # TODO check against actual data. Or maybe there's an internal/private version of metadata that includes Quidel stats? + + # TODO check against actual data. Or maybe there's an internal/private version of metadata that includes Quidel stats? + # this is quidel non-flu signals, other is flu + "quidel" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), "safegraph" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), "usa-facts" = glue("county, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), @@ -427,7 +431,10 @@ leftover_signal_geos_manual <- tibble::tribble( "indicator-combination", "nmf_day_doc_fbs_ght", combo_geos, # Quidel flu signals - # TODO check against actual data. Or maybe there's an internal/private version of metadata that includes Quidel stats? + + # TODO check against actual data. Or maybe there's an internal/private version of metadata that includes Quidel stats? Nat was only looking at metadata + #for each of these quidel signals, make request to API for each possible geotype (county, hrr, etc) to see if data comes back + "quidel", "raw_pct_negative", quidel_geos, "quidel", "smoothed_pct_negative", quidel_geos, "quidel", "raw_tests_per_device", quidel_geos, @@ -470,10 +477,12 @@ avail_geos <- c( "nchs-mortality" = "weekly", "quidel" = "daily", "safegraph" = "weekly", - "usa-facts" = "weekly" + "usa-facts" = "weekly", + "youtube-survey" = NA_character_ ) -# TOOD to be renamed to "Typical Reporting Lag" @Carlyn +# TODO to be renamed to "Typical Reporting Lag" @Carlyn + col <- "Typical Reporting Lag" # The number of days as an unstructured field, e.g. "3-5 days", from the last # day of a reported period until the first reported value for that period is @@ -510,15 +519,17 @@ reporting_lag <- c( "nchs-mortality" = "11-17 days", "quidel" = "5-6 days", "safegraph" = "3-11 days", - "usa-facts" = "2-8 days" + "usa-facts" = "2-8 days", + "youtube-survey" = NA_character_ ) + # Index (using `[]`) into the map using the data_source (or source division) # column and save to the relevant field. # Using the data_source to index into the map puts the output into the same # order as the dataframe. source_updated[, col] <- reporting_lag[source_updated$data_source] -# TOOD to be renamed to "Typical Revision Cadence" @Carlyn +# TODO to be renamed to "Typical Revision Cadence" @Carlyn col <- "Typical Revision Cadence" # How frequently are revised values (AKA backfill) usually made available as # an unstructured field, e.g. "Weekly (usually Fridays)", "daily", etc. If @@ -542,7 +553,8 @@ revision_cadence <- c( "nchs-mortality" = "Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7)", "quidel" = NA_character_, # Happens, up to 6+ weeks after the report date. # TODO "safegraph" = "None", - "usa-facts" = "None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates." + "usa-facts" = "None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.", + "youtube-survey" = NA_character_ ) source_updated[, col] <- revision_cadence[source_updated$data_source] @@ -567,7 +579,8 @@ demo_scope <- c( "nchs-mortality" = "All", "quidel" = "Nationwide Quidel testing equipment network", "safegraph" = "Safegraph panel members who use mobile devices", - "usa-facts" = "All" + "usa-facts" = "All", + "youtube-survey" = NA_character_ ) source_updated[, col] <- demo_scope[source_updated$data_source] @@ -598,7 +611,8 @@ demo_breakdowns <- c( "nchs-mortality" = "None", "quidel" = "age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)", "safegraph" = "None", - "usa-facts" = "None" + "usa-facts" = "None", + "youtube-survey" = NA_character_ ) source_updated[, col] <- demo_breakdowns[source_updated$data_source] # Quidel covid has age bands, but quidel flu doesn't. @@ -636,12 +650,14 @@ data_censoring <- c( "nchs-mortality" = "Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading", "quidel" = "Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests", "safegraph" = NA_character_, - "usa-facts" = NA_character_ + "usa-facts" = NA_character_, + "youtube-survey" = NA_character_ ) signal_specific_censoring <- tibble::tribble( ~data_source, ~signal, ~note, "dsew-cpr", "covid_naat_pct_positive_7dav", "Discarded when the 7dav NAAT test volume provided in the same originating spreadsheet, corresponding to a period ~4 days earlier, is 5 or fewer. This removes 10-20% of counties (https://github.com/cmu-delphi/covidcast-indicators/issues/1513). It is unknown what, if any, censoring the data source performs", + ) source_updated[, col] <- data_censoring[source_updated$data_source] @@ -674,7 +690,8 @@ missingness <- c( "nchs-mortality" = NA_character_, "quidel" = NA_character_, "safegraph" = NA_character_, - "usa-facts" = NA_character_ + "usa-facts" = NA_character_, + "youtube-survey" = NA_character_ ) source_updated[, col] <- missingness[source_updated$data_source] @@ -700,7 +717,8 @@ orgs_allowed_access <- c( "nchs-mortality" = "public", "quidel" = "Delphi", "safegraph" = "public", - "usa-facts" = "public" + "usa-facts" = "public", + "youtube-survey" = NA_character_ ) source_updated[, col] <- orgs_allowed_access[source_updated$data_source] @@ -722,7 +740,8 @@ orgs_allowed_know <- c( "nchs-mortality" = "public", "quidel" = "public", "safegraph" = "public", - "usa-facts" = "public" + "usa-facts" = "public", + "youtube-survey" = NA_character_ ) source_updated[, col] <- orgs_allowed_know[source_updated$data_source] @@ -745,7 +764,8 @@ license <- c( "nchs-mortality" = "NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm)", "quidel" = "CC BY", "safegraph" = "CC BY", - "usa-facts" = "CC BY" + "usa-facts" = "CC BY", + "youtube-survey" = NA_character_ ) source_updated[, col] <- license[source_updated$data_source] @@ -753,45 +773,56 @@ source_updated[, col] <- license[source_updated$data_source] col <- "Use Restrictions" # Any important DUA restrictions on use, publication, sharing, linkage, etc.? use_restrictions <- c( - "chng" = NA_character_, - "covid-act-now" = NA_character_, - "doctor-visits" = NA_character_, - "dsew-cpr" = NA_character_, - "fb-survey" = NA_character_, + "chng" = NA_character_, #change DUA in confidential Google drive, generic contract terms + "covid-act-now" = NA_character_, #public + "doctor-visits" = NA_character_, #optum DUA in confidential Google drive, generic contract terms + "dsew-cpr" = NA_character_, #public + "fb-survey" = NA_character_, # "ght" = NA_character_, "google-survey" = NA_character_, "google-symptoms" = NA_character_, "hhs" = NA_character_, - "hospital-admissions" = NA_character_, + "hospital-admissions" = NA_character_, #optum DUA in confidential Google drive, generic contract terms "indicator-combination" = NA_character_, "jhu-csse" = NA_character_, "nchs-mortality" = NA_character_, - "quidel" = NA_character_, + "quidel" = "Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics.", #Quidel DUA in confidential Google drive, "safegraph" = NA_character_, - "usa-facts" = NA_character_ + "usa-facts" = NA_character_, + "youtube-survey" = NA_character_ ) source_updated[, col] <- use_restrictions[source_updated$data_source] # TODO + +#aa <- epidatr::covidcast_epidata() +#aa$sources$`jhu-csse`$dua + +#purrr::map(aa$sources, ~ .x$license) + +#bb <- aa$sources$`fb-survey`$signals %>% tibble::as_tibble() +#bb + + col <- "Link to DUA" dua_link <- c( - "chng" = "https://cmu.box.com/s/cto4to822zecr3oyq1kkk9xmzhtq9tl2", - "covid-act-now" = NA_character_, # contract? - "doctor-visits" = "https://cmu.box.com/s/l2tz6kmiws6jyty2azwb43poiepz0565", - "dsew-cpr" = NA_character_, - "fb-survey" = "https://cmu.box.com/s/qfxplcdrcn9retfzx4zniyugbd9h3bos", - "ght" = NA_character_, - "google-survey" = NA_character_, # contract? - "google-symptoms" = NA_character_, - "hhs" = NA_character_, - "hospital-admissions" = "https://cmu.box.com/s/l2tz6kmiws6jyty2azwb43poiepz0565", - "indicator-combination" = NA_character_, - "jhu-csse" = NA_character_, - "nchs-mortality" = NA_character_, - "quidel" = NA_character_, - "safegraph" = "https://cmu.box.com/s/m0p1wpet4vuvey7od83n70h0e97ky2kg", - "usa-facts" = NA_character_, - "youtube-survey" = NA_character_ # contract? + "chng" = "https://drive.google.com/drive/u/1/folders/1GKYSFb6C_8jSHTg-65eVzSOT433oIDrf", #"https://cmu.box.com/s/cto4to822zecr3oyq1kkk9xmzhtq9tl2" + "covid-act-now" = NA_character_, #public, maybe contract for other specific project #@Carlyn + "doctor-visits" = "https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf", #"https://cmu.box.com/s/l2tz6kmiws6jyty2azwb43poiepz0565", + "dsew-cpr" = NA_character_, #public + "fb-survey" = "https://cmu.box.com/s/qfxplcdrcn9retfzx4zniyugbd9h3bos",#@Alex R. + "ght" = NA_character_, #public, has an API doesn't require password + "google-survey" = NA_character_, #@Carlyn has requested DUA from Roni + "google-symptoms" = NA_character_, #public + "hhs" = NA_character_, #public gov't + "hospital-admissions" = "https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf", #"https://cmu.box.com/s/l2tz6kmiws6jyty2azwb43poiepz0565", + "indicator-combination" = "see Doctor Visits, Facebook Survey, and Google Health Trends", + "jhu-csse" = NA_character_, #public + "nchs-mortality" = "https://www.cdc.gov/nchs/data_access/restrictions.htm", + "quidel" = "https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS", + "safegraph" = "https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x", + "usa-facts" = NA_character_, #public + "youtube-survey" = NA_character_, #contract expected ) source_updated[, col] <- dua_link[source_updated$data_source] From d338f431d279ff26b73eb2bd610df8356b5bd176 Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Tue, 7 May 2024 13:11:34 -0400 Subject: [PATCH 03/30] remove column name change TODOs --- scripts/signal_spreadsheet_updater.R | 27 ++++++++++----------------- 1 file changed, 10 insertions(+), 17 deletions(-) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index d9b33983d..aa96a7eb4 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -20,8 +20,8 @@ metadata <- pub_covidcast_meta() metadata$last_update <- as.Date(as.POSIXct(metadata$last_update, origin = "1970-01-01")) -#Patch NCHS-mortality max_time data into metadata, and min_time -source_name = "nchs-mortality" #optional to use this variable +# Patch NCHS-mortality max_time data into metadata, and min_time +source_name = "nchs-mortality" nchs_row_nums = which(metadata$data_source == source_name) metadata$min_time <- as.character(metadata$min_time) @@ -38,7 +38,7 @@ for (index in nchs_row_nums) { geo_values = "*", time_values = epirange(199001, 203001) ) - column = epidata$time_value #col variable is optional, helps minimize typing + column = epidata$time_value metadata[index, "min_time"] = epidatr:::date_to_epiweek(min(column)) %>% as.character() %>>% { paste0(substr(., 1, 4), "-", substr(., 5, 6)) } @@ -371,7 +371,6 @@ avail_geos <- c( # TODO check against actual data. Or maybe there's an internal/private version of metadata that includes Quidel stats? # this is quidel non-flu signals, other is flu - "quidel" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), "safegraph" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), "usa-facts" = glue("county, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), @@ -431,10 +430,8 @@ leftover_signal_geos_manual <- tibble::tribble( "indicator-combination", "nmf_day_doc_fbs_ght", combo_geos, # Quidel flu signals - # TODO check against actual data. Or maybe there's an internal/private version of metadata that includes Quidel stats? Nat was only looking at metadata #for each of these quidel signals, make request to API for each possible geotype (county, hrr, etc) to see if data comes back - "quidel", "raw_pct_negative", quidel_geos, "quidel", "smoothed_pct_negative", quidel_geos, "quidel", "raw_tests_per_device", quidel_geos, @@ -481,7 +478,6 @@ avail_geos <- c( "youtube-survey" = NA_character_ ) -# TODO to be renamed to "Typical Reporting Lag" @Carlyn col <- "Typical Reporting Lag" # The number of days as an unstructured field, e.g. "3-5 days", from the last @@ -529,7 +525,6 @@ reporting_lag <- c( # order as the dataframe. source_updated[, col] <- reporting_lag[source_updated$data_source] -# TODO to be renamed to "Typical Revision Cadence" @Carlyn col <- "Typical Revision Cadence" # How frequently are revised values (AKA backfill) usually made available as # an unstructured field, e.g. "Weekly (usually Fridays)", "daily", etc. If @@ -584,7 +579,7 @@ demo_scope <- c( ) source_updated[, col] <- demo_scope[source_updated$data_source] -# TODO rename to "Demographic Breakdowns" @Carlyn + col <- "Demographic Breakdowns" # What demographic breakdowns are available, e.g. "by age groups 0-17, # 18-64, 65+", "by race/ethnicity", "by gender". @@ -618,7 +613,7 @@ source_updated[, col] <- demo_breakdowns[source_updated$data_source] # Quidel covid has age bands, but quidel flu doesn't. source_updated[source_update$`Source Subdivision` == "quidel-flu", col] <- "None" -# TODO name in spreadsheet ends with a space -- remove @Carlyn + col <- "Severity Pyramid Rungs" # One or more rungs to which this signal best relates: # https://docs.google.com/presentation/d/1K458kZsncwwjNMOnlkaqHA_0Vm7PEz6g43fYy4GII10/edit#slide=id.g10e023ed748_0_163 @@ -696,8 +691,6 @@ missingness <- c( source_updated[, col] <- missingness[source_updated$data_source] -# TODO best guess, should check -# TODO fix capitalization in name @Carlyn col <- "Who may access this signal?" # Who has the right to access this signal? E.g. "Delphi, CDC" or "Delphi, # ACHD, PADOH", or "public". Separate different orgs by comma. @@ -722,7 +715,7 @@ orgs_allowed_access <- c( ) source_updated[, col] <- orgs_allowed_access[source_updated$data_source] -# TODO best guess, should check + col <- "Who may be told about this signal?" orgs_allowed_know <- c( "chng" = "public", @@ -746,7 +739,6 @@ orgs_allowed_know <- c( source_updated[, col] <- orgs_allowed_know[source_updated$data_source] -# TODO add column to spreadsheet @Carlyn col <- "License" license <- c( "chng" = "CC BY-NC", @@ -769,6 +761,7 @@ license <- c( ) source_updated[, col] <- license[source_updated$data_source] + # TODO col <- "Use Restrictions" # Any important DUA restrictions on use, publication, sharing, linkage, etc.? @@ -793,7 +786,6 @@ use_restrictions <- c( ) source_updated[, col] <- use_restrictions[source_updated$data_source] -# TODO #aa <- epidatr::covidcast_epidata() #aa$sources$`jhu-csse`$dua @@ -803,7 +795,7 @@ source_updated[, col] <- use_restrictions[source_updated$data_source] #bb <- aa$sources$`fb-survey`$signals %>% tibble::as_tibble() #bb - +# TODO col <- "Link to DUA" dua_link <- c( "chng" = "https://drive.google.com/drive/u/1/folders/1GKYSFb6C_8jSHTg-65eVzSOT433oIDrf", #"https://cmu.box.com/s/cto4to822zecr3oyq1kkk9xmzhtq9tl2" @@ -829,8 +821,9 @@ source_updated[, col] <- dua_link[source_updated$data_source] source_updated + # TODO: save updated signals table to CSV [readr::read_csv] # Final manual steps: -# open CSV in a GUI editor (excel or google sheets). copy scope date columns and paste into original spreadsheet online [manual] \ No newline at end of file +# open CSV in a GUI editor (excel or google sheets). copy scope date columns and paste into original spreadsheet online [manual] From 71bbe3e7144ea7f48c1d374b6b80d21e8b0ec881 Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Tue, 7 May 2024 16:54:20 -0400 Subject: [PATCH 04/30] info about censoring --- scripts/signal_spreadsheet_updater.R | 20 +++++++++++--------- 1 file changed, 11 insertions(+), 9 deletions(-) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index aa96a7eb4..93e5de5b8 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -10,6 +10,8 @@ suppressPackageStartupMessages({ options(warn = 1) +# TODO all info for youtube-survey + # COVIDcast metadata # Metadata documentation: https://cmu-delphi.github.io/delphi-epidata/api/covidcast_meta.html @@ -617,9 +619,9 @@ source_updated[source_update$`Source Subdivision` == "quidel-flu", col] <- "None col <- "Severity Pyramid Rungs" # One or more rungs to which this signal best relates: # https://docs.google.com/presentation/d/1K458kZsncwwjNMOnlkaqHA_0Vm7PEz6g43fYy4GII10/edit#slide=id.g10e023ed748_0_163 +# Added manually to signal spreadsheet. -# TODO col <- "Data Censoring" # Has any of the data been censored (e.g. small counts)? # @@ -635,17 +637,17 @@ data_censoring <- c( "fb-survey" = "Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.", - "ght" = NA_character_, - "google-survey" = NA_character_, - "google-symptoms" = "Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the raw datasets", - "hhs" = NA_character_, # TODO + "ght" = "Reported as 0 query when search volume is below a certain threshold, as set by Google. Areas with low query volume hence exhibit jumps and zero-inflation, as small variations in the signal can cause it to be sometimes truncated to 0 and sometimes reported at its actual level", + "google-survey" = "Discarded when an estimate is based on fewer than 100 survey responses", + "google-symptoms" = "Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data", + "hhs" = "None", "hospital-admissions" = "Discarded if over a given 7-day period an estimate is computed with 500 or fewer observations", - "indicator-combination" = NA_character_, - "jhu-csse" = NA_character_, # TODO + "indicator-combination" = "None. However underlying signals may perform their own censoring", + "jhu-csse" = "None", "nchs-mortality" = "Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading", "quidel" = "Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests", - "safegraph" = NA_character_, - "usa-facts" = NA_character_, + "safegraph" = "None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details", + "usa-facts" = "None", "youtube-survey" = NA_character_ ) signal_specific_censoring <- tibble::tribble( From cc5ee22899cc79cd16edbe8c0a11b664d5b057de Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Tue, 7 May 2024 18:48:53 -0400 Subject: [PATCH 05/30] clean up censor section --- scripts/signal_spreadsheet_updater.R | 13 +++++-------- 1 file changed, 5 insertions(+), 8 deletions(-) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index 93e5de5b8..5d44aa045 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -623,17 +623,14 @@ col <- "Severity Pyramid Rungs" col <- "Data Censoring" -# Has any of the data been censored (e.g. small counts)? -# -# TODO: If so how, and how much impact does it have (e.g. approximate fraction of -# counts affected). -# +# Has any of the data been censored (e.g. small counts)? If so how, and how +# much impact does it have (e.g. approximate fraction of counts affected). # This is an unstructured text field. data_censoring <- c( "chng" = "Discarded if over a given 7-day period an estimate is computed with 100 or fewer observations", - "covid-act-now" = "Discarded if sample size (total tests performed) is 0. It is unknown what, if any, censoring the data source performs", + "covid-act-now" = "Discarded if sample size (total tests performed) is 0", "doctor-visits" = "Discarded if over a given 7-day period an estimate is computed with 500 or fewer observations", - "dsew-cpr" = "It is unknown what, if any, censoring the data source performs", + "dsew-cpr" = "None", "fb-survey" = "Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.", @@ -653,7 +650,7 @@ data_censoring <- c( signal_specific_censoring <- tibble::tribble( ~data_source, ~signal, ~note, "dsew-cpr", "covid_naat_pct_positive_7dav", "Discarded when the 7dav NAAT test volume provided in the same originating - spreadsheet, corresponding to a period ~4 days earlier, is 5 or fewer. This removes 10-20% of counties (https://github.com/cmu-delphi/covidcast-indicators/issues/1513). It is unknown what, if any, censoring the data source performs", + spreadsheet, corresponding to a period ~4 days earlier, is 5 or fewer. This removes 10-20% of counties (https://github.com/cmu-delphi/covidcast-indicators/issues/1513)", ) source_updated[, col] <- data_censoring[source_updated$data_source] From 903e79cd1b1c70b335cb8d9d4e3171398569d18e Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Tue, 7 May 2024 18:49:56 -0400 Subject: [PATCH 06/30] add backfill/lag tool --- scripts/signal_spreadsheet_updater.R | 75 ++++++++++++++++++++++++++++ 1 file changed, 75 insertions(+) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index 5d44aa045..e96111303 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -480,6 +480,81 @@ avail_geos <- c( "youtube-survey" = NA_character_ ) +# # Tool: Investigate reporting lag and revision cadence +# source <- "indicator-combination-nmf" +# signal <- "nmf_day_doc_fbc_fbs_ght" +# # Not available for all indicators. Try nation. Avoid smaller geos because +# # processing later will take a while. +# geo_type <- "state" + +# # Consider a range of issues. About 2 weeks is probably fine. Not all indicators +# # are available in this time range, so you may need to make another range of +# # dates that is years or months different. +# about_2weeks_issues <- c( +# "2021-02-01", +# "2021-02-02", +# "2021-02-04", +# "2021-02-05", +# "2021-02-06", +# "2021-02-07", +# "2021-02-08", +# "2021-02-09", +# "2021-02-10", +# "2021-02-11", +# "2021-02-12", +# "2021-02-13", +# "2021-02-14", +# "2021-02-15", +# "2021-02-16" +# ) + + +# epidata <- pub_covidcast( +# source, +# signal, +# geo_type = geo_type, +# geo_values = "*", +# time_type = "day", +# issues = about_2weeks_issues +# ) + + +# # Make sure data is looking reasonable +# # Number of reference dates reported in each issue +# count(epidata, issue) + +# # Number of locations reported for each issue and reference date +# count(epidata, issue, time_value) + + +# ## Revision cadence +# # For each location and reference date, are all reported values the same across +# # all lags we're checking? +# revision_comparison <- epidata %>% +# group_by(time_value, geo_value) %>% +# summarize( +# no_backfill = case_when( +# length(unique(value)) == 1 ~ "TRUE", +# # If only two different values, are they approximately the same? +# length(unique(value)) == 2 ~ all.equal(unique(value)[1], unique(value)[2]) %>% as.character(), +# # If three different values, list them +# length(unique(value)) > 2 ~ paste(unique(value), collapse = ", "), +# ) +# ) +# # Are all reference dates without any lag? +# all(revision_comparison$no_backfill == "TRUE") +# View(revision_comparison) + + +# ## Reporting lag +# # Find how lagged the newest reported value is for each issue. +# epidata_slice <- epidata %>% group_by(issue) %>% slice_min(lag) +# # Find the most common min lag. We expect a relatively narrow range of lags. At +# # most, a data source should be updated weekly such that it has a range of lags +# # of 7 days (e.g. 5-12 days). For data updated daily, we expect a range of lags +# # of only a few days (e.g. 2-4 days or even 2-3 days). +# table(epidata_slice$lag) + col <- "Typical Reporting Lag" # The number of days as an unstructured field, e.g. "3-5 days", from the last From d068b3e31aff9c601416e624aea3a9d032867edf Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Wed, 8 May 2024 13:48:19 -0400 Subject: [PATCH 07/30] add missingness --- scripts/signal_spreadsheet_updater.R | 176 ++++++++++++++++++++++----- 1 file changed, 148 insertions(+), 28 deletions(-) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index e96111303..11dbf1422 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -486,7 +486,7 @@ avail_geos <- c( # # Not available for all indicators. Try nation. Avoid smaller geos because # # processing later will take a while. # geo_type <- "state" - +# # # Consider a range of issues. About 2 weeks is probably fine. Not all indicators # # are available in this time range, so you may need to make another range of # # dates that is years or months different. @@ -507,8 +507,8 @@ avail_geos <- c( # "2021-02-15", # "2021-02-16" # ) - - +# +# # epidata <- pub_covidcast( # source, # signal, @@ -517,16 +517,16 @@ avail_geos <- c( # time_type = "day", # issues = about_2weeks_issues # ) - - +# +# # # Make sure data is looking reasonable # # Number of reference dates reported in each issue # count(epidata, issue) - +# # # Number of locations reported for each issue and reference date # count(epidata, issue, time_value) - - +# +# # ## Revision cadence # # For each location and reference date, are all reported values the same across # # all lags we're checking? @@ -544,8 +544,8 @@ avail_geos <- c( # # Are all reference dates without any lag? # all(revision_comparison$no_backfill == "TRUE") # View(revision_comparison) - - +# +# # ## Reporting lag # # Find how lagged the newest reported value is for each issue. # epidata_slice <- epidata %>% group_by(issue) %>% slice_min(lag) @@ -730,7 +730,66 @@ signal_specific_censoring <- tibble::tribble( ) source_updated[, col] <- data_censoring[source_updated$data_source] -# TODO +# Add signal_specific_censoring info +source_updated <- left_join( + source_updated, signal_specific_censoring, + by = c("Signal" = "signal", "data_source") +) %>% + mutate(`Data Censoring` = coalesce(note, `Data Censoring`)) %>% + select(-note) + + +# # Tool: Investigate state and county coverage +# suppressPackageStartupMessages({ +# library(epidatr) # Access Delphi API +# library(dplyr) # Data handling +# library(ggplot2) +# }) +# +# +# # COVIDcast metadata +# # Metadata documentation: https://cmu-delphi.github.io/delphi-epidata/api/covidcast_meta.html +# metadata <- pub_covidcast_meta() +# # Convert `last_update` into a datetime. +# # metadata$last_update <- as.POSIXct(metadata$last_update, origin = "1970-01-01") +# ## If don't want the hours, etc, truncate with `as.Date` +# metadata$last_update <- as.Date(as.POSIXct(metadata$last_update, origin = "1970-01-01")) +# +# one_sig_per_source <- metadata %>% +# arrange(desc(signal)) %>% +# group_by(data_source) %>% +# slice_head(n = 1) +# +# state_filtered <- metadata %>% +# filter(geo_type == "state") %>% +# select(data_source, signal, geo_type, num_locations) %>% +# mutate(pct_locations = num_locations / 51 * 100) +# first_sig_per_source_state <- state_filtered %>% +# group_by(data_source) %>% +# slice_head(n = 1) +# first_sig_per_source_state +# +# ggplot( +# data = state_filtered, +# aes(x = data_source, y = pct_locations) +# ) + geom_boxplot() +# +# +# county_filtered <- metadata %>% +# filter(geo_type == "county") %>% +# select(data_source, signal, geo_type, num_locations) %>% +# mutate(pct_locations = num_locations / 3143 * 100) +# first_sig_per_source_county <- county_filtered %>% +# group_by(data_source) %>% +# slice_head(n = 1) +# first_sig_per_source_county +# +# ggplot( +# data = county_filtered, +# aes(x = data_source, y = pct_locations) +# ) + geom_boxplot() + + col <- "Missingness" # How much missingness is there, and for what reasons? Is it possible to # distinguish a missing value from a true zero? This is an unstructured text @@ -743,27 +802,88 @@ col <- "Missingness" # not sure what to do. Maybe just summarize the current state, e.g. "85% # counties available in mid 2020, then gradually declined to 8% of counties # by April 2024", and leave it at that. We could occasionally update it. + +all_counties_terr <- "Data is available for all counties and some territorial county equivalents." +all_states <- "Data is available for all states." +all_states_terr <- "Data is available for all states and some territories." missingness <- c( - "chng" = NA_character_, - "covid-act-now" = "A few counties, most notably in California, are not covered by this data source", - "doctor-visits" = NA_character_, - "dsew-cpr" = NA_character_, - "fb-survey" = "A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)", - "ght" = NA_character_, - "google-survey" = NA_character_, - "google-symptoms" = NA_character_, - "hhs" = NA_character_, - "hospital-admissions" = NA_character_, - "indicator-combination" = NA_character_, - "jhu-csse" = NA_character_, - "nchs-mortality" = NA_character_, - "quidel" = NA_character_, - "safegraph" = NA_character_, - "usa-facts" = NA_character_, - "youtube-survey" = NA_character_ + "chng" = paste("Data is available for nearly all (99%) of counties.", all_states_terr), + "covid-act-now" = paste("Data is available for nearly all (99%) of counties. A few counties, most notably in California, are not covered by this data source", all_states), + "doctor-visits" = paste("Data is available for about 80% of counties", all_states_terr), + "dsew-cpr" = paste(all_counties_terr, all_states_terr), + "fb-survey" = "Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)", + "ght" = all_states, + "google-survey" = paste("Data is available for about 20% of counties", all_states), + "google-symptoms" = NA_character_, # below + "hhs" = all_states_terr, + "hospital-admissions" = paste("Data is available for about 35% of counties", all_states), + "indicator-combination" = paste(all_counties_terr, all_states_terr), + "jhu-csse" = paste(all_counties_terr, all_states_terr), + "nchs-mortality" = paste(all_states_terr), + "quidel" = "Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.", # TODO + "safegraph" = paste(all_counties_terr, all_states_terr), + "usa-facts" = paste(all_counties_terr, all_states), + "youtube-survey" = NA_character_ # below ) source_updated[, col] <- missingness[source_updated$data_source] +google_symptoms_note <- "Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason" +signal_specific_missingness <- tibble::tribble( + ~data_source, ~signal, ~note, + "indicator-combination", "nmf_day_doc_fbc_fbs_ght", paste("Data is available for about 80% of counties", all_states_terr), + "indicator-combination", "nmf_day_doc_fbs_ght", paste("Data is available for about 70% of counties", all_states_terr), + + "safegraph", "bars_visit_num", "Data is available for about 10% of counties. Data is available for about 90% of states", + "safegraph", "bars_visit_prop", "Data is available for about 10% of counties. Data is available for about 90% of states", + "safegraph", "restaurants_visit_num", paste("Data is available for about 80% of counties", all_states_terr), + "safegraph", "restaurants_visit_prop", paste("Data is available for about 80% of counties", all_states_terr), + + "fb-survey", "smoothed_cli", paste("Data is available for about 50% of counties.", all_states_terr, "Availability declines over time as survey response rate decreases"), + "fb-survey", "smoothed_ili", paste("Data is available for about 50% of counties.", all_states_terr, "Availability declines over time as survey response rate decreases"), + "fb-survey", "smoothed_wcli", paste("Data is available for about 50% of counties.", all_states_terr, "Availability declines over time as survey response rate decreases"), + "fb-survey", "smoothed_wili", paste("Data is available for about 50% of counties.", all_states_terr, "Availability declines over time as survey response rate decreases"), + "fb-survey", "smoothed_travel_outside_state_5d", paste("Data is available for about 45% of counties.", all_states_terr, "Availability declines over time as survey response rate decreases"), + "fb-survey", "smoothed_wtravel_outside_state_5d", paste("Data is available for about 45% of counties.", all_states_terr, "Availability declines over time as survey response rate decreases"), + "fb-survey", "smoothed_nohh_cmnty_cli", paste("Data is available for about 40% of counties.", all_states_terr, "Availability declines over time as survey response rate decreases"), + "fb-survey", "smoothed_hh_cmnty_cli", paste("Data is available for about 40% of counties.", all_states_terr, "Availability declines over time as survey response rate decreases"), + "fb-survey", "smoothed_whh_cmnty_cli", paste("Data is available for about 35% of counties.", all_states_terr, "Availability declines over time as survey response rate decreases"), + "fb-survey", "smoothed_wnohh_cmnty_cli", paste("Data is available for about 35% of counties.", all_states_terr, "Availability declines over time as survey response rate decreases"), + + "youtube-survey", "raw_cli", "Data is available for about 40% of states", + "youtube-survey", "raw_ili", "Data is available for about 40% of states", + "youtube-survey", "smoothed_cli", "Data is available for about 80% of states", + "youtube-survey", "smoothed_ili", "Data is available for about 80% of states", + + "google-symptoms", "ageusia_raw_search", paste("Data is available for about 3-4% of counties. Data is available for about 85% of states.", google_symptoms_note), + "google-symptoms", "ageusia_smoothed_search", paste("Data is available for about 3-4% of counties. Data is available for about 85% of states.", google_symptoms_note), + "google-symptoms", "anosmia_raw_search", paste("Data is available for about 3-4% of counties. Data is available for about 85% of states.", google_symptoms_note), + "google-symptoms", "anosmia_smoothed_search", paste("Data is available for about 3-4% of counties. Data is available for about 85% of states.", google_symptoms_note), + "google-symptoms", "s01_raw_search", paste("Data is available for about 50% of counties.", all_states, google_symptoms_note), + "google-symptoms", "s01_smoothed_search", paste("Data is available for about 50% of counties.", all_states, google_symptoms_note), + "google-symptoms", "s02_raw_search", paste("Data is available for about 65% of counties.", all_states, google_symptoms_note), + "google-symptoms", "s02_smoothed_search", paste("Data is available for about 65% of counties.", all_states, google_symptoms_note), + "google-symptoms", "s03_raw_search", paste("Data is available for about 50% of counties.", all_states, google_symptoms_note), + "google-symptoms", "s03_smoothed_search", paste("Data is available for about 50% of counties.", all_states, google_symptoms_note), + "google-symptoms", "s04_raw_search", paste("Data is available for about 30% of counties.", all_states, google_symptoms_note), + "google-symptoms", "s04_smoothed_search", paste("Data is available for about 30% of counties.", all_states, google_symptoms_note), + "google-symptoms", "s05_raw_search", paste("Data is available for about 3-4% of counties. Data is available for about 90% of states.", google_symptoms_note), + "google-symptoms", "s05_smoothed_search", paste("Data is available for about 3-4% of counties. Data is available for about 90% of states.", google_symptoms_note), + "google-symptoms", "s06_raw_search", paste("Data is available for about 30% of counties.", all_states, google_symptoms_note), + "google-symptoms", "s06_smoothed_search", paste("Data is available for about 30% of counties.", all_states, google_symptoms_note), + "google-symptoms", "scontrol_raw_search", paste("Data is available for about 45% of counties.", all_states, google_symptoms_note), + "google-symptoms", "scontrol_smoothed_search", paste("Data is available for about 45% of counties.", all_states, google_symptoms_note), + "google-symptoms", "sum_anosmia_ageusia_raw_search", paste("Data is available for about 3-4% of counties. Data is available for about 85% of states.", google_symptoms_note), + "google-symptoms", "sum_anosmia_ageusia_smoothed_search", paste("Data is available for about 3-4% of counties. Data is available for about 85% of states.", google_symptoms_note), +) + +# Add signal-specific missingness +source_updated <- left_join( + source_updated, signal_specific_missingness, + by = c("Signal" = "signal", "data_source") +) %>% + mutate(`Missingness` = coalesce(note, `Missingness`)) %>% + select(-note) + col <- "Who may access this signal?" # Who has the right to access this signal? E.g. "Delphi, CDC" or "Delphi, From 6a3733d169b2464ae4e6b90ca416a889edd30578 Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Wed, 8 May 2024 13:49:53 -0400 Subject: [PATCH 08/30] save output --- scripts/signal_spreadsheet_updater.R | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index 11dbf1422..492dc93fc 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -1013,10 +1013,9 @@ dua_link <- c( source_updated[, col] <- dua_link[source_updated$data_source] -source_updated - -# TODO: save updated signals table to CSV [readr::read_csv] +# Save updated signals table to CSV [readr::write_csv] +write_csv(source_updated, file = "updated_signal_spreadsheet.csv") # Final manual steps: From a29cee3f5669c63810395e26813823ebf268523b Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Wed, 8 May 2024 16:19:01 -0400 Subject: [PATCH 09/30] cleanup --- scripts/signal_spreadsheet_updater.R | 26 +++++++++++++++++++------- 1 file changed, 19 insertions(+), 7 deletions(-) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index 492dc93fc..bf8a8c0fa 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -110,14 +110,14 @@ new_fields <- c( "Temporal Scope Start", "Temporal Scope End", "Reporting Cadence", - "Reporting Lag", - "Revision Cadence", + "Typical Reporting Lag", + "Typical Revision Cadence", "Demographic Scope", - "Demographic Disaggregation", ###Change to "Demographic Breakdowns" when granted sheet access + "Demographic Breakdowns", "Severity Pyramid Rungs", "Data Censoring", "Missingness", - "Who may Access this signal?", + "Who may access this signal?", "Who may be told about this signal?", "Use Restrictions", "Link to DUA" @@ -132,7 +132,7 @@ new_fields_with_missings <- names(new_fields_with_missings[unlist(new_fields_wit message( paste(new_fields_with_missings, collapse = ", "), - " columns contain missing values and need to be filled in programmatically" + " columns contain missing values and need to be filled in" ) @@ -688,7 +688,7 @@ demo_breakdowns <- c( ) source_updated[, col] <- demo_breakdowns[source_updated$data_source] # Quidel covid has age bands, but quidel flu doesn't. -source_updated[source_update$`Source Subdivision` == "quidel-flu", col] <- "None" +source_updated[source_updated$`Source Subdivision` == "quidel-flu", col] <- "None" col <- "Severity Pyramid Rungs" @@ -1008,12 +1008,24 @@ dua_link <- c( "quidel" = "https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS", "safegraph" = "https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x", "usa-facts" = NA_character_, #public - "youtube-survey" = NA_character_, #contract expected + "youtube-survey" = NA_character_ #contract expected ) source_updated[, col] <- dua_link[source_updated$data_source] +new_fields_with_missings <- lapply(new_fields, function(col) { + any(is.na(source_updated[, col])) +}) +new_fields_with_missings <- names(new_fields_with_missings[unlist(new_fields_with_missings)]) + +message( + paste(new_fields_with_missings, collapse = ", "), + " columns still contain missing values and need to be filled in" +) + + + # Save updated signals table to CSV [readr::write_csv] write_csv(source_updated, file = "updated_signal_spreadsheet.csv") From b671c36fccc85db7775919b48a4a6c4576e6ca88 Mon Sep 17 00:00:00 2001 From: Tina Townes Date: Thu, 9 May 2024 02:07:34 -0400 Subject: [PATCH 10/30] updates to DUA, Quidel --- scripts/quidelMissingness.R | 246 ++++ scripts/signal_spreadsheet_updater.R | 221 ++-- scripts/updated_signal_spreadsheet.csv | 1539 ++++++++++++++++++++++++ 3 files changed, 1895 insertions(+), 111 deletions(-) create mode 100644 scripts/quidelMissingness.R create mode 100644 scripts/updated_signal_spreadsheet.csv diff --git a/scripts/quidelMissingness.R b/scripts/quidelMissingness.R new file mode 100644 index 000000000..07ed80180 --- /dev/null +++ b/scripts/quidelMissingness.R @@ -0,0 +1,246 @@ +library(epidatr) +library(dplyr) + +signals <- c( + #"covid_ag_raw_pct_positive", #"county", "state" + #"covid_ag_raw_pct_positive_age_0_4", #"county", "state" + #"covid_ag_smoothed_pct_positive", #"county", "state" + #"covid_ag_smoothed_pct_positive_age_0_4", #"county", "state" + #"covid_ag_smoothed_pct_positive_age_18_49" #"county", "state" + #"covid_ag_smoothed_pct_positive_age_65plus" #"county", "state" + + + "covid_ag_raw_pct_positive", #"hrr", "msa", "hhs", "nation" + "covid_ag_smoothed_pct_positive" #"hrr", "msa", "hhs", "nation" + + #"raw_pct_negative", #FLU + #"raw_tests_per_device", #FLU + #"smoothed_pct_negative", #FLU + #"smoothed_tests_per_device" #FLU +) +names(signals) <- signals +lapply(signals, function(signal) { + source <- "quidel" + signal <- signals + geo_type <- "msa" #"county", "state", "hrr", "msa", "hhs", "nation" + time_type <- "day" + + print(signal) + print(geo_type) + + epidata <- pub_covidcast( + source, + signal, + geo_type = geo_type, + geo_values = "*", + time_type = time_type, + time_values = c( + "2021-03-01", + "2021-03-02", + "2021-03-03", + "2021-03-04", + "2021-03-05", + "2021-03-06", + "2021-03-07", + "2021-03-08", + "2021-03-09", + "2021-03-10", + "2021-03-11", + "2021-03-12", + "2021-03-13", + "2021-03-14", + "2021-03-15", + "2021-03-16", + "2021-03-17", + "2021-03-18", + "2021-03-19", + "2021-03-20", + "2021-03-21", + "2021-03-22", + "2021-03-23", + "2021-03-24", + "2021-03-25", + "2021-03-26", + "2021-03-27", + "2021-03-28", + "2021-03-29", + "2021-03-30" + ) + ) + + # Number of locations reported for each reference date + count_geos_by_date <- count(epidata, time_value) + # print(count_geos_by_date) + print(max(count_geos_by_date$n) / 3143 * 100) + print(mean(count_geos_by_date$n) / 3143 * 100) + + return(max(count_geos_by_date$n) / 3143 * 100) + +}) + +####################################### geo_type = "county" +# covid_ag_raw_pct_positive +# "covid_ag_raw_pct_positive" +# covid_ag_raw_pct_positive_age_0_4 +# "covid_ag_raw_pct_positive_age_0_4" +# covid_ag_smoothed_pct_positive +# "covid_ag_smoothed_pct_positive" +# covid_ag_smoothed_pct_positive_age_0_4 +# "covid_ag_smoothed_pct_positive_age_0_4" +# covid_ag_smoothed_pct_positive_age_18_49 +# "covid_ag_smoothed_pct_positive_age_18_49" +# [1] "county" +# [1] 76.32835 +# [1] 72.70973 +# covid_ag_raw_pct_positive +# "covid_ag_raw_pct_positive" +# covid_ag_raw_pct_positive_age_0_4 +# "covid_ag_raw_pct_positive_age_0_4" +# covid_ag_smoothed_pct_positive +# "covid_ag_smoothed_pct_positive" +# covid_ag_smoothed_pct_positive_age_0_4 +# "covid_ag_smoothed_pct_positive_age_0_4" +# covid_ag_smoothed_pct_positive_age_18_49 +# "covid_ag_smoothed_pct_positive_age_18_49" +# [1] "county" +# [1] 76.32835 +# [1] 72.70973 +# covid_ag_raw_pct_positive +# "covid_ag_raw_pct_positive" +# covid_ag_raw_pct_positive_age_0_4 +# "covid_ag_raw_pct_positive_age_0_4" +# covid_ag_smoothed_pct_positive +# "covid_ag_smoothed_pct_positive" +# covid_ag_smoothed_pct_positive_age_0_4 +# "covid_ag_smoothed_pct_positive_age_0_4" +# covid_ag_smoothed_pct_positive_age_18_49 +# "covid_ag_smoothed_pct_positive_age_18_49" +# [1] "county" +# [1] 76.32835 +# [1] 72.70973 +# covid_ag_raw_pct_positive +# "covid_ag_raw_pct_positive" +# covid_ag_raw_pct_positive_age_0_4 +# "covid_ag_raw_pct_positive_age_0_4" +# covid_ag_smoothed_pct_positive +# "covid_ag_smoothed_pct_positive" +# covid_ag_smoothed_pct_positive_age_0_4 +# "covid_ag_smoothed_pct_positive_age_0_4" +# covid_ag_smoothed_pct_positive_age_18_49 +# "covid_ag_smoothed_pct_positive_age_18_49" +# [1] "county" +# [1] 76.32835 +# [1] 72.70973 +# covid_ag_raw_pct_positive +# "covid_ag_raw_pct_positive" +# covid_ag_raw_pct_positive_age_0_4 +# "covid_ag_raw_pct_positive_age_0_4" +# covid_ag_smoothed_pct_positive +# "covid_ag_smoothed_pct_positive" +# covid_ag_smoothed_pct_positive_age_0_4 +# "covid_ag_smoothed_pct_positive_age_0_4" +# covid_ag_smoothed_pct_positive_age_18_49 +# "covid_ag_smoothed_pct_positive_age_18_49" +# [1] "county" +# [1] 76.32835 +# [1] 72.70973 +# $covid_ag_raw_pct_positive +# [1] 76.32835 +# +# $covid_ag_raw_pct_positive_age_0_4 +# [1] 76.32835 +# +# $covid_ag_smoothed_pct_positive +# [1] 76.32835 +# +# $covid_ag_smoothed_pct_positive_age_0_4 +# [1] 76.32835 +# +# $covid_ag_smoothed_pct_positive_age_18_49 +# [1] 76.32835 + + + +####################################### geo_type = "state" +# covid_ag_raw_pct_positive +# "covid_ag_raw_pct_positive" +# covid_ag_raw_pct_positive_age_0_4 +# "covid_ag_raw_pct_positive_age_0_4" +# covid_ag_smoothed_pct_positive +# "covid_ag_smoothed_pct_positive" +# covid_ag_smoothed_pct_positive_age_0_4 +# "covid_ag_smoothed_pct_positive_age_0_4" +# covid_ag_smoothed_pct_positive_age_18_49 +# "covid_ag_smoothed_pct_positive_age_18_49" +# [1] "state" +# [1] 6.04518 +# [1] 5.738679 +# covid_ag_raw_pct_positive +# "covid_ag_raw_pct_positive" +# covid_ag_raw_pct_positive_age_0_4 +# "covid_ag_raw_pct_positive_age_0_4" +# covid_ag_smoothed_pct_positive +# "covid_ag_smoothed_pct_positive" +# covid_ag_smoothed_pct_positive_age_0_4 +# "covid_ag_smoothed_pct_positive_age_0_4" +# covid_ag_smoothed_pct_positive_age_18_49 +# "covid_ag_smoothed_pct_positive_age_18_49" +# [1] "state" +# [1] 6.04518 +# [1] 5.738679 +# covid_ag_raw_pct_positive +# "covid_ag_raw_pct_positive" +# covid_ag_raw_pct_positive_age_0_4 +# "covid_ag_raw_pct_positive_age_0_4" +# covid_ag_smoothed_pct_positive +# "covid_ag_smoothed_pct_positive" +# covid_ag_smoothed_pct_positive_age_0_4 +# "covid_ag_smoothed_pct_positive_age_0_4" +# covid_ag_smoothed_pct_positive_age_18_49 +# "covid_ag_smoothed_pct_positive_age_18_49" +# [1] "state" +# [1] 6.04518 +# [1] 5.738679 +# covid_ag_raw_pct_positive +# "covid_ag_raw_pct_positive" +# covid_ag_raw_pct_positive_age_0_4 +# "covid_ag_raw_pct_positive_age_0_4" +# covid_ag_smoothed_pct_positive +# "covid_ag_smoothed_pct_positive" +# covid_ag_smoothed_pct_positive_age_0_4 +# "covid_ag_smoothed_pct_positive_age_0_4" +# covid_ag_smoothed_pct_positive_age_18_49 +# "covid_ag_smoothed_pct_positive_age_18_49" +# [1] "state" +# [1] 6.04518 +# [1] 5.738679 +# covid_ag_raw_pct_positive +# "covid_ag_raw_pct_positive" +# covid_ag_raw_pct_positive_age_0_4 +# "covid_ag_raw_pct_positive_age_0_4" +# covid_ag_smoothed_pct_positive +# "covid_ag_smoothed_pct_positive" +# covid_ag_smoothed_pct_positive_age_0_4 +# "covid_ag_smoothed_pct_positive_age_0_4" +# covid_ag_smoothed_pct_positive_age_18_49 +# "covid_ag_smoothed_pct_positive_age_18_49" +# [1] "state" +# [1] 6.04518 +# [1] 5.738679 +# $covid_ag_raw_pct_positive +# [1] 6.04518 +# +# $covid_ag_raw_pct_positive_age_0_4 +# [1] 6.04518 +# +# $covid_ag_smoothed_pct_positive +# [1] 6.04518 +# +# $covid_ag_smoothed_pct_positive_age_0_4 +# [1] 6.04518 +# +# $covid_ag_smoothed_pct_positive_age_18_49 +# [1] 6.04518 + +####################################### geo_type = "state" + diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index 492dc93fc..f678b5bb8 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -10,7 +10,7 @@ suppressPackageStartupMessages({ options(warn = 1) -# TODO all info for youtube-survey +# (unable to find more) TODO all info for youtube-survey, https://github.com/cmu-delphi/covid-19/tree/main/youtube # COVIDcast metadata # Metadata documentation: https://cmu-delphi.github.io/delphi-epidata/api/covidcast_meta.html @@ -110,15 +110,16 @@ new_fields <- c( "Temporal Scope Start", "Temporal Scope End", "Reporting Cadence", - "Reporting Lag", - "Revision Cadence", + "Typical Reporting Lag", #originally Reporting Lag + "Typical Revision Cadence", #originally Revision Cadence "Demographic Scope", - "Demographic Disaggregation", ###Change to "Demographic Breakdowns" when granted sheet access + "Demographic Breakdowns", "Severity Pyramid Rungs", "Data Censoring", "Missingness", - "Who may Access this signal?", + "Who may access this signal?", "Who may be told about this signal?", + "License", "Use Restrictions", "Link to DUA" ) @@ -190,7 +191,7 @@ source5 <- source4 %>% # Inactive data_sources list inactive_sources <- c( "jhu-csse", "dsew-cpr", "fb-survey", "covid-act-now", "ght", "google-survey", - "indicator-combination", "safegraph", "usa-facts" + "indicator-combination", "safegraph", "usa-facts", "youtube-survey" ) # Inactive signals list, where some signals for a given data source are active @@ -310,7 +311,7 @@ geo_scope <- c( "quidel" = "USA", "safegraph" = "USA", "usa-facts" = "USA", - "youtube-survey" = NA_character_ + "youtube-survey" = "USA" ) source_updated[, col] <- geo_scope[source_updated$data_source] @@ -370,10 +371,9 @@ avail_geos <- c( "indicator-combination" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), "jhu-csse" = glue("county, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), "nchs-mortality" = glue("state, nation"), - - # TODO check against actual data. Or maybe there's an internal/private version of metadata that includes Quidel stats? - # this is quidel non-flu signals, other is flu - "quidel" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), + # Quidel non-flu signals + # (done) TODO check against actual data. Or maybe there's an internal/private version of metadata that includes Quidel stats? + "quidel" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), #geos all contain data "safegraph" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), "usa-facts" = glue("county, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), "youtube-survey" = "state{delphi_agg_text}" @@ -432,12 +432,12 @@ leftover_signal_geos_manual <- tibble::tribble( "indicator-combination", "nmf_day_doc_fbs_ght", combo_geos, # Quidel flu signals - # TODO check against actual data. Or maybe there's an internal/private version of metadata that includes Quidel stats? Nat was only looking at metadata - #for each of these quidel signals, make request to API for each possible geotype (county, hrr, etc) to see if data comes back - "quidel", "raw_pct_negative", quidel_geos, - "quidel", "smoothed_pct_negative", quidel_geos, - "quidel", "raw_tests_per_device", quidel_geos, - "quidel", "smoothed_tests_per_device", quidel_geos + # (done) TODO check against actual data. Or maybe there's an internal/private version of metadata that includes Quidel stats? Nat was only looking at metadata + # for each of these quidel signals, make request to API for each possible geotype (county, hrr, etc) to see if data comes back + "quidel", "raw_pct_negative", quidel_geos, #only state, msa + "quidel", "smoothed_pct_negative", quidel_geos, #only state, msa + "quidel", "raw_tests_per_device", quidel_geos, #only state, msa + "quidel", "smoothed_tests_per_device", quidel_geos#only state, msa ) source_updated[, col] <- coalesce(avail_geos[source_updated$data_source], source_updated[[col]]) @@ -477,84 +477,83 @@ avail_geos <- c( "quidel" = "daily", "safegraph" = "weekly", "usa-facts" = "weekly", - "youtube-survey" = NA_character_ + "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube ) # # Tool: Investigate reporting lag and revision cadence -# source <- "indicator-combination-nmf" -# signal <- "nmf_day_doc_fbc_fbs_ght" +source <- "quidel" +signal <- "covid_ag_raw_pct_positive" # # Not available for all indicators. Try nation. Avoid smaller geos because # # processing later will take a while. -# geo_type <- "state" -# +geo_type <- "nation" + # # Consider a range of issues. About 2 weeks is probably fine. Not all indicators # # are available in this time range, so you may need to make another range of # # dates that is years or months different. -# about_2weeks_issues <- c( -# "2021-02-01", -# "2021-02-02", -# "2021-02-04", -# "2021-02-05", -# "2021-02-06", -# "2021-02-07", -# "2021-02-08", -# "2021-02-09", -# "2021-02-10", -# "2021-02-11", -# "2021-02-12", -# "2021-02-13", -# "2021-02-14", -# "2021-02-15", -# "2021-02-16" -# ) -# -# -# epidata <- pub_covidcast( -# source, -# signal, -# geo_type = geo_type, -# geo_values = "*", -# time_type = "day", -# issues = about_2weeks_issues -# ) -# -# +about_2weeks_issues <- c( + "2023-02-01", + "2023-02-02", + "2023-02-04", + "2023-02-05", + "2023-02-06", + "2023-02-07", + "2023-02-08", + "2023-02-09", + "2023-02-10", + "2023-02-11", + "2023-02-12", + "2023-02-13", + "2023-02-14", + "2023-02-15", + "2023-02-16" +) + + +epidata <- pub_covidcast( + source, + signal, + geo_type = geo_type, + geo_values = "*", + time_type = "day", + issues = about_2weeks_issues +) + + # # Make sure data is looking reasonable # # Number of reference dates reported in each issue -# count(epidata, issue) -# +count(epidata, issue) # between 35 to 41 + # # Number of locations reported for each issue and reference date -# count(epidata, issue, time_value) -# -# +count(epidata, issue, time_value) # 1 + + # ## Revision cadence # # For each location and reference date, are all reported values the same across # # all lags we're checking? -# revision_comparison <- epidata %>% -# group_by(time_value, geo_value) %>% -# summarize( -# no_backfill = case_when( -# length(unique(value)) == 1 ~ "TRUE", -# # If only two different values, are they approximately the same? -# length(unique(value)) == 2 ~ all.equal(unique(value)[1], unique(value)[2]) %>% as.character(), -# # If three different values, list them -# length(unique(value)) > 2 ~ paste(unique(value), collapse = ", "), -# ) -# ) +revision_comparison <- epidata %>% + group_by(time_value, geo_value) %>% + summarize( + no_backfill = case_when( + length(unique(value)) == 1 ~ "TRUE", + # If only two different values, are they approximately the same? + length(unique(value)) == 2 ~ all.equal(unique(value)[1], unique(value)[2]) %>% as.character(), + # If three different values, list them + length(unique(value)) > 2 ~ paste(unique(value), collapse = ", "), + ) + ) # # Are all reference dates without any lag? -# all(revision_comparison$no_backfill == "TRUE") -# View(revision_comparison) -# -# +all(revision_comparison$no_backfill == "TRUE") # [1] FALSE +View(revision_comparison) # 3 values TRUE, two have "Mean relative difference", rest are decimals + + # ## Reporting lag # # Find how lagged the newest reported value is for each issue. -# epidata_slice <- epidata %>% group_by(issue) %>% slice_min(lag) + epidata_slice <- epidata %>% group_by(issue) %>% slice_min(lag) # # Find the most common min lag. We expect a relatively narrow range of lags. At # # most, a data source should be updated weekly such that it has a range of lags # # of 7 days (e.g. 5-12 days). For data updated daily, we expect a range of lags # # of only a few days (e.g. 2-4 days or even 2-3 days). -# table(epidata_slice$lag) - +table(epidata_slice$lag) # 5 and 15 = weekly col <- "Typical Reporting Lag" # The number of days as an unstructured field, e.g. "3-5 days", from the last @@ -593,7 +592,7 @@ reporting_lag <- c( "quidel" = "5-6 days", "safegraph" = "3-11 days", "usa-facts" = "2-8 days", - "youtube-survey" = NA_character_ + "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube ) # Index (using `[]`) into the map using the data_source (or source division) @@ -623,10 +622,10 @@ revision_cadence <- c( corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.", "nchs-mortality" = "Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7)", - "quidel" = NA_character_, # Happens, up to 6+ weeks after the report date. # TODO + "quidel" = "Weekly. Happens, up to 6+ weeks after the report date.", # (done) TODO, "safegraph" = "None", "usa-facts" = "None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.", - "youtube-survey" = NA_character_ + "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube ) source_updated[, col] <- revision_cadence[source_updated$data_source] @@ -652,7 +651,7 @@ demo_scope <- c( "quidel" = "Nationwide Quidel testing equipment network", "safegraph" = "Safegraph panel members who use mobile devices", "usa-facts" = "All", - "youtube-survey" = NA_character_ + "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube ) source_updated[, col] <- demo_scope[source_updated$data_source] @@ -684,11 +683,11 @@ demo_breakdowns <- c( "quidel" = "age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)", "safegraph" = "None", "usa-facts" = "None", - "youtube-survey" = NA_character_ + "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube ) source_updated[, col] <- demo_breakdowns[source_updated$data_source] # Quidel covid has age bands, but quidel flu doesn't. -source_updated[source_update$`Source Subdivision` == "quidel-flu", col] <- "None" +source_updated[source_updated$`Source Subdivision` == "quidel-flu", col] <- "None" col <- "Severity Pyramid Rungs" @@ -720,7 +719,7 @@ data_censoring <- c( "quidel" = "Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests", "safegraph" = "None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details", "usa-facts" = "None", - "youtube-survey" = NA_character_ + "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube ) signal_specific_censoring <- tibble::tribble( ~data_source, ~signal, ~note, @@ -820,7 +819,7 @@ missingness <- c( "indicator-combination" = paste(all_counties_terr, all_states_terr), "jhu-csse" = paste(all_counties_terr, all_states_terr), "nchs-mortality" = paste(all_states_terr), - "quidel" = "Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.", # TODO + "quidel" = "Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.", # (done, see "quidelMissingness.R") TODO "safegraph" = paste(all_counties_terr, all_states_terr), "usa-facts" = paste(all_counties_terr, all_states), "youtube-survey" = NA_character_ # below @@ -905,7 +904,7 @@ orgs_allowed_access <- c( "quidel" = "Delphi", "safegraph" = "public", "usa-facts" = "public", - "youtube-survey" = NA_character_ + "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube ) source_updated[, col] <- orgs_allowed_access[source_updated$data_source] @@ -928,7 +927,7 @@ orgs_allowed_know <- c( "quidel" = "public", "safegraph" = "public", "usa-facts" = "public", - "youtube-survey" = NA_character_ + "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube ) source_updated[, col] <- orgs_allowed_know[source_updated$data_source] @@ -951,32 +950,32 @@ license <- c( "quidel" = "CC BY", "safegraph" = "CC BY", "usa-facts" = "CC BY", - "youtube-survey" = NA_character_ + "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube ) source_updated[, col] <- license[source_updated$data_source] -# TODO +# (done) TODO col <- "Use Restrictions" # Any important DUA restrictions on use, publication, sharing, linkage, etc.? use_restrictions <- c( - "chng" = NA_character_, #change DUA in confidential Google drive, generic contract terms - "covid-act-now" = NA_character_, #public - "doctor-visits" = NA_character_, #optum DUA in confidential Google drive, generic contract terms - "dsew-cpr" = NA_character_, #public - "fb-survey" = NA_character_, # - "ght" = NA_character_, - "google-survey" = NA_character_, - "google-symptoms" = NA_character_, - "hhs" = NA_character_, - "hospital-admissions" = NA_character_, #optum DUA in confidential Google drive, generic contract terms - "indicator-combination" = NA_character_, - "jhu-csse" = NA_character_, - "nchs-mortality" = NA_character_, - "quidel" = "Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics.", #Quidel DUA in confidential Google drive, - "safegraph" = NA_character_, - "usa-facts" = NA_character_, - "youtube-survey" = NA_character_ + "chng" = "CC BY-NC", #DUA in confidential Google drive, generic contract terms + "covid-act-now" = "CC BY-NC", #public + "doctor-visits" = "CC BY-NC", #optum DUA in confidential Google drive, generic contract terms + "dsew-cpr" = "Public Domain US Government (https://www.usa.gov/government-works)", #public + "fb-survey" = "Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.", # @AlexR + "ght" = "Google Terms of Service (https://policies.google.com/terms)", #public, no Delphi documentation, + "google-survey" = "CC BY", + "google-symptoms" = "Google Terms of Service (https://policies.google.com/terms)", + "hhs" = "Public Domain US Government (https://www.usa.gov/government-works)", + "hospital-admissions" = "CC BY", #optum DUA in confidential Google drive, generic contract terms + "indicator-combination" = "CC BY", + "jhu-csse" = "CC BY", + "nchs-mortality" = "NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm)", + "quidel" = "Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).", #Quidel DUA in confidential Google drive, + "safegraph" = "CC BY", + "usa-facts" = "CC BY", + "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube ) source_updated[, col] <- use_restrictions[source_updated$data_source] @@ -989,26 +988,26 @@ source_updated[, col] <- use_restrictions[source_updated$data_source] #bb <- aa$sources$`fb-survey`$signals %>% tibble::as_tibble() #bb -# TODO +# (done) TODO col <- "Link to DUA" dua_link <- c( "chng" = "https://drive.google.com/drive/u/1/folders/1GKYSFb6C_8jSHTg-65eVzSOT433oIDrf", #"https://cmu.box.com/s/cto4to822zecr3oyq1kkk9xmzhtq9tl2" "covid-act-now" = NA_character_, #public, maybe contract for other specific project #@Carlyn - "doctor-visits" = "https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf", #"https://cmu.box.com/s/l2tz6kmiws6jyty2azwb43poiepz0565", + "doctor-visits" = "https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf", #"https://cmu.box.com/s/l2tz6kmiws6jyty2azwb43poiepz0565" "dsew-cpr" = NA_character_, #public - "fb-survey" = "https://cmu.box.com/s/qfxplcdrcn9retfzx4zniyugbd9h3bos",#@Alex R. - "ght" = NA_character_, #public, has an API doesn't require password + "fb-survey" = NA_character_, # wait for OK from @Alex R. "https://drive.google.com/file/d/1zd6A5gS8ncvz18_pCQfL7UVRvUJVHDdn/view?usp=drive_link", "https://cmu.box.com/s/qfxplcdrcn9retfzx4zniyugbd9h3bos" + "ght" = NA_character_, #public, has an API doesn't require password, no Delphi documentation, "google-survey" = NA_character_, #@Carlyn has requested DUA from Roni "google-symptoms" = NA_character_, #public - "hhs" = NA_character_, #public gov't - "hospital-admissions" = "https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf", #"https://cmu.box.com/s/l2tz6kmiws6jyty2azwb43poiepz0565", + "hhs" = NA_character_, #public + "hospital-admissions" = "https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf", #"https://cmu.box.com/s/l2tz6kmiws6jyty2azwb43poiepz0565" "indicator-combination" = "see Doctor Visits, Facebook Survey, and Google Health Trends", "jhu-csse" = NA_character_, #public "nchs-mortality" = "https://www.cdc.gov/nchs/data_access/restrictions.htm", "quidel" = "https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS", "safegraph" = "https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x", "usa-facts" = NA_character_, #public - "youtube-survey" = NA_character_, #contract expected + "youtube-survey" = NA_character_ #looking for contract, https://github.com/cmu-delphi/covid-19/tree/main/youtube ) source_updated[, col] <- dua_link[source_updated$data_source] @@ -1019,4 +1018,4 @@ write_csv(source_updated, file = "updated_signal_spreadsheet.csv") # Final manual steps: -# open CSV in a GUI editor (excel or google sheets). copy scope date columns and paste into original spreadsheet online [manual] +# open CSV in a GUI editor (excel or google sheets). copy scope date columns and paste into original spreadsheet online [manual] \ No newline at end of file diff --git a/scripts/updated_signal_spreadsheet.csv b/scripts/updated_signal_spreadsheet.csv new file mode 100644 index 000000000..8fe71d5cb --- /dev/null +++ b/scripts/updated_signal_spreadsheet.csv @@ -0,0 +1,1539 @@ +Source Subdivision,Signal BaseName,base_is_other,Signal,Compute From Base,Name,Active,Short Description,Description,Source Name,"Pathogen/ +Disease Area",Signal Type,Geographic Scope,Available Geography,Temporal Scope Start,Temporal Scope Start Note,Temporal Scope End,Temporal Scope End Note,Time Type,Time Label,Reporting Cadence,Typical Reporting Lag,Typical Revision Cadence,Demographic Scope,Demographic Breakdowns,Severity Pyramid Rungs,Data Censoring,Missingness,Value Label,Format,Category,High Values Are,Is Smoothed,Is Weighted,Is Cumulative,Has StdErr,Has Sample Size,Who may access this signal?,Who may be told about this signal?,License,Use Restrictions,Link to DUA,Link,data_source +chng,smoothed_outpatient_cli,FALSE,smoothed_outpatient_cli,FALSE,COVID-Related Doctor Visits,TRUE,Estimated percentage of outpatient doctor visits primarily about COVID-related symptoms,"Estimated percentage of outpatient doctor visits primarily about COVID-related symptoms, based on Change Healthcare claims data that has been de-identified in accordance with HIPAA privacy regulations, smoothed in time using a Gaussian linear smoother",Change Healthcare,covid,Public behavior,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,Ongoing,NA,day,Date,daily,4-5 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 4-6 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 45 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Change Healthcare network,None,outpatient visit,Discarded if over a given 7-day period an estimate is computed with 100 or fewer observations,Data is available for nearly all (99%) of counties. Data is available for all states and some territories.,Value,raw,early,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY-NC,CC BY-NC,https://drive.google.com/drive/u/1/folders/1GKYSFb6C_8jSHTg-65eVzSOT433oIDrf,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/chng.html,chng +chng,smoothed_outpatient_cli,TRUE,smoothed_adj_outpatient_cli,FALSE,COVID-Related Doctor Visits (Day-adjusted),TRUE,NA,"Estimated percentage of outpatient doctor visits primarily about COVID-related symptoms, based on Change Healthcare claims data that has been de-identified in accordance with HIPAA privacy regulations, smoothed in time using a Gaussian linear smoother, and adjusted to reduce day-of-week effects",Change Healthcare,covid,Outpatient insurance claims,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,Ongoing,NA,day,Date,daily,4-5 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 4-6 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 45 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Change Healthcare network,None,outpatient visit,Discarded if over a given 7-day period an estimate is computed with 100 or fewer observations,Data is available for nearly all (99%) of counties. Data is available for all states and some territories.,Value,raw,early,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY-NC,CC BY-NC,https://drive.google.com/drive/u/1/folders/1GKYSFb6C_8jSHTg-65eVzSOT433oIDrf,NA,chng +chng,smoothed_outpatient_covid,FALSE,smoothed_outpatient_covid,FALSE,COVID-Confirmed Doctor Visits,TRUE,COVID-Confirmed Doctor Visits,"Estimated percentage of outpatient doctor visits with confirmed COVID-19, based on Change Healthcare claims data that has been de-identified in accordance with HIPAA privacy regulations, smoothed in time using a Gaussian linear smoother",Change Healthcare,covid,Outpatient insurance claims,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,Ongoing,NA,day,Date,daily,4-5 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 4-6 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 45 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Change Healthcare network,None,outpatient visit,Discarded if over a given 7-day period an estimate is computed with 100 or fewer observations,Data is available for nearly all (99%) of counties. Data is available for all states and some territories.,Value,raw,early,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY-NC,CC BY-NC,https://drive.google.com/drive/u/1/folders/1GKYSFb6C_8jSHTg-65eVzSOT433oIDrf,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/chng.html,chng +chng,smoothed_outpatient_covid,TRUE,smoothed_adj_outpatient_covid,FALSE,COVID-Confirmed Doctor Visits (Day-adjusted),TRUE,NA,"Estimated percentage of outpatient doctor visits with confirmed COVID-19, based on Change Healthcare claims data that has been de-identified in accordance with HIPAA privacy regulations, smoothed in time using a Gaussian linear smoother, and adjusted to reduce day-of-week effects",Change Healthcare,covid,Outpatient insurance claims,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,Ongoing,NA,day,Date,daily,4-5 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 4-6 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 45 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Change Healthcare network,None,outpatient visit,Discarded if over a given 7-day period an estimate is computed with 100 or fewer observations,Data is available for nearly all (99%) of counties. Data is available for all states and some territories.,Value,raw,early,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY-NC,CC BY-NC,https://drive.google.com/drive/u/1/folders/1GKYSFb6C_8jSHTg-65eVzSOT433oIDrf,NA,chng +chng,smoothed_outpatient_flu,FALSE,smoothed_outpatient_flu,FALSE,Influenza-Confirmed Doctor Visits,TRUE,Estimated percentage of outpatient doctor visits with confirmed influenza,"Estimated percentage of outpatient doctor visits with confirmed influenza, based on Change Healthcare claims data that has been de-identified in accordance with HIPAA privacy regulations, smoothed in time using a Gaussian linear smoother",Change Healthcare,flu,Outpatient insurance claims,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,Ongoing,NA,day,Day,daily,4-5 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 4-6 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 45 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Change Healthcare network,None,outpatient visit,Discarded if over a given 7-day period an estimate is computed with 100 or fewer observations,Data is available for nearly all (99%) of counties. Data is available for all states and some territories.,Value,raw,early,bad,TRUE,FALSE,FALSE,NA,NA,public,public,CC BY-NC,CC BY-NC,https://drive.google.com/drive/u/1/folders/1GKYSFb6C_8jSHTg-65eVzSOT433oIDrf,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/chng.html,chng +chng,smoothed_outpatient_flu,TRUE,smoothed_adj_outpatient_flu,FALSE,Influenza-Confirmed Doctor Visits (Day-adjusted),TRUE,NA,"Estimated percentage of outpatient doctor visits with confirmed influenza, based on Change Healthcare claims data that has been de-identified in accordance with HIPAA privacy regulations, smoothed in time using a Gaussian linear smoother, and adjusted to reduce day-of-week effects",Change Healthcare,flu,Outpatient insurance claims,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,Ongoing,NA,day,Day,daily,4-5 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 4-6 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 45 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Change Healthcare network,None,outpatient visit,Discarded if over a given 7-day period an estimate is computed with 100 or fewer observations,Data is available for nearly all (99%) of counties. Data is available for all states and some territories.,Value,raw,early,bad,TRUE,FALSE,FALSE,NA,NA,public,public,CC BY-NC,CC BY-NC,https://drive.google.com/drive/u/1/folders/1GKYSFb6C_8jSHTg-65eVzSOT433oIDrf,NA,chng +covid-act-now,pcr_specimen_positivity_rate,FALSE,pcr_specimen_positivity_rate,FALSE,PCR Test Positivity Rate,FALSE,Proportion of PCR specimens tested that have a positive result,NA,Covid Act Now (CAN),covid,Testing,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-03-01,NA,2021-12-02,NA,day,Date,daily,2-9 days,"Daily. Most recent test positivity rates do not change substantially (having a median delta of close to 0). However, most recent total tests performed are expected to increase in later data revisions (having a median increase of 7%). Values more than 5 days in the past are expected to remain fairly static (with total tests performed having a median increase of 1% of less), as most major revisions have already occurred.",Hospital patients,None,infected,Discarded if sample size (total tests performed) is 0,"Data is available for nearly all (99%) of counties. A few counties, most notably in California, are not covered by this data source Data is available for all states.",Value,fraction,cases_testing,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY-NC,CC BY-NC,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/covid-act-now.html,covid-act-now +covid-act-now,pcr_specimen_total_tests,FALSE,pcr_specimen_total_tests,FALSE,Total Number of PCR Tests,FALSE,Total number of PCR specimens tested,NA,Covid Act Now (CAN),covid,Testing,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-03-01,NA,2021-12-02,NA,day,Date,daily,2-9 days,"Daily. Most recent test positivity rates do not change substantially (having a median delta of close to 0). However, most recent total tests performed are expected to increase in later data revisions (having a median increase of 7%). Values more than 5 days in the past are expected to remain fairly static (with total tests performed having a median increase of 1% of less), as most major revisions have already occurred.",Hospital patients,None,population,Discarded if sample size (total tests performed) is 0,"Data is available for nearly all (99%) of counties. A few counties, most notably in California, are not covered by this data source Data is available for all states.",Value,count,cases_testing,good,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY-NC,CC BY-NC,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/covid-act-now.html,covid-act-now +doctor-visits,smoothed_cli,FALSE,smoothed_cli,FALSE,COVID-Related Doctor Visits,TRUE,Percentage of daily doctor visits that are due to COVID-like symptoms,"Estimated percentage of outpatient doctor visits that are primarily about COVID-related symptoms, based on data from health system partners, smoothed in time using a Gaussian linear smoother",Doctor Visits From Claims,covid,Outpatient insurance claims,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,Ongoing,NA,day,Date,daily,3-6 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 5-7 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 50 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Optum network,None,outpatient visit,Discarded if over a given 7-day period an estimate is computed with 500 or fewer observations,Data is available for about 80% of counties Data is available for all states and some territories.,Percentage,percent,early,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY-NC,CC BY-NC,https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/doctor-visits.html,doctor-visits +doctor-visits,smoothed_cli,TRUE,smoothed_adj_cli,FALSE,COVID-Related Doctor Visits (Day-adjusted),TRUE,NA,"Estimated percentage of outpatient doctor visits that are primarily about COVID-related symptoms, based on data from health system partners, smoothed in time using a Gaussian linear smoother, and adjusted to reduce day-of-week effects",Doctor Visits From Claims,covid,Outpatient insurance claims,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,Ongoing,NA,day,Date,daily,3-6 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 5-7 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 50 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Optum network,None,outpatient visit,Discarded if over a given 7-day period an estimate is computed with 500 or fewer observations,Data is available for about 80% of counties Data is available for all states and some territories.,Percentage,percent,early,bad,TRUE,TRUE,FALSE,FALSE,FALSE,public,public,CC BY-NC,CC BY-NC,https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf,NA,doctor-visits +dsew-cpr,booster_doses_admin_7dav,FALSE,booster_doses_admin_7dav,FALSE,booster_doses_admin_7dav,FALSE,COVID-19 booster vaccine doses administered each day,"COVID-19 booster vaccine doses administered each day, based on the daily Community Profile Report (CPR) published by the Data Strategy and Execution Workgroup of the White House COVID-19 Team, smoothed in time with a 7-day average. + +""Doses administered shown by date of report, not date of administration. ... [A] booster dose includes anyone who is fully vaccinated and has received another dose of COVID-19 vaccine since August 13, 2021. This includes people who received booster doses and people who received additional doses."" - from the CPR data dictionary.",COVID-19 Community Profile Report,covid,Vaccines,USA,"state, hhs, nation (by Delphi)",2021-11-01,NA,2023-02-22,NA,day,Day,daily,3-9 days,Daily. This data source is susceptible to large corrections that can create strange data effects such as negative counts and sudden changes of 1M+ counts from one day to the next.,All,None,population,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,public,good,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/dsew-cpr.html,dsew-cpr +dsew-cpr,confirmed_admissions_covid_1d_7dav,FALSE,confirmed_admissions_covid_1d_7dav,FALSE,Confirmed COVID Admissions per day,FALSE,All confirmed COVID-19 hospital admissions occurring each day,"All confirmed COVID-19 hospital admissions occurring each day, based on the daily Community Profile Report published by the Data Strategy and Execution Workgroup of the White House COVID-19 Team, smoothed in time with a 7-day average. + +Other sources of hospital admissions data in COVIDcast include [HHS](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/hhs.html) and [medical insurance claims](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/hospital-admissions.html). The CPR differs from these sources in that it is part of the public health surveillance stream (like HHS, unlike claims) but is available at a daily-county level (like claims, unlike HHS). CPR hospital admissions figures at the state level and above are meant to match those from HHS, but are known to differ. See the [Limitations section of the technical documentation](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/dsew-cpr.html#limitations) for more details.",COVID-19 Community Profile Report,covid,Vaccines,USA,"county, msa, state, hhs, nation (by Delphi)",2020-12-16,"Start dates vary by geo: county 2021-01-07, hhs 2020-12-16, msa 2021-01-07, nation 2020-12-16, state 2020-12-16",2023-02-21,NA,NA,Date,daily,3-9 days,Daily. This data source is susceptible to large corrections that can create strange data effects such as negative counts and sudden changes of 1M+ counts from one day to the next.,All,None,hospitalized,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/dsew-cpr.html,dsew-cpr +dsew-cpr,confirmed_admissions_covid_1d_7dav,TRUE,confirmed_admissions_covid_1d_prop_7dav,FALSE,Confirmed COVID Admissions per day (per 100k people),FALSE,NA,NA,COVID-19 Community Profile Report,covid,Vaccines,USA,"county, msa, state, hhs, nation (by Delphi)",2020-12-16,"Start dates vary by geo: county 2021-01-07, hhs 2020-12-16, msa 2021-01-07, nation 2020-12-16, state 2020-12-16",2023-02-21,NA,day,Date,daily,3-9 days,Daily. This data source is susceptible to large corrections that can create strange data effects such as negative counts and sudden changes of 1M+ counts from one day to the next.,All,None,hospitalized,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,NA,dsew-cpr +dsew-cpr,doses_admin_7dav,FALSE,doses_admin_7dav,FALSE,doses_admin_7dav,FALSE,COVID-19 vaccine doses administered each day,"COVID-19 vaccine doses administered each day, based on the daily Community Profile Report (CPR) published by the Data Strategy and Execution Workgroup of the White House COVID-19 Team, smoothed in time with a 7-day average. + +""Doses administered shown by date of report, not date of administration."" - from the CPR data dictionary.",COVID-19 Community Profile Report,covid,Vaccines,USA,"state, hhs, nation (by Delphi)",2021-05-02,NA,2023-02-22,NA,day,Day,daily,3-9 days,Daily. This data source is susceptible to large corrections that can create strange data effects such as negative counts and sudden changes of 1M+ counts from one day to the next.,All,None,population,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,public,good,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/dsew-cpr.html,dsew-cpr +dsew-cpr,people_booster_doses,FALSE,people_booster_doses,FALSE,people_booster_doses,FALSE,Cumulative number of people who have received a booster dose of the COVID-19 vaccine,"Cumulative number of people who have received a booster dose of the COVID-19 vaccine, based on the daily Community Profile Report (CPR) published by the Data Strategy and Execution Workgroup of the White House COVID-19 Team, smoothed in time with a 7-day average. + +""The count of people who received a booster dose includes anyone who is fully vaccinated and has received another dose of COVID-19 vaccine since 2021-08-13. This includes people who received booster doses and people who received additional doses"" - from the CPR data dictionary.",COVID-19 Community Profile Report,covid,Vaccines,USA,"state, hhs, nation (by Delphi)",2021-11-01,NA,2023-02-22,NA,day,Day,daily,3-9 days,Daily. This data source is susceptible to large corrections that can create strange data effects such as negative counts and sudden changes of 1M+ counts from one day to the next.,All,None,population,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,public,good,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/dsew-cpr.html,dsew-cpr +dsew-cpr,people_full_vaccinated,FALSE,people_full_vaccinated,FALSE,people_full_vaccinated,FALSE,Cumulative number of people who have received a full course of the COVID-19 vaccine,"Cumulative number of people who have received a full course of the COVID-19 vaccine, based on the daily Community Profile Report (CPR) published by the Data Strategy and Execution Workgroup of the White House COVID-19 Team, smoothed in time with a 7-day average. + +""People fully vaccinated includes those who have received two doses of the Pfizer-BioNTech or Moderna vaccine and those who have received one dose of the J&J/Janssen vaccine"" - from the CPR data dictionary.",COVID-19 Community Profile Report,covid,Vaccines,USA,"county, msa, state, hhs, nation (by Delphi)",2021-01-15,"Start dates vary by geo: county 2021-04-12, hhs 2021-01-15, msa 2021-04-12, nation 2021-01-15, state 2021-01-15",2023-02-22,NA,day,Day,daily,3-9 days,Daily. This data source is susceptible to large corrections that can create strange data effects such as negative counts and sudden changes of 1M+ counts from one day to the next.,All,None,population,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,public,good,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/dsew-cpr.html,dsew-cpr +fb-survey,raw_wcli,FALSE,raw_wcli,FALSE,COVID-Like Symptoms,FALSE,Estimated percentage of people with COVID-like illness,"{source_description} For this signal, we estimate the percentage of people self-reporting COVID-like symptoms, defined here as fever along with either cough, shortness of breath, or difficulty breathing. While many other conditions can cause these symptoms, comparing the rates of COVID-like symptoms across the country can suggest where COVID is most active.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-06,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,early,bad,FALSE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,"[Survey details](https://delphi.cmu.edu/covidcast/surveys/) +[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#ili-and-cli-indicators)",fb-survey +fb-survey,raw_wcli,TRUE,raw_cli,FALSE,COVID-Like Symptoms (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-06,NA,2022-06-26,"End dates vary by geo: county 2022-06-25, hrr 2022-06-25, msa 2022-06-25, nation 2022-06-26, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,early,bad,FALSE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,raw_wcli,TRUE,smoothed_cli,FALSE,COVID-Like Symptoms (Unweighted 7-day average),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-06,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.",Data is available for about 50% of counties. Data is available for all states and some territories. Availability declines over time as survey response rate decreases,Percentage,percent,early,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,raw_wcli,TRUE,smoothed_wcli,FALSE,COVID-Like Symptoms (7-day average),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-06,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.",Data is available for about 50% of counties. Data is available for all states and some territories. Availability declines over time as survey response rate decreases,Percentage,percent,early,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,raw_whh_cmnty_cli,FALSE,raw_whh_cmnty_cli,FALSE,COVID-Like Symptoms in Community,FALSE,Estimated percentage of people reporting illness in their local community,"{source_description} We also ask them if they know anyone in their local community who has COVID-like symptoms, defined here as fever along with either cough, shortness of breath, or difficulty breathing. For this indicator, we estimate the percentage of people who know someone, in their household or outside it, who has these symptoms. While many conditions can cause these symptoms, not just COVID, comparing the rates across the country can suggest where COVID is most active.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-15,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,early,bad,FALSE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,"[Survey details](https://delphi.cmu.edu/covidcast/surveys/) +[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#ili-and-cli-indicators)",fb-survey +fb-survey,raw_whh_cmnty_cli,TRUE,raw_hh_cmnty_cli,FALSE,COVID-Like Symptoms in Community (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-15,NA,2022-06-26,"End dates vary by geo: county 2022-06-25, hrr 2022-06-25, msa 2022-06-25, nation 2022-06-26, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,early,bad,FALSE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,raw_whh_cmnty_cli,TRUE,smoothed_hh_cmnty_cli,FALSE,COVID-Like Symptoms in Community (Unweighted 7-day average),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-15,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.",Data is available for about 40% of counties. Data is available for all states and some territories. Availability declines over time as survey response rate decreases,Percentage,percent,early,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,raw_whh_cmnty_cli,TRUE,smoothed_whh_cmnty_cli,FALSE,COVID-Like Symptoms in Community (7-day average),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-15,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.",Data is available for about 35% of counties. Data is available for all states and some territories. Availability declines over time as survey response rate decreases,Percentage,percent,early,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,raw_wili,FALSE,raw_wili,FALSE,Flu-Like Symptoms,FALSE,Estimated percentage of people with influenza-like illness,"{source_description} For this signal, we estimate the percentage of people self-reporting influenza-like symptoms, defined here as fever along with either cough or sore throat. While many other conditions can cause these symptoms, comparing the rates of influenza-like symptoms across the country can suggest where the flu is most active.",Delphi US COVID-19 Trends and Impact Survey,flu,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-06,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,early,bad,FALSE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#ili-and-cli-indicators,fb-survey +fb-survey,raw_wili,TRUE,raw_ili,FALSE,Flu-Like Symptoms (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,flu,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-06,NA,2022-06-26,"End dates vary by geo: county 2022-06-25, hrr 2022-06-25, msa 2022-06-25, nation 2022-06-26, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,early,bad,FALSE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,raw_wili,TRUE,smoothed_ili,FALSE,Flu-Like Symptoms (Unweighted 7-day average),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,flu,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-06,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.",Data is available for about 50% of counties. Data is available for all states and some territories. Availability declines over time as survey response rate decreases,Percentage,percent,early,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,raw_wili,TRUE,smoothed_wili,FALSE,Flu-Like Symptoms (7-day average),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,flu,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-06,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.",Data is available for about 50% of counties. Data is available for all states and some territories. Availability declines over time as survey response rate decreases,Percentage,percent,early,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,raw_wnohh_cmnty_cli,FALSE,raw_wnohh_cmnty_cli,FALSE,COVID-Like Symptoms in Community Outside Household,FALSE,Estimated percentage of people reporting illness in their local community not including their household,"{source_description} We also ask them if they know anyone in their local community who has COVID-like symptoms, defined here as fever along with either cough, shortness of breath, or difficulty breathing. For this indicator, we estimate the percentage of people who know someone outside their household who has these symptoms. While many conditions can cause these symptoms, not just COVID, comparing the rates across the country can suggest where COVID is most active.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-15,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,early,bad,FALSE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#ili-and-cli-indicators,fb-survey +fb-survey,raw_wnohh_cmnty_cli,TRUE,raw_nohh_cmnty_cli,FALSE,COVID-Like Symptoms in Community Outside Household (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-15,NA,2022-06-26,"End dates vary by geo: county 2022-06-25, hrr 2022-06-25, msa 2022-06-25, nation 2022-06-26, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,early,bad,FALSE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,raw_wnohh_cmnty_cli,TRUE,smoothed_nohh_cmnty_cli,FALSE,COVID-Like Symptoms in Community Outside Household (Unweighted 7-day average),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-15,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.",Data is available for about 40% of counties. Data is available for all states and some territories. Availability declines over time as survey response rate decreases,Percentage,percent,early,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,raw_wnohh_cmnty_cli,TRUE,smoothed_wnohh_cmnty_cli,FALSE,COVID-Like Symptoms in Community Outside Household (7-day average),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-15,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.",Data is available for about 35% of counties. Data is available for all states and some territories. Availability declines over time as survey response rate decreases,Percentage,percent,early,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_waccept_covid_vaccine,FALSE,smoothed_waccept_covid_vaccine,FALSE,COVID-19 Vaccine Acceptance,FALSE,"Estimated percentage of respondents who would definitely or probably choose to get vaccinated, if a COVID-19 vaccine were offered to them today.","{source_description} We also ask questions about well-being and various mitigation measures, including vaccine acceptance. For this signal, we estimate the percentage of people who would ""definitely"" or ""probably"" choose to be vaccinated if a COVID vaccine were offered to them today. + +Note: Until January 6, 2021, all respondents answered this question; beginning on that date, only respondents who said they have not received a COVID vaccine are asked this question. + +Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey +fb-survey,smoothed_waccept_covid_vaccine,TRUE,smoothed_accept_covid_vaccine,FALSE,COVID-19 Vaccine Acceptance (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_waccept_covid_vaccine_no_appointment,FALSE,smoothed_waccept_covid_vaccine_no_appointment,FALSE,COVID-19 Vaccine Acceptance Among Unvaccinated,FALSE,"Estimated percentage of respondents who would definitely or probably choose to get vaccinated, if a vaccine were offered to them today, among respondents who have not yet been vaccinated and do not have an appointment to do so.","Estimated percentage of respondents who would definitely or probably choose to get vaccinated, if a vaccine were offered to them today, among respondents who have not yet been vaccinated and do not have an appointment to do so. + +Based on survey item V3a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,"Start dates vary by geo: county 2021-05-20, hrr 2021-05-21, msa 2021-05-21, nation 2021-05-20, state 2021-05-20",2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey +fb-survey,smoothed_waccept_covid_vaccine_no_appointment,TRUE,smoothed_accept_covid_vaccine_no_appointment,FALSE,COVID-19 Vaccine Acceptance Among Unvaccinated (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,"Start dates vary by geo: county 2021-05-20, hrr 2021-05-21, msa 2021-05-21, nation 2021-05-20, state 2021-05-20",2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wanxious_5d,FALSE,smoothed_wanxious_5d,FALSE,Anxious (Last Five Days),FALSE,"Estimated percentage of respondents who reported feeling ""nervous, anxious, or on edge"" for most or all of the past 5 days.","Estimated percentage of respondents who reported feeling ""nervous, anxious, or on edge"" for most or all of the past 5 days. + +Discontinued as of Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mental-health-indicators,fb-survey +fb-survey,smoothed_wanxious_5d,TRUE,smoothed_anxious_5d,FALSE,Anxious (Last Five Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wanxious_7d,FALSE,smoothed_wanxious_7d,FALSE,Anxious (Last Seven Days),FALSE,"Estimated percentage of respondents who reported feeling ""nervous, anxious, or on edge"" for most or all of the past 7 days.","Estimated percentage of respondents who reported feeling ""nervous, anxious, or on edge"" for most or all of the past 7 days. + +This item was shown to respondents starting in Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mental-health-indicators,fb-survey +fb-survey,smoothed_wanxious_7d,TRUE,smoothed_anxious_7d,FALSE,Anxious (Last Seven Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wappointment_not_vaccinated,FALSE,smoothed_wappointment_not_vaccinated,FALSE,COVID-19 Vaccine Appointments Among Unvaccinated,FALSE,"Estimated percentage of respondents who have an appointment to get a COVID-19 vaccine, among respondents who have not yet been vaccinated.","Estimated percentage of respondents who have an appointment to get a COVID-19 vaccine, among respondents who have not yet been vaccinated. + +Based on survey item V11a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,"Start dates vary by geo: county 2021-05-20, hrr 2021-05-21, msa 2021-05-21, nation 2021-05-20, state 2021-05-20",2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey +fb-survey,smoothed_wappointment_not_vaccinated,TRUE,smoothed_appointment_not_vaccinated,FALSE,COVID-19 Vaccine Appointments Among Unvaccinated (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,"Start dates vary by geo: county 2021-05-20, hrr 2021-05-21, msa 2021-05-21, nation 2021-05-20, state 2021-05-20",2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wappointment_or_accept_covid_vaccine,FALSE,smoothed_wappointment_or_accept_covid_vaccine,FALSE,COVID-19 Vaccine Acceptance and Appointments Among Unvaccinated,FALSE,"Estimated percentage of respondents who either have an appointment to get a COVID-19 vaccine or would definitely or probably choose to get vaccinated, if a vaccine were offered to them today, among respondents who have not yet been vaccinated","Estimated percentage of respondents who either have an appointment to get a COVID-19 vaccine or would definitely or probably choose to get vaccinated, if a vaccine were offered to them today, among respondents who have not yet been vaccinated + +Based on survey items V11a and V3a. V11a was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,"Start dates vary by geo: county 2021-05-20, hrr 2021-05-21, msa 2021-05-20, nation 2021-05-20, state 2021-05-20",2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey +fb-survey,smoothed_wappointment_or_accept_covid_vaccine,TRUE,smoothed_appointment_or_accept_covid_vaccine,FALSE,COVID-19 Vaccine Acceptance and Appointments Among Unvaccinated (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,"Start dates vary by geo: county 2021-05-20, hrr 2021-05-21, msa 2021-05-20, nation 2021-05-20, state 2021-05-20",2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wbelief_children_immune,FALSE,smoothed_wbelief_children_immune,FALSE,Belief Children Can't Get COVID-19,FALSE,Estimated percentage of people who believe that the statement “Children cannot get COVID-19” is definitely or probably true.,"Estimated percentage of people who believe that the statement “Children cannot get COVID-19” is definitely or probably true. + +Based on survey item I2. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-15, msa 2022-02-17, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#belief-experience-and-information-indicators,fb-survey +fb-survey,smoothed_wbelief_children_immune,TRUE,smoothed_belief_children_immune,FALSE,Belief Children Can't Get COVID-19 (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-15, msa 2022-02-17, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wbelief_created_small_group,FALSE,smoothed_wbelief_created_small_group,FALSE,Belief COVID-19 Deliberately Created to Manipulate Events,FALSE,Estimated percentage of people who believe that the statement “COVID-19 was deliberately created by a small group of people who secretly manipulate world events” is definitely or probably true.,"Estimated percentage of people who believe that the statement “COVID-19 was deliberately created by a small group of people who secretly manipulate world events” is definitely or probably true. + +Based on survey item I3. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#belief-experience-and-information-indicators,fb-survey +fb-survey,smoothed_wbelief_created_small_group,TRUE,smoothed_belief_created_small_group,FALSE,Belief COVID-19 Deliberately Created to Manipulate Events (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wbelief_distancing_effective,FALSE,smoothed_wbelief_distancing_effective,FALSE,Belief Social Distancing is Effective,FALSE,Estimated percentage of respondents who believe that social distancing is either very or moderately effective for preventing the spread of COVID-19.,"Estimated percentage of respondents who believe that social distancing is either very or moderately effective for preventing the spread of COVID-19. + +Based on survey item G2. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#belief-experience-and-information-indicators,fb-survey +fb-survey,smoothed_wbelief_distancing_effective,TRUE,smoothed_belief_distancing_effective,FALSE,Belief Social Distancing is Effective (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wbelief_govt_exploitation,FALSE,smoothed_wbelief_govt_exploitation,FALSE,Belief COVID-19 Exploited to Control People,FALSE,Estimated percentage of people who indicate that the statement “The COVID-19 pandemic is being exploited by the government to control people” is definitely or probably true.,"Estimated percentage of people who indicate that the statement “The COVID-19 pandemic is being exploited by the government to control people” is definitely or probably true. + +Based on survey item I4. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#belief-experience-and-information-indicators,fb-survey +fb-survey,smoothed_wbelief_govt_exploitation,TRUE,smoothed_belief_govt_exploitation,FALSE,Belief COVID-19 Exploited to Control People (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wbelief_masking_effective,FALSE,smoothed_wbelief_masking_effective,FALSE,Belief Masks Are Effective,FALSE,Estimated percentage of respondents who believe that wearing a face mask is either very or moderately effective for preventing the spread of COVID-19.,"Estimated percentage of respondents who believe that wearing a face mask is either very or moderately effective for preventing the spread of COVID-19. + +Based on survey item G2. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#belief-experience-and-information-indicators,fb-survey +fb-survey,smoothed_wbelief_masking_effective,TRUE,smoothed_belief_masking_effective,FALSE,Belief Masks Are Effective (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wbelief_vaccinated_mask_unnecessary,FALSE,smoothed_wbelief_vaccinated_mask_unnecessary,FALSE,Belief Vaccines Make Masks Unnecessary,FALSE,Estimated percentage of people who believe that the statement “Getting the COVID-19 vaccine means that you can stop wearing a mask around people outside your household” is definitely or probably true.,"Estimated percentage of people who believe that the statement “Getting the COVID-19 vaccine means that you can stop wearing a mask around people outside your household” is definitely or probably true. + +Based on survey item I1. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-15, msa 2022-02-17, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#belief-experience-and-information-indicators,fb-survey +fb-survey,smoothed_wbelief_vaccinated_mask_unnecessary,TRUE,smoothed_belief_vaccinated_mask_unnecessary,FALSE,Belief Vaccines Make Masks Unnecessary (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-15, msa 2022-02-17, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wcovid_vaccinated,FALSE,smoothed_wcovid_vaccinated,FALSE,COVID-19 Vaccinated,FALSE,Estimated percentage of respondents who have already received a vaccine for COVID-19.,"Estimated percentage of respondents who have already received a vaccine for COVID-19. + +Note: The Centers for Disease Control compiles data on vaccine administration across the United States. This signal may differ from CDC data because of survey biases and should not be treated as authoritative. However, the survey signal is not subject to the lags and reporting problems in official vaccination data.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-01-06,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey +fb-survey,smoothed_wcovid_vaccinated,TRUE,smoothed_covid_vaccinated,FALSE,COVID-19 Vaccinated (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-01-06,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wcovid_vaccinated_appointment_or_accept,FALSE,smoothed_wcovid_vaccinated_appointment_or_accept,FALSE,"COVID-19 Vaccine Acceptance: Vaccinated, Appointment, or Accept",FALSE,"Estimated percentage of respondents who either have already received a COVID vaccine, have an appointment to receive a COVID vaccine, or would definitely or probably choose to receive one if it were offered to them today.","Estimated percentage of respondents who either have already received a COVID vaccine, have an appointment to receive a COVID vaccine, or would definitely or probably choose to receive one if it were offered to them today. +",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,"[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators) +[Wave 11 revision updates](https://cmu-delphi.github.io/delphi-epidata/symptom-survey/coding.html#wave-11)",fb-survey +fb-survey,smoothed_wcovid_vaccinated_appointment_or_accept,TRUE,smoothed_covid_vaccinated_appointment_or_accept,FALSE,"COVID-19 Vaccine Acceptance: Vaccinated, Appointment, or Accept (Unweighted)",FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wcovid_vaccinated_friends,FALSE,smoothed_wcovid_vaccinated_friends,FALSE,Friends and Family Vaccinated,FALSE,Estimated percentage of respondents who report that most of their friends and family have received a COVID-19 vaccine.,"Estimated percentage of respondents who report that most of their friends and family have received a COVID-19 vaccine. + +Based on survey item H3. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey +fb-survey,smoothed_wcovid_vaccinated_friends,TRUE,smoothed_covid_vaccinated_friends,FALSE,Friends and Family Vaccinated (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wcovid_vaccinated_or_accept,FALSE,smoothed_wcovid_vaccinated_or_accept,FALSE,COVID-19 Vaccinated or Vaccine Acceptance,FALSE,"Estimated percentage of respondents who either have already received a COVID vaccine or would definitely or probably choose to get vaccinated, if a vaccine were offered to them today.","Estimated percentage of respondents who either have already received a COVID vaccine or would definitely or probably choose to get vaccinated, if a vaccine were offered to them today. + +Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey +fb-survey,smoothed_wcovid_vaccinated_or_accept,TRUE,smoothed_covid_vaccinated_or_accept,FALSE,COVID-19 Vaccinated or Vaccine Acceptance (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wdelayed_care_cost,FALSE,smoothed_wdelayed_care_cost,FALSE,Delayed Healthcare Due to Cost,FALSE,Estimated percentage of respondents who have ever delayed or not sought medical care in the past year because of cost.,"Estimated percentage of respondents who have ever delayed or not sought medical care in the past year because of cost. + +Based on survey item K1. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#medical-care-experiences,fb-survey +fb-survey,smoothed_wdelayed_care_cost,TRUE,smoothed_delayed_care_cost,FALSE,Delayed Healthcare Due to Cost (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wdepressed_5d,FALSE,smoothed_wdepressed_5d,FALSE,Depressed (Last Five Days),FALSE,Estimated percentage of respondents who reported feeling depressed for most or all of the past 5 days.,"Estimated percentage of respondents who reported feeling depressed for most or all of the past 5 days. + +Discontinued as of Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mental-health-indicators,fb-survey +fb-survey,smoothed_wdepressed_5d,TRUE,smoothed_depressed_5d,FALSE,Depressed (Last Five Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wdepressed_7d,FALSE,smoothed_wdepressed_7d,FALSE,Depressed (Last Seven Days),FALSE,Estimated percentage of respondents who reported feeling depressed for most or all of the past 7 days.,"Estimated percentage of respondents who reported feeling depressed for most or all of the past 7 days. + +This item was shown to respondents starting in Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mental-health-indicators,fb-survey +fb-survey,smoothed_wdepressed_7d,TRUE,smoothed_depressed_7d,FALSE,Depressed (Last Seven Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wdontneed_reason_dont_spend_time,FALSE,smoothed_wdontneed_reason_dont_spend_time,FALSE,Vaccine Not Needed: Do Not Spend Time,FALSE,Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they don't spend time with high-risk people,"Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they don't spend time with high-risk people, among respondents who provided at least one reason for why they believe a COVID-19 vaccine is unnecessary.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-25,"End dates vary by geo: county 2022-06-25, hrr 2022-06-19, msa 2022-06-25, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-believing-vaccine-is-unnecessary,fb-survey +fb-survey,smoothed_wdontneed_reason_dont_spend_time,TRUE,smoothed_dontneed_reason_dont_spend_time,FALSE,Vaccine Not Needed: Do Not Spend Time (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-27,"End dates vary by geo: county 2022-06-27, hrr 2022-06-19, msa 2022-06-26, nation 2022-06-27, state 2022-06-27",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wdontneed_reason_had_covid,FALSE,smoothed_wdontneed_reason_had_covid,FALSE,Vaccine Not Needed: Had Covid,FALSE,Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they already had the illness,"Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they already had the illness, among respondents who provided at least one reason for why they believe a COVID-19 vaccine is unnecessary.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-25,"End dates vary by geo: county 2022-06-25, hrr 2022-06-19, msa 2022-06-25, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-believing-vaccine-is-unnecessary,fb-survey +fb-survey,smoothed_wdontneed_reason_had_covid,TRUE,smoothed_dontneed_reason_had_covid,FALSE,Vaccine Not Needed: Had Covid (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-27,"End dates vary by geo: county 2022-06-27, hrr 2022-06-19, msa 2022-06-26, nation 2022-06-27, state 2022-06-27",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wdontneed_reason_not_beneficial,FALSE,smoothed_wdontneed_reason_not_beneficial,FALSE,Vaccine Not Needed: Not Beneficial,FALSE,Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they don't think vaccines are beneficial,"Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they don't think vaccines are beneficial, among respondents who provided at least one reason for why they believe a COVID-19 vaccine is unnecessary.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-25,"End dates vary by geo: county 2022-06-25, hrr 2022-06-19, msa 2022-06-25, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-believing-vaccine-is-unnecessary,fb-survey +fb-survey,smoothed_wdontneed_reason_not_beneficial,TRUE,smoothed_dontneed_reason_not_beneficial,FALSE,Vaccine Not Needed: Not Beneficial (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-27,"End dates vary by geo: county 2022-06-27, hrr 2022-06-19, msa 2022-06-26, nation 2022-06-27, state 2022-06-27",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wdontneed_reason_not_high_risk,FALSE,smoothed_wdontneed_reason_not_high_risk,FALSE,Vaccine Not Needed: Not High Risk,FALSE,Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they are not in a high-risk group,"Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they are not in a high-risk group, among respondents who provided at least one reason for why they believe a COVID-19 vaccine is unnecessary.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-25,"End dates vary by geo: county 2022-06-25, hrr 2022-06-19, msa 2022-06-25, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-believing-vaccine-is-unnecessary,fb-survey +fb-survey,smoothed_wdontneed_reason_not_high_risk,TRUE,smoothed_dontneed_reason_not_high_risk,FALSE,Vaccine Not Needed: Not High Risk (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-27,"End dates vary by geo: county 2022-06-27, hrr 2022-06-19, msa 2022-06-26, nation 2022-06-27, state 2022-06-27",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wdontneed_reason_not_serious,FALSE,smoothed_wdontneed_reason_not_serious,FALSE,Vaccine Not Needed: Not Serious,FALSE,Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they don't believe COVID-19 is a serious illness,"Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they don't believe COVID-19 is a serious illness, among respondents who provided at least one reason for why they believe a COVID-19 vaccine is unnecessary.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-25,"End dates vary by geo: county 2022-06-25, hrr 2022-06-19, msa 2022-06-25, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-believing-vaccine-is-unnecessary,fb-survey +fb-survey,smoothed_wdontneed_reason_not_serious,TRUE,smoothed_dontneed_reason_not_serious,FALSE,Vaccine Not Needed: Not Serious (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-27,"End dates vary by geo: county 2022-06-27, hrr 2022-06-19, msa 2022-06-26, nation 2022-06-27, state 2022-06-27",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wdontneed_reason_other,FALSE,smoothed_wdontneed_reason_other,FALSE,Vaccine Not Needed: Other,FALSE,Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine for another reason,"Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine for another reason, among respondents who provided at least one reason for why they believe a COVID-19 vaccine is unnecessary.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-25,"End dates vary by geo: county 2022-06-25, hrr 2022-06-19, msa 2022-06-25, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-believing-vaccine-is-unnecessary,fb-survey +fb-survey,smoothed_wdontneed_reason_other,TRUE,smoothed_dontneed_reason_other,FALSE,Vaccine Not Needed: Other (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-27,"End dates vary by geo: county 2022-06-27, hrr 2022-06-19, msa 2022-06-26, nation 2022-06-27, state 2022-06-27",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wdontneed_reason_precautions,FALSE,smoothed_wdontneed_reason_precautions,FALSE,Vaccine Not Needed: Precautions,FALSE,"Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they will use other precautions, such as a mask, instead","Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they will use other precautions, such as a mask, instead, among respondents who provided at least one reason for why they believe a COVID-19 vaccine is unnecessary.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-25,"End dates vary by geo: county 2022-06-25, hrr 2022-06-19, msa 2022-06-25, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-believing-vaccine-is-unnecessary,fb-survey +fb-survey,smoothed_wdontneed_reason_precautions,TRUE,smoothed_dontneed_reason_precautions,FALSE,Vaccine Not Needed: Precautions (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-27,"End dates vary by geo: county 2022-06-27, hrr 2022-06-19, msa 2022-06-26, nation 2022-06-27, state 2022-06-27",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wfelt_isolated_5d,FALSE,smoothed_wfelt_isolated_5d,FALSE,Felt Isolated (Last Five Days),FALSE,"Estimated percentage of respondents who reported feeling ""isolated from others"" for most or all of the past 5 days.","Estimated percentage of respondents who reported feeling ""isolated from others"" for most or all of the past 5 days. + +Discontinued as of Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mental-health-indicators,fb-survey +fb-survey,smoothed_wfelt_isolated_5d,TRUE,smoothed_felt_isolated_5d,FALSE,Felt Isolated (Last Five Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wfelt_isolated_7d,FALSE,smoothed_wfelt_isolated_7d,FALSE,Felt Isolated (Last Seven Days),FALSE,"Estimated percentage of respondents who reported feeling ""isolated from others"" for most or all of the past 7 days.","Estimated percentage of respondents who reported feeling ""isolated from others"" for most or all of the past 7 days. + +This item was shown to respondents starting in Wave 10, March 2, 2021. + +Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2021-08-08,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mental-health-indicators,fb-survey +fb-survey,smoothed_wfelt_isolated_7d,TRUE,smoothed_felt_isolated_7d,FALSE,Felt Isolated (Last Seven Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2021-08-08,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_whad_covid_ever,FALSE,smoothed_whad_covid_ever,FALSE,Ever Had COVID-19,FALSE,Estimated percentage of people who report having ever had COVID-19.,"Estimated percentage of people who report having ever had COVID-19. + +Based on survey item B13. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",ascertained (case),"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,late,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#testing-indicators,fb-survey +fb-survey,smoothed_whad_covid_ever,TRUE,smoothed_had_covid_ever,FALSE,Ever Had COVID-19 (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",ascertained (case),"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,late,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_whesitancy_reason_allergic,FALSE,smoothed_whesitancy_reason_allergic,FALSE,Vaccine Hesitancy: Allergic,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they are worried about having an allergic reaction,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they are worried about having an allergic reaction, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. + +This item was shown to respondents starting in Wave 8, February 8, 2021. + +Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey +fb-survey,smoothed_whesitancy_reason_allergic,TRUE,smoothed_hesitancy_reason_allergic,FALSE,Vaccine Hesitancy: Allergic (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_whesitancy_reason_cost,FALSE,smoothed_whesitancy_reason_cost,FALSE,Vaccine Hesitancy: Cost,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they are worried about the cost,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they are worried about the cost, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. + +This item was shown to respondents starting in Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey +fb-survey,smoothed_whesitancy_reason_cost,TRUE,smoothed_hesitancy_reason_cost,FALSE,Vaccine Hesitancy: Cost (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_whesitancy_reason_dislike_vaccines,FALSE,smoothed_whesitancy_reason_dislike_vaccines,FALSE,Vaccine Hesitancy: Dislike Vaccines,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they dislike vaccines,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they dislike vaccines, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. + +This item was shown to respondents starting in Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-12-25,"End dates vary by geo: county 2021-12-24, hrr 2021-12-22, msa 2021-12-23, nation 2021-12-25, state 2021-12-24",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey +fb-survey,smoothed_whesitancy_reason_dislike_vaccines,TRUE,smoothed_hesitancy_reason_dislike_vaccines,FALSE,Vaccine Hesitancy: Dislike Vaccines (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-12-25,"End dates vary by geo: county 2021-12-24, hrr 2021-12-22, msa 2021-12-23, nation 2021-12-25, state 2021-12-24",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_whesitancy_reason_dislike_vaccines_generally,FALSE,smoothed_whesitancy_reason_dislike_vaccines_generally,FALSE,Vaccine Hesitance: Dislike Vaccines Generally,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they dislike vaccines generally,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they dislike vaccines generally, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. + +This item was shown to respondents starting in Wave 12, December 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-19, hrr 2021-12-20, msa 2021-12-20, nation 2021-12-19, state 2021-12-19",2022-06-25,NA,day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey +fb-survey,smoothed_whesitancy_reason_dislike_vaccines_generally,TRUE,smoothed_hesitancy_reason_dislike_vaccines_generally,FALSE,Vaccine Hesitance: Dislike Vaccines Generally (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-19, hrr 2021-12-20, msa 2021-12-20, nation 2021-12-19, state 2021-12-19",2022-06-27,NA,day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,NA,NA,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_whesitancy_reason_distrust_gov,FALSE,smoothed_whesitancy_reason_distrust_gov,FALSE,Vaccine Hesitancy: Distrust Government,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they don't trust the government,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they don't trust the government, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. + +This item was shown to respondents starting in Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey +fb-survey,smoothed_whesitancy_reason_distrust_gov,TRUE,smoothed_hesitancy_reason_distrust_gov,FALSE,Vaccine Hesitancy: Distrust Government (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_whesitancy_reason_distrust_vaccines,FALSE,smoothed_whesitancy_reason_distrust_vaccines,FALSE,Vaccine Hesitancy: Distrust Vaccines,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they don't trust COVID-19 vaccines,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they don't trust COVID-19 vaccines, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. + +This item was shown to respondents starting in Wave 8, February 8, 2021. + +Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey +fb-survey,smoothed_whesitancy_reason_distrust_vaccines,TRUE,smoothed_hesitancy_reason_distrust_vaccines,FALSE,Vaccine Hesitancy: Distrust Vaccines (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_whesitancy_reason_health_condition,FALSE,smoothed_whesitancy_reason_health_condition,FALSE,Vaccine Hesitancy: Health Condition,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they have a health condition that may impact the safety of a COVID-19 vaccine,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they have a health condition that may impact the safety of a COVID-19 vaccine, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. + +This item was shown to respondents starting in Wave 8, February 8, 2021. + +Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey +fb-survey,smoothed_whesitancy_reason_health_condition,TRUE,smoothed_hesitancy_reason_health_condition,FALSE,Vaccine Hesitancy: Health Condition (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_whesitancy_reason_ineffective,FALSE,smoothed_whesitancy_reason_ineffective,FALSE,Vaccine Hesitancy: Ineffective,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they don't know if a COVID-19 vaccine will work,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they don't know if a COVID-19 vaccine will work, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. + +This item was shown to respondents starting in Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey +fb-survey,smoothed_whesitancy_reason_ineffective,TRUE,smoothed_hesitancy_reason_ineffective,FALSE,Vaccine Hesitancy: Ineffective (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_whesitancy_reason_low_priority,FALSE,smoothed_whesitancy_reason_low_priority,FALSE,Vaccine Hesitancy: Low Priority,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they think other people need it more than they do,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they think other people need it more than they do, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. + +This item was shown to respondents starting in Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey +fb-survey,smoothed_whesitancy_reason_low_priority,TRUE,smoothed_hesitancy_reason_low_priority,FALSE,Vaccine Hesitancy: Low Priority (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_whesitancy_reason_not_recommended,FALSE,smoothed_whesitancy_reason_not_recommended,FALSE,Vaccine Hesitancy: Was Not Recommended,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because their doctor did not recommend it,"Estimated percentage of respondents who say they are hesitant to get vaccinated because their doctor did not recommend it, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. + +This item was shown to respondents starting in Wave 8, February 8, 2021. + +Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey +fb-survey,smoothed_whesitancy_reason_not_recommended,TRUE,smoothed_hesitancy_reason_not_recommended,FALSE,Vaccine Hesitancy: Was Not Recommended (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_whesitancy_reason_other,FALSE,smoothed_whesitancy_reason_other,FALSE,Vaccine Hesitancy: Other,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated for another reason,"Estimated percentage of respondents who say they are hesitant to get vaccinated for another reason, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. + +This item was shown to respondents starting in Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey +fb-survey,smoothed_whesitancy_reason_other,TRUE,smoothed_hesitancy_reason_other,FALSE,Vaccine Hesitancy: Other (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_whesitancy_reason_pregnant,FALSE,smoothed_whesitancy_reason_pregnant,FALSE,Vaccine Hesitancy: Pregnant,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they are pregnant or breastfeeding,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they are pregnant or breastfeeding, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. + +This item was shown to respondents starting in Wave 8, February 8, 2021. + +Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey +fb-survey,smoothed_whesitancy_reason_pregnant,TRUE,smoothed_hesitancy_reason_pregnant,FALSE,Vaccine Hesitancy: Pregnant (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_whesitancy_reason_religious,FALSE,smoothed_whesitancy_reason_religious,FALSE,Vaccine Hesitancy: Religious,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because it is against their religious beliefs,"Estimated percentage of respondents who say they are hesitant to get vaccinated because it is against their religious beliefs, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. + +This item was shown to respondents starting in Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey +fb-survey,smoothed_whesitancy_reason_religious,TRUE,smoothed_hesitancy_reason_religious,FALSE,Vaccine Hesitancy: Religious (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_whesitancy_reason_sideeffects,FALSE,smoothed_whesitancy_reason_sideeffects,FALSE,Vaccine Hesitancy: Side Effects,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they are worried about side effects,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they are worried about side effects, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. + +This item was shown to respondents starting in Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey +fb-survey,smoothed_whesitancy_reason_sideeffects,TRUE,smoothed_hesitancy_reason_sideeffects,FALSE,Vaccine Hesitancy: Side Effects (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_whesitancy_reason_unnecessary,FALSE,smoothed_whesitancy_reason_unnecessary,FALSE,Vaccine Hesitancy: Unnecessary,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they don't believe they need a COVID-19 vaccine,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they don't believe they need a COVID-19 vaccine, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. + +This item was shown to respondents starting in Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey +fb-survey,smoothed_whesitancy_reason_unnecessary,TRUE,smoothed_hesitancy_reason_unnecessary,FALSE,Vaccine Hesitancy: Unnecessary (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_whesitancy_reason_wait_safety,FALSE,smoothed_whesitancy_reason_wait_safety,FALSE,Vaccine Hesitancy: Wait For Safety,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they want to wait to see if the COVID-19 vaccines are safe,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they want to wait to see if the COVID-19 vaccines are safe, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. + +This item was shown to respondents starting in Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey +fb-survey,smoothed_whesitancy_reason_wait_safety,TRUE,smoothed_hesitancy_reason_wait_safety,FALSE,Vaccine Hesitancy: Wait For Safety (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_winperson_school_fulltime,FALSE,smoothed_winperson_school_fulltime,FALSE,In-person School Full-time,FALSE,Estimated percentage of people who had any children attending in-person school on a full-time basis,"Estimated percentage of people who had any children attending in-person school on a full-time basis, among people reporting any pre-K-grade 12 children in their household.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-11-24,NA,2021-12-24,"End dates vary by geo: county 2021-12-24, hrr 2021-12-22, msa 2021-12-24, nation 2021-12-24, state 2021-12-24",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#schooling-indicators,fb-survey +fb-survey,smoothed_winperson_school_fulltime,TRUE,smoothed_inperson_school_fulltime,FALSE,In-person School Full-time (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-11-24,NA,2021-12-24,"End dates vary by geo: county 2021-12-24, hrr 2021-12-22, msa 2021-12-24, nation 2021-12-24, state 2021-12-24",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_winperson_school_fulltime_oldest,FALSE,smoothed_winperson_school_fulltime_oldest,FALSE,In-person School Full-time (Oldest Child),FALSE,Estimated percentage of people whose oldest child is attending in-person school on a full-time basis,"Estimated percentage of people whose oldest child is attending in-person school on a full-time basis, among people reporting any pre-K-grade 12 children in their household. + +This item was shown to respondents starting in Wave 12, December 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-19, hrr 2021-12-21, msa 2021-12-20, nation 2021-12-19, state 2021-12-19",2022-06-25,NA,day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#schooling-indicators,fb-survey +fb-survey,smoothed_winperson_school_fulltime_oldest,TRUE,smoothed_inperson_school_fulltime_oldest,FALSE,In-person School Full-time (Oldest Child) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-19, hrr 2021-12-21, msa 2021-12-20, nation 2021-12-19, state 2021-12-19",2022-06-27,NA,day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_winperson_school_parttime,FALSE,smoothed_winperson_school_parttime,FALSE,In-person School Part-time,FALSE,Estimated percentage of people who had any children attending in-person school on a part-time basis,"Estimated percentage of people who had any children attending in-person school on a part-time basis, among people reporting any pre-K-grade 12 children in their household.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-11-24,NA,2021-12-24,"End dates vary by geo: county 2021-12-24, hrr 2021-12-22, msa 2021-12-23, nation 2021-12-24, state 2021-12-24",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#schooling-indicators,fb-survey +fb-survey,smoothed_winperson_school_parttime,TRUE,smoothed_inperson_school_parttime,FALSE,In-person School Part-time (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-11-24,NA,2021-12-24,"End dates vary by geo: county 2021-12-24, hrr 2021-12-22, msa 2021-12-23, nation 2021-12-24, state 2021-12-24",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_winperson_school_parttime_oldest,FALSE,smoothed_winperson_school_parttime_oldest,FALSE,In-person School Part-time (Oldest Child),FALSE,Estimated percentage of people whose oldest child is attending in-person school on a part-time basis,"Estimated percentage of people whose oldest child is attending in-person school on a part-time basis, among people reporting any pre-K-grade 12 children in their household. + +This item was shown to respondents starting in Wave 12, December 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-19, hrr 2021-12-21, msa 2021-12-20, nation 2021-12-19, state 2021-12-19",2022-06-25,NA,day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#schooling-indicators,fb-survey +fb-survey,smoothed_winperson_school_parttime_oldest,TRUE,smoothed_inperson_school_parttime_oldest,FALSE,In-person School Part-time (Oldest Child) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-19, hrr 2021-12-21, msa 2021-12-20, nation 2021-12-19, state 2021-12-19",2022-06-27,NA,day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wlarge_event_1d,FALSE,smoothed_wlarge_event_1d,FALSE,Large Event (Last 24 Hours),FALSE,"Estimated percentage of respondents who ""attended an event with more than 10 people"" in the past 24 hours","Estimated percentage of respondents who ""attended an event with more than 10 people"" in the past 24 hours. + +This item was shown to respondents starting in Wave 4, September 8, 2020. + +Discontinued as of Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey +fb-survey,smoothed_wlarge_event_1d,TRUE,smoothed_large_event_1d,FALSE,Large Event (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wlarge_event_indoors_1d,FALSE,smoothed_wlarge_event_indoors_1d,FALSE,Large Event Indoors (Last 24 Hours),FALSE,"Estimated percentage of respondents who ""attended an indoor event with more than 10 people"" in the past 24 hours","Estimated percentage of respondents who ""attended an indoor event with more than 10 people"" in the past 24 hours. + +This item was shown to respondents starting in Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey +fb-survey,smoothed_wlarge_event_indoors_1d,TRUE,smoothed_large_event_indoors_1d,FALSE,Large Event Indoors (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wothers_distanced_public,FALSE,smoothed_wothers_distanced_public,FALSE,Other People Socially Distanced,FALSE,Estimated percentage of respondents who reported that all or most people they enountered in public in the past 7 days maintained a distance of at least 6 feet.,"Estimated percentage of respondents who reported that all or most people they enountered in public in the past 7 days maintained a distance of at least 6 feet. Respondents who said that they have not been in public for the past 7 days are excluded. + +Based on survey item H1. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey +fb-survey,smoothed_wothers_distanced_public,TRUE,smoothed_others_distanced_public,FALSE,Other People Socially Distanced (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wothers_masked,FALSE,smoothed_wothers_masked,FALSE,Other People Masked When Not Distanced,FALSE,"Estimated percentage of respondents who say that most or all other people wear masks, when they are in public and social distancing is not possible.","Estimated percentage of respondents who say that most or all other people wear masks, when they are in public and social distancing is not possible. + +This item was shown to respondents starting in Wave 5, November 24, 2020. + +Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-11-24,NA,2021-08-08,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mask-use,fb-survey +fb-survey,smoothed_wothers_masked,TRUE,smoothed_others_masked,FALSE,Other People Masked When Not Distanced (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-11-24,NA,2021-08-08,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wothers_masked_public,FALSE,smoothed_wothers_masked_public,FALSE,Other People Masked,FALSE,"Estimated percentage of respondents who say that most or all other people wear masks, when they are in public.","Estimated percentage of respondents who say that most or all other people wear masks, when they are in public. Respondents who said that they have not been in public for the past 7 days are excluded. + +Based on survey item H2. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mask-use,fb-survey +fb-survey,smoothed_wothers_masked_public,TRUE,smoothed_others_masked_public,FALSE,Other People Masked (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wpublic_transit_1d,FALSE,smoothed_wpublic_transit_1d,FALSE,Public Transit (Last 24 Hours),FALSE,"Estimated percentage of respondents who ""used public transit"" in the past 24 hours","Estimated percentage of respondents who ""used public transit"" in the past 24 hours + +This item was shown to respondents starting in Wave 4, September 8, 2020.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey +fb-survey,smoothed_wpublic_transit_1d,TRUE,smoothed_public_transit_1d,FALSE,Public Transit (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wrace_treated_fairly_healthcare,FALSE,smoothed_wrace_treated_fairly_healthcare,FALSE,Race Treated Fairly in Healthcare,FALSE,Estimated percentage of respondents who somewhat or strongly agree that people of their race are treated fairly in a healthcare setting.,"Estimated percentage of respondents who somewhat or strongly agree that people of their race are treated fairly in a healthcare setting. + +Based on survey item K2. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#medical-care-experiences,fb-survey +fb-survey,smoothed_wrace_treated_fairly_healthcare,TRUE,smoothed_race_treated_fairly_healthcare,FALSE,Race Treated Fairly in Healthcare (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wreceived_2_vaccine_doses,FALSE,smoothed_wreceived_2_vaccine_doses,FALSE,Received 2 Vaccine Doses,FALSE,Estimated percentage of respondents who have received two doses of a COVID-19 vaccine,"Estimated percentage of respondents who have received two doses of a COVID-19 vaccine, among respondents who have received either one or two doses of a COVID-19 vaccine. + +This item was shown to respondents starting in Wave 7, January 12, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-01-13,"Start dates vary by geo: county 2021-01-13, hrr 2021-01-14, msa 2021-01-13, nation 2021-01-13, state 2021-01-13",2021-11-14,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey +fb-survey,smoothed_wreceived_2_vaccine_doses,TRUE,smoothed_received_2_vaccine_doses,FALSE,Received 2 Vaccine Doses (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-01-13,"Start dates vary by geo: county 2021-01-13, hrr 2021-01-14, msa 2021-01-13, nation 2021-01-13, state 2021-01-13",2021-11-14,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wreceived_news_cdc,FALSE,smoothed_wreceived_news_cdc,FALSE,COVID News From CDC,FALSE,Estimated percentage of respondents who received news about COVID-19 from the CDC in the past 7 days.,"Estimated percentage of respondents who received news about COVID-19 from the CDC in the past 7 days. + +Based on survey item I5. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey +fb-survey,smoothed_wreceived_news_cdc,TRUE,smoothed_received_news_cdc,FALSE,COVID News From CDC (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wreceived_news_experts,FALSE,smoothed_wreceived_news_experts,FALSE,COVID News From Scientists,FALSE,Estimated percentage of respondents who received news about COVID-19 from scientists and other health experts in the past 7 days.,"Estimated percentage of respondents who received news about COVID-19 from scientists and other health experts in the past 7 days. + +Based on survey item I5. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey +fb-survey,smoothed_wreceived_news_experts,TRUE,smoothed_received_news_experts,FALSE,COVID News From Scientists (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wreceived_news_friends,FALSE,smoothed_wreceived_news_friends,FALSE,COVID News From Friends,FALSE,Estimated percentage of respondents who received news about COVID-19 from friends and family in the past 7 days.,"Estimated percentage of respondents who received news about COVID-19 from friends and family in the past 7 days. + +Based on survey item I5. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey +fb-survey,smoothed_wreceived_news_friends,TRUE,smoothed_received_news_friends,FALSE,COVID News From Friends (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wreceived_news_govt_health,FALSE,smoothed_wreceived_news_govt_health,FALSE,COVID News From Health Officials,FALSE,Estimated percentage of respondents who received news about COVID-19 from government health authorities or officials in the past 7 days.,"Estimated percentage of respondents who received news about COVID-19 from government health authorities or officials in the past 7 days. + +Based on survey item I5. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey +fb-survey,smoothed_wreceived_news_govt_health,TRUE,smoothed_received_news_govt_health,FALSE,COVID News From Health Officials (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wreceived_news_journalists,FALSE,smoothed_wreceived_news_journalists,FALSE,COVID News From Journalists,FALSE,Estimated percentage of respondents who received news about COVID-19 from journalists in the past 7 days.,"Estimated percentage of respondents who received news about COVID-19 from journalists in the past 7 days. + +Based on survey item I5. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey +fb-survey,smoothed_wreceived_news_journalists,TRUE,smoothed_received_news_journalists,FALSE,COVID News From Journalists (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wreceived_news_local_health,FALSE,smoothed_wreceived_news_local_health,FALSE,COVID News From Local Health Workers,FALSE,"Estimated percentage of respondents who received news about COVID-19 from local health workers, clinics, and community organizations in the past 7 days.","Estimated percentage of respondents who received news about COVID-19 from local health workers, clinics, and community organizations in the past 7 days. + +Based on survey item I5. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey +fb-survey,smoothed_wreceived_news_local_health,TRUE,smoothed_received_news_local_health,FALSE,COVID News From Local Health Workers (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wreceived_news_none,FALSE,smoothed_wreceived_news_none,FALSE,COVID News From None of Above,FALSE,Estimated percentage of respondents who in the past 7 days received news about COVID-19 from none of the listed sources in the question.,"Estimated percentage of respondents who in the past 7 days received news about COVID-19 from none of the listed sources in the question. + +Based on survey item I5. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey +fb-survey,smoothed_wreceived_news_none,TRUE,smoothed_received_news_none,FALSE,COVID News From None of Above (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wreceived_news_politicians,FALSE,smoothed_wreceived_news_politicians,FALSE,COVID News From Politicians,FALSE,Estimated percentage of respondents who received news about COVID-19 from politicians in the past 7 days.,"Estimated percentage of respondents who received news about COVID-19 from politicians in the past 7 days. + +Based on survey item I5. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey +fb-survey,smoothed_wreceived_news_politicians,TRUE,smoothed_received_news_politicians,FALSE,COVID News From Politicians (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wreceived_news_religious,FALSE,smoothed_wreceived_news_religious,FALSE,COVID News From Religious Leaders,FALSE,Estimated percentage of respondents who received news about COVID-19 from religious leaders in the past 7 days.,"Estimated percentage of respondents who received news about COVID-19 from religious leaders in the past 7 days. + +Based on survey item I5. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey +fb-survey,smoothed_wreceived_news_religious,TRUE,smoothed_received_news_religious,FALSE,COVID News From Religious Leaders (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wrestaurant_1d,FALSE,smoothed_wrestaurant_1d,FALSE,Restaurant (Last 24 Hours),FALSE,"Estimated percentage of respondents who went to a ""bar, restaurant, or cafe"" in the past 24 hours","Estimated percentage of respondents who went to a ""bar, restaurant, or cafe"" in the past 24 hours. + +This item was shown to respondents starting in Wave 4, September 8, 2020. + +Discontinued as of Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey +fb-survey,smoothed_wrestaurant_1d,TRUE,smoothed_restaurant_1d,FALSE,Restaurant (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wrestaurant_indoors_1d,FALSE,smoothed_wrestaurant_indoors_1d,FALSE,Restaurant Indoors (Last 24 Hours),FALSE,"Estimated percentage of respondents who went to an indoor ""bar, restaurant, or cafe"" in the past 24 hours","Estimated percentage of respondents who went to an indoor ""bar, restaurant, or cafe"" in the past 24 hours. + +This item was shown to respondents starting in Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey +fb-survey,smoothed_wrestaurant_indoors_1d,TRUE,smoothed_restaurant_indoors_1d,FALSE,Restaurant Indoors (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wscreening_tested_positive_14d,FALSE,smoothed_wscreening_tested_positive_14d,FALSE,Screening Tested Positive (Last 14 Days),FALSE,Estimated test positivity rate (percent) among people tested for COVID-19 in the past 14 days,"Estimated test positivity rate (percent) among people tested for COVID-19 in the past 14 days who were being screened with no symptoms or known exposure. + +Note: Until Wave 11 (May 19, 2021), this included people who said they were tested while receiving other medical care, because their employer or school required it, after attending a large outdoor gathering, or prior to visiting friends or family. After that date, this includes people who said they were tested while receiving other medical care, because their employer or school required it, prior to visiting friends or family, or prior to domestic or international travel.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-19,NA,2022-02-18,"End dates vary by geo: county 2022-02-16, hrr 2022-02-03, msa 2022-02-12, nation 2022-02-18, state 2022-02-16",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",ascertained (case),"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#testing-indicators,fb-survey +fb-survey,smoothed_wscreening_tested_positive_14d,TRUE,smoothed_screening_tested_positive_14d,FALSE,Screening Tested Positive (Last 14 Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-19,NA,2022-02-18,"End dates vary by geo: county 2022-02-16, hrr 2022-02-03, msa 2022-02-12, nation 2022-02-18, state 2022-02-16",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",ascertained (case),"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wshop_1d,FALSE,smoothed_wshop_1d,FALSE,Shop (Last 24 Hours),FALSE,"Estimated percentage of respondents who went to a ""market, grocery store, or pharmacy"" in the past 24 hours","Estimated percentage of respondents who went to a ""market, grocery store, or pharmacy"" in the past 24 hours + +Discontinued as of Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey +fb-survey,smoothed_wshop_1d,TRUE,smoothed_shop_1d,FALSE,Shop (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wshop_indoors_1d,FALSE,smoothed_wshop_indoors_1d,FALSE,Shop Indoors (Last 24 Hours),FALSE,"Estimated percentage of respondents who went to an ""indoor market, grocery store, or pharmacy"" in the past 24 hours","Estimated percentage of respondents who went to an ""indoor market, grocery store, or pharmacy"" in the past 24 hours + +This item was shown to respondents starting in Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey +fb-survey,smoothed_wshop_indoors_1d,TRUE,smoothed_shop_indoors_1d,FALSE,Shop Indoors (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wspent_time_1d,FALSE,smoothed_wspent_time_1d,FALSE,Spent Time (Last 24 Hours),FALSE,"Estimated percentage of respondents who ""spent time with someone who isn't currently staying with you"" in the past 24 hours","Estimated percentage of respondents who ""spent time with someone who isn't currently staying with you"" in the past 24 hours + +Discontinued as of Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey +fb-survey,smoothed_wspent_time_1d,TRUE,smoothed_spent_time_1d,FALSE,Spent Time (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wspent_time_indoors_1d,FALSE,smoothed_wspent_time_indoors_1d,FALSE,Spent Time Indoors (Last 24 Hours),FALSE,"Estimated percentage of respondents who ""spent time indoors with someone who isn't currently staying with you"" in the past 24 hours","Estimated percentage of respondents who ""spent time indoors with someone who isn't currently staying with you"" in the past 24 hours + +This item was shown to respondents starting in Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey +fb-survey,smoothed_wspent_time_indoors_1d,TRUE,smoothed_spent_time_indoors_1d,FALSE,Spent Time Indoors (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wtested_14d,FALSE,smoothed_wtested_14d,FALSE,Tested (Last 14 Days),FALSE,"Estimated percentage of people who were tested for COVID-19 in the past 14 days, regardless of their test result",NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#testing-indicators,fb-survey +fb-survey,smoothed_wtested_14d,TRUE,smoothed_tested_14d,FALSE,Tested (Last 14 Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wtested_positive_14d,FALSE,smoothed_wtested_positive_14d,FALSE,Tested Positive (Last 14 Days),FALSE,Estimated test positivity rate (percent) among people tested for COVID-19 in the past 14 days,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,"Start dates vary by geo: county 2020-09-08, hrr 2020-09-09, msa 2020-09-08, nation 2020-09-08, state 2020-09-08",2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",ascertained (case),"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#testing-indicators,fb-survey +fb-survey,smoothed_wtested_positive_14d,TRUE,smoothed_tested_positive_14d,FALSE,Tested Positive (Last 14 Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,"Start dates vary by geo: county 2020-09-08, hrr 2020-09-09, msa 2020-09-08, nation 2020-09-08, state 2020-09-08",2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",ascertained (case),"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wtravel_outside_state_5d,FALSE,smoothed_wtravel_outside_state_5d,FALSE,Travel Outside State (Last 5 Days),FALSE,Estimated percentage of respondents who report traveling outside their state in the past 5 days,"Estimated percentage of respondents who report traveling outside their state in the past 5 days + +Discontinued as of Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-06,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.",Data is available for about 45% of counties. Data is available for all states and some territories. Availability declines over time as survey response rate decreases,Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey +fb-survey,smoothed_wtravel_outside_state_5d,TRUE,smoothed_travel_outside_state_5d,FALSE,Travel Outside State (Last 5 Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-06,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.",Data is available for about 45% of counties. Data is available for all states and some territories. Availability declines over time as survey response rate decreases,Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wtravel_outside_state_7d,FALSE,smoothed_wtravel_outside_state_7d,FALSE,Travel Outside State (Last 7 Days),FALSE,Estimated percentage of respondents who report traveling outside their state in the past 7 days.,"Estimated percentage of respondents who report traveling outside their state in the past 7 days. + +This item was shown to respondents starting in Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-02-20,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-20, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey +fb-survey,smoothed_wtravel_outside_state_7d,TRUE,smoothed_travel_outside_state_7d,FALSE,Travel Outside State (Last 7 Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-02-20,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-20, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wtrust_covid_info_cdc,FALSE,smoothed_wtrust_covid_info_cdc,FALSE,Trust COVID Info From CDC,FALSE,Estimated percentage of respondents who trust the Centers for Disease Control (CDC) to provide accurate news and information about COVID-19.,"Estimated percentage of respondents who trust the Centers for Disease Control (CDC) to provide accurate news and information about COVID-19. + +Based on survey item I6. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey +fb-survey,smoothed_wtrust_covid_info_cdc,TRUE,smoothed_trust_covid_info_cdc,FALSE,Trust COVID Info From CDC (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wtrust_covid_info_doctors,FALSE,smoothed_wtrust_covid_info_doctors,FALSE,Trust COVID Info From Doctors,FALSE,Estimated percentage of respondents who trust doctors and other health professionals they go to for medical care to provide accurate news and information about COVID-19.,"Estimated percentage of respondents who trust doctors and other health professionals they go to for medical care to provide accurate news and information about COVID-19. + +Based on survey item I6. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey +fb-survey,smoothed_wtrust_covid_info_doctors,TRUE,smoothed_trust_covid_info_doctors,FALSE,Trust COVID Info From Doctors (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wtrust_covid_info_experts,FALSE,smoothed_wtrust_covid_info_experts,FALSE,Trust COVID Info From Scientists,FALSE,Estimated percentage of respondents who trust scientists and other health experts to provide accurate news and information about COVID-19.,"Estimated percentage of respondents who trust scientists and other health experts to provide accurate news and information about COVID-19. + +Based on survey item I6. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey +fb-survey,smoothed_wtrust_covid_info_experts,TRUE,smoothed_trust_covid_info_experts,FALSE,Trust COVID Info From Scientists (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wtrust_covid_info_friends,FALSE,smoothed_wtrust_covid_info_friends,FALSE,Trust COVID Info From Friends,FALSE,Estimated percentage of respondents who trust friends and family to provide accurate news and information about COVID-19.,"Estimated percentage of respondents who trust friends and family to provide accurate news and information about COVID-19. + +Based on survey item I6. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey +fb-survey,smoothed_wtrust_covid_info_friends,TRUE,smoothed_trust_covid_info_friends,FALSE,Trust COVID Info From Friends (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wtrust_covid_info_govt_health,FALSE,smoothed_wtrust_covid_info_govt_health,FALSE,Trust COVID Info From Health Officials,FALSE,Estimated percentage of respondents who trust government health officials to provide accurate news and information about COVID-19.,"Estimated percentage of respondents who trust government health officials to provide accurate news and information about COVID-19. + +Based on survey item I6. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey +fb-survey,smoothed_wtrust_covid_info_govt_health,TRUE,smoothed_trust_covid_info_govt_health,FALSE,Trust COVID Info From Health Officials (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wtrust_covid_info_journalists,FALSE,smoothed_wtrust_covid_info_journalists,FALSE,Trust COVID Info From Journalists,FALSE,Estimated percentage of respondents who trust journalists to provide accurate news and information about COVID-19.,"Estimated percentage of respondents who trust journalists to provide accurate news and information about COVID-19. + +Based on survey item I6. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey +fb-survey,smoothed_wtrust_covid_info_journalists,TRUE,smoothed_trust_covid_info_journalists,FALSE,Trust COVID Info From Journalists (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wtrust_covid_info_politicians,FALSE,smoothed_wtrust_covid_info_politicians,FALSE,Trust COVID Info From Politicians,FALSE,Estimated percentage of respondents who trust politicians to provide accurate news and information about COVID-19.,"Estimated percentage of respondents who trust politicians to provide accurate news and information about COVID-19. + +Based on survey item I6. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey +fb-survey,smoothed_wtrust_covid_info_politicians,TRUE,smoothed_trust_covid_info_politicians,FALSE,Trust COVID Info From Politicians (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wtrust_covid_info_religious,FALSE,smoothed_wtrust_covid_info_religious,FALSE,Trust COVID Info From Religious Leaders,FALSE,Estimated percentage of respondents who trust religious leaders to provide accurate news and information about COVID-19.,"Estimated percentage of respondents who trust religious leaders to provide accurate news and information about COVID-19. + +Based on survey item I6. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey +fb-survey,smoothed_wtrust_covid_info_religious,TRUE,smoothed_trust_covid_info_religious,FALSE,Trust COVID Info From Religious Leaders (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wtry_vaccinate_1m,FALSE,smoothed_wtry_vaccinate_1m,FALSE,Will Get COVID-19 Vaccine Within a Month,FALSE,"Estimated percentage of respondents who report that they will try to get the COVID-19 vaccine within a week to a month, among unvaccinated respondents who do not have a vaccination appointment and who are uncertain about getting vaccinated (i.e. did not say they definitely would get vaccinated, nor that they definitely would not).","Estimated percentage of respondents who report that they will try to get the COVID-19 vaccine within a week to a month, among unvaccinated respondents who do not have a vaccination appointment and who are uncertain about getting vaccinated (i.e. did not say they definitely would get vaccinated, nor that they definitely would not). + +Based on survey item V16. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,"Start dates vary by geo: county 2021-06-04, hrr 2021-06-06, msa 2021-06-04, nation 2021-06-04, state 2021-06-04",2022-06-25,"End dates vary by geo: county 2022-06-25, hrr 2022-02-24, msa 2022-05-24, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey +fb-survey,smoothed_wtry_vaccinate_1m,TRUE,smoothed_try_vaccinate_1m,FALSE,Will Get COVID-19 Vaccine Within a Month (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,"Start dates vary by geo: county 2021-06-04, hrr 2021-06-06, msa 2021-06-04, nation 2021-06-04, state 2021-06-04",2022-06-27,"End dates vary by geo: county 2022-06-27, hrr 2022-02-24, msa 2022-05-25, nation 2022-06-27, state 2022-06-27",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccinate_child_oldest,FALSE,smoothed_wvaccinate_child_oldest,FALSE,Will Vaccinate Oldest Child for COVID-19,FALSE,Estimated percentage of respondents with children who report that they will definitely or probably get the vaccine for their oldest child.,"Estimated percentage of respondents with children who report that they will definitely or probably get the vaccine for their oldest child. + +Based on survey item P3. This item was shown to respondents starting in Wave 12, December 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-19, hrr 2021-12-21, msa 2021-12-20, nation 2021-12-19, state 2021-12-19",2022-06-25,NA,day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey +fb-survey,smoothed_wvaccinate_child_oldest,TRUE,smoothed_vaccinate_child_oldest,FALSE,Will Vaccinate Oldest Child for COVID-19 (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-19, hrr 2021-12-21, msa 2021-12-20, nation 2021-12-19, state 2021-12-19",2022-06-27,NA,day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccinate_children,FALSE,smoothed_wvaccinate_children,FALSE,Will Vaccinate Children for COVID-19,FALSE,Estimated percentage of respondents with children who report that they will definitely or probably get the vaccine for their children.,"Estimated percentage of respondents with children who report that they will definitely or probably get the vaccine for their children. + +Based on survey item E4. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2021-12-25,"End dates vary by geo: county 2021-12-24, hrr 2021-12-23, msa 2021-12-24, nation 2021-12-25, state 2021-12-24",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey +fb-survey,smoothed_wvaccinate_children,TRUE,smoothed_vaccinate_children,FALSE,Will Vaccinate Children for COVID-19 (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2021-12-25,"End dates vary by geo: county 2021-12-24, hrr 2021-12-23, msa 2021-12-24, nation 2021-12-25, state 2021-12-24",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_appointment_location,FALSE,smoothed_wvaccine_barrier_appointment_location,FALSE,Vaccine Barrier: Appointment Locations,FALSE,"Estimated percentage of respondents who report available appointment locations as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report available appointment locations as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. + +Based on survey items V15a and V15b. This item was shown to respondents starting in Wave 12, December 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_appointment_location,TRUE,smoothed_vaccine_barrier_appointment_location,FALSE,Vaccine Barrier: Appointment Locations (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_appointment_location_has,FALSE,smoothed_wvaccine_barrier_appointment_location_has,FALSE,Vaccine Barrier (Among Vaccinated): Appointment Locations,FALSE,"Estimated percentage of respondents who report available appointment locations as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report available appointment locations as a barrier to getting the vaccine, among those who have already been vaccinated. + +Based on survey item V15a. This item was shown to respondents starting in Wave 12, December 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_appointment_location_has,TRUE,smoothed_vaccine_barrier_appointment_location_has,FALSE,Vaccine Barrier (Among Vaccinated): Appointment Locations (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,NA,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_appointment_location_tried,FALSE,smoothed_wvaccine_barrier_appointment_location_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Appointment Locations,FALSE,"Estimated percentage of respondents who report available appointment locations as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report available appointment locations as a barrier to getting the vaccine, among those who have tried to get vaccinated. + +Based on survey item V15b. This item was shown to respondents starting in Wave 12, December 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-24, nation 2021-12-19, state 2021-12-24",2022-06-25,NA,day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_appointment_location_tried,TRUE,smoothed_vaccine_barrier_appointment_location_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Appointment Locations (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-24, nation 2021-12-19, state 2021-12-24",2022-06-27,"End dates vary by geo: county 2022-06-25, nation 2022-06-27, state 2022-06-25",day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,NA,NA,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_appointment_time,FALSE,smoothed_wvaccine_barrier_appointment_time,FALSE,Vaccine Barrier: Appointment Times,FALSE,"Estimated percentage of respondents who report lack of vaccine or vaccine appointments as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report lack of vaccine or vaccine appointments as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. + +Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_appointment_time,TRUE,smoothed_vaccine_barrier_appointment_time,FALSE,Vaccine Barrier: Appointment Times (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_appointment_time_has,FALSE,smoothed_wvaccine_barrier_appointment_time_has,FALSE,Vaccine Barrier (Among Vaccinated): Appointment Times,FALSE,"Estimated percentage of respondents who report available appointment times as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report available appointment times as a barrier to getting the vaccine, among those who have already been vaccinated. + +Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_appointment_time_has,TRUE,smoothed_vaccine_barrier_appointment_time_has,FALSE,Vaccine Barrier (Among Vaccinated): Appointment Times (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_appointment_time_tried,FALSE,smoothed_wvaccine_barrier_appointment_time_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Appointment Times,FALSE,"Estimated percentage of respondents who report available appointment times as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report available appointment times as a barrier to getting the vaccine, among those who have tried to get vaccinated. + +Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_appointment_time_tried,TRUE,smoothed_vaccine_barrier_appointment_time_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Appointment Times (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_childcare,FALSE,smoothed_wvaccine_barrier_childcare,FALSE,Vaccine Barrier: Childcare,FALSE,"Estimated percentage of respondents who report lack of childcare as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report lack of childcare as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. + +Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_childcare,TRUE,smoothed_vaccine_barrier_childcare,FALSE,Vaccine Barrier: Childcare (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_childcare_has,FALSE,smoothed_wvaccine_barrier_childcare_has,FALSE,Vaccine Barrier (Among Vaccinated): Childcare,FALSE,"Estimated percentage of respondents who report lack of childcare as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report lack of childcare as a barrier to getting the vaccine, among those who have already been vaccinated. + +Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_childcare_has,TRUE,smoothed_vaccine_barrier_childcare_has,FALSE,Vaccine Barrier (Among Vaccinated): Childcare (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_childcare_tried,FALSE,smoothed_wvaccine_barrier_childcare_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Childcare,FALSE,"Estimated percentage of respondents who report lack of childcare as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report lack of childcare as a barrier to getting the vaccine, among those who have tried to get vaccinated. + +Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_childcare_tried,TRUE,smoothed_vaccine_barrier_childcare_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Childcare (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_document,FALSE,smoothed_wvaccine_barrier_document,FALSE,Vaccine Barrier: Documents,FALSE,"Estimated percentage of respondents who report inability to provide required documents as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report inability to provide required documents as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. + +Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_document,TRUE,smoothed_vaccine_barrier_document,FALSE,Vaccine Barrier: Documents (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_document_has,FALSE,smoothed_wvaccine_barrier_document_has,FALSE,Vaccine Barrier (Among Vaccinated): Documents,FALSE,"Estimated percentage of respondents who report inability to provide required documents as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report inability to provide required documents as a barrier to getting the vaccine, among those who have already been vaccinated. + +Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_document_has,TRUE,smoothed_vaccine_barrier_document_has,FALSE,Vaccine Barrier (Among Vaccinated): Documents (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_document_tried,FALSE,smoothed_wvaccine_barrier_document_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Documents,FALSE,"Estimated percentage of respondents who report inability to provide required documents as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report inability to provide required documents as a barrier to getting the vaccine, among those who have tried to get vaccinated. + +Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_document_tried,TRUE,smoothed_vaccine_barrier_document_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Documents (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_eligible,FALSE,smoothed_wvaccine_barrier_eligible,FALSE,Vaccine Barrier: Eligibility,FALSE,"Estimated percentage of respondents who report eligibility requirements as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report eligibility requirements as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. + +Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_eligible,TRUE,smoothed_vaccine_barrier_eligible,FALSE,Vaccine Barrier: Eligibility (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_eligible_has,FALSE,smoothed_wvaccine_barrier_eligible_has,FALSE,Vaccine Barrier (Among Vaccinated): Eligibility,FALSE,"Estimated percentage of respondents who report eligibility requirements as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report eligibility requirements as a barrier to getting the vaccine, among those who have already been vaccinated. + +Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_eligible_has,TRUE,smoothed_vaccine_barrier_eligible_has,FALSE,Vaccine Barrier (Among Vaccinated): Eligibility (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_eligible_tried,FALSE,smoothed_wvaccine_barrier_eligible_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Eligibility,FALSE,"Estimated percentage of respondents who report eligibility requirements as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report eligibility requirements as a barrier to getting the vaccine, among those who have tried to get vaccinated. + +Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_eligible_tried,TRUE,smoothed_vaccine_barrier_eligible_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Eligibility (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_language,FALSE,smoothed_wvaccine_barrier_language,FALSE,Vaccine Barrier: Language,FALSE,"Estimated percentage of respondents who report information not being available in their native language as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report information not being available in their native language as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. + +Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_language,TRUE,smoothed_vaccine_barrier_language,FALSE,Vaccine Barrier: Language (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_language_has,FALSE,smoothed_wvaccine_barrier_language_has,FALSE,Vaccine Barrier (Among Vaccinated): Language,FALSE,"Estimated percentage of respondents who report information not being available in their native language as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report information not being available in their native language as a barrier to getting the vaccine, among those who have already been vaccinated. + +Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_language_has,TRUE,smoothed_vaccine_barrier_language_has,FALSE,Vaccine Barrier (Among Vaccinated): Language (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_language_tried,FALSE,smoothed_wvaccine_barrier_language_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Language,FALSE,"Estimated percentage of respondents who report information not being available in their native language as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report information not being available in their native language as a barrier to getting the vaccine, among those who have tried to get vaccinated. + +Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_language_tried,TRUE,smoothed_vaccine_barrier_language_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Language (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_no_appointments,FALSE,smoothed_wvaccine_barrier_no_appointments,FALSE,Vaccine Barrier: No Appointments,FALSE,"Estimated percentage of respondents who report lack of vaccine or vaccine appointments as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report lack of vaccine or vaccine appointments as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. + +Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_no_appointments,TRUE,smoothed_vaccine_barrier_no_appointments,FALSE,Vaccine Barrier: No Appointments (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_no_appointments_has,FALSE,smoothed_wvaccine_barrier_no_appointments_has,FALSE,Vaccine Barrier (Among Vaccinated): No Appointments,FALSE,"Estimated percentage of respondents who report lack of vaccine or vaccine appointments as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report lack of vaccine or vaccine appointments as a barrier to getting the vaccine, among those who have already been vaccinated. + +Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_no_appointments_has,TRUE,smoothed_vaccine_barrier_no_appointments_has,FALSE,Vaccine Barrier (Among Vaccinated): No Appointments (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_no_appointments_tried,FALSE,smoothed_wvaccine_barrier_no_appointments_tried,FALSE,Vaccine Barrier (Among Unvaccinated): No Appointments,FALSE,"Estimated percentage of respondents who report lack of vaccine or vaccine appointments as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report lack of vaccine or vaccine appointments as a barrier to getting the vaccine, among those who have tried to get vaccinated. + +Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_no_appointments_tried,TRUE,smoothed_vaccine_barrier_no_appointments_tried,FALSE,Vaccine Barrier (Among Unvaccinated): No Appointments (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_none,FALSE,smoothed_wvaccine_barrier_none,FALSE,Vaccine Barrier: None of Above,FALSE,"Estimated percentage of respondents who report experiencing none of the listed barriers to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report experiencing none of the listed barriers to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. + +Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_none,TRUE,smoothed_vaccine_barrier_none,FALSE,Vaccine Barrier: None of Above (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_none_has,FALSE,smoothed_wvaccine_barrier_none_has,FALSE,Vaccine Barrier (Among Vaccinated): None of Above,FALSE,"Estimated percentage of respondents who report experiencing none of the listed barriers to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report experiencing none of the listed barriers to getting the vaccine, among those who have already been vaccinated. + +Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_none_has,TRUE,smoothed_vaccine_barrier_none_has,FALSE,Vaccine Barrier (Among Vaccinated): None of Above (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_none_tried,FALSE,smoothed_wvaccine_barrier_none_tried,FALSE,Vaccine Barrier (Among Unvaccinated): None of Above,FALSE,"Estimated percentage of respondents who report experiencing none of the listed barriers to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report experiencing none of the listed barriers to getting the vaccine, among those who have tried to get vaccinated. + +Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_none_tried,TRUE,smoothed_vaccine_barrier_none_tried,FALSE,Vaccine Barrier (Among Unvaccinated): None of Above (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_other,FALSE,smoothed_wvaccine_barrier_other,FALSE,Vaccine Barrier: Other,FALSE,"Estimated percentage of respondents who report experiencing some other barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report experiencing some other barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. + +Based on survey items V15a and V15b. This item was shown to respondents starting in Wave 12, December 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_other,TRUE,smoothed_vaccine_barrier_other,FALSE,Vaccine Barrier: Other (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_other_has,FALSE,smoothed_wvaccine_barrier_other_has,FALSE,Vaccine Barrier (Among Vaccinated): Other,FALSE,"Estimated percentage of respondents who report experiencing some other barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report experiencing some other barrier to getting the vaccine, among those who have already been vaccinated. + +Based on survey item V15a. This item was shown to respondents starting in Wave 12, December 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_other_has,TRUE,smoothed_vaccine_barrier_other_has,FALSE,Vaccine Barrier (Among Vaccinated): Other (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_other_tried,FALSE,smoothed_wvaccine_barrier_other_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Other,FALSE,"Estimated percentage of respondents who report experiencing some other barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report experiencing some other barrier to getting the vaccine, among those who have tried to get vaccinated. + +Based on survey item V15b. This item was shown to respondents starting in Wave 12, December 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-24, nation 2021-12-19, state 2021-12-24",2022-06-25,NA,day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_other_tried,TRUE,smoothed_vaccine_barrier_other_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Other (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-24, nation 2021-12-19, state 2021-12-24",2022-06-27,"End dates vary by geo: county 2022-06-25, nation 2022-06-27, state 2022-06-25",day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_technical_difficulties,FALSE,smoothed_wvaccine_barrier_technical_difficulties,FALSE,Vaccine Barrier: Technical Problems,FALSE,"Estimated percentage of respondents who report technical difficulties with the website or phone line as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report technical difficulties with the website or phone line as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. + +Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_technical_difficulties,TRUE,smoothed_vaccine_barrier_technical_difficulties,FALSE,Vaccine Barrier: Technical Problems (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_technical_difficulties_has,FALSE,smoothed_wvaccine_barrier_technical_difficulties_has,FALSE,Vaccine Barrier (Among Vaccinated): Technical Problems,FALSE,"Estimated percentage of respondents who report technical difficulties with the website or phone line as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report technical difficulties with the website or phone line as a barrier to getting the vaccine, among those who have already been vaccinated. + +Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_technical_difficulties_has,TRUE,smoothed_vaccine_barrier_technical_difficulties_has,FALSE,Vaccine Barrier (Among Vaccinated): Technical Problems (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_technical_difficulties_tried,FALSE,smoothed_wvaccine_barrier_technical_difficulties_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Technical Problems,FALSE,"Estimated percentage of respondents who report technical difficulties with the website or phone line as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report technical difficulties with the website or phone line as a barrier to getting the vaccine, among those who have tried to get vaccinated. + +Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_technical_difficulties_tried,TRUE,smoothed_vaccine_barrier_technical_difficulties_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Technical Problems (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_technology_access,FALSE,smoothed_wvaccine_barrier_technology_access,FALSE,Vaccine Barrier: Technology Access,FALSE,"Estimated percentage of respondents who report limited access to internet or phone as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report limited access to internet or phone as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. + +Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_technology_access,TRUE,smoothed_vaccine_barrier_technology_access,FALSE,Vaccine Barrier: Technology Access (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_technology_access_has,FALSE,smoothed_wvaccine_barrier_technology_access_has,FALSE,Vaccine Barrier (Among Vaccinated): Technology Access,FALSE,"Estimated percentage of respondents who report limited access to internet or phone as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report limited access to internet or phone as a barrier to getting the vaccine, among those who have already been vaccinated. + +Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_technology_access_has,TRUE,smoothed_vaccine_barrier_technology_access_has,FALSE,Vaccine Barrier (Among Vaccinated): Technology Access (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_technology_access_tried,FALSE,smoothed_wvaccine_barrier_technology_access_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Technology Access,FALSE,"Estimated percentage of respondents who report limited access to internet or phone as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report limited access to internet or phone as a barrier to getting the vaccine, among those who have tried to get vaccinated. + +Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_technology_access_tried,TRUE,smoothed_vaccine_barrier_technology_access_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Technology Access (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_time,FALSE,smoothed_wvaccine_barrier_time,FALSE,Vaccine Barrier: Time Off,FALSE,"Estimated percentage of respondents who report difficulty getting time away from work or school as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report difficulty getting time away from work or school as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. + +Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_time,TRUE,smoothed_vaccine_barrier_time,FALSE,Vaccine Barrier: Time Off (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_time_has,FALSE,smoothed_wvaccine_barrier_time_has,FALSE,Vaccine Barrier (Among Vaccinated): Time Off,FALSE,"Estimated percentage of respondents who report difficulty getting time away from work or school as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report difficulty getting time away from work or school as a barrier to getting the vaccine, among those who have already been vaccinated. + +Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_time_has,TRUE,smoothed_vaccine_barrier_time_has,FALSE,Vaccine Barrier (Among Vaccinated): Time Off (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_time_tried,FALSE,smoothed_wvaccine_barrier_time_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Time Off,FALSE,"Estimated percentage of respondents who report difficulty getting time away from work or school as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report difficulty getting time away from work or school as a barrier to getting the vaccine, among those who have tried to get vaccinated. + +Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_time_tried,TRUE,smoothed_vaccine_barrier_time_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Time Off (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_travel,FALSE,smoothed_wvaccine_barrier_travel,FALSE,Vaccine Barrier: Travel,FALSE,"Estimated percentage of respondents who report difficulty traveling to vaccination sites as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report difficulty traveling to vaccination sites as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. + +Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_travel,TRUE,smoothed_vaccine_barrier_travel,FALSE,Vaccine Barrier: Travel (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_travel_has,FALSE,smoothed_wvaccine_barrier_travel_has,FALSE,Vaccine Barrier (Among Vaccinated): Travel,FALSE,"Estimated percentage of respondents who report difficulty traveling to vaccination sites as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report difficulty traveling to vaccination sites as a barrier to getting the vaccine, among those who have already been vaccinated. + +Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_travel_has,TRUE,smoothed_vaccine_barrier_travel_has,FALSE,Vaccine Barrier (Among Vaccinated): Travel (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_travel_tried,FALSE,smoothed_wvaccine_barrier_travel_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Travel,FALSE,"Estimated percentage of respondents who report difficulty traveling to vaccination sites as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report difficulty traveling to vaccination sites as a barrier to getting the vaccine, among those who have tried to get vaccinated. + +Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_travel_tried,TRUE,smoothed_vaccine_barrier_travel_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Travel (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_type,FALSE,smoothed_wvaccine_barrier_type,FALSE,Vaccine Barrier: Vaccine Type,FALSE,"Estimated percentage of respondents who report available vaccine type as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report available vaccine type as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. + +Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_type,TRUE,smoothed_vaccine_barrier_type,FALSE,Vaccine Barrier: Vaccine Type (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_type_has,FALSE,smoothed_wvaccine_barrier_type_has,FALSE,Vaccine Barrier (Among Vaccinated): Vaccine Type,FALSE,"Estimated percentage of respondents who report available vaccine type as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report available vaccine type as a barrier to getting the vaccine, among those who have already been vaccinated. + +Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_type_has,TRUE,smoothed_vaccine_barrier_type_has,FALSE,Vaccine Barrier (Among Vaccinated): Vaccine Type (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_barrier_type_tried,FALSE,smoothed_wvaccine_barrier_type_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Vaccine Type,FALSE,"Estimated percentage of respondents who report available vaccine type as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report available vaccine type as a barrier to getting the vaccine, among those who have tried to get vaccinated. + +Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey +fb-survey,smoothed_wvaccine_barrier_type_tried,TRUE,smoothed_vaccine_barrier_type_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Vaccine Type (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_likely_doctors,FALSE,smoothed_wvaccine_likely_doctors,FALSE,Vaccine Likely: Doctors,FALSE,Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by doctors and other health professionals they go to for medical care,"Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by doctors and other health professionals they go to for medical care, among respondents who have not yet been vaccinated. + +Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#outreach-and-image,fb-survey +fb-survey,smoothed_wvaccine_likely_doctors,TRUE,smoothed_vaccine_likely_doctors,FALSE,Vaccine Likely: Doctors (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_likely_friends,FALSE,smoothed_wvaccine_likely_friends,FALSE,Vaccine Likely: Friends,FALSE,Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by friends and family,"Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by friends and family, among respondents who have not yet been vaccinated. + +Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#outreach-and-image,fb-survey +fb-survey,smoothed_wvaccine_likely_friends,TRUE,smoothed_vaccine_likely_friends,FALSE,Vaccine Likely: Friends (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_likely_govt_health,FALSE,smoothed_wvaccine_likely_govt_health,FALSE,Vaccine Likely: Government Health,FALSE,Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by government health officials,"Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by government health officials, among respondents who have not yet been vaccinated. + +Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#outreach-and-image,fb-survey +fb-survey,smoothed_wvaccine_likely_govt_health,TRUE,smoothed_vaccine_likely_govt_health,FALSE,Vaccine Likely: Government Health (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_likely_local_health,FALSE,smoothed_wvaccine_likely_local_health,FALSE,Vaccine Likely: Local Health,FALSE,Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by local health workers,"Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by local health workers, among respondents who have not yet been vaccinated. + +Discontinued as of Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-03-16,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#outreach-and-image,fb-survey +fb-survey,smoothed_wvaccine_likely_local_health,TRUE,smoothed_vaccine_likely_local_health,FALSE,Vaccine Likely: Local Health (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-03-16,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_likely_politicians,FALSE,smoothed_wvaccine_likely_politicians,FALSE,Vaccine Likely: Politicians,FALSE,Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by politicians,"Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by politicians, among respondents who have not yet been vaccinated. + +Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#outreach-and-image,fb-survey +fb-survey,smoothed_wvaccine_likely_politicians,TRUE,smoothed_vaccine_likely_politicians,FALSE,Vaccine Likely: Politicians (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wvaccine_likely_who,FALSE,smoothed_wvaccine_likely_who,FALSE,Vaccine Likely: WHO,FALSE,Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by the World Health Organization,"Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by the World Health Organization, among respondents who have not yet been vaccinated. + +Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#outreach-and-image,fb-survey +fb-survey,smoothed_wvaccine_likely_who,TRUE,smoothed_vaccine_likely_who,FALSE,Vaccine Likely: WHO (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wwant_info_children_education,FALSE,smoothed_wwant_info_children_education,FALSE,Want Information: Education,FALSE,Estimated percentage of people who want more information about how to support their children’s education.,"Estimated percentage of people who want more information about how to support their children’s education. + +Based on survey item I7. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#desired-information,fb-survey +fb-survey,smoothed_wwant_info_children_education,TRUE,smoothed_want_info_children_education,FALSE,Want Information: Education (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wwant_info_covid_treatment,FALSE,smoothed_wwant_info_covid_treatment,FALSE,Want Information: COVID Treatment,FALSE,Estimated percentage of people who want more information about the treatment of COVID-19.,"Estimated percentage of people who want more information about the treatment of COVID-19. + +Based on survey item I7. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#desired-information,fb-survey +fb-survey,smoothed_wwant_info_covid_treatment,TRUE,smoothed_want_info_covid_treatment,FALSE,Want Information: COVID Treatment (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wwant_info_covid_variants,FALSE,smoothed_wwant_info_covid_variants,FALSE,Want Information: COVID Variants,FALSE,Estimated percentage of people who want more information about COVID-19 variants and mutations.,"Estimated percentage of people who want more information about COVID-19 variants and mutations. + +Based on survey item I7. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#desired-information,fb-survey +fb-survey,smoothed_wwant_info_covid_variants,TRUE,smoothed_want_info_covid_variants,FALSE,Want Information: COVID Variants (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wwant_info_employment,FALSE,smoothed_wwant_info_employment,FALSE,Want Information: Employment,FALSE,Estimated percentage of people who want more information about employment and other economic and financial issues.,"Estimated percentage of people who want more information about employment and other economic and financial issues. + +Based on survey item I7. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#desired-information,fb-survey +fb-survey,smoothed_wwant_info_employment,TRUE,smoothed_want_info_employment,FALSE,Want Information: Employment (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wwant_info_mental_health,FALSE,smoothed_wwant_info_mental_health,FALSE,Want Information: Mental Health,FALSE,Estimated percentage of people who want more information about how to maintain their mental health.,"Estimated percentage of people who want more information about how to maintain their mental health. + +Based on survey item I7. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#desired-information,fb-survey +fb-survey,smoothed_wwant_info_mental_health,TRUE,smoothed_want_info_mental_health,FALSE,Want Information: Mental Health (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wwant_info_none,FALSE,smoothed_wwant_info_none,FALSE,Want Information: None of Above,FALSE,Estimated percentage of people who want more information about none of the listed topics.,"Estimated percentage of people who want more information about none of the listed topics. + +Based on survey item I7. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#desired-information,fb-survey +fb-survey,smoothed_wwant_info_none,TRUE,smoothed_want_info_none,FALSE,Want Information: None of Above (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wwant_info_relationships,FALSE,smoothed_wwant_info_relationships,FALSE,Want Information: Relationships,FALSE,Estimated percentage of people who want more information about how to maintain their social relationships despite physical distancing.,"Estimated percentage of people who want more information about how to maintain their social relationships despite physical distancing. + +Based on survey item I7. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#desired-information,fb-survey +fb-survey,smoothed_wwant_info_relationships,TRUE,smoothed_want_info_relationships,FALSE,Want Information: Relationships (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wwant_info_vaccine_access,FALSE,smoothed_wwant_info_vaccine_access,FALSE,Want Information: Vaccine Access,FALSE,Estimated percentage of people who want more information about how to get a COVID-19 vaccine.,"Estimated percentage of people who want more information about how to get a COVID-19 vaccine. + +Based on survey item I7. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#desired-information,fb-survey +fb-survey,smoothed_wwant_info_vaccine_access,TRUE,smoothed_want_info_vaccine_access,FALSE,Want Information: Vaccine Access (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wwant_info_vaccine_types,FALSE,smoothed_wwant_info_vaccine_types,FALSE,Want Information: Vaccine Types,FALSE,Estimated percentage of people who want more information about different types of COVID-19 vaccines.,"Estimated percentage of people who want more information about different types of COVID-19 vaccines. + +Based on survey item I7. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#desired-information,fb-survey +fb-survey,smoothed_wwant_info_vaccine_types,TRUE,smoothed_want_info_vaccine_types,FALSE,Want Information: Vaccine Types (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wwanted_test_14d,FALSE,smoothed_wwanted_test_14d,FALSE,Wanted Test (Last 14 Days),FALSE,"Estimated percentage of people who wanted to be tested for COVID-19 in the past 14 days, out of people who were not tested in that time","Estimated percentage of people who wanted to be tested for COVID-19 in the past 14 days, out of people who were not tested in that time. + +Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-08-08,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#testing-indicators,fb-survey +fb-survey,smoothed_wwanted_test_14d,TRUE,smoothed_wanted_test_14d,FALSE,Wanted Test (Last 14 Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-08-08,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wwearing_mask,FALSE,smoothed_wwearing_mask,FALSE,People Wearing Masks (Last 5 Days),FALSE,Estimated percentage of people who wore a mask for most or all of the time while in public in the past 5 days; those not in public in the past 5 days are not counted.,"Estimated percentage of people who wore a mask for most or all of the time while in public in the past 5 days; those not in public in the past 5 days are not counted. + +Discontinued as of Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-02-22,"End dates vary by geo: county 2021-02-21, hrr 2021-02-20, msa 2021-02-21, nation 2021-02-22, state 2021-02-21",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,"[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mask-use) +[Interpreting mask use in context](https://delphi.cmu.edu/blog/2020/12/13/are-masks-widely-used-in-public/) +[Wave 10 revision updates](https://cmu-delphi.github.io/delphi-epidata/symptom-survey/coding.html#wave-10)",fb-survey +fb-survey,smoothed_wwearing_mask,TRUE,smoothed_wearing_mask,FALSE,People Wearing Masks (Last 5 Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-02-22,"End dates vary by geo: county 2021-02-21, hrr 2021-02-20, msa 2021-02-21, nation 2021-02-22, state 2021-02-21",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wwearing_mask_7d,FALSE,smoothed_wwearing_mask_7d,FALSE,People Wearing Masks (Last 7 Days),FALSE,Estimated percentage of people who wore a mask for most or all of the time while in public in the past 7 days; those not in public in the past 7 days are not counted.,"{source_description} We also ask them if they wear a mask when they are in public. For this signal, we estimate the percentage of people who say they wear a mask most or all of the time when they are in public. + +This item was shown to respondents starting in Wave 8, February 8, 2021, replacing a 5-day version of the same question.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,"[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mask-use) +[Interpreting mask use in context](https://delphi.cmu.edu/blog/2020/12/13/are-masks-widely-used-in-public/) +[Wave 10 revision updates](https://cmu-delphi.github.io/delphi-epidata/symptom-survey/coding.html#wave-10)",fb-survey +fb-survey,smoothed_wwearing_mask_7d,TRUE,smoothed_wearing_mask_7d,FALSE,People Wearing Masks (Last 7 Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wwork_outside_home_1d,FALSE,smoothed_wwork_outside_home_1d,FALSE,Work Outside Home (Last 24 Hours),FALSE,Estimated percentage of respondents who worked or went to school outside their home in the past 24 hours,"Estimated percentage of respondents who worked or went to school outside their home in the past 24 hours. + +This item was shown to respondents starting in Wave 4, September 8, 2020. + +Discontinued as of Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey +fb-survey,smoothed_wwork_outside_home_1d,TRUE,smoothed_work_outside_home_1d,FALSE,Work Outside Home (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wwork_outside_home_indoors_1d,FALSE,smoothed_wwork_outside_home_indoors_1d,FALSE,Work Outside Home Indoors (Last 24 Hours),FALSE,Estimated percentage of respondents who worked or went to school outside their home in an indoor setting in the past 24 hours,"Estimated percentage of respondents who worked or went to school outside their home in an indoor setting in the past 24 hours. + +This item was shown to respondents starting in Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey +fb-survey,smoothed_wwork_outside_home_indoors_1d,TRUE,smoothed_work_outside_home_indoors_1d,FALSE,Work Outside Home Indoors (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wworried_become_ill,FALSE,smoothed_wworried_become_ill,FALSE,Worried Become Ill,FALSE,"Estimated percentage of respondents who reported feeling very or somewhat worried that ""you or someone in your immediate family might become seriously ill from COVID-19""","Estimated percentage of respondents who reported feeling very or somewhat worried that ""you or someone in your immediate family might become seriously ill from COVID-19"". + +Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-08-08,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mental-health-indicators,fb-survey +fb-survey,smoothed_wworried_become_ill,TRUE,smoothed_worried_become_ill,FALSE,Worried Become Ill (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-08-08,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wworried_catch_covid,FALSE,smoothed_wworried_catch_covid,FALSE,Worried About Catching COVID,FALSE,Estimated percentage of respondents worrying either a great deal or a moderate amount about catching COVID-19.,"Estimated percentage of respondents worrying either a great deal or a moderate amount about catching COVID-19. + +Based on survey item G1. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#desired-information,fb-survey +fb-survey,smoothed_wworried_catch_covid,TRUE,smoothed_worried_catch_covid,FALSE,Worried About Catching COVID (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wworried_finances,FALSE,smoothed_wworried_finances,FALSE,Worried Finances,FALSE,"Estimated percentage of respondents who report being very or somewhat worried about their ""household's finances for the next month""",NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mental-health-indicators,fb-survey +fb-survey,smoothed_wworried_finances,TRUE,smoothed_worried_finances,FALSE,Worried Finances (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +fb-survey,smoothed_wworried_vaccine_side_effects,FALSE,smoothed_wworried_vaccine_side_effects,FALSE,Worried Vaccine Side Effects,FALSE,"Estimated percentage of respondents who are very or moderately concerned that they would ""experience a side effect from a COVID-19 vaccination.""","Estimated percentage of respondents who are very or moderately concerned that they would ""experience a side effect from a COVID-19 vaccination."" + +Note: Until Wave 10, March 2, 2021, all respondents answered this question, including those who had already received one or more doses of a COVID-19 vaccine; beginning on that date, only respondents who said they have not received a COVID vaccine are asked this question.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-01-13,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey +fb-survey,smoothed_wworried_vaccine_side_effects,TRUE,smoothed_worried_vaccine_side_effects,FALSE,Worried Vaccine Side Effects (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-01-13,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. + + This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey +ght,raw_search,NA,raw_search,FALSE,COVID-Related Searches,FALSE,"Google search volume for COVID-related searches, in arbitrary units that are normalized for population","Google search volume for COVID-related searches, in arbitrary units that are normalized for population + +Discontinued March 8, 2021.",Google Health Trends,covid,Search volume,USA,"hrr (by Delphi), msa (by Delphi), dma, state",2020-02-01,NA,2021-03-04,NA,day,Date,daily,4-5 days,None,Google search users,None,population,"Reported as 0 query when search volume is below a certain threshold, as set by Google. Areas with low query volume hence exhibit jumps and zero-inflation, as small variations in the signal can cause it to be sometimes truncated to 0 and sometimes reported at its actual level",Data is available for all states.,Value,raw,public,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/ght.html,ght +ght,raw_search,NA,smoothed_search,FALSE,COVID-Related Searches (Gaussian smoothed),FALSE,NA,"{base_short_description), smoothed in time using a Gaussian linear smoother. + +Discontinued March 8, 2021.",Google Health Trends,covid,Search volume,USA,"hrr (by Delphi), msa (by Delphi), dma, state",2020-02-01,NA,2021-03-04,NA,day,Date,daily,4-5 days,None,Google search users,None,population,"Reported as 0 query when search volume is below a certain threshold, as set by Google. Areas with low query volume hence exhibit jumps and zero-inflation, as small variations in the signal can cause it to be sometimes truncated to 0 and sometimes reported at its actual level",Data is available for all states.,Value,raw,public,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,ght +google-survey,raw_cli,FALSE,raw_cli,FALSE,COVID-Like Illness,FALSE,Estimated percentage of people who know someone in their community with COVID-like illness.,"Estimated percentage of people who know someone in their community with COVID-like illness. + +Discontinued May 16, 2020.",Google Symptom Surveys,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi)",2020-04-11,NA,2020-05-14,NA,day,Date,daily,1-2 days,"Daily, for 3 consecutive issues for each report date","Google ad publisher website, Google's Opinions Reward app, and similar application users",None,symptomatic,Discarded when an estimate is based on fewer than 100 survey responses,Data is available for about 20% of counties Data is available for all states.,Value,raw,early,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-survey.html,google-survey +google-survey,raw_cli,TRUE,smoothed_cli,FALSE,COVID-Like Illness (7-day average),FALSE,NA,NA,Google Symptom Surveys,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi)",2020-04-11,NA,2020-05-14,NA,day,Date,daily,1-2 days,"Daily, for 3 consecutive issues for each report date","Google ad publisher website, Google's Opinions Reward app, and similar application users",None,symptomatic,Discarded when an estimate is based on fewer than 100 survey responses,Data is available for about 20% of counties Data is available for all states.,Value,raw,early,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,google-survey +google-symptoms,ageusia_raw_search,FALSE,ageusia_raw_search,FALSE,Ageusia Searches,FALSE,"Google search volume for ageusia-related searches, in arbitrary units that are normalized for overall search users",NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-13,"Start dates vary by geo: county 2020-02-13, hhs 2020-02-14, hrr 2020-02-13, msa 2020-02-13, nation 2020-02-14, state 2020-02-13",2022-01-20,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 3-4% of counties. Data is available for about 85% of states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-symptoms.html,google-symptoms +google-symptoms,ageusia_raw_search,TRUE,ageusia_smoothed_search,TRUE,Ageusia Searches (7-day average),FALSE,NA,NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,2022-01-20,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 3-4% of counties. Data is available for about 85% of states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,google-symptoms +google-symptoms,anosmia_raw_search,FALSE,anosmia_raw_search,FALSE,Anosmia Searches,FALSE,"Google search volume for anosmia-related searches, in arbitrary units that are normalized for overall search users",NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-13,"Start dates vary by geo: county 2020-02-13, hhs 2020-02-14, hrr 2020-02-13, msa 2020-02-13, nation 2020-02-14, state 2020-02-13",2022-01-20,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 3-4% of counties. Data is available for about 85% of states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-symptoms.html,google-symptoms +google-symptoms,anosmia_raw_search,TRUE,anosmia_smoothed_search,TRUE,Anosmia Searches (7-day average),FALSE,NA,NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,2022-01-20,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 3-4% of counties. Data is available for about 85% of states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,google-symptoms +google-symptoms,s01_raw_search,FALSE,s01_raw_search,FALSE,"Searches for: Cough, Phlegm, Sputum, Upper respiratory tract infection",TRUE,"The average relative frequency of searches for Cough, Phlegm, Sputum, and Upper respiratory tract infection, in arbitrary units that are normalized against overall search patterns within each region.","The average relative frequency of searches for Cough, Phlegm, Sputum, and Upper respiratory tract infection, in arbitrary units that are normalized against overall search patterns within each region. + +The symptoms in this set showed positive correlation with cases, especially after Omicron was declared a variant of concern by the WHO.",Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-14,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 50% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-symptoms.html,google-symptoms +google-symptoms,s01_raw_search,TRUE,s01_smoothed_search,FALSE,"Searches for: Cough, Phlegm, Sputum, Upper respiratory tract infection (7-day average)",TRUE,NA,NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 50% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,google-symptoms +google-symptoms,s02_raw_search,FALSE,s02_raw_search,FALSE,"Searches for: Nasal congestion, Post nasal drip, Rhinorrhea, Sinusitis, Rhinitis, Common cold",TRUE,"The average relative frequency of searches for Nasal congestion, Post nasal drip, Rhinorrhea, Sinusitis, Rhinitis, and Common cold, in arbitrary units that are normalized against overall search patterns within each region.","The average relative frequency of searches for Nasal congestion, Post nasal drip, Rhinorrhea, Sinusitis, Rhinitis, and Common cold, in arbitrary units that are normalized against overall search patterns within each region. + +The symptoms in this set showed positive correlation with cases, especially after Omicron was declared a variant of concern by the WHO.",Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-14,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 65% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-symptoms.html,google-symptoms +google-symptoms,s02_raw_search,TRUE,s02_smoothed_search,FALSE,"Searches for: Nasal congestion, Post nasal drip, Rhinorrhea, Sinusitis, Rhinitis, Common cold (7-day average)",TRUE,NA,NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 65% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,google-symptoms +google-symptoms,s03_raw_search,FALSE,s03_raw_search,FALSE,"Searches for: Fever, Hyperthermia, Chills, Shivering, Low grade fever",TRUE,"The average relative frequency of searches for Fever, Hyperthermia, Chills, Shivering, and Low grade fever, in arbitrary units that are normalized against overall search patterns within each region.","The average relative frequency of searches for Fever, Hyperthermia, Chills, Shivering, and Low grade fever, in arbitrary units that are normalized against overall search patterns within each region. + +The symptoms in this set showed positive correlation with cases, especially after Omicron was declared a variant of concern by the WHO.",Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-14,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 50% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-symptoms.html,google-symptoms +google-symptoms,s03_raw_search,TRUE,s03_smoothed_search,FALSE,"Searches for: Fever, Hyperthermia, Chills, Shivering, Low grade fever (7-day average)",TRUE,NA,NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 50% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,google-symptoms +google-symptoms,s04_raw_search,FALSE,s04_raw_search,FALSE,"Searches for: Shortness of breath, Wheeze, Croup, Pneumonia, Asthma, Crackles, Acute bronchitis, Bronchitis",TRUE,"The average relative frequency of searches for Shortness of breath, Wheeze, Croup, Pneumonia, Asthma, Crackles, Acute bronchitis, and Bronchitis, in arbitrary units that are normalized against overall search patterns within each region.","The average relative frequency of searches for Shortness of breath, Wheeze, Croup, Pneumonia, Asthma, Crackles, Acute bronchitis, and Bronchitis, in arbitrary units that are normalized against overall search patterns within each region. + +The symptoms in this set showed positive correlation with cases, especially after Omicron was declared a variant of concern by the WHO.",Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-14,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 30% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-symptoms.html,google-symptoms +google-symptoms,s04_raw_search,TRUE,s04_smoothed_search,FALSE,"Searches for: Shortness of breath, Wheeze, Croup, Pneumonia, Asthma, Crackles, Acute bronchitis, Bronchitis (7-day average)",TRUE,NA,NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 30% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,google-symptoms +google-symptoms,s05_raw_search,FALSE,s05_raw_search,FALSE,"Searches for: Anosmia, Dysgeusia, Ageusia",TRUE,"The average relative frequency of searches for Anosmia, Dysgeusia, and Ageusia, in arbitrary units that are normalized against overall search patterns within each region.","The average relative frequency of searches for Anosmia, Dysgeusia, and Ageusia, in arbitrary units that are normalized against overall search patterns within each region. + +The symptoms in this set showed positive correlation with cases, especially after Omicron was declared a variant of concern by the WHO.",Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-14,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 3-4% of counties. Data is available for about 90% of states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-symptoms.html,google-symptoms +google-symptoms,s05_raw_search,TRUE,s05_smoothed_search,FALSE,"Searches for: Anosmia, Dysgeusia, Ageusia (7-day average)",TRUE,NA,NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 3-4% of counties. Data is available for about 90% of states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,google-symptoms +google-symptoms,s06_raw_search,FALSE,s06_raw_search,FALSE,"Searches for: Laryngitis, Sore throat, Throat irritation",TRUE,"The average relative frequency of searches for Laryngitis, Sore throat, and Throat irritation, in arbitrary units that are normalized against overall search patterns within each region.","The average relative frequency of searches for Laryngitis, Sore throat, and Throat irritation, in arbitrary units that are normalized against overall search patterns within each region. + +The symptoms in this set showed positive correlation with cases, especially after Omicron was declared a variant of concern by the WHO.",Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-14,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 30% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-symptoms.html,google-symptoms +google-symptoms,s06_raw_search,TRUE,s06_smoothed_search,FALSE,"Searches for: Laryngitis, Sore throat, Throat irritation (7-day average)",TRUE,NA,NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 30% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,google-symptoms +google-symptoms,scontrol_raw_search,FALSE,scontrol_raw_search,FALSE,"Searches for: Type 2 diabetes, Urinary tract infection, Hair loss, Candidiasis, Weight gain",TRUE,"The average relative frequency of searches for Type 2 diabetes, Urinary tract infection, Hair loss, Candidiasis, and Weight gain, in arbitrary units that are normalized against overall search patterns within each region.","The average relative frequency of searches for Type 2 diabetes, Urinary tract infection, Hair loss, Candidiasis, and Weight gain, in arbitrary units that are normalized against overall search patterns within each region. + +The symptoms in this set are not COVID-19 related. This signal is intended to be used as a negative control.",Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-14,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 45% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-symptoms.html,google-symptoms +google-symptoms,scontrol_raw_search,TRUE,scontrol_smoothed_search,FALSE,"Searches for: Type 2 diabetes, Urinary tract infection, Hair loss, Candidiasis, Weight gain (7-day average)",TRUE,NA,NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 45% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,neutral,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,google-symptoms +google-symptoms,sum_anosmia_ageusia_raw_search,FALSE,sum_anosmia_ageusia_raw_search,FALSE,Sum Anosmia Ageusia Searches,FALSE,"The sum of Google search volume for anosmia and ageusia related searches, in arbitrary units that are normalized for overall search users",NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-13,"Start dates vary by geo: county 2020-02-13, hhs 2020-02-14, hrr 2020-02-13, msa 2020-02-13, nation 2020-02-14, state 2020-02-13",2022-01-20,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 3-4% of counties. Data is available for about 85% of states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-symptoms.html,google-symptoms +google-symptoms,sum_anosmia_ageusia_raw_search,TRUE,sum_anosmia_ageusia_smoothed_search,TRUE,Sum Anosmia Ageusia Searches (7-day average),FALSE,NA,NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,2022-01-20,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 3-4% of counties. Data is available for about 85% of states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,google-symptoms +hhs,confirmed_admissions_covid_1d,FALSE,confirmed_admissions_covid_1d,FALSE,Confirmed COVID-19 Admissions per day,TRUE,Sum of adult and pediatric confirmed COVID-19 hospital admissions occurring each day.,The U.S. Department of Health & Human Services (HHS) receives reports from hospital systems on their capacity and admissions. This signal reports the number of adult and pediatric hospital admissions with confirmed COVID-19 occurring each day,U.S. Department of Health & Human Services,covid,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2019-12-31,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/hhs.html,hhs +hhs,confirmed_admissions_covid_1d,TRUE,confirmed_admissions_covid_1d_prop,FALSE,Confirmed COVID-19 Admissions per day (per 100k people),TRUE,NA,NA,U.S. Department of Health & Human Services,covid,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2019-12-31,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,NA,hhs +hhs,confirmed_admissions_covid_1d,NA,confirmed_admissions_covid_1d_7dav,TRUE,Confirmed COVID-19 Admissions per day (7-day average),TRUE,NA,NA,U.S. Department of Health & Human Services,covid,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2020-01-06,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,count,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,NA,hhs +hhs,confirmed_admissions_covid_1d,NA,confirmed_admissions_covid_1d_prop_7dav,FALSE,"Confirmed COVID-19 Admissions per day (7-day average, per 100k people)",TRUE,NA,NA,U.S. Department of Health & Human Services,covid,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2020-01-06,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,per100k,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,NA,hhs +hhs,confirmed_admissions_influenza_1d,NA,confirmed_admissions_influenza_1d,FALSE,Confirmed Influenza Admissions per day,TRUE,All confirmed influenza hospital admissions occurring each day.,The U.S. Department of Health & Human Services (HHS) receives reports from hospital systems on their capacity and admissions. This signal reports the number of adult and pediatric hospital admissions with confirmed influenza occurring each day,U.S. Department of Health & Human Services,flu,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2019-12-31,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/hhs.html,hhs +hhs,confirmed_admissions_influenza_1d,NA,confirmed_admissions_influenza_1d_7dav,FALSE,Confirmed Influenza Admissions per day (7-day average),TRUE,NA,NA,U.S. Department of Health & Human Services,flu,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2020-01-06,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,count,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,NA,hhs +hhs,confirmed_admissions_influenza_1d,NA,confirmed_admissions_influenza_1d_prop,FALSE,Confirmed Influenza Admissions per day (per 100k people),TRUE,NA,NA,U.S. Department of Health & Human Services,flu,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2019-12-31,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,NA,hhs +hhs,confirmed_admissions_influenza_1d,NA,confirmed_admissions_influenza_1d_prop_7dav,FALSE,"Confirmed Influenza Admissions per day (7-day average, per 100k people)",TRUE,NA,NA,U.S. Department of Health & Human Services,flu,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2020-01-06,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,per100k,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,NA,hhs +hhs,sum_confirmed_suspected_admissions_covid_1d,FALSE,sum_confirmed_suspected_admissions_covid_1d,FALSE,Confirmed and Suspected COVID-19 Admissions per day,TRUE,Sum of adult and pediatric confirmed and suspected COVID-19 hospital admissions occurring each day.,The U.S. Department of Health & Human Services (HHS) receives reports from hospital systems on their capacity and admissions. This signal reports the number of adult and pediatric hospital admissions with suspected COVID-19 occurring each day,U.S. Department of Health & Human Services,covid,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2019-12-31,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/hhs.html,hhs +hhs,sum_confirmed_suspected_admissions_covid_1d,TRUE,sum_confirmed_suspected_admissions_covid_1d_prop,FALSE,Confirmed and Suspected COVID-19 Admissions per day (per 100k people),TRUE,NA,NA,U.S. Department of Health & Human Services,covid,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2019-12-31,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,NA,hhs +hhs,sum_confirmed_suspected_admissions_covid_1d,NA,sum_confirmed_suspected_admissions_covid_1d_7dav,TRUE,Confirmed and Suspected COVID-19 Admissions per day (7-day average),TRUE,NA,NA,U.S. Department of Health & Human Services,covid,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2020-01-06,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,count,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,NA,hhs +hhs,sum_confirmed_suspected_admissions_covid_1d,NA,sum_confirmed_suspected_admissions_covid_1d_prop_7dav,FALSE,"Confirmed and Suspected COVID-19 Admissions per day (7-day average, per 100k people)",TRUE,NA,NA,U.S. Department of Health & Human Services,covid,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2020-01-06,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,per100k,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,NA,hhs +hospital-admissions,smoothed_covid19,FALSE,smoothed_covid19,FALSE,COVID-19 Admissions (EMR and Claims),FALSE,Estimated percentage of new hospital admissions with COVID-associated diagnoses,"Estimated percentage of new hospital admissions with COVID-associated diagnoses, based on counts of electronic medical records and claims from health system partners, smoothed in time using a Gaussian linear smoother. + +Discontinued October 1, 2020.",Hospital Admissions From Claims,covid,Inpatient insurance claims,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi)",2020-02-01,NA,2020-09-27,NA,day,Date,daily,3-4 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 7-13 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 57 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Optum network,None,hospitalized,Discarded if over a given 7-day period an estimate is computed with 500 or fewer observations,Data is available for about 35% of counties Data is available for all states.,Percentage,percent,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/hospital-admissions.html,hospital-admissions +hospital-admissions,smoothed_covid19,TRUE,smoothed_adj_covid19,FALSE,COVID-19 Admissions (EMR and Claims) (Day-adjusted),FALSE,NA,"{base_short_description}, based on counts of electronic medical records and claims from health system partners, smoothed in time using a Gaussian linear smoother, and adjusted to reduce day-of-week effects. + +Discontinued October 1, 2020.",Hospital Admissions From Claims,covid,Inpatient insurance claims,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi)",2020-02-01,NA,2020-09-27,NA,day,Date,daily,3-4 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 7-13 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 57 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Optum network,None,hospitalized,Discarded if over a given 7-day period an estimate is computed with 500 or fewer observations,Data is available for about 35% of counties Data is available for all states.,Percentage,percent,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf,NA,hospital-admissions +hospital-admissions,smoothed_covid19_from_claims,FALSE,smoothed_covid19_from_claims,FALSE,COVID-19 Admissions (Claims),TRUE,Estimated percentage of new hospital admissions with COVID-associated diagnoses,"Estimated percentage of new hospital admissions with COVID-associated diagnoses, based on counts of claims from health system partners, smoothed in time using a Gaussian linear smoother.",Hospital Admissions From Claims,covid,Inpatient insurance claims,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,Ongoing,NA,day,Date,daily,3-4 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 7-13 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 57 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Optum network,None,hospitalized,Discarded if over a given 7-day period an estimate is computed with 500 or fewer observations,Data is available for about 35% of counties Data is available for all states.,Percentage,percent,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/hospital-admissions.html,hospital-admissions +hospital-admissions,smoothed_covid19_from_claims,TRUE,smoothed_adj_covid19_from_claims,FALSE,COVID-19 Admissions (Claims) (Day-adjusted),TRUE,NA,"{base_short_description}, based on counts of claims from health system partners, smoothed in time using a Gaussian linear smoother, and adjusted to reduce day-of-week effects.",Hospital Admissions From Claims,covid,Inpatient insurance claims,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,Ongoing,NA,day,Date,daily,3-4 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 7-13 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 57 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Optum network,None,hospitalized,Discarded if over a given 7-day period an estimate is computed with 500 or fewer observations,Data is available for about 35% of counties Data is available for all states.,Percentage,percent,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf,NA,hospital-admissions +indicator-combination-cases-deaths,confirmed_cumulative_num,FALSE,confirmed_cumulative_num,FALSE,Confirmed COVID Cases (Cumulative),FALSE,Cumulative confirmed COVID cases,Confirmed COVID-19 cases as reported by [USAFacts](https://usafacts.org/visualizations/coronavirus-covid-19-spread-map/) and [JHU-CSSE](https://github.com/CSSEGISandData/COVID-19),Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,ascertained (case),None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,cases_testing,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/indicator-combination-inactive.html#compositional-signals-confirmed-cases-and-deaths,indicator-combination +indicator-combination-cases-deaths,confirmed_cumulative_num,TRUE,confirmed_7dav_incidence_num,TRUE,"Confirmed COVID Cases (Daily new, 7-day average)",FALSE,"Daily new confirmed COVID cases, 7-day average",NA,Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,ascertained (case),None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,cases_testing,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",NA,indicator-combination +indicator-combination-cases-deaths,confirmed_cumulative_num,TRUE,confirmed_7dav_incidence_prop,FALSE,"Confirmed COVID Cases (Daily new, 7-day average, per 100k people)",FALSE,"Daily new confirmed COVID cases, 7-day average, per 100k people",NA,Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,ascertained (case),None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,cases_testing,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",NA,indicator-combination +indicator-combination-cases-deaths,confirmed_cumulative_num,TRUE,confirmed_cumulative_prop,FALSE,"Confirmed COVID Cases (Cumulative, per 100k people)",FALSE,"Cumulative confirmed COVID cases, per 100k people",NA,Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,ascertained (case),None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,cases_testing,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",NA,indicator-combination +indicator-combination-cases-deaths,confirmed_cumulative_num,TRUE,confirmed_incidence_num,TRUE,Confirmed COVID Cases (Daily new),FALSE,Daily new confirmed COVID cases,NA,Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,ascertained (case),None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,cases_testing,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",NA,indicator-combination +indicator-combination-cases-deaths,confirmed_cumulative_num,TRUE,confirmed_incidence_prop,FALSE,"Confirmed COVID Cases (Daily new, per 100k people)",FALSE,"Daily new confirmed COVID cases, per 100k people",NA,Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,ascertained (case),None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,cases_testing,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",NA,indicator-combination +indicator-combination-cases-deaths,deaths_cumulative_num,FALSE,deaths_cumulative_num,FALSE,Confirmed COVID Deaths (Cumulative),FALSE,Cumulative confirmed COVID deaths,Confirmed COVID-19 deaths as reported by [USAFacts](https://usafacts.org/visualizations/coronavirus-covid-19-spread-map/) and [JHU-CSSE](https://github.com/CSSEGISandData/COVID-19),Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,dead,None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,cases_testing,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/indicator-combination-inactive.html#compositional-signals-confirmed-cases-and-deaths,indicator-combination +indicator-combination-cases-deaths,deaths_cumulative_num,TRUE,deaths_7dav_incidence_num,TRUE,"Confirmed COVID Deaths (Daily new, 7-day average)",FALSE,"Daily new confirmed COVID deaths, 7-day average",NA,Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,dead,None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,cases_testing,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",NA,indicator-combination +indicator-combination-cases-deaths,deaths_cumulative_num,TRUE,deaths_7dav_incidence_prop,FALSE,"Confirmed COVID Deaths (Daily new, 7-day average, per 100k people)",FALSE,"Daily new confirmed COVID deaths, 7-day average, per 100k people",NA,Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,dead,None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,cases_testing,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",NA,indicator-combination +indicator-combination-cases-deaths,deaths_cumulative_num,TRUE,deaths_cumulative_prop,FALSE,"Confirmed COVID Deaths (Cumulative, per 100k people)",FALSE,"Cumulative confirmed COVID deaths, per 100k people",NA,Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,dead,None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,cases_testing,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",NA,indicator-combination +indicator-combination-cases-deaths,deaths_cumulative_num,TRUE,deaths_incidence_num,TRUE,Confirmed COVID Deaths (Daily new),FALSE,Daily new confirmed COVID deaths,NA,Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,dead,None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,cases_testing,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",NA,indicator-combination +indicator-combination-cases-deaths,deaths_cumulative_num,TRUE,deaths_incidence_prop,FALSE,"Confirmed COVID Deaths (Daily new, per 100k people)",FALSE,"Daily new confirmed COVID deaths, per 100k people",NA,Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,dead,None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,cases_testing,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",NA,indicator-combination +indicator-combination-nmf,nmf_day_doc_fbc_fbs_ght,nmf_day_doc_fbc_fbs_ght,nmf_day_doc_fbc_fbs_ght,FALSE,NMF Combination (with community symptoms),FALSE,Rank-1 NMF approximation to reconstruct 4 other signals.,"This signal uses a rank-1 approximation, from a nonnegative matrix factorization approach, to identify an underlying signal that best reconstructs the Doctor Visits (smoothed_adj_cli), Facebook Symptoms surveys (smoothed_cli), Facebook Symptoms in Community surveys (smoothed_hh_cmnty_cli), and Search Trends (smoothed_search) indicators. It does not include official reports (cases and deaths from the jhu-csse source). Higher values of the combined signal correspond to higher values of the other indicators, but the scale (units) of the combination is arbitrary. Note that the Search Trends source is not available at the county level, so county values of this signal do not use it. + +Discontinued March 17, 2021.",Statistical Combination (NMF),covid,NA,USA,"county (by Delphi), msa (by Delphi), state (by Delphi)",2020-04-15,NA,2021-03-16,"End dates vary by geo: county 2021-03-16, msa 2021-03-16, state 2021-03-15",day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,infected,None. However underlying signals may perform their own censoring,Data is available for about 80% of counties Data is available for all states and some territories.,Value,raw,early,bad,FALSE,FALSE,FALSE,TRUE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/indicator-combination-inactive.html#statistical-combination-signals,indicator-combination +indicator-combination-nmf,nmf_day_doc_fbs_ght,nmf_day_doc_fbs_ght,nmf_day_doc_fbs_ght,FALSE,NMF Combination (without community symptoms),FALSE,Rank-1 NMF approximation to reconstruct 3 other signals.,"This signal uses a rank-1 approximation, from a nonnegative matrix factorization approach, to identify an underlying signal that best reconstructs the Doctor Visits (doctor-visits:smoothed_cli), Facebook Symptoms surveys (fb-surveys:smoothed_cli), and Search Trends (ght:smoothed_search) indicators. It does not include official reports (cases and deaths from the jhu-csse source). Higher values of the combined signal correspond to higher values of the other indicators, but the scale (units) of the combination is arbitrary. Note that the Search Trends source is not available at the county level, so county values of this signal do not use it. + +Discontinued May 28, 2020.",Statistical Combination (NMF),covid,NA,USA,"county (by Delphi), msa (by Delphi), state (by Delphi)",2020-04-06,NA,2020-05-26,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,infected,None. However underlying signals may perform their own censoring,Data is available for about 70% of counties Data is available for all states and some territories.,Value,raw,early,bad,FALSE,FALSE,FALSE,TRUE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/indicator-combination-inactive.html#statistical-combination-signals,indicator-combination +jhu-csse,confirmed_cumulative_num,FALSE,confirmed_cumulative_num,FALSE,Confirmed COVID Cases (Cumulative),FALSE,Cumulative confirmed COVID cases,Confirmed COVID-19 cases as reported by [JHU-CSSE](https://github.com/CSSEGISandData/COVID-19),Johns Hopkins University,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-22,"Start dates vary by geo: county 2020-01-22, hhs 2020-02-20, hrr 2020-01-22, msa 2020-01-22, nation 2020-02-20, state 2020-01-22",2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which + Delphi diffs to compute incidence. Raw cumulative figures are sometimes + corrected by adjusting the reported value for a single day, but revisions + do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,cases_testing,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/jhu-csse.html,jhu-csse +jhu-csse,confirmed_cumulative_num,TRUE,confirmed_7dav_incidence_num,TRUE,"Confirmed COVID Cases (Daily new, 7-day average)",FALSE,"Daily new confirmed COVID cases, 7-day average",NA,Johns Hopkins University,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which + Delphi diffs to compute incidence. Raw cumulative figures are sometimes + corrected by adjusting the reported value for a single day, but revisions + do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,cases_testing,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,jhu-csse +jhu-csse,confirmed_cumulative_num,TRUE,confirmed_7dav_incidence_prop,FALSE,"Confirmed COVID Cases (Daily new, 7-day average, per 100k people)",FALSE,"Daily new confirmed COVID cases, 7-day average, per 100k people",NA,Johns Hopkins University,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which + Delphi diffs to compute incidence. Raw cumulative figures are sometimes + corrected by adjusting the reported value for a single day, but revisions + do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,cases_testing,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,jhu-csse +jhu-csse,confirmed_cumulative_num,TRUE,confirmed_cumulative_prop,FALSE,"Confirmed COVID Cases (Cumulative, per 100k people)",FALSE,"Cumulative confirmed COVID cases, per 100k people",NA,Johns Hopkins University,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-22,"Start dates vary by geo: county 2020-01-22, hhs 2020-02-20, hrr 2020-01-22, msa 2020-01-22, nation 2020-02-20, state 2020-01-22",2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which + Delphi diffs to compute incidence. Raw cumulative figures are sometimes + corrected by adjusting the reported value for a single day, but revisions + do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,cases_testing,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,jhu-csse +jhu-csse,confirmed_cumulative_num,TRUE,confirmed_incidence_num,TRUE,Confirmed COVID Cases (Daily new),FALSE,Daily new confirmed COVID cases,NA,Johns Hopkins University,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-22,"Start dates vary by geo: county 2020-01-22, hhs 2020-02-20, hrr 2020-01-22, msa 2020-01-22, nation 2020-02-20, state 2020-01-22",2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which + Delphi diffs to compute incidence. Raw cumulative figures are sometimes + corrected by adjusting the reported value for a single day, but revisions + do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,cases_testing,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,jhu-csse +jhu-csse,confirmed_cumulative_num,TRUE,confirmed_incidence_prop,FALSE,"Confirmed COVID Cases (Daily new, per 100k people)",FALSE,"Daily new confirmed COVID cases, per 100k people",NA,Johns Hopkins University,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-22,"Start dates vary by geo: county 2020-01-22, hhs 2020-02-20, hrr 2020-01-22, msa 2020-01-22, nation 2020-02-20, state 2020-01-22",2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which + Delphi diffs to compute incidence. Raw cumulative figures are sometimes + corrected by adjusting the reported value for a single day, but revisions + do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,cases_testing,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,jhu-csse +jhu-csse,deaths_cumulative_num,FALSE,deaths_cumulative_num,FALSE,Confirmed COVID Deaths (Cumulative),FALSE,Cumulative confirmed COVID deaths,Confirmed COVID-19 deaths as reported by [JHU-CSSE](https://github.com/CSSEGISandData/COVID-19),Johns Hopkins University,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-22,"Start dates vary by geo: county 2020-01-22, hhs 2020-02-20, hrr 2020-01-22, msa 2020-01-22, nation 2020-02-20, state 2020-01-22",2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which + Delphi diffs to compute incidence. Raw cumulative figures are sometimes + corrected by adjusting the reported value for a single day, but revisions + do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/jhu-csse.html,jhu-csse +jhu-csse,deaths_cumulative_num,TRUE,deaths_7dav_incidence_num,TRUE,"Confirmed COVID Deaths (Daily new, 7-day average)",FALSE,"Daily new confirmed COVID deaths, 7-day average",NA,Johns Hopkins University,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which + Delphi diffs to compute incidence. Raw cumulative figures are sometimes + corrected by adjusting the reported value for a single day, but revisions + do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,jhu-csse +jhu-csse,deaths_cumulative_num,TRUE,deaths_7dav_incidence_prop,FALSE,"Confirmed COVID Deaths (Daily new, 7-day average, per 100k people)",FALSE,"Daily new confirmed COVID deaths, 7-day average, per 100k people",NA,Johns Hopkins University,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which + Delphi diffs to compute incidence. Raw cumulative figures are sometimes + corrected by adjusting the reported value for a single day, but revisions + do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,jhu-csse +jhu-csse,deaths_cumulative_num,TRUE,deaths_cumulative_prop,FALSE,"Confirmed COVID Deaths (Cumulative, per 100k people)",FALSE,"Cumulative confirmed COVID deaths, per 100k people",NA,Johns Hopkins University,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-22,"Start dates vary by geo: county 2020-01-22, hhs 2020-02-20, hrr 2020-01-22, msa 2020-01-22, nation 2020-02-20, state 2020-01-22",2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which + Delphi diffs to compute incidence. Raw cumulative figures are sometimes + corrected by adjusting the reported value for a single day, but revisions + do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,jhu-csse +jhu-csse,deaths_cumulative_num,TRUE,deaths_incidence_num,TRUE,Confirmed COVID Deaths (Daily new),FALSE,Daily new confirmed COVID deaths,NA,Johns Hopkins University,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-22,"Start dates vary by geo: county 2020-01-22, hhs 2020-02-20, hrr 2020-01-22, msa 2020-01-22, nation 2020-02-20, state 2020-01-22",2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which + Delphi diffs to compute incidence. Raw cumulative figures are sometimes + corrected by adjusting the reported value for a single day, but revisions + do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,jhu-csse +jhu-csse,deaths_cumulative_num,TRUE,deaths_incidence_prop,FALSE,"Confirmed COVID Deaths (Daily new, per 100k people)",FALSE,"Daily new confirmed COVID deaths, per 100k people",NA,Johns Hopkins University,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-22,"Start dates vary by geo: county 2020-01-22, hhs 2020-02-20, hrr 2020-01-22, msa 2020-01-22, nation 2020-02-20, state 2020-01-22",2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which + Delphi diffs to compute incidence. Raw cumulative figures are sometimes + corrected by adjusting the reported value for a single day, but revisions + do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,jhu-csse +nchs-mortality,deaths_allcause_incidence_num,FALSE,deaths_allcause_incidence_num,FALSE,All Causes Deaths (Weekly new),TRUE,Number of weekly new deaths from all causes,"Number of weekly new deaths from all causes. + +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,n/a,Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html,nchs-mortality +nchs-mortality,deaths_allcause_incidence_num,TRUE,deaths_allcause_incidence_prop,FALSE,"All Causes Deaths (Weekly new, per 100k people)",TRUE,"Number of weekly new deaths from all causes, per 100k people","Number of weekly new deaths from all causes, per 100k people. + +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,n/a,Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,NA,nchs-mortality +nchs-mortality,deaths_covid_and_pneumonia_notflu_incidence_num,FALSE,deaths_covid_and_pneumonia_notflu_incidence_num,FALSE,COVID and Pneumonia excl. Influenza Deaths (Weekly new),TRUE,"Number of weekly new deaths involving COVID-19 and Pneumonia, excluding Influenza","Number of weekly new deaths involving COVID-19 and Pneumonia, excluding Influenza . + +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,"covid, pneumonia",Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html,nchs-mortality +nchs-mortality,deaths_covid_and_pneumonia_notflu_incidence_num,TRUE,deaths_covid_and_pneumonia_notflu_incidence_prop,FALSE,"COVID and Pneumonia excl. Influenza Deaths (Weekly new, per 100k people)",TRUE,"Number of weekly new deaths involving COVID-19 and Pneumonia, excluding Influenza, per 100k people","Number of weekly new deaths involving COVID-19 and Pneumonia, excluding Influenza, per 100k people. + +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,covid,Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,NA,nchs-mortality +nchs-mortality,deaths_covid_incidence_num,FALSE,deaths_covid_incidence_num,FALSE,Confirmed or Presumed COVID Deaths (Weekly new),TRUE,Number of weekly new deaths with confirmed or presumed COVID-19,"Number of weekly new deaths with confirmed or presumed COVID-19 . + +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,covid,Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html,nchs-mortality +nchs-mortality,deaths_covid_incidence_num,TRUE,deaths_covid_incidence_prop,FALSE,"Confirmed or Presumed COVID Deaths (Weekly new, per 100k people)",TRUE,"Number of weekly new deaths with confirmed or presumed COVID-19, per 100k people","Number of weekly new deaths with confirmed or presumed COVID-19, per 100k people. + +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,covid,Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,NA,nchs-mortality +nchs-mortality,deaths_flu_incidence_num,FALSE,deaths_flu_incidence_num,FALSE,Influenza Deaths (Weekly new),TRUE,"Number of weekly new deaths involving Influenza and at least one of (Pneumonia, COVID-19)","Number of weekly new deaths involving Influenza and at least one of (Pneumonia, COVID-19). + +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,flu,Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html,nchs-mortality +nchs-mortality,deaths_flu_incidence_num,TRUE,deaths_flu_incidence_prop,FALSE,"Influenza Deaths (Weekly new, per 100k people)",TRUE,"Number of weekly new deaths involving Influenza and at least one of (Pneumonia, COVID-19), per 100k people","Number of weekly new deaths involving Influenza and at least one of (Pneumonia, COVID-19), per 100k people. + +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,flu,Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,NA,nchs-mortality +nchs-mortality,deaths_percent_of_expected,FALSE,deaths_percent_of_expected,FALSE,Percentage of Expected Deaths,TRUE,Weekly new deaths for all causes in 2020 as a percentage of the average number across the same week in 2017-2019.,"Weekly new deaths for all causes in 2020 as a percentage of the average number across the same week in 2017-2019.. + +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,n/a,Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Percentage,percent,late,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html,nchs-mortality +nchs-mortality,deaths_pneumonia_notflu_incidence_num,FALSE,deaths_pneumonia_notflu_incidence_num,FALSE,Pneumonia excl. Influenza Deaths (Weekly new),TRUE,"Number of weekly new deaths involving Pneumonia, excluding Influenza deaths","Number of weekly new deaths involving Pneumonia, excluding Influenza deaths . + +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,pneumonia,Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html,nchs-mortality +nchs-mortality,deaths_pneumonia_notflu_incidence_num,TRUE,deaths_pneumonia_notflu_incidence_prop,FALSE,"Pneumonia excl. Influenza Deaths (Weekly new, per 100k people)",TRUE,"Number of weekly new deaths involving Pneumonia, excluding Influenza deaths, per 100k people","Number of weekly new deaths involving Pneumonia, excluding Influenza deaths, per 100k people. + +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,pneumonia,Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,NA,nchs-mortality +nchs-mortality,deaths_pneumonia_or_flu_or_covid_incidence_num,FALSE,deaths_pneumonia_or_flu_or_covid_incidence_num,FALSE,"COVID, Pneumonia or Influenza Deaths (Weekly new)",TRUE,"Number of weekly new deaths involving Pneumonia, Influenza, or COVID-19","Number of weekly new deaths involving Pneumonia, Influenza, or COVID-19 . + +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,"pneumonia, flu, covid",Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html,nchs-mortality +nchs-mortality,deaths_pneumonia_or_flu_or_covid_incidence_num,TRUE,deaths_pneumonia_or_flu_or_covid_incidence_prop,FALSE,"COVID, Pneumonia or Influenza Deaths (Weekly new, per 100k people)",TRUE,"Number of weekly new deaths involving Pneumonia, Influenza, or COVID-19, per 100k people","Number of weekly new deaths involving Pneumonia, Influenza, or COVID-19, per 100k people. + +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,"pneumonia, flu, covid",Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,NA,nchs-mortality +quidel-covid-ag,covid_ag_raw_pct_positive,FALSE,covid_ag_raw_pct_positive,FALSE,COVID-19 Antigen Tests: Percent Positive,TRUE,Percentage of antigen tests that were positive for COVID-19,"When a patient (whether at a doctor's office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19.",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests),quidel +quidel-covid-ag,covid_ag_raw_pct_positive,TRUE,covid_ag_smoothed_pct_positive,FALSE,COVID-19 Antigen Tests: Percent Positive (7-day average),TRUE,NA,NA,Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,NA,quidel +quidel-covid-ag,covid_ag_raw_pct_positive_age_0_17,FALSE,covid_ag_raw_pct_positive_age_0_17,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 0-17",TRUE,Percentage of antigen tests that were positive for COVID-19 among people ages 0-17,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 0-17",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests),quidel +quidel-covid-ag,covid_ag_raw_pct_positive_age_0_17,TRUE,covid_ag_smoothed_pct_positive_age_0_17,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 0-17 (Smoothed)",TRUE,NA,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 0-17, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,NA,quidel +quidel-covid-ag,covid_ag_raw_pct_positive_age_0_4,FALSE,covid_ag_raw_pct_positive_age_0_4,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 0-4",TRUE,Percentage of antigen tests that were positive for COVID-19 among people ages 0-4,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 0-4",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,"End dates vary by geo: county 2024-05-03, hhs 2024-05-03, hrr 2024-04-27, msa 2024-04-27, nation 2024-05-03, state 2024-05-03",day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests),quidel +quidel-covid-ag,covid_ag_raw_pct_positive_age_0_4,TRUE,covid_ag_smoothed_pct_positive_age_0_4,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 0-4 (Smoothed)",TRUE,NA,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 0-4, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,NA,quidel +quidel-covid-ag,covid_ag_raw_pct_positive_age_18_49,FALSE,covid_ag_raw_pct_positive_age_18_49,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 18-49",TRUE,Percentage of antigen tests that were positive for COVID-19 among people ages 18-49,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 18-49",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,"End dates vary by geo: county 2024-05-02, hhs 2024-05-02, hrr 2024-05-01, msa 2024-05-01, nation 2024-05-03, state 2024-05-02",day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests),quidel +quidel-covid-ag,covid_ag_raw_pct_positive_age_18_49,TRUE,covid_ag_smoothed_pct_positive_age_18_49,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 18-49 (Smoothed)",TRUE,NA,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 18-49, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,NA,quidel +quidel-covid-ag,covid_ag_raw_pct_positive_age_5_17,FALSE,covid_ag_raw_pct_positive_age_5_17,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 5-17",TRUE,Percentage of antigen tests that were positive for COVID-19 among people ages 5-17,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 5-17",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests),quidel +quidel-covid-ag,covid_ag_raw_pct_positive_age_5_17,TRUE,covid_ag_smoothed_pct_positive_age_5_17,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 5-17 (Smoothed)",TRUE,NA,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 5-17, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,NA,quidel +quidel-covid-ag,covid_ag_raw_pct_positive_age_50_64,FALSE,covid_ag_raw_pct_positive_age_50_64,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 50-64",TRUE,Percentage of antigen tests that were positive for COVID-19 among people ages 50-64,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 50-64",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,"End dates vary by geo: county 2024-05-01, hhs 2024-05-01, hrr 2024-05-01, msa 2024-05-01, nation 2024-05-03, state 2024-05-01",day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests),quidel +quidel-covid-ag,covid_ag_raw_pct_positive_age_50_64,TRUE,covid_ag_smoothed_pct_positive_age_50_64,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 50-64 (Smoothed)",TRUE,NA,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 50-64, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,NA,quidel +quidel-covid-ag,covid_ag_raw_pct_positive_age_65plus,FALSE,covid_ag_raw_pct_positive_age_65plus,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 65+",TRUE,Percentage of antigen tests that were positive for COVID-19 among people age 65 and above,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 65 and above",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,"End dates vary by geo: county 2024-04-19, hhs 2024-05-01, hrr 2024-04-19, msa 2024-04-19, nation 2024-05-03, state 2024-04-19",day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests),quidel +quidel-covid-ag,covid_ag_raw_pct_positive_age_65plus,TRUE,covid_ag_smoothed_pct_positive_age_65plus,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 65+ (Smoothed)",TRUE,NA,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 65 and above, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,NA,quidel +quidel-flu,raw_pct_negative,FALSE,raw_pct_negative,FALSE,Flu Tests: Percent Negative,FALSE,"The percentage of flu tests that are negative, suggesting the patient's illness has another cause, possibly COVID-19","The percentage of flu tests that are negative, suggesting the patient's illness has another cause, possibly COVID-19 . + +Discontinued May 19, 2020.",Quidel Inc. (Flu),flu,Testing,USA,"msa (by Delphi), state (by Delphi)",2020-01-31,NA,2020-05-10,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,None,population,"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,late,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#flu-tests,quidel +quidel-flu,raw_pct_negative,TRUE,smoothed_pct_negative,FALSE,Flu Tests: Percent Negative (7-day average),FALSE,NA,NA,Quidel Inc. (Flu),flu,Testing,USA,"msa (by Delphi), state (by Delphi)",2020-01-31,NA,2020-05-10,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,None,population,"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,late,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,NA,quidel +quidel-flu,raw_tests_per_device,FALSE,raw_tests_per_device,FALSE,Flu Tests: Tests Per Device,FALSE,The average number of flu tests conducted by each testing device; measures volume of testing,"The average number of flu tests conducted by each testing device; measures volume of testing . + +Discontinued May 19, 2020.",Quidel Inc. (Flu),flu,Testing,USA,"msa (by Delphi), state (by Delphi)",2020-01-31,NA,2020-05-10,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,None,population,"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Number of Tests,count,late,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#flu-tests,quidel +quidel-flu,raw_tests_per_device,TRUE,smoothed_tests_per_device,FALSE,Flu Tests: Tests Per Device (7-day average),FALSE,NA,NA,Quidel Inc. (Flu),flu,Testing,USA,"msa (by Delphi), state (by Delphi)",2020-01-31,NA,2020-05-10,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,None,population,"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Number of Tests,count,late,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,NA,quidel +safegraph-daily,completely_home_prop,FALSE,completely_home_prop,FALSE,Completely Home,FALSE,The fraction of mobile devices that did not leave the immediate area of their home,"The fraction of mobile devices that did not leave the immediate area of their home. This is SafeGraph’s completely_home_device_count / device_count. + +Discontinued April 19th, 2021.",SafeGraph (Daily),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-12-01, hrr 2019-01-01, msa 2019-01-01, nation 2020-12-01, state 2019-01-01",2021-04-16,NA,day,Date,daily,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,public,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph +safegraph-daily,completely_home_prop,TRUE,completely_home_prop_7dav,FALSE,Completely Home (7-day average),FALSE,NA,NA,SafeGraph (Daily),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-12-01, hrr 2019-01-01, msa 2019-01-01, nation 2020-12-01, state 2019-01-01",2021-04-16,NA,day,Date,daily,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,public,neutral,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph +safegraph-daily,full_time_work_prop,FALSE,full_time_work_prop,FALSE,Full Time Work/School,FALSE,The fraction of mobile devices that spent more than 6 hours at one location other than their home during the daytime,"The fraction of mobile devices that spent more than 6 hours at one location other than their home during the daytime. This is SafeGraph’s full_time_work_behavior_devices / device_count. + +Discontinued April 19th, 2021.",SafeGraph (Daily),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-12-01, hrr 2019-01-01, msa 2019-01-01, nation 2020-12-01, state 2019-01-01",2021-04-16,NA,day,Date,daily,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,public,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph +safegraph-daily,full_time_work_prop,TRUE,full_time_work_prop_7dav,FALSE,Full Time Work/School (7-day average),FALSE,NA,NA,SafeGraph (Daily),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-12-01, hrr 2019-01-01, msa 2019-01-01, nation 2020-12-01, state 2019-01-01",2021-04-16,NA,day,Date,daily,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,public,neutral,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph +safegraph-daily,median_home_dwell_time,FALSE,median_home_dwell_time,FALSE,Median Home Dwell Time,FALSE,"The median time spent at home for all devices at this location for this time period, in minutes","The median time spent at home for all devices at this location for this time period, in minutes. + +Discontinued April 19th, 2021.",SafeGraph (Daily),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-12-01, hrr 2019-01-01, msa 2019-01-01, nation 2020-12-01, state 2019-01-01",2021-04-16,NA,day,Date,daily,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,public,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph +safegraph-daily,median_home_dwell_time,TRUE,median_home_dwell_time_7dav,FALSE,Median Home Dwell Time (7-day average),FALSE,NA,NA,SafeGraph (Daily),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-12-01, hrr 2019-01-01, msa 2019-01-01, nation 2020-12-01, state 2019-01-01",2021-04-16,NA,day,Date,daily,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,public,neutral,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph +safegraph-daily,part_time_work_prop,FALSE,part_time_work_prop,FALSE,Part Time Work/School,FALSE,The fraction of devices that spent between 3 and 6 hours at one location other than their home during the daytime,"The fraction of devices that spent between 3 and 6 hours at one location other than their home during the daytime. This is SafeGraph’s part_time_work_behavior_devices / device_count. + +Discontinued April 19th, 2021.",SafeGraph (Daily),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-12-01, hrr 2019-01-01, msa 2019-01-01, nation 2020-12-01, state 2019-01-01",2021-04-16,NA,day,Date,daily,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,public,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph +safegraph-daily,part_time_work_prop,TRUE,part_time_work_prop_7dav,FALSE,Part Time Work/School (7-day average),FALSE,NA,NA,SafeGraph (Daily),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-12-01, hrr 2019-01-01, msa 2019-01-01, nation 2020-12-01, state 2019-01-01",2021-04-16,NA,day,Date,daily,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,public,neutral,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph +safegraph-weekly,bars_visit_num,FALSE,bars_visit_num,FALSE,Bar Visits,FALSE,"Daily number of visits to bars, based on SafeGraph's Weekly Patterns dataset","Delphi receives data from [SafeGraph](https://docs.safegraph.com/docs/weekly-patterns), which collects weekly insights on Points of Interest (POI) using anonymized location data from mobile phones. We select locations that qualify as ""Drinking Places (alcoholic beverages)"" from all the [core places](https://docs.safegraph.com/v4.0/docs/places-manual#section-core-places), then count the number of visits. + +Note that these counts only include people whose visits are tracked because they are in SafeGraph's panel; they do not include all bar visits by everyone in the population.",SafeGraph (Weekly),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-11-23, hrr 2019-01-01, msa 2019-01-01, nation 2020-11-23, state 2019-01-01",2022-05-01,NA,day,Date,weekly,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for about 10% of counties. Data is available for about 90% of states,Visits,count,public,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph +safegraph-weekly,bars_visit_num,TRUE,bars_visit_prop,FALSE,Bar Visits (per 100k people),FALSE,NA,NA,SafeGraph (Weekly),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-11-23, hrr 2019-01-01, msa 2019-01-01, nation 2020-11-23, state 2019-01-01",2022-05-01,NA,day,Date,weekly,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for about 10% of counties. Data is available for about 90% of states,"Visits per 100,000 people",per100k,public,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph +safegraph-weekly,restaurants_visit_num,FALSE,restaurants_visit_num,FALSE,Restaurant Visits,FALSE,"Daily number of visits to restaurants, based on SafeGraph's Weekly Patterns dataset","Delphi receives data from [SafeGraph](https://docs.safegraph.com/docs/weekly-patterns), which collects weekly insights on Points of Interest (POI) using anonymized location data from mobile phones. We select locations that qualify as ""Full-Service Restaurants"" from all the [core places](https://docs.safegraph.com/v4.0/docs/places-manual#section-core-places), then count the number of visits. + +Note that these counts only include people whose visits are tracked because they are in SafeGraph's panel; they do not include all restaurant visits by everyone in the population.",SafeGraph (Weekly),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-11-23, hrr 2019-01-01, msa 2019-01-01, nation 2020-11-23, state 2019-01-01",2022-05-01,NA,day,Date,weekly,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for about 80% of counties Data is available for all states and some territories.,Visits,count,public,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph +safegraph-weekly,restaurants_visit_num,TRUE,restaurants_visit_prop,FALSE,Restaurant Visits (per 100k people),FALSE,NA,NA,SafeGraph (Weekly),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-11-23, hrr 2019-01-01, msa 2019-01-01, nation 2020-11-23, state 2019-01-01",2022-05-01,NA,day,Date,weekly,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for about 80% of counties Data is available for all states and some territories.,"Visits per 100,000 people",per100k,public,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph +usa-facts,confirmed_cumulative_num,FALSE,confirmed_cumulative_num,FALSE,Confirmed COVID Cases (Cumulative),FALSE,Cumulative confirmed COVID cases,Confirmed COVID-19 cases as reported by [USAFacts](https://usafacts.org/visualizations/coronavirus-covid-19-spread-map/),USAFacts,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-25,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,count,cases_testing,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts +usa-facts,confirmed_cumulative_num,TRUE,confirmed_7dav_incidence_num,TRUE,"Confirmed COVID Cases (Daily new, 7-day average)",FALSE,"Daily new confirmed COVID cases, 7-day average",NA,USAFacts,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,count,cases_testing,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts +usa-facts,confirmed_cumulative_num,TRUE,confirmed_7dav_incidence_prop,FALSE,"Confirmed COVID Cases (Daily new, 7-day average, per 100k people)",FALSE,"Daily new confirmed COVID cases, 7-day average, per 100k people",NA,USAFacts,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,per100k,cases_testing,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts +usa-facts,confirmed_cumulative_num,TRUE,confirmed_cumulative_prop,FALSE,"Confirmed COVID Cases (Cumulative, per 100k people)",FALSE,"Cumulative confirmed COVID cases, per 100k people",NA,USAFacts,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-25,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,per100k,cases_testing,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts +usa-facts,confirmed_cumulative_num,TRUE,confirmed_incidence_num,TRUE,Confirmed COVID Cases (Daily new),FALSE,Daily new confirmed COVID cases,NA,USAFacts,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-25,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,count,cases_testing,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts +usa-facts,confirmed_cumulative_num,TRUE,confirmed_incidence_prop,FALSE,"Confirmed COVID Cases (Daily new, per 100k people)",FALSE,"Daily new confirmed COVID cases, per 100k people",NA,USAFacts,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-25,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,per100k,cases_testing,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts +usa-facts,deaths_cumulative_num,FALSE,deaths_cumulative_num,FALSE,Confirmed COVID Deaths (Cumulative),FALSE,Cumulative confirmed COVID deaths,Confirmed COVID-19 deaths as reported by [USAFacts](https://usafacts.org/visualizations/coronavirus-covid-19-spread-map/),USAFacts,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-25,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,count,late,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts +usa-facts,deaths_cumulative_num,TRUE,deaths_7dav_incidence_num,TRUE,"Confirmed COVID Deaths (Daily new, 7-day average)",FALSE,"Daily new confirmed COVID deaths, 7-day average",NA,USAFacts,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,count,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts +usa-facts,deaths_cumulative_num,TRUE,deaths_7dav_incidence_prop,FALSE,"Confirmed COVID Deaths (Daily new, 7-day average, per 100k people)",FALSE,"Daily new confirmed COVID deaths, 7-day average, per 100k people",NA,USAFacts,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,per100k,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts +usa-facts,deaths_cumulative_num,TRUE,deaths_cumulative_prop,FALSE,"Confirmed COVID Deaths (Cumulative, per 100k people)",FALSE,"Cumulative confirmed COVID deaths, per 100k people",NA,USAFacts,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-25,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,per100k,late,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts +usa-facts,deaths_cumulative_num,TRUE,deaths_incidence_num,TRUE,Confirmed COVID Deaths (Daily new),FALSE,Daily new confirmed COVID deaths,NA,USAFacts,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-25,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts +usa-facts,deaths_cumulative_num,TRUE,deaths_incidence_prop,FALSE,"Confirmed COVID Deaths (Daily new, per 100k people)",FALSE,"Daily new confirmed COVID deaths, per 100k people",NA,USAFacts,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-25,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts From dca3427e7bfbf078c75894797ac11bb374842580 Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Thu, 9 May 2024 11:59:36 -0400 Subject: [PATCH 11/30] Revert "updates to DUA, Quidel" This reverts commit b671c36fccc85db7775919b48a4a6c4576e6ca88. --- scripts/quidelMissingness.R | 246 ---- scripts/signal_spreadsheet_updater.R | 221 ++-- scripts/updated_signal_spreadsheet.csv | 1539 ------------------------ 3 files changed, 111 insertions(+), 1895 deletions(-) delete mode 100644 scripts/quidelMissingness.R delete mode 100644 scripts/updated_signal_spreadsheet.csv diff --git a/scripts/quidelMissingness.R b/scripts/quidelMissingness.R deleted file mode 100644 index 07ed80180..000000000 --- a/scripts/quidelMissingness.R +++ /dev/null @@ -1,246 +0,0 @@ -library(epidatr) -library(dplyr) - -signals <- c( - #"covid_ag_raw_pct_positive", #"county", "state" - #"covid_ag_raw_pct_positive_age_0_4", #"county", "state" - #"covid_ag_smoothed_pct_positive", #"county", "state" - #"covid_ag_smoothed_pct_positive_age_0_4", #"county", "state" - #"covid_ag_smoothed_pct_positive_age_18_49" #"county", "state" - #"covid_ag_smoothed_pct_positive_age_65plus" #"county", "state" - - - "covid_ag_raw_pct_positive", #"hrr", "msa", "hhs", "nation" - "covid_ag_smoothed_pct_positive" #"hrr", "msa", "hhs", "nation" - - #"raw_pct_negative", #FLU - #"raw_tests_per_device", #FLU - #"smoothed_pct_negative", #FLU - #"smoothed_tests_per_device" #FLU -) -names(signals) <- signals -lapply(signals, function(signal) { - source <- "quidel" - signal <- signals - geo_type <- "msa" #"county", "state", "hrr", "msa", "hhs", "nation" - time_type <- "day" - - print(signal) - print(geo_type) - - epidata <- pub_covidcast( - source, - signal, - geo_type = geo_type, - geo_values = "*", - time_type = time_type, - time_values = c( - "2021-03-01", - "2021-03-02", - "2021-03-03", - "2021-03-04", - "2021-03-05", - "2021-03-06", - "2021-03-07", - "2021-03-08", - "2021-03-09", - "2021-03-10", - "2021-03-11", - "2021-03-12", - "2021-03-13", - "2021-03-14", - "2021-03-15", - "2021-03-16", - "2021-03-17", - "2021-03-18", - "2021-03-19", - "2021-03-20", - "2021-03-21", - "2021-03-22", - "2021-03-23", - "2021-03-24", - "2021-03-25", - "2021-03-26", - "2021-03-27", - "2021-03-28", - "2021-03-29", - "2021-03-30" - ) - ) - - # Number of locations reported for each reference date - count_geos_by_date <- count(epidata, time_value) - # print(count_geos_by_date) - print(max(count_geos_by_date$n) / 3143 * 100) - print(mean(count_geos_by_date$n) / 3143 * 100) - - return(max(count_geos_by_date$n) / 3143 * 100) - -}) - -####################################### geo_type = "county" -# covid_ag_raw_pct_positive -# "covid_ag_raw_pct_positive" -# covid_ag_raw_pct_positive_age_0_4 -# "covid_ag_raw_pct_positive_age_0_4" -# covid_ag_smoothed_pct_positive -# "covid_ag_smoothed_pct_positive" -# covid_ag_smoothed_pct_positive_age_0_4 -# "covid_ag_smoothed_pct_positive_age_0_4" -# covid_ag_smoothed_pct_positive_age_18_49 -# "covid_ag_smoothed_pct_positive_age_18_49" -# [1] "county" -# [1] 76.32835 -# [1] 72.70973 -# covid_ag_raw_pct_positive -# "covid_ag_raw_pct_positive" -# covid_ag_raw_pct_positive_age_0_4 -# "covid_ag_raw_pct_positive_age_0_4" -# covid_ag_smoothed_pct_positive -# "covid_ag_smoothed_pct_positive" -# covid_ag_smoothed_pct_positive_age_0_4 -# "covid_ag_smoothed_pct_positive_age_0_4" -# covid_ag_smoothed_pct_positive_age_18_49 -# "covid_ag_smoothed_pct_positive_age_18_49" -# [1] "county" -# [1] 76.32835 -# [1] 72.70973 -# covid_ag_raw_pct_positive -# "covid_ag_raw_pct_positive" -# covid_ag_raw_pct_positive_age_0_4 -# "covid_ag_raw_pct_positive_age_0_4" -# covid_ag_smoothed_pct_positive -# "covid_ag_smoothed_pct_positive" -# covid_ag_smoothed_pct_positive_age_0_4 -# "covid_ag_smoothed_pct_positive_age_0_4" -# covid_ag_smoothed_pct_positive_age_18_49 -# "covid_ag_smoothed_pct_positive_age_18_49" -# [1] "county" -# [1] 76.32835 -# [1] 72.70973 -# covid_ag_raw_pct_positive -# "covid_ag_raw_pct_positive" -# covid_ag_raw_pct_positive_age_0_4 -# "covid_ag_raw_pct_positive_age_0_4" -# covid_ag_smoothed_pct_positive -# "covid_ag_smoothed_pct_positive" -# covid_ag_smoothed_pct_positive_age_0_4 -# "covid_ag_smoothed_pct_positive_age_0_4" -# covid_ag_smoothed_pct_positive_age_18_49 -# "covid_ag_smoothed_pct_positive_age_18_49" -# [1] "county" -# [1] 76.32835 -# [1] 72.70973 -# covid_ag_raw_pct_positive -# "covid_ag_raw_pct_positive" -# covid_ag_raw_pct_positive_age_0_4 -# "covid_ag_raw_pct_positive_age_0_4" -# covid_ag_smoothed_pct_positive -# "covid_ag_smoothed_pct_positive" -# covid_ag_smoothed_pct_positive_age_0_4 -# "covid_ag_smoothed_pct_positive_age_0_4" -# covid_ag_smoothed_pct_positive_age_18_49 -# "covid_ag_smoothed_pct_positive_age_18_49" -# [1] "county" -# [1] 76.32835 -# [1] 72.70973 -# $covid_ag_raw_pct_positive -# [1] 76.32835 -# -# $covid_ag_raw_pct_positive_age_0_4 -# [1] 76.32835 -# -# $covid_ag_smoothed_pct_positive -# [1] 76.32835 -# -# $covid_ag_smoothed_pct_positive_age_0_4 -# [1] 76.32835 -# -# $covid_ag_smoothed_pct_positive_age_18_49 -# [1] 76.32835 - - - -####################################### geo_type = "state" -# covid_ag_raw_pct_positive -# "covid_ag_raw_pct_positive" -# covid_ag_raw_pct_positive_age_0_4 -# "covid_ag_raw_pct_positive_age_0_4" -# covid_ag_smoothed_pct_positive -# "covid_ag_smoothed_pct_positive" -# covid_ag_smoothed_pct_positive_age_0_4 -# "covid_ag_smoothed_pct_positive_age_0_4" -# covid_ag_smoothed_pct_positive_age_18_49 -# "covid_ag_smoothed_pct_positive_age_18_49" -# [1] "state" -# [1] 6.04518 -# [1] 5.738679 -# covid_ag_raw_pct_positive -# "covid_ag_raw_pct_positive" -# covid_ag_raw_pct_positive_age_0_4 -# "covid_ag_raw_pct_positive_age_0_4" -# covid_ag_smoothed_pct_positive -# "covid_ag_smoothed_pct_positive" -# covid_ag_smoothed_pct_positive_age_0_4 -# "covid_ag_smoothed_pct_positive_age_0_4" -# covid_ag_smoothed_pct_positive_age_18_49 -# "covid_ag_smoothed_pct_positive_age_18_49" -# [1] "state" -# [1] 6.04518 -# [1] 5.738679 -# covid_ag_raw_pct_positive -# "covid_ag_raw_pct_positive" -# covid_ag_raw_pct_positive_age_0_4 -# "covid_ag_raw_pct_positive_age_0_4" -# covid_ag_smoothed_pct_positive -# "covid_ag_smoothed_pct_positive" -# covid_ag_smoothed_pct_positive_age_0_4 -# "covid_ag_smoothed_pct_positive_age_0_4" -# covid_ag_smoothed_pct_positive_age_18_49 -# "covid_ag_smoothed_pct_positive_age_18_49" -# [1] "state" -# [1] 6.04518 -# [1] 5.738679 -# covid_ag_raw_pct_positive -# "covid_ag_raw_pct_positive" -# covid_ag_raw_pct_positive_age_0_4 -# "covid_ag_raw_pct_positive_age_0_4" -# covid_ag_smoothed_pct_positive -# "covid_ag_smoothed_pct_positive" -# covid_ag_smoothed_pct_positive_age_0_4 -# "covid_ag_smoothed_pct_positive_age_0_4" -# covid_ag_smoothed_pct_positive_age_18_49 -# "covid_ag_smoothed_pct_positive_age_18_49" -# [1] "state" -# [1] 6.04518 -# [1] 5.738679 -# covid_ag_raw_pct_positive -# "covid_ag_raw_pct_positive" -# covid_ag_raw_pct_positive_age_0_4 -# "covid_ag_raw_pct_positive_age_0_4" -# covid_ag_smoothed_pct_positive -# "covid_ag_smoothed_pct_positive" -# covid_ag_smoothed_pct_positive_age_0_4 -# "covid_ag_smoothed_pct_positive_age_0_4" -# covid_ag_smoothed_pct_positive_age_18_49 -# "covid_ag_smoothed_pct_positive_age_18_49" -# [1] "state" -# [1] 6.04518 -# [1] 5.738679 -# $covid_ag_raw_pct_positive -# [1] 6.04518 -# -# $covid_ag_raw_pct_positive_age_0_4 -# [1] 6.04518 -# -# $covid_ag_smoothed_pct_positive -# [1] 6.04518 -# -# $covid_ag_smoothed_pct_positive_age_0_4 -# [1] 6.04518 -# -# $covid_ag_smoothed_pct_positive_age_18_49 -# [1] 6.04518 - -####################################### geo_type = "state" - diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index edc178160..0ffbe3450 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -10,7 +10,7 @@ suppressPackageStartupMessages({ options(warn = 1) -# (unable to find more) TODO all info for youtube-survey, https://github.com/cmu-delphi/covid-19/tree/main/youtube +# TODO all info for youtube-survey # COVIDcast metadata # Metadata documentation: https://cmu-delphi.github.io/delphi-epidata/api/covidcast_meta.html @@ -110,16 +110,15 @@ new_fields <- c( "Temporal Scope Start", "Temporal Scope End", "Reporting Cadence", - "Typical Reporting Lag", #originally Reporting Lag - "Typical Revision Cadence", #originally Revision Cadence + "Reporting Lag", + "Revision Cadence", "Demographic Scope", - "Demographic Breakdowns", + "Demographic Disaggregation", ###Change to "Demographic Breakdowns" when granted sheet access "Severity Pyramid Rungs", "Data Censoring", "Missingness", - "Who may access this signal?", + "Who may Access this signal?", "Who may be told about this signal?", - "License", "Use Restrictions", "Link to DUA" ) @@ -191,7 +190,7 @@ source5 <- source4 %>% # Inactive data_sources list inactive_sources <- c( "jhu-csse", "dsew-cpr", "fb-survey", "covid-act-now", "ght", "google-survey", - "indicator-combination", "safegraph", "usa-facts", "youtube-survey" + "indicator-combination", "safegraph", "usa-facts" ) # Inactive signals list, where some signals for a given data source are active @@ -311,7 +310,7 @@ geo_scope <- c( "quidel" = "USA", "safegraph" = "USA", "usa-facts" = "USA", - "youtube-survey" = "USA" + "youtube-survey" = NA_character_ ) source_updated[, col] <- geo_scope[source_updated$data_source] @@ -371,9 +370,10 @@ avail_geos <- c( "indicator-combination" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), "jhu-csse" = glue("county, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), "nchs-mortality" = glue("state, nation"), - # Quidel non-flu signals - # (done) TODO check against actual data. Or maybe there's an internal/private version of metadata that includes Quidel stats? - "quidel" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), #geos all contain data + + # TODO check against actual data. Or maybe there's an internal/private version of metadata that includes Quidel stats? + # this is quidel non-flu signals, other is flu + "quidel" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), "safegraph" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), "usa-facts" = glue("county, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), "youtube-survey" = "state{delphi_agg_text}" @@ -432,12 +432,12 @@ leftover_signal_geos_manual <- tibble::tribble( "indicator-combination", "nmf_day_doc_fbs_ght", combo_geos, # Quidel flu signals - # (done) TODO check against actual data. Or maybe there's an internal/private version of metadata that includes Quidel stats? Nat was only looking at metadata - # for each of these quidel signals, make request to API for each possible geotype (county, hrr, etc) to see if data comes back - "quidel", "raw_pct_negative", quidel_geos, #only state, msa - "quidel", "smoothed_pct_negative", quidel_geos, #only state, msa - "quidel", "raw_tests_per_device", quidel_geos, #only state, msa - "quidel", "smoothed_tests_per_device", quidel_geos#only state, msa + # TODO check against actual data. Or maybe there's an internal/private version of metadata that includes Quidel stats? Nat was only looking at metadata + #for each of these quidel signals, make request to API for each possible geotype (county, hrr, etc) to see if data comes back + "quidel", "raw_pct_negative", quidel_geos, + "quidel", "smoothed_pct_negative", quidel_geos, + "quidel", "raw_tests_per_device", quidel_geos, + "quidel", "smoothed_tests_per_device", quidel_geos ) source_updated[, col] <- coalesce(avail_geos[source_updated$data_source], source_updated[[col]]) @@ -477,83 +477,84 @@ avail_geos <- c( "quidel" = "daily", "safegraph" = "weekly", "usa-facts" = "weekly", - "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube + "youtube-survey" = NA_character_ ) # # Tool: Investigate reporting lag and revision cadence -source <- "quidel" -signal <- "covid_ag_raw_pct_positive" +# source <- "indicator-combination-nmf" +# signal <- "nmf_day_doc_fbc_fbs_ght" # # Not available for all indicators. Try nation. Avoid smaller geos because # # processing later will take a while. -geo_type <- "nation" - +# geo_type <- "state" +# # # Consider a range of issues. About 2 weeks is probably fine. Not all indicators # # are available in this time range, so you may need to make another range of # # dates that is years or months different. -about_2weeks_issues <- c( - "2023-02-01", - "2023-02-02", - "2023-02-04", - "2023-02-05", - "2023-02-06", - "2023-02-07", - "2023-02-08", - "2023-02-09", - "2023-02-10", - "2023-02-11", - "2023-02-12", - "2023-02-13", - "2023-02-14", - "2023-02-15", - "2023-02-16" -) - - -epidata <- pub_covidcast( - source, - signal, - geo_type = geo_type, - geo_values = "*", - time_type = "day", - issues = about_2weeks_issues -) - - +# about_2weeks_issues <- c( +# "2021-02-01", +# "2021-02-02", +# "2021-02-04", +# "2021-02-05", +# "2021-02-06", +# "2021-02-07", +# "2021-02-08", +# "2021-02-09", +# "2021-02-10", +# "2021-02-11", +# "2021-02-12", +# "2021-02-13", +# "2021-02-14", +# "2021-02-15", +# "2021-02-16" +# ) +# +# +# epidata <- pub_covidcast( +# source, +# signal, +# geo_type = geo_type, +# geo_values = "*", +# time_type = "day", +# issues = about_2weeks_issues +# ) +# +# # # Make sure data is looking reasonable # # Number of reference dates reported in each issue -count(epidata, issue) # between 35 to 41 - +# count(epidata, issue) +# # # Number of locations reported for each issue and reference date -count(epidata, issue, time_value) # 1 - - +# count(epidata, issue, time_value) +# +# # ## Revision cadence # # For each location and reference date, are all reported values the same across # # all lags we're checking? -revision_comparison <- epidata %>% - group_by(time_value, geo_value) %>% - summarize( - no_backfill = case_when( - length(unique(value)) == 1 ~ "TRUE", - # If only two different values, are they approximately the same? - length(unique(value)) == 2 ~ all.equal(unique(value)[1], unique(value)[2]) %>% as.character(), - # If three different values, list them - length(unique(value)) > 2 ~ paste(unique(value), collapse = ", "), - ) - ) +# revision_comparison <- epidata %>% +# group_by(time_value, geo_value) %>% +# summarize( +# no_backfill = case_when( +# length(unique(value)) == 1 ~ "TRUE", +# # If only two different values, are they approximately the same? +# length(unique(value)) == 2 ~ all.equal(unique(value)[1], unique(value)[2]) %>% as.character(), +# # If three different values, list them +# length(unique(value)) > 2 ~ paste(unique(value), collapse = ", "), +# ) +# ) # # Are all reference dates without any lag? -all(revision_comparison$no_backfill == "TRUE") # [1] FALSE -View(revision_comparison) # 3 values TRUE, two have "Mean relative difference", rest are decimals - - +# all(revision_comparison$no_backfill == "TRUE") +# View(revision_comparison) +# +# # ## Reporting lag # # Find how lagged the newest reported value is for each issue. - epidata_slice <- epidata %>% group_by(issue) %>% slice_min(lag) +# epidata_slice <- epidata %>% group_by(issue) %>% slice_min(lag) # # Find the most common min lag. We expect a relatively narrow range of lags. At # # most, a data source should be updated weekly such that it has a range of lags # # of 7 days (e.g. 5-12 days). For data updated daily, we expect a range of lags # # of only a few days (e.g. 2-4 days or even 2-3 days). -table(epidata_slice$lag) # 5 and 15 = weekly +# table(epidata_slice$lag) + col <- "Typical Reporting Lag" # The number of days as an unstructured field, e.g. "3-5 days", from the last @@ -592,7 +593,7 @@ reporting_lag <- c( "quidel" = "5-6 days", "safegraph" = "3-11 days", "usa-facts" = "2-8 days", - "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube + "youtube-survey" = NA_character_ ) # Index (using `[]`) into the map using the data_source (or source division) @@ -622,10 +623,10 @@ revision_cadence <- c( corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.", "nchs-mortality" = "Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7)", - "quidel" = "Weekly. Happens, up to 6+ weeks after the report date.", # (done) TODO, + "quidel" = NA_character_, # Happens, up to 6+ weeks after the report date. # TODO "safegraph" = "None", "usa-facts" = "None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.", - "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube + "youtube-survey" = NA_character_ ) source_updated[, col] <- revision_cadence[source_updated$data_source] @@ -651,7 +652,7 @@ demo_scope <- c( "quidel" = "Nationwide Quidel testing equipment network", "safegraph" = "Safegraph panel members who use mobile devices", "usa-facts" = "All", - "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube + "youtube-survey" = NA_character_ ) source_updated[, col] <- demo_scope[source_updated$data_source] @@ -683,11 +684,11 @@ demo_breakdowns <- c( "quidel" = "age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)", "safegraph" = "None", "usa-facts" = "None", - "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube + "youtube-survey" = NA_character_ ) source_updated[, col] <- demo_breakdowns[source_updated$data_source] # Quidel covid has age bands, but quidel flu doesn't. -source_updated[source_updated$`Source Subdivision` == "quidel-flu", col] <- "None" +source_updated[source_update$`Source Subdivision` == "quidel-flu", col] <- "None" col <- "Severity Pyramid Rungs" @@ -719,7 +720,7 @@ data_censoring <- c( "quidel" = "Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests", "safegraph" = "None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details", "usa-facts" = "None", - "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube + "youtube-survey" = NA_character_ ) signal_specific_censoring <- tibble::tribble( ~data_source, ~signal, ~note, @@ -819,7 +820,7 @@ missingness <- c( "indicator-combination" = paste(all_counties_terr, all_states_terr), "jhu-csse" = paste(all_counties_terr, all_states_terr), "nchs-mortality" = paste(all_states_terr), - "quidel" = "Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.", # (done, see "quidelMissingness.R") TODO + "quidel" = "Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.", # TODO "safegraph" = paste(all_counties_terr, all_states_terr), "usa-facts" = paste(all_counties_terr, all_states), "youtube-survey" = NA_character_ # below @@ -904,7 +905,7 @@ orgs_allowed_access <- c( "quidel" = "Delphi", "safegraph" = "public", "usa-facts" = "public", - "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube + "youtube-survey" = NA_character_ ) source_updated[, col] <- orgs_allowed_access[source_updated$data_source] @@ -927,7 +928,7 @@ orgs_allowed_know <- c( "quidel" = "public", "safegraph" = "public", "usa-facts" = "public", - "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube + "youtube-survey" = NA_character_ ) source_updated[, col] <- orgs_allowed_know[source_updated$data_source] @@ -950,32 +951,32 @@ license <- c( "quidel" = "CC BY", "safegraph" = "CC BY", "usa-facts" = "CC BY", - "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube + "youtube-survey" = NA_character_ ) source_updated[, col] <- license[source_updated$data_source] -# (done) TODO +# TODO col <- "Use Restrictions" # Any important DUA restrictions on use, publication, sharing, linkage, etc.? use_restrictions <- c( - "chng" = "CC BY-NC", #DUA in confidential Google drive, generic contract terms - "covid-act-now" = "CC BY-NC", #public - "doctor-visits" = "CC BY-NC", #optum DUA in confidential Google drive, generic contract terms - "dsew-cpr" = "Public Domain US Government (https://www.usa.gov/government-works)", #public - "fb-survey" = "Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.", # @AlexR - "ght" = "Google Terms of Service (https://policies.google.com/terms)", #public, no Delphi documentation, - "google-survey" = "CC BY", - "google-symptoms" = "Google Terms of Service (https://policies.google.com/terms)", - "hhs" = "Public Domain US Government (https://www.usa.gov/government-works)", - "hospital-admissions" = "CC BY", #optum DUA in confidential Google drive, generic contract terms - "indicator-combination" = "CC BY", - "jhu-csse" = "CC BY", - "nchs-mortality" = "NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm)", - "quidel" = "Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).", #Quidel DUA in confidential Google drive, - "safegraph" = "CC BY", - "usa-facts" = "CC BY", - "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube + "chng" = NA_character_, #change DUA in confidential Google drive, generic contract terms + "covid-act-now" = NA_character_, #public + "doctor-visits" = NA_character_, #optum DUA in confidential Google drive, generic contract terms + "dsew-cpr" = NA_character_, #public + "fb-survey" = NA_character_, # + "ght" = NA_character_, + "google-survey" = NA_character_, + "google-symptoms" = NA_character_, + "hhs" = NA_character_, + "hospital-admissions" = NA_character_, #optum DUA in confidential Google drive, generic contract terms + "indicator-combination" = NA_character_, + "jhu-csse" = NA_character_, + "nchs-mortality" = NA_character_, + "quidel" = "Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics.", #Quidel DUA in confidential Google drive, + "safegraph" = NA_character_, + "usa-facts" = NA_character_, + "youtube-survey" = NA_character_ ) source_updated[, col] <- use_restrictions[source_updated$data_source] @@ -988,25 +989,25 @@ source_updated[, col] <- use_restrictions[source_updated$data_source] #bb <- aa$sources$`fb-survey`$signals %>% tibble::as_tibble() #bb -# (done) TODO +# TODO col <- "Link to DUA" dua_link <- c( "chng" = "https://drive.google.com/drive/u/1/folders/1GKYSFb6C_8jSHTg-65eVzSOT433oIDrf", #"https://cmu.box.com/s/cto4to822zecr3oyq1kkk9xmzhtq9tl2" "covid-act-now" = NA_character_, #public, maybe contract for other specific project #@Carlyn - "doctor-visits" = "https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf", #"https://cmu.box.com/s/l2tz6kmiws6jyty2azwb43poiepz0565" + "doctor-visits" = "https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf", #"https://cmu.box.com/s/l2tz6kmiws6jyty2azwb43poiepz0565", "dsew-cpr" = NA_character_, #public - "fb-survey" = NA_character_, # wait for OK from @Alex R. "https://drive.google.com/file/d/1zd6A5gS8ncvz18_pCQfL7UVRvUJVHDdn/view?usp=drive_link", "https://cmu.box.com/s/qfxplcdrcn9retfzx4zniyugbd9h3bos" - "ght" = NA_character_, #public, has an API doesn't require password, no Delphi documentation, + "fb-survey" = "https://cmu.box.com/s/qfxplcdrcn9retfzx4zniyugbd9h3bos",#@Alex R. + "ght" = NA_character_, #public, has an API doesn't require password "google-survey" = NA_character_, #@Carlyn has requested DUA from Roni "google-symptoms" = NA_character_, #public - "hhs" = NA_character_, #public - "hospital-admissions" = "https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf", #"https://cmu.box.com/s/l2tz6kmiws6jyty2azwb43poiepz0565" + "hhs" = NA_character_, #public gov't + "hospital-admissions" = "https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf", #"https://cmu.box.com/s/l2tz6kmiws6jyty2azwb43poiepz0565", "indicator-combination" = "see Doctor Visits, Facebook Survey, and Google Health Trends", "jhu-csse" = NA_character_, #public "nchs-mortality" = "https://www.cdc.gov/nchs/data_access/restrictions.htm", "quidel" = "https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS", "safegraph" = "https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x", - "usa-facts" = NA_character_, #public, + "usa-facts" = NA_character_, #public "youtube-survey" = NA_character_ #looking for contract, https://github.com/cmu-delphi/covid-19/tree/main/youtube ) source_updated[, col] <- dua_link[source_updated$data_source] @@ -1030,4 +1031,4 @@ write_csv(source_updated, file = "updated_signal_spreadsheet.csv") # Final manual steps: -# open CSV in a GUI editor (excel or google sheets). copy scope date columns and paste into original spreadsheet online [manual] \ No newline at end of file +# open CSV in a GUI editor (excel or google sheets). copy scope date columns and paste into original spreadsheet online [manual] diff --git a/scripts/updated_signal_spreadsheet.csv b/scripts/updated_signal_spreadsheet.csv deleted file mode 100644 index 8fe71d5cb..000000000 --- a/scripts/updated_signal_spreadsheet.csv +++ /dev/null @@ -1,1539 +0,0 @@ -Source Subdivision,Signal BaseName,base_is_other,Signal,Compute From Base,Name,Active,Short Description,Description,Source Name,"Pathogen/ -Disease Area",Signal Type,Geographic Scope,Available Geography,Temporal Scope Start,Temporal Scope Start Note,Temporal Scope End,Temporal Scope End Note,Time Type,Time Label,Reporting Cadence,Typical Reporting Lag,Typical Revision Cadence,Demographic Scope,Demographic Breakdowns,Severity Pyramid Rungs,Data Censoring,Missingness,Value Label,Format,Category,High Values Are,Is Smoothed,Is Weighted,Is Cumulative,Has StdErr,Has Sample Size,Who may access this signal?,Who may be told about this signal?,License,Use Restrictions,Link to DUA,Link,data_source -chng,smoothed_outpatient_cli,FALSE,smoothed_outpatient_cli,FALSE,COVID-Related Doctor Visits,TRUE,Estimated percentage of outpatient doctor visits primarily about COVID-related symptoms,"Estimated percentage of outpatient doctor visits primarily about COVID-related symptoms, based on Change Healthcare claims data that has been de-identified in accordance with HIPAA privacy regulations, smoothed in time using a Gaussian linear smoother",Change Healthcare,covid,Public behavior,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,Ongoing,NA,day,Date,daily,4-5 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 4-6 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 45 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Change Healthcare network,None,outpatient visit,Discarded if over a given 7-day period an estimate is computed with 100 or fewer observations,Data is available for nearly all (99%) of counties. Data is available for all states and some territories.,Value,raw,early,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY-NC,CC BY-NC,https://drive.google.com/drive/u/1/folders/1GKYSFb6C_8jSHTg-65eVzSOT433oIDrf,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/chng.html,chng -chng,smoothed_outpatient_cli,TRUE,smoothed_adj_outpatient_cli,FALSE,COVID-Related Doctor Visits (Day-adjusted),TRUE,NA,"Estimated percentage of outpatient doctor visits primarily about COVID-related symptoms, based on Change Healthcare claims data that has been de-identified in accordance with HIPAA privacy regulations, smoothed in time using a Gaussian linear smoother, and adjusted to reduce day-of-week effects",Change Healthcare,covid,Outpatient insurance claims,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,Ongoing,NA,day,Date,daily,4-5 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 4-6 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 45 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Change Healthcare network,None,outpatient visit,Discarded if over a given 7-day period an estimate is computed with 100 or fewer observations,Data is available for nearly all (99%) of counties. Data is available for all states and some territories.,Value,raw,early,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY-NC,CC BY-NC,https://drive.google.com/drive/u/1/folders/1GKYSFb6C_8jSHTg-65eVzSOT433oIDrf,NA,chng -chng,smoothed_outpatient_covid,FALSE,smoothed_outpatient_covid,FALSE,COVID-Confirmed Doctor Visits,TRUE,COVID-Confirmed Doctor Visits,"Estimated percentage of outpatient doctor visits with confirmed COVID-19, based on Change Healthcare claims data that has been de-identified in accordance with HIPAA privacy regulations, smoothed in time using a Gaussian linear smoother",Change Healthcare,covid,Outpatient insurance claims,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,Ongoing,NA,day,Date,daily,4-5 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 4-6 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 45 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Change Healthcare network,None,outpatient visit,Discarded if over a given 7-day period an estimate is computed with 100 or fewer observations,Data is available for nearly all (99%) of counties. Data is available for all states and some territories.,Value,raw,early,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY-NC,CC BY-NC,https://drive.google.com/drive/u/1/folders/1GKYSFb6C_8jSHTg-65eVzSOT433oIDrf,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/chng.html,chng -chng,smoothed_outpatient_covid,TRUE,smoothed_adj_outpatient_covid,FALSE,COVID-Confirmed Doctor Visits (Day-adjusted),TRUE,NA,"Estimated percentage of outpatient doctor visits with confirmed COVID-19, based on Change Healthcare claims data that has been de-identified in accordance with HIPAA privacy regulations, smoothed in time using a Gaussian linear smoother, and adjusted to reduce day-of-week effects",Change Healthcare,covid,Outpatient insurance claims,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,Ongoing,NA,day,Date,daily,4-5 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 4-6 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 45 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Change Healthcare network,None,outpatient visit,Discarded if over a given 7-day period an estimate is computed with 100 or fewer observations,Data is available for nearly all (99%) of counties. Data is available for all states and some territories.,Value,raw,early,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY-NC,CC BY-NC,https://drive.google.com/drive/u/1/folders/1GKYSFb6C_8jSHTg-65eVzSOT433oIDrf,NA,chng -chng,smoothed_outpatient_flu,FALSE,smoothed_outpatient_flu,FALSE,Influenza-Confirmed Doctor Visits,TRUE,Estimated percentage of outpatient doctor visits with confirmed influenza,"Estimated percentage of outpatient doctor visits with confirmed influenza, based on Change Healthcare claims data that has been de-identified in accordance with HIPAA privacy regulations, smoothed in time using a Gaussian linear smoother",Change Healthcare,flu,Outpatient insurance claims,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,Ongoing,NA,day,Day,daily,4-5 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 4-6 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 45 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Change Healthcare network,None,outpatient visit,Discarded if over a given 7-day period an estimate is computed with 100 or fewer observations,Data is available for nearly all (99%) of counties. Data is available for all states and some territories.,Value,raw,early,bad,TRUE,FALSE,FALSE,NA,NA,public,public,CC BY-NC,CC BY-NC,https://drive.google.com/drive/u/1/folders/1GKYSFb6C_8jSHTg-65eVzSOT433oIDrf,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/chng.html,chng -chng,smoothed_outpatient_flu,TRUE,smoothed_adj_outpatient_flu,FALSE,Influenza-Confirmed Doctor Visits (Day-adjusted),TRUE,NA,"Estimated percentage of outpatient doctor visits with confirmed influenza, based on Change Healthcare claims data that has been de-identified in accordance with HIPAA privacy regulations, smoothed in time using a Gaussian linear smoother, and adjusted to reduce day-of-week effects",Change Healthcare,flu,Outpatient insurance claims,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,Ongoing,NA,day,Day,daily,4-5 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 4-6 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 45 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Change Healthcare network,None,outpatient visit,Discarded if over a given 7-day period an estimate is computed with 100 or fewer observations,Data is available for nearly all (99%) of counties. Data is available for all states and some territories.,Value,raw,early,bad,TRUE,FALSE,FALSE,NA,NA,public,public,CC BY-NC,CC BY-NC,https://drive.google.com/drive/u/1/folders/1GKYSFb6C_8jSHTg-65eVzSOT433oIDrf,NA,chng -covid-act-now,pcr_specimen_positivity_rate,FALSE,pcr_specimen_positivity_rate,FALSE,PCR Test Positivity Rate,FALSE,Proportion of PCR specimens tested that have a positive result,NA,Covid Act Now (CAN),covid,Testing,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-03-01,NA,2021-12-02,NA,day,Date,daily,2-9 days,"Daily. Most recent test positivity rates do not change substantially (having a median delta of close to 0). However, most recent total tests performed are expected to increase in later data revisions (having a median increase of 7%). Values more than 5 days in the past are expected to remain fairly static (with total tests performed having a median increase of 1% of less), as most major revisions have already occurred.",Hospital patients,None,infected,Discarded if sample size (total tests performed) is 0,"Data is available for nearly all (99%) of counties. A few counties, most notably in California, are not covered by this data source Data is available for all states.",Value,fraction,cases_testing,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY-NC,CC BY-NC,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/covid-act-now.html,covid-act-now -covid-act-now,pcr_specimen_total_tests,FALSE,pcr_specimen_total_tests,FALSE,Total Number of PCR Tests,FALSE,Total number of PCR specimens tested,NA,Covid Act Now (CAN),covid,Testing,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-03-01,NA,2021-12-02,NA,day,Date,daily,2-9 days,"Daily. Most recent test positivity rates do not change substantially (having a median delta of close to 0). However, most recent total tests performed are expected to increase in later data revisions (having a median increase of 7%). Values more than 5 days in the past are expected to remain fairly static (with total tests performed having a median increase of 1% of less), as most major revisions have already occurred.",Hospital patients,None,population,Discarded if sample size (total tests performed) is 0,"Data is available for nearly all (99%) of counties. A few counties, most notably in California, are not covered by this data source Data is available for all states.",Value,count,cases_testing,good,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY-NC,CC BY-NC,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/covid-act-now.html,covid-act-now -doctor-visits,smoothed_cli,FALSE,smoothed_cli,FALSE,COVID-Related Doctor Visits,TRUE,Percentage of daily doctor visits that are due to COVID-like symptoms,"Estimated percentage of outpatient doctor visits that are primarily about COVID-related symptoms, based on data from health system partners, smoothed in time using a Gaussian linear smoother",Doctor Visits From Claims,covid,Outpatient insurance claims,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,Ongoing,NA,day,Date,daily,3-6 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 5-7 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 50 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Optum network,None,outpatient visit,Discarded if over a given 7-day period an estimate is computed with 500 or fewer observations,Data is available for about 80% of counties Data is available for all states and some territories.,Percentage,percent,early,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY-NC,CC BY-NC,https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/doctor-visits.html,doctor-visits -doctor-visits,smoothed_cli,TRUE,smoothed_adj_cli,FALSE,COVID-Related Doctor Visits (Day-adjusted),TRUE,NA,"Estimated percentage of outpatient doctor visits that are primarily about COVID-related symptoms, based on data from health system partners, smoothed in time using a Gaussian linear smoother, and adjusted to reduce day-of-week effects",Doctor Visits From Claims,covid,Outpatient insurance claims,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,Ongoing,NA,day,Date,daily,3-6 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 5-7 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 50 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Optum network,None,outpatient visit,Discarded if over a given 7-day period an estimate is computed with 500 or fewer observations,Data is available for about 80% of counties Data is available for all states and some territories.,Percentage,percent,early,bad,TRUE,TRUE,FALSE,FALSE,FALSE,public,public,CC BY-NC,CC BY-NC,https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf,NA,doctor-visits -dsew-cpr,booster_doses_admin_7dav,FALSE,booster_doses_admin_7dav,FALSE,booster_doses_admin_7dav,FALSE,COVID-19 booster vaccine doses administered each day,"COVID-19 booster vaccine doses administered each day, based on the daily Community Profile Report (CPR) published by the Data Strategy and Execution Workgroup of the White House COVID-19 Team, smoothed in time with a 7-day average. - -""Doses administered shown by date of report, not date of administration. ... [A] booster dose includes anyone who is fully vaccinated and has received another dose of COVID-19 vaccine since August 13, 2021. This includes people who received booster doses and people who received additional doses."" - from the CPR data dictionary.",COVID-19 Community Profile Report,covid,Vaccines,USA,"state, hhs, nation (by Delphi)",2021-11-01,NA,2023-02-22,NA,day,Day,daily,3-9 days,Daily. This data source is susceptible to large corrections that can create strange data effects such as negative counts and sudden changes of 1M+ counts from one day to the next.,All,None,population,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,public,good,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/dsew-cpr.html,dsew-cpr -dsew-cpr,confirmed_admissions_covid_1d_7dav,FALSE,confirmed_admissions_covid_1d_7dav,FALSE,Confirmed COVID Admissions per day,FALSE,All confirmed COVID-19 hospital admissions occurring each day,"All confirmed COVID-19 hospital admissions occurring each day, based on the daily Community Profile Report published by the Data Strategy and Execution Workgroup of the White House COVID-19 Team, smoothed in time with a 7-day average. - -Other sources of hospital admissions data in COVIDcast include [HHS](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/hhs.html) and [medical insurance claims](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/hospital-admissions.html). The CPR differs from these sources in that it is part of the public health surveillance stream (like HHS, unlike claims) but is available at a daily-county level (like claims, unlike HHS). CPR hospital admissions figures at the state level and above are meant to match those from HHS, but are known to differ. See the [Limitations section of the technical documentation](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/dsew-cpr.html#limitations) for more details.",COVID-19 Community Profile Report,covid,Vaccines,USA,"county, msa, state, hhs, nation (by Delphi)",2020-12-16,"Start dates vary by geo: county 2021-01-07, hhs 2020-12-16, msa 2021-01-07, nation 2020-12-16, state 2020-12-16",2023-02-21,NA,NA,Date,daily,3-9 days,Daily. This data source is susceptible to large corrections that can create strange data effects such as negative counts and sudden changes of 1M+ counts from one day to the next.,All,None,hospitalized,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/dsew-cpr.html,dsew-cpr -dsew-cpr,confirmed_admissions_covid_1d_7dav,TRUE,confirmed_admissions_covid_1d_prop_7dav,FALSE,Confirmed COVID Admissions per day (per 100k people),FALSE,NA,NA,COVID-19 Community Profile Report,covid,Vaccines,USA,"county, msa, state, hhs, nation (by Delphi)",2020-12-16,"Start dates vary by geo: county 2021-01-07, hhs 2020-12-16, msa 2021-01-07, nation 2020-12-16, state 2020-12-16",2023-02-21,NA,day,Date,daily,3-9 days,Daily. This data source is susceptible to large corrections that can create strange data effects such as negative counts and sudden changes of 1M+ counts from one day to the next.,All,None,hospitalized,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,NA,dsew-cpr -dsew-cpr,doses_admin_7dav,FALSE,doses_admin_7dav,FALSE,doses_admin_7dav,FALSE,COVID-19 vaccine doses administered each day,"COVID-19 vaccine doses administered each day, based on the daily Community Profile Report (CPR) published by the Data Strategy and Execution Workgroup of the White House COVID-19 Team, smoothed in time with a 7-day average. - -""Doses administered shown by date of report, not date of administration."" - from the CPR data dictionary.",COVID-19 Community Profile Report,covid,Vaccines,USA,"state, hhs, nation (by Delphi)",2021-05-02,NA,2023-02-22,NA,day,Day,daily,3-9 days,Daily. This data source is susceptible to large corrections that can create strange data effects such as negative counts and sudden changes of 1M+ counts from one day to the next.,All,None,population,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,public,good,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/dsew-cpr.html,dsew-cpr -dsew-cpr,people_booster_doses,FALSE,people_booster_doses,FALSE,people_booster_doses,FALSE,Cumulative number of people who have received a booster dose of the COVID-19 vaccine,"Cumulative number of people who have received a booster dose of the COVID-19 vaccine, based on the daily Community Profile Report (CPR) published by the Data Strategy and Execution Workgroup of the White House COVID-19 Team, smoothed in time with a 7-day average. - -""The count of people who received a booster dose includes anyone who is fully vaccinated and has received another dose of COVID-19 vaccine since 2021-08-13. This includes people who received booster doses and people who received additional doses"" - from the CPR data dictionary.",COVID-19 Community Profile Report,covid,Vaccines,USA,"state, hhs, nation (by Delphi)",2021-11-01,NA,2023-02-22,NA,day,Day,daily,3-9 days,Daily. This data source is susceptible to large corrections that can create strange data effects such as negative counts and sudden changes of 1M+ counts from one day to the next.,All,None,population,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,public,good,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/dsew-cpr.html,dsew-cpr -dsew-cpr,people_full_vaccinated,FALSE,people_full_vaccinated,FALSE,people_full_vaccinated,FALSE,Cumulative number of people who have received a full course of the COVID-19 vaccine,"Cumulative number of people who have received a full course of the COVID-19 vaccine, based on the daily Community Profile Report (CPR) published by the Data Strategy and Execution Workgroup of the White House COVID-19 Team, smoothed in time with a 7-day average. - -""People fully vaccinated includes those who have received two doses of the Pfizer-BioNTech or Moderna vaccine and those who have received one dose of the J&J/Janssen vaccine"" - from the CPR data dictionary.",COVID-19 Community Profile Report,covid,Vaccines,USA,"county, msa, state, hhs, nation (by Delphi)",2021-01-15,"Start dates vary by geo: county 2021-04-12, hhs 2021-01-15, msa 2021-04-12, nation 2021-01-15, state 2021-01-15",2023-02-22,NA,day,Day,daily,3-9 days,Daily. This data source is susceptible to large corrections that can create strange data effects such as negative counts and sudden changes of 1M+ counts from one day to the next.,All,None,population,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,public,good,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/dsew-cpr.html,dsew-cpr -fb-survey,raw_wcli,FALSE,raw_wcli,FALSE,COVID-Like Symptoms,FALSE,Estimated percentage of people with COVID-like illness,"{source_description} For this signal, we estimate the percentage of people self-reporting COVID-like symptoms, defined here as fever along with either cough, shortness of breath, or difficulty breathing. While many other conditions can cause these symptoms, comparing the rates of COVID-like symptoms across the country can suggest where COVID is most active.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-06,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,early,bad,FALSE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,"[Survey details](https://delphi.cmu.edu/covidcast/surveys/) -[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#ili-and-cli-indicators)",fb-survey -fb-survey,raw_wcli,TRUE,raw_cli,FALSE,COVID-Like Symptoms (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-06,NA,2022-06-26,"End dates vary by geo: county 2022-06-25, hrr 2022-06-25, msa 2022-06-25, nation 2022-06-26, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,early,bad,FALSE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,raw_wcli,TRUE,smoothed_cli,FALSE,COVID-Like Symptoms (Unweighted 7-day average),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-06,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.",Data is available for about 50% of counties. Data is available for all states and some territories. Availability declines over time as survey response rate decreases,Percentage,percent,early,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,raw_wcli,TRUE,smoothed_wcli,FALSE,COVID-Like Symptoms (7-day average),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-06,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.",Data is available for about 50% of counties. Data is available for all states and some territories. Availability declines over time as survey response rate decreases,Percentage,percent,early,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,raw_whh_cmnty_cli,FALSE,raw_whh_cmnty_cli,FALSE,COVID-Like Symptoms in Community,FALSE,Estimated percentage of people reporting illness in their local community,"{source_description} We also ask them if they know anyone in their local community who has COVID-like symptoms, defined here as fever along with either cough, shortness of breath, or difficulty breathing. For this indicator, we estimate the percentage of people who know someone, in their household or outside it, who has these symptoms. While many conditions can cause these symptoms, not just COVID, comparing the rates across the country can suggest where COVID is most active.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-15,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,early,bad,FALSE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,"[Survey details](https://delphi.cmu.edu/covidcast/surveys/) -[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#ili-and-cli-indicators)",fb-survey -fb-survey,raw_whh_cmnty_cli,TRUE,raw_hh_cmnty_cli,FALSE,COVID-Like Symptoms in Community (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-15,NA,2022-06-26,"End dates vary by geo: county 2022-06-25, hrr 2022-06-25, msa 2022-06-25, nation 2022-06-26, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,early,bad,FALSE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,raw_whh_cmnty_cli,TRUE,smoothed_hh_cmnty_cli,FALSE,COVID-Like Symptoms in Community (Unweighted 7-day average),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-15,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.",Data is available for about 40% of counties. Data is available for all states and some territories. Availability declines over time as survey response rate decreases,Percentage,percent,early,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,raw_whh_cmnty_cli,TRUE,smoothed_whh_cmnty_cli,FALSE,COVID-Like Symptoms in Community (7-day average),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-15,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.",Data is available for about 35% of counties. Data is available for all states and some territories. Availability declines over time as survey response rate decreases,Percentage,percent,early,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,raw_wili,FALSE,raw_wili,FALSE,Flu-Like Symptoms,FALSE,Estimated percentage of people with influenza-like illness,"{source_description} For this signal, we estimate the percentage of people self-reporting influenza-like symptoms, defined here as fever along with either cough or sore throat. While many other conditions can cause these symptoms, comparing the rates of influenza-like symptoms across the country can suggest where the flu is most active.",Delphi US COVID-19 Trends and Impact Survey,flu,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-06,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,early,bad,FALSE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#ili-and-cli-indicators,fb-survey -fb-survey,raw_wili,TRUE,raw_ili,FALSE,Flu-Like Symptoms (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,flu,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-06,NA,2022-06-26,"End dates vary by geo: county 2022-06-25, hrr 2022-06-25, msa 2022-06-25, nation 2022-06-26, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,early,bad,FALSE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,raw_wili,TRUE,smoothed_ili,FALSE,Flu-Like Symptoms (Unweighted 7-day average),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,flu,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-06,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.",Data is available for about 50% of counties. Data is available for all states and some territories. Availability declines over time as survey response rate decreases,Percentage,percent,early,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,raw_wili,TRUE,smoothed_wili,FALSE,Flu-Like Symptoms (7-day average),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,flu,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-06,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.",Data is available for about 50% of counties. Data is available for all states and some territories. Availability declines over time as survey response rate decreases,Percentage,percent,early,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,raw_wnohh_cmnty_cli,FALSE,raw_wnohh_cmnty_cli,FALSE,COVID-Like Symptoms in Community Outside Household,FALSE,Estimated percentage of people reporting illness in their local community not including their household,"{source_description} We also ask them if they know anyone in their local community who has COVID-like symptoms, defined here as fever along with either cough, shortness of breath, or difficulty breathing. For this indicator, we estimate the percentage of people who know someone outside their household who has these symptoms. While many conditions can cause these symptoms, not just COVID, comparing the rates across the country can suggest where COVID is most active.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-15,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,early,bad,FALSE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#ili-and-cli-indicators,fb-survey -fb-survey,raw_wnohh_cmnty_cli,TRUE,raw_nohh_cmnty_cli,FALSE,COVID-Like Symptoms in Community Outside Household (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-15,NA,2022-06-26,"End dates vary by geo: county 2022-06-25, hrr 2022-06-25, msa 2022-06-25, nation 2022-06-26, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,early,bad,FALSE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,raw_wnohh_cmnty_cli,TRUE,smoothed_nohh_cmnty_cli,FALSE,COVID-Like Symptoms in Community Outside Household (Unweighted 7-day average),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-15,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.",Data is available for about 40% of counties. Data is available for all states and some territories. Availability declines over time as survey response rate decreases,Percentage,percent,early,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,raw_wnohh_cmnty_cli,TRUE,smoothed_wnohh_cmnty_cli,FALSE,COVID-Like Symptoms in Community Outside Household (7-day average),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-15,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",symptomatic,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.",Data is available for about 35% of counties. Data is available for all states and some territories. Availability declines over time as survey response rate decreases,Percentage,percent,early,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_waccept_covid_vaccine,FALSE,smoothed_waccept_covid_vaccine,FALSE,COVID-19 Vaccine Acceptance,FALSE,"Estimated percentage of respondents who would definitely or probably choose to get vaccinated, if a COVID-19 vaccine were offered to them today.","{source_description} We also ask questions about well-being and various mitigation measures, including vaccine acceptance. For this signal, we estimate the percentage of people who would ""definitely"" or ""probably"" choose to be vaccinated if a COVID vaccine were offered to them today. - -Note: Until January 6, 2021, all respondents answered this question; beginning on that date, only respondents who said they have not received a COVID vaccine are asked this question. - -Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey -fb-survey,smoothed_waccept_covid_vaccine,TRUE,smoothed_accept_covid_vaccine,FALSE,COVID-19 Vaccine Acceptance (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_waccept_covid_vaccine_no_appointment,FALSE,smoothed_waccept_covid_vaccine_no_appointment,FALSE,COVID-19 Vaccine Acceptance Among Unvaccinated,FALSE,"Estimated percentage of respondents who would definitely or probably choose to get vaccinated, if a vaccine were offered to them today, among respondents who have not yet been vaccinated and do not have an appointment to do so.","Estimated percentage of respondents who would definitely or probably choose to get vaccinated, if a vaccine were offered to them today, among respondents who have not yet been vaccinated and do not have an appointment to do so. - -Based on survey item V3a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,"Start dates vary by geo: county 2021-05-20, hrr 2021-05-21, msa 2021-05-21, nation 2021-05-20, state 2021-05-20",2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey -fb-survey,smoothed_waccept_covid_vaccine_no_appointment,TRUE,smoothed_accept_covid_vaccine_no_appointment,FALSE,COVID-19 Vaccine Acceptance Among Unvaccinated (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,"Start dates vary by geo: county 2021-05-20, hrr 2021-05-21, msa 2021-05-21, nation 2021-05-20, state 2021-05-20",2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wanxious_5d,FALSE,smoothed_wanxious_5d,FALSE,Anxious (Last Five Days),FALSE,"Estimated percentage of respondents who reported feeling ""nervous, anxious, or on edge"" for most or all of the past 5 days.","Estimated percentage of respondents who reported feeling ""nervous, anxious, or on edge"" for most or all of the past 5 days. - -Discontinued as of Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mental-health-indicators,fb-survey -fb-survey,smoothed_wanxious_5d,TRUE,smoothed_anxious_5d,FALSE,Anxious (Last Five Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wanxious_7d,FALSE,smoothed_wanxious_7d,FALSE,Anxious (Last Seven Days),FALSE,"Estimated percentage of respondents who reported feeling ""nervous, anxious, or on edge"" for most or all of the past 7 days.","Estimated percentage of respondents who reported feeling ""nervous, anxious, or on edge"" for most or all of the past 7 days. - -This item was shown to respondents starting in Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mental-health-indicators,fb-survey -fb-survey,smoothed_wanxious_7d,TRUE,smoothed_anxious_7d,FALSE,Anxious (Last Seven Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wappointment_not_vaccinated,FALSE,smoothed_wappointment_not_vaccinated,FALSE,COVID-19 Vaccine Appointments Among Unvaccinated,FALSE,"Estimated percentage of respondents who have an appointment to get a COVID-19 vaccine, among respondents who have not yet been vaccinated.","Estimated percentage of respondents who have an appointment to get a COVID-19 vaccine, among respondents who have not yet been vaccinated. - -Based on survey item V11a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,"Start dates vary by geo: county 2021-05-20, hrr 2021-05-21, msa 2021-05-21, nation 2021-05-20, state 2021-05-20",2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey -fb-survey,smoothed_wappointment_not_vaccinated,TRUE,smoothed_appointment_not_vaccinated,FALSE,COVID-19 Vaccine Appointments Among Unvaccinated (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,"Start dates vary by geo: county 2021-05-20, hrr 2021-05-21, msa 2021-05-21, nation 2021-05-20, state 2021-05-20",2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wappointment_or_accept_covid_vaccine,FALSE,smoothed_wappointment_or_accept_covid_vaccine,FALSE,COVID-19 Vaccine Acceptance and Appointments Among Unvaccinated,FALSE,"Estimated percentage of respondents who either have an appointment to get a COVID-19 vaccine or would definitely or probably choose to get vaccinated, if a vaccine were offered to them today, among respondents who have not yet been vaccinated","Estimated percentage of respondents who either have an appointment to get a COVID-19 vaccine or would definitely or probably choose to get vaccinated, if a vaccine were offered to them today, among respondents who have not yet been vaccinated - -Based on survey items V11a and V3a. V11a was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,"Start dates vary by geo: county 2021-05-20, hrr 2021-05-21, msa 2021-05-20, nation 2021-05-20, state 2021-05-20",2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey -fb-survey,smoothed_wappointment_or_accept_covid_vaccine,TRUE,smoothed_appointment_or_accept_covid_vaccine,FALSE,COVID-19 Vaccine Acceptance and Appointments Among Unvaccinated (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,"Start dates vary by geo: county 2021-05-20, hrr 2021-05-21, msa 2021-05-20, nation 2021-05-20, state 2021-05-20",2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wbelief_children_immune,FALSE,smoothed_wbelief_children_immune,FALSE,Belief Children Can't Get COVID-19,FALSE,Estimated percentage of people who believe that the statement “Children cannot get COVID-19” is definitely or probably true.,"Estimated percentage of people who believe that the statement “Children cannot get COVID-19” is definitely or probably true. - -Based on survey item I2. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-15, msa 2022-02-17, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#belief-experience-and-information-indicators,fb-survey -fb-survey,smoothed_wbelief_children_immune,TRUE,smoothed_belief_children_immune,FALSE,Belief Children Can't Get COVID-19 (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-15, msa 2022-02-17, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wbelief_created_small_group,FALSE,smoothed_wbelief_created_small_group,FALSE,Belief COVID-19 Deliberately Created to Manipulate Events,FALSE,Estimated percentage of people who believe that the statement “COVID-19 was deliberately created by a small group of people who secretly manipulate world events” is definitely or probably true.,"Estimated percentage of people who believe that the statement “COVID-19 was deliberately created by a small group of people who secretly manipulate world events” is definitely or probably true. - -Based on survey item I3. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#belief-experience-and-information-indicators,fb-survey -fb-survey,smoothed_wbelief_created_small_group,TRUE,smoothed_belief_created_small_group,FALSE,Belief COVID-19 Deliberately Created to Manipulate Events (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wbelief_distancing_effective,FALSE,smoothed_wbelief_distancing_effective,FALSE,Belief Social Distancing is Effective,FALSE,Estimated percentage of respondents who believe that social distancing is either very or moderately effective for preventing the spread of COVID-19.,"Estimated percentage of respondents who believe that social distancing is either very or moderately effective for preventing the spread of COVID-19. - -Based on survey item G2. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#belief-experience-and-information-indicators,fb-survey -fb-survey,smoothed_wbelief_distancing_effective,TRUE,smoothed_belief_distancing_effective,FALSE,Belief Social Distancing is Effective (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wbelief_govt_exploitation,FALSE,smoothed_wbelief_govt_exploitation,FALSE,Belief COVID-19 Exploited to Control People,FALSE,Estimated percentage of people who indicate that the statement “The COVID-19 pandemic is being exploited by the government to control people” is definitely or probably true.,"Estimated percentage of people who indicate that the statement “The COVID-19 pandemic is being exploited by the government to control people” is definitely or probably true. - -Based on survey item I4. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#belief-experience-and-information-indicators,fb-survey -fb-survey,smoothed_wbelief_govt_exploitation,TRUE,smoothed_belief_govt_exploitation,FALSE,Belief COVID-19 Exploited to Control People (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wbelief_masking_effective,FALSE,smoothed_wbelief_masking_effective,FALSE,Belief Masks Are Effective,FALSE,Estimated percentage of respondents who believe that wearing a face mask is either very or moderately effective for preventing the spread of COVID-19.,"Estimated percentage of respondents who believe that wearing a face mask is either very or moderately effective for preventing the spread of COVID-19. - -Based on survey item G2. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#belief-experience-and-information-indicators,fb-survey -fb-survey,smoothed_wbelief_masking_effective,TRUE,smoothed_belief_masking_effective,FALSE,Belief Masks Are Effective (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wbelief_vaccinated_mask_unnecessary,FALSE,smoothed_wbelief_vaccinated_mask_unnecessary,FALSE,Belief Vaccines Make Masks Unnecessary,FALSE,Estimated percentage of people who believe that the statement “Getting the COVID-19 vaccine means that you can stop wearing a mask around people outside your household” is definitely or probably true.,"Estimated percentage of people who believe that the statement “Getting the COVID-19 vaccine means that you can stop wearing a mask around people outside your household” is definitely or probably true. - -Based on survey item I1. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-15, msa 2022-02-17, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#belief-experience-and-information-indicators,fb-survey -fb-survey,smoothed_wbelief_vaccinated_mask_unnecessary,TRUE,smoothed_belief_vaccinated_mask_unnecessary,FALSE,Belief Vaccines Make Masks Unnecessary (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-15, msa 2022-02-17, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wcovid_vaccinated,FALSE,smoothed_wcovid_vaccinated,FALSE,COVID-19 Vaccinated,FALSE,Estimated percentage of respondents who have already received a vaccine for COVID-19.,"Estimated percentage of respondents who have already received a vaccine for COVID-19. - -Note: The Centers for Disease Control compiles data on vaccine administration across the United States. This signal may differ from CDC data because of survey biases and should not be treated as authoritative. However, the survey signal is not subject to the lags and reporting problems in official vaccination data.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-01-06,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey -fb-survey,smoothed_wcovid_vaccinated,TRUE,smoothed_covid_vaccinated,FALSE,COVID-19 Vaccinated (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-01-06,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wcovid_vaccinated_appointment_or_accept,FALSE,smoothed_wcovid_vaccinated_appointment_or_accept,FALSE,"COVID-19 Vaccine Acceptance: Vaccinated, Appointment, or Accept",FALSE,"Estimated percentage of respondents who either have already received a COVID vaccine, have an appointment to receive a COVID vaccine, or would definitely or probably choose to receive one if it were offered to them today.","Estimated percentage of respondents who either have already received a COVID vaccine, have an appointment to receive a COVID vaccine, or would definitely or probably choose to receive one if it were offered to them today. -",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,"[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators) -[Wave 11 revision updates](https://cmu-delphi.github.io/delphi-epidata/symptom-survey/coding.html#wave-11)",fb-survey -fb-survey,smoothed_wcovid_vaccinated_appointment_or_accept,TRUE,smoothed_covid_vaccinated_appointment_or_accept,FALSE,"COVID-19 Vaccine Acceptance: Vaccinated, Appointment, or Accept (Unweighted)",FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wcovid_vaccinated_friends,FALSE,smoothed_wcovid_vaccinated_friends,FALSE,Friends and Family Vaccinated,FALSE,Estimated percentage of respondents who report that most of their friends and family have received a COVID-19 vaccine.,"Estimated percentage of respondents who report that most of their friends and family have received a COVID-19 vaccine. - -Based on survey item H3. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey -fb-survey,smoothed_wcovid_vaccinated_friends,TRUE,smoothed_covid_vaccinated_friends,FALSE,Friends and Family Vaccinated (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wcovid_vaccinated_or_accept,FALSE,smoothed_wcovid_vaccinated_or_accept,FALSE,COVID-19 Vaccinated or Vaccine Acceptance,FALSE,"Estimated percentage of respondents who either have already received a COVID vaccine or would definitely or probably choose to get vaccinated, if a vaccine were offered to them today.","Estimated percentage of respondents who either have already received a COVID vaccine or would definitely or probably choose to get vaccinated, if a vaccine were offered to them today. - -Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey -fb-survey,smoothed_wcovid_vaccinated_or_accept,TRUE,smoothed_covid_vaccinated_or_accept,FALSE,COVID-19 Vaccinated or Vaccine Acceptance (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wdelayed_care_cost,FALSE,smoothed_wdelayed_care_cost,FALSE,Delayed Healthcare Due to Cost,FALSE,Estimated percentage of respondents who have ever delayed or not sought medical care in the past year because of cost.,"Estimated percentage of respondents who have ever delayed or not sought medical care in the past year because of cost. - -Based on survey item K1. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#medical-care-experiences,fb-survey -fb-survey,smoothed_wdelayed_care_cost,TRUE,smoothed_delayed_care_cost,FALSE,Delayed Healthcare Due to Cost (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wdepressed_5d,FALSE,smoothed_wdepressed_5d,FALSE,Depressed (Last Five Days),FALSE,Estimated percentage of respondents who reported feeling depressed for most or all of the past 5 days.,"Estimated percentage of respondents who reported feeling depressed for most or all of the past 5 days. - -Discontinued as of Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mental-health-indicators,fb-survey -fb-survey,smoothed_wdepressed_5d,TRUE,smoothed_depressed_5d,FALSE,Depressed (Last Five Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wdepressed_7d,FALSE,smoothed_wdepressed_7d,FALSE,Depressed (Last Seven Days),FALSE,Estimated percentage of respondents who reported feeling depressed for most or all of the past 7 days.,"Estimated percentage of respondents who reported feeling depressed for most or all of the past 7 days. - -This item was shown to respondents starting in Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mental-health-indicators,fb-survey -fb-survey,smoothed_wdepressed_7d,TRUE,smoothed_depressed_7d,FALSE,Depressed (Last Seven Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wdontneed_reason_dont_spend_time,FALSE,smoothed_wdontneed_reason_dont_spend_time,FALSE,Vaccine Not Needed: Do Not Spend Time,FALSE,Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they don't spend time with high-risk people,"Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they don't spend time with high-risk people, among respondents who provided at least one reason for why they believe a COVID-19 vaccine is unnecessary.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-25,"End dates vary by geo: county 2022-06-25, hrr 2022-06-19, msa 2022-06-25, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-believing-vaccine-is-unnecessary,fb-survey -fb-survey,smoothed_wdontneed_reason_dont_spend_time,TRUE,smoothed_dontneed_reason_dont_spend_time,FALSE,Vaccine Not Needed: Do Not Spend Time (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-27,"End dates vary by geo: county 2022-06-27, hrr 2022-06-19, msa 2022-06-26, nation 2022-06-27, state 2022-06-27",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wdontneed_reason_had_covid,FALSE,smoothed_wdontneed_reason_had_covid,FALSE,Vaccine Not Needed: Had Covid,FALSE,Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they already had the illness,"Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they already had the illness, among respondents who provided at least one reason for why they believe a COVID-19 vaccine is unnecessary.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-25,"End dates vary by geo: county 2022-06-25, hrr 2022-06-19, msa 2022-06-25, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-believing-vaccine-is-unnecessary,fb-survey -fb-survey,smoothed_wdontneed_reason_had_covid,TRUE,smoothed_dontneed_reason_had_covid,FALSE,Vaccine Not Needed: Had Covid (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-27,"End dates vary by geo: county 2022-06-27, hrr 2022-06-19, msa 2022-06-26, nation 2022-06-27, state 2022-06-27",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wdontneed_reason_not_beneficial,FALSE,smoothed_wdontneed_reason_not_beneficial,FALSE,Vaccine Not Needed: Not Beneficial,FALSE,Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they don't think vaccines are beneficial,"Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they don't think vaccines are beneficial, among respondents who provided at least one reason for why they believe a COVID-19 vaccine is unnecessary.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-25,"End dates vary by geo: county 2022-06-25, hrr 2022-06-19, msa 2022-06-25, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-believing-vaccine-is-unnecessary,fb-survey -fb-survey,smoothed_wdontneed_reason_not_beneficial,TRUE,smoothed_dontneed_reason_not_beneficial,FALSE,Vaccine Not Needed: Not Beneficial (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-27,"End dates vary by geo: county 2022-06-27, hrr 2022-06-19, msa 2022-06-26, nation 2022-06-27, state 2022-06-27",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wdontneed_reason_not_high_risk,FALSE,smoothed_wdontneed_reason_not_high_risk,FALSE,Vaccine Not Needed: Not High Risk,FALSE,Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they are not in a high-risk group,"Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they are not in a high-risk group, among respondents who provided at least one reason for why they believe a COVID-19 vaccine is unnecessary.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-25,"End dates vary by geo: county 2022-06-25, hrr 2022-06-19, msa 2022-06-25, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-believing-vaccine-is-unnecessary,fb-survey -fb-survey,smoothed_wdontneed_reason_not_high_risk,TRUE,smoothed_dontneed_reason_not_high_risk,FALSE,Vaccine Not Needed: Not High Risk (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-27,"End dates vary by geo: county 2022-06-27, hrr 2022-06-19, msa 2022-06-26, nation 2022-06-27, state 2022-06-27",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wdontneed_reason_not_serious,FALSE,smoothed_wdontneed_reason_not_serious,FALSE,Vaccine Not Needed: Not Serious,FALSE,Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they don't believe COVID-19 is a serious illness,"Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they don't believe COVID-19 is a serious illness, among respondents who provided at least one reason for why they believe a COVID-19 vaccine is unnecessary.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-25,"End dates vary by geo: county 2022-06-25, hrr 2022-06-19, msa 2022-06-25, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-believing-vaccine-is-unnecessary,fb-survey -fb-survey,smoothed_wdontneed_reason_not_serious,TRUE,smoothed_dontneed_reason_not_serious,FALSE,Vaccine Not Needed: Not Serious (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-27,"End dates vary by geo: county 2022-06-27, hrr 2022-06-19, msa 2022-06-26, nation 2022-06-27, state 2022-06-27",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wdontneed_reason_other,FALSE,smoothed_wdontneed_reason_other,FALSE,Vaccine Not Needed: Other,FALSE,Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine for another reason,"Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine for another reason, among respondents who provided at least one reason for why they believe a COVID-19 vaccine is unnecessary.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-25,"End dates vary by geo: county 2022-06-25, hrr 2022-06-19, msa 2022-06-25, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-believing-vaccine-is-unnecessary,fb-survey -fb-survey,smoothed_wdontneed_reason_other,TRUE,smoothed_dontneed_reason_other,FALSE,Vaccine Not Needed: Other (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-27,"End dates vary by geo: county 2022-06-27, hrr 2022-06-19, msa 2022-06-26, nation 2022-06-27, state 2022-06-27",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wdontneed_reason_precautions,FALSE,smoothed_wdontneed_reason_precautions,FALSE,Vaccine Not Needed: Precautions,FALSE,"Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they will use other precautions, such as a mask, instead","Estimated percentage of respondents who say they don't need to get a COVID-19 vaccine because they will use other precautions, such as a mask, instead, among respondents who provided at least one reason for why they believe a COVID-19 vaccine is unnecessary.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-25,"End dates vary by geo: county 2022-06-25, hrr 2022-06-19, msa 2022-06-25, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-believing-vaccine-is-unnecessary,fb-survey -fb-survey,smoothed_wdontneed_reason_precautions,TRUE,smoothed_dontneed_reason_precautions,FALSE,Vaccine Not Needed: Precautions (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,"Start dates vary by geo: county 2021-02-09, hrr 2021-02-12, msa 2021-02-11, nation 2021-02-09, state 2021-02-09",2022-06-27,"End dates vary by geo: county 2022-06-27, hrr 2022-06-19, msa 2022-06-26, nation 2022-06-27, state 2022-06-27",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wfelt_isolated_5d,FALSE,smoothed_wfelt_isolated_5d,FALSE,Felt Isolated (Last Five Days),FALSE,"Estimated percentage of respondents who reported feeling ""isolated from others"" for most or all of the past 5 days.","Estimated percentage of respondents who reported feeling ""isolated from others"" for most or all of the past 5 days. - -Discontinued as of Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mental-health-indicators,fb-survey -fb-survey,smoothed_wfelt_isolated_5d,TRUE,smoothed_felt_isolated_5d,FALSE,Felt Isolated (Last Five Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wfelt_isolated_7d,FALSE,smoothed_wfelt_isolated_7d,FALSE,Felt Isolated (Last Seven Days),FALSE,"Estimated percentage of respondents who reported feeling ""isolated from others"" for most or all of the past 7 days.","Estimated percentage of respondents who reported feeling ""isolated from others"" for most or all of the past 7 days. - -This item was shown to respondents starting in Wave 10, March 2, 2021. - -Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2021-08-08,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mental-health-indicators,fb-survey -fb-survey,smoothed_wfelt_isolated_7d,TRUE,smoothed_felt_isolated_7d,FALSE,Felt Isolated (Last Seven Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2021-08-08,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_whad_covid_ever,FALSE,smoothed_whad_covid_ever,FALSE,Ever Had COVID-19,FALSE,Estimated percentage of people who report having ever had COVID-19.,"Estimated percentage of people who report having ever had COVID-19. - -Based on survey item B13. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",ascertained (case),"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,late,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#testing-indicators,fb-survey -fb-survey,smoothed_whad_covid_ever,TRUE,smoothed_had_covid_ever,FALSE,Ever Had COVID-19 (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",ascertained (case),"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,late,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_whesitancy_reason_allergic,FALSE,smoothed_whesitancy_reason_allergic,FALSE,Vaccine Hesitancy: Allergic,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they are worried about having an allergic reaction,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they are worried about having an allergic reaction, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. - -This item was shown to respondents starting in Wave 8, February 8, 2021. - -Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey -fb-survey,smoothed_whesitancy_reason_allergic,TRUE,smoothed_hesitancy_reason_allergic,FALSE,Vaccine Hesitancy: Allergic (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_whesitancy_reason_cost,FALSE,smoothed_whesitancy_reason_cost,FALSE,Vaccine Hesitancy: Cost,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they are worried about the cost,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they are worried about the cost, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. - -This item was shown to respondents starting in Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey -fb-survey,smoothed_whesitancy_reason_cost,TRUE,smoothed_hesitancy_reason_cost,FALSE,Vaccine Hesitancy: Cost (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_whesitancy_reason_dislike_vaccines,FALSE,smoothed_whesitancy_reason_dislike_vaccines,FALSE,Vaccine Hesitancy: Dislike Vaccines,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they dislike vaccines,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they dislike vaccines, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. - -This item was shown to respondents starting in Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-12-25,"End dates vary by geo: county 2021-12-24, hrr 2021-12-22, msa 2021-12-23, nation 2021-12-25, state 2021-12-24",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey -fb-survey,smoothed_whesitancy_reason_dislike_vaccines,TRUE,smoothed_hesitancy_reason_dislike_vaccines,FALSE,Vaccine Hesitancy: Dislike Vaccines (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-12-25,"End dates vary by geo: county 2021-12-24, hrr 2021-12-22, msa 2021-12-23, nation 2021-12-25, state 2021-12-24",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_whesitancy_reason_dislike_vaccines_generally,FALSE,smoothed_whesitancy_reason_dislike_vaccines_generally,FALSE,Vaccine Hesitance: Dislike Vaccines Generally,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they dislike vaccines generally,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they dislike vaccines generally, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. - -This item was shown to respondents starting in Wave 12, December 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-19, hrr 2021-12-20, msa 2021-12-20, nation 2021-12-19, state 2021-12-19",2022-06-25,NA,day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey -fb-survey,smoothed_whesitancy_reason_dislike_vaccines_generally,TRUE,smoothed_hesitancy_reason_dislike_vaccines_generally,FALSE,Vaccine Hesitance: Dislike Vaccines Generally (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-19, hrr 2021-12-20, msa 2021-12-20, nation 2021-12-19, state 2021-12-19",2022-06-27,NA,day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,NA,NA,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_whesitancy_reason_distrust_gov,FALSE,smoothed_whesitancy_reason_distrust_gov,FALSE,Vaccine Hesitancy: Distrust Government,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they don't trust the government,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they don't trust the government, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. - -This item was shown to respondents starting in Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey -fb-survey,smoothed_whesitancy_reason_distrust_gov,TRUE,smoothed_hesitancy_reason_distrust_gov,FALSE,Vaccine Hesitancy: Distrust Government (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_whesitancy_reason_distrust_vaccines,FALSE,smoothed_whesitancy_reason_distrust_vaccines,FALSE,Vaccine Hesitancy: Distrust Vaccines,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they don't trust COVID-19 vaccines,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they don't trust COVID-19 vaccines, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. - -This item was shown to respondents starting in Wave 8, February 8, 2021. - -Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey -fb-survey,smoothed_whesitancy_reason_distrust_vaccines,TRUE,smoothed_hesitancy_reason_distrust_vaccines,FALSE,Vaccine Hesitancy: Distrust Vaccines (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_whesitancy_reason_health_condition,FALSE,smoothed_whesitancy_reason_health_condition,FALSE,Vaccine Hesitancy: Health Condition,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they have a health condition that may impact the safety of a COVID-19 vaccine,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they have a health condition that may impact the safety of a COVID-19 vaccine, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. - -This item was shown to respondents starting in Wave 8, February 8, 2021. - -Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey -fb-survey,smoothed_whesitancy_reason_health_condition,TRUE,smoothed_hesitancy_reason_health_condition,FALSE,Vaccine Hesitancy: Health Condition (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_whesitancy_reason_ineffective,FALSE,smoothed_whesitancy_reason_ineffective,FALSE,Vaccine Hesitancy: Ineffective,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they don't know if a COVID-19 vaccine will work,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they don't know if a COVID-19 vaccine will work, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. - -This item was shown to respondents starting in Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey -fb-survey,smoothed_whesitancy_reason_ineffective,TRUE,smoothed_hesitancy_reason_ineffective,FALSE,Vaccine Hesitancy: Ineffective (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_whesitancy_reason_low_priority,FALSE,smoothed_whesitancy_reason_low_priority,FALSE,Vaccine Hesitancy: Low Priority,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they think other people need it more than they do,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they think other people need it more than they do, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. - -This item was shown to respondents starting in Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey -fb-survey,smoothed_whesitancy_reason_low_priority,TRUE,smoothed_hesitancy_reason_low_priority,FALSE,Vaccine Hesitancy: Low Priority (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_whesitancy_reason_not_recommended,FALSE,smoothed_whesitancy_reason_not_recommended,FALSE,Vaccine Hesitancy: Was Not Recommended,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because their doctor did not recommend it,"Estimated percentage of respondents who say they are hesitant to get vaccinated because their doctor did not recommend it, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. - -This item was shown to respondents starting in Wave 8, February 8, 2021. - -Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey -fb-survey,smoothed_whesitancy_reason_not_recommended,TRUE,smoothed_hesitancy_reason_not_recommended,FALSE,Vaccine Hesitancy: Was Not Recommended (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_whesitancy_reason_other,FALSE,smoothed_whesitancy_reason_other,FALSE,Vaccine Hesitancy: Other,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated for another reason,"Estimated percentage of respondents who say they are hesitant to get vaccinated for another reason, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. - -This item was shown to respondents starting in Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey -fb-survey,smoothed_whesitancy_reason_other,TRUE,smoothed_hesitancy_reason_other,FALSE,Vaccine Hesitancy: Other (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_whesitancy_reason_pregnant,FALSE,smoothed_whesitancy_reason_pregnant,FALSE,Vaccine Hesitancy: Pregnant,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they are pregnant or breastfeeding,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they are pregnant or breastfeeding, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. - -This item was shown to respondents starting in Wave 8, February 8, 2021. - -Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey -fb-survey,smoothed_whesitancy_reason_pregnant,TRUE,smoothed_hesitancy_reason_pregnant,FALSE,Vaccine Hesitancy: Pregnant (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_whesitancy_reason_religious,FALSE,smoothed_whesitancy_reason_religious,FALSE,Vaccine Hesitancy: Religious,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because it is against their religious beliefs,"Estimated percentage of respondents who say they are hesitant to get vaccinated because it is against their religious beliefs, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. - -This item was shown to respondents starting in Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey -fb-survey,smoothed_whesitancy_reason_religious,TRUE,smoothed_hesitancy_reason_religious,FALSE,Vaccine Hesitancy: Religious (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_whesitancy_reason_sideeffects,FALSE,smoothed_whesitancy_reason_sideeffects,FALSE,Vaccine Hesitancy: Side Effects,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they are worried about side effects,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they are worried about side effects, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. - -This item was shown to respondents starting in Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey -fb-survey,smoothed_whesitancy_reason_sideeffects,TRUE,smoothed_hesitancy_reason_sideeffects,FALSE,Vaccine Hesitancy: Side Effects (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_whesitancy_reason_unnecessary,FALSE,smoothed_whesitancy_reason_unnecessary,FALSE,Vaccine Hesitancy: Unnecessary,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they don't believe they need a COVID-19 vaccine,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they don't believe they need a COVID-19 vaccine, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. - -This item was shown to respondents starting in Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey -fb-survey,smoothed_whesitancy_reason_unnecessary,TRUE,smoothed_hesitancy_reason_unnecessary,FALSE,Vaccine Hesitancy: Unnecessary (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_whesitancy_reason_wait_safety,FALSE,smoothed_whesitancy_reason_wait_safety,FALSE,Vaccine Hesitancy: Wait For Safety,FALSE,Estimated percentage of respondents who say they are hesitant to get vaccinated because they want to wait to see if the COVID-19 vaccines are safe,"Estimated percentage of respondents who say they are hesitant to get vaccinated because they want to wait to see if the COVID-19 vaccines are safe, among respondents who answered ""Yes, probably"", ""No, probably not"", or ""No, definitely not"" when asked if they would get vaccinated if offered. - -This item was shown to respondents starting in Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey -fb-survey,smoothed_whesitancy_reason_wait_safety,TRUE,smoothed_hesitancy_reason_wait_safety,FALSE,Vaccine Hesitancy: Wait For Safety (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_winperson_school_fulltime,FALSE,smoothed_winperson_school_fulltime,FALSE,In-person School Full-time,FALSE,Estimated percentage of people who had any children attending in-person school on a full-time basis,"Estimated percentage of people who had any children attending in-person school on a full-time basis, among people reporting any pre-K-grade 12 children in their household.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-11-24,NA,2021-12-24,"End dates vary by geo: county 2021-12-24, hrr 2021-12-22, msa 2021-12-24, nation 2021-12-24, state 2021-12-24",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#schooling-indicators,fb-survey -fb-survey,smoothed_winperson_school_fulltime,TRUE,smoothed_inperson_school_fulltime,FALSE,In-person School Full-time (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-11-24,NA,2021-12-24,"End dates vary by geo: county 2021-12-24, hrr 2021-12-22, msa 2021-12-24, nation 2021-12-24, state 2021-12-24",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_winperson_school_fulltime_oldest,FALSE,smoothed_winperson_school_fulltime_oldest,FALSE,In-person School Full-time (Oldest Child),FALSE,Estimated percentage of people whose oldest child is attending in-person school on a full-time basis,"Estimated percentage of people whose oldest child is attending in-person school on a full-time basis, among people reporting any pre-K-grade 12 children in their household. - -This item was shown to respondents starting in Wave 12, December 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-19, hrr 2021-12-21, msa 2021-12-20, nation 2021-12-19, state 2021-12-19",2022-06-25,NA,day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#schooling-indicators,fb-survey -fb-survey,smoothed_winperson_school_fulltime_oldest,TRUE,smoothed_inperson_school_fulltime_oldest,FALSE,In-person School Full-time (Oldest Child) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-19, hrr 2021-12-21, msa 2021-12-20, nation 2021-12-19, state 2021-12-19",2022-06-27,NA,day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_winperson_school_parttime,FALSE,smoothed_winperson_school_parttime,FALSE,In-person School Part-time,FALSE,Estimated percentage of people who had any children attending in-person school on a part-time basis,"Estimated percentage of people who had any children attending in-person school on a part-time basis, among people reporting any pre-K-grade 12 children in their household.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-11-24,NA,2021-12-24,"End dates vary by geo: county 2021-12-24, hrr 2021-12-22, msa 2021-12-23, nation 2021-12-24, state 2021-12-24",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#schooling-indicators,fb-survey -fb-survey,smoothed_winperson_school_parttime,TRUE,smoothed_inperson_school_parttime,FALSE,In-person School Part-time (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-11-24,NA,2021-12-24,"End dates vary by geo: county 2021-12-24, hrr 2021-12-22, msa 2021-12-23, nation 2021-12-24, state 2021-12-24",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_winperson_school_parttime_oldest,FALSE,smoothed_winperson_school_parttime_oldest,FALSE,In-person School Part-time (Oldest Child),FALSE,Estimated percentage of people whose oldest child is attending in-person school on a part-time basis,"Estimated percentage of people whose oldest child is attending in-person school on a part-time basis, among people reporting any pre-K-grade 12 children in their household. - -This item was shown to respondents starting in Wave 12, December 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-19, hrr 2021-12-21, msa 2021-12-20, nation 2021-12-19, state 2021-12-19",2022-06-25,NA,day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#schooling-indicators,fb-survey -fb-survey,smoothed_winperson_school_parttime_oldest,TRUE,smoothed_inperson_school_parttime_oldest,FALSE,In-person School Part-time (Oldest Child) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-19, hrr 2021-12-21, msa 2021-12-20, nation 2021-12-19, state 2021-12-19",2022-06-27,NA,day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wlarge_event_1d,FALSE,smoothed_wlarge_event_1d,FALSE,Large Event (Last 24 Hours),FALSE,"Estimated percentage of respondents who ""attended an event with more than 10 people"" in the past 24 hours","Estimated percentage of respondents who ""attended an event with more than 10 people"" in the past 24 hours. - -This item was shown to respondents starting in Wave 4, September 8, 2020. - -Discontinued as of Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey -fb-survey,smoothed_wlarge_event_1d,TRUE,smoothed_large_event_1d,FALSE,Large Event (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wlarge_event_indoors_1d,FALSE,smoothed_wlarge_event_indoors_1d,FALSE,Large Event Indoors (Last 24 Hours),FALSE,"Estimated percentage of respondents who ""attended an indoor event with more than 10 people"" in the past 24 hours","Estimated percentage of respondents who ""attended an indoor event with more than 10 people"" in the past 24 hours. - -This item was shown to respondents starting in Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey -fb-survey,smoothed_wlarge_event_indoors_1d,TRUE,smoothed_large_event_indoors_1d,FALSE,Large Event Indoors (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wothers_distanced_public,FALSE,smoothed_wothers_distanced_public,FALSE,Other People Socially Distanced,FALSE,Estimated percentage of respondents who reported that all or most people they enountered in public in the past 7 days maintained a distance of at least 6 feet.,"Estimated percentage of respondents who reported that all or most people they enountered in public in the past 7 days maintained a distance of at least 6 feet. Respondents who said that they have not been in public for the past 7 days are excluded. - -Based on survey item H1. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey -fb-survey,smoothed_wothers_distanced_public,TRUE,smoothed_others_distanced_public,FALSE,Other People Socially Distanced (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wothers_masked,FALSE,smoothed_wothers_masked,FALSE,Other People Masked When Not Distanced,FALSE,"Estimated percentage of respondents who say that most or all other people wear masks, when they are in public and social distancing is not possible.","Estimated percentage of respondents who say that most or all other people wear masks, when they are in public and social distancing is not possible. - -This item was shown to respondents starting in Wave 5, November 24, 2020. - -Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-11-24,NA,2021-08-08,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mask-use,fb-survey -fb-survey,smoothed_wothers_masked,TRUE,smoothed_others_masked,FALSE,Other People Masked When Not Distanced (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-11-24,NA,2021-08-08,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wothers_masked_public,FALSE,smoothed_wothers_masked_public,FALSE,Other People Masked,FALSE,"Estimated percentage of respondents who say that most or all other people wear masks, when they are in public.","Estimated percentage of respondents who say that most or all other people wear masks, when they are in public. Respondents who said that they have not been in public for the past 7 days are excluded. - -Based on survey item H2. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mask-use,fb-survey -fb-survey,smoothed_wothers_masked_public,TRUE,smoothed_others_masked_public,FALSE,Other People Masked (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wpublic_transit_1d,FALSE,smoothed_wpublic_transit_1d,FALSE,Public Transit (Last 24 Hours),FALSE,"Estimated percentage of respondents who ""used public transit"" in the past 24 hours","Estimated percentage of respondents who ""used public transit"" in the past 24 hours - -This item was shown to respondents starting in Wave 4, September 8, 2020.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey -fb-survey,smoothed_wpublic_transit_1d,TRUE,smoothed_public_transit_1d,FALSE,Public Transit (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wrace_treated_fairly_healthcare,FALSE,smoothed_wrace_treated_fairly_healthcare,FALSE,Race Treated Fairly in Healthcare,FALSE,Estimated percentage of respondents who somewhat or strongly agree that people of their race are treated fairly in a healthcare setting.,"Estimated percentage of respondents who somewhat or strongly agree that people of their race are treated fairly in a healthcare setting. - -Based on survey item K2. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#medical-care-experiences,fb-survey -fb-survey,smoothed_wrace_treated_fairly_healthcare,TRUE,smoothed_race_treated_fairly_healthcare,FALSE,Race Treated Fairly in Healthcare (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wreceived_2_vaccine_doses,FALSE,smoothed_wreceived_2_vaccine_doses,FALSE,Received 2 Vaccine Doses,FALSE,Estimated percentage of respondents who have received two doses of a COVID-19 vaccine,"Estimated percentage of respondents who have received two doses of a COVID-19 vaccine, among respondents who have received either one or two doses of a COVID-19 vaccine. - -This item was shown to respondents starting in Wave 7, January 12, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-01-13,"Start dates vary by geo: county 2021-01-13, hrr 2021-01-14, msa 2021-01-13, nation 2021-01-13, state 2021-01-13",2021-11-14,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey -fb-survey,smoothed_wreceived_2_vaccine_doses,TRUE,smoothed_received_2_vaccine_doses,FALSE,Received 2 Vaccine Doses (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-01-13,"Start dates vary by geo: county 2021-01-13, hrr 2021-01-14, msa 2021-01-13, nation 2021-01-13, state 2021-01-13",2021-11-14,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wreceived_news_cdc,FALSE,smoothed_wreceived_news_cdc,FALSE,COVID News From CDC,FALSE,Estimated percentage of respondents who received news about COVID-19 from the CDC in the past 7 days.,"Estimated percentage of respondents who received news about COVID-19 from the CDC in the past 7 days. - -Based on survey item I5. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey -fb-survey,smoothed_wreceived_news_cdc,TRUE,smoothed_received_news_cdc,FALSE,COVID News From CDC (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wreceived_news_experts,FALSE,smoothed_wreceived_news_experts,FALSE,COVID News From Scientists,FALSE,Estimated percentage of respondents who received news about COVID-19 from scientists and other health experts in the past 7 days.,"Estimated percentage of respondents who received news about COVID-19 from scientists and other health experts in the past 7 days. - -Based on survey item I5. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey -fb-survey,smoothed_wreceived_news_experts,TRUE,smoothed_received_news_experts,FALSE,COVID News From Scientists (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wreceived_news_friends,FALSE,smoothed_wreceived_news_friends,FALSE,COVID News From Friends,FALSE,Estimated percentage of respondents who received news about COVID-19 from friends and family in the past 7 days.,"Estimated percentage of respondents who received news about COVID-19 from friends and family in the past 7 days. - -Based on survey item I5. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey -fb-survey,smoothed_wreceived_news_friends,TRUE,smoothed_received_news_friends,FALSE,COVID News From Friends (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wreceived_news_govt_health,FALSE,smoothed_wreceived_news_govt_health,FALSE,COVID News From Health Officials,FALSE,Estimated percentage of respondents who received news about COVID-19 from government health authorities or officials in the past 7 days.,"Estimated percentage of respondents who received news about COVID-19 from government health authorities or officials in the past 7 days. - -Based on survey item I5. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey -fb-survey,smoothed_wreceived_news_govt_health,TRUE,smoothed_received_news_govt_health,FALSE,COVID News From Health Officials (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wreceived_news_journalists,FALSE,smoothed_wreceived_news_journalists,FALSE,COVID News From Journalists,FALSE,Estimated percentage of respondents who received news about COVID-19 from journalists in the past 7 days.,"Estimated percentage of respondents who received news about COVID-19 from journalists in the past 7 days. - -Based on survey item I5. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey -fb-survey,smoothed_wreceived_news_journalists,TRUE,smoothed_received_news_journalists,FALSE,COVID News From Journalists (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wreceived_news_local_health,FALSE,smoothed_wreceived_news_local_health,FALSE,COVID News From Local Health Workers,FALSE,"Estimated percentage of respondents who received news about COVID-19 from local health workers, clinics, and community organizations in the past 7 days.","Estimated percentage of respondents who received news about COVID-19 from local health workers, clinics, and community organizations in the past 7 days. - -Based on survey item I5. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey -fb-survey,smoothed_wreceived_news_local_health,TRUE,smoothed_received_news_local_health,FALSE,COVID News From Local Health Workers (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wreceived_news_none,FALSE,smoothed_wreceived_news_none,FALSE,COVID News From None of Above,FALSE,Estimated percentage of respondents who in the past 7 days received news about COVID-19 from none of the listed sources in the question.,"Estimated percentage of respondents who in the past 7 days received news about COVID-19 from none of the listed sources in the question. - -Based on survey item I5. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey -fb-survey,smoothed_wreceived_news_none,TRUE,smoothed_received_news_none,FALSE,COVID News From None of Above (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wreceived_news_politicians,FALSE,smoothed_wreceived_news_politicians,FALSE,COVID News From Politicians,FALSE,Estimated percentage of respondents who received news about COVID-19 from politicians in the past 7 days.,"Estimated percentage of respondents who received news about COVID-19 from politicians in the past 7 days. - -Based on survey item I5. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey -fb-survey,smoothed_wreceived_news_politicians,TRUE,smoothed_received_news_politicians,FALSE,COVID News From Politicians (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wreceived_news_religious,FALSE,smoothed_wreceived_news_religious,FALSE,COVID News From Religious Leaders,FALSE,Estimated percentage of respondents who received news about COVID-19 from religious leaders in the past 7 days.,"Estimated percentage of respondents who received news about COVID-19 from religious leaders in the past 7 days. - -Based on survey item I5. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey -fb-survey,smoothed_wreceived_news_religious,TRUE,smoothed_received_news_religious,FALSE,COVID News From Religious Leaders (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wrestaurant_1d,FALSE,smoothed_wrestaurant_1d,FALSE,Restaurant (Last 24 Hours),FALSE,"Estimated percentage of respondents who went to a ""bar, restaurant, or cafe"" in the past 24 hours","Estimated percentage of respondents who went to a ""bar, restaurant, or cafe"" in the past 24 hours. - -This item was shown to respondents starting in Wave 4, September 8, 2020. - -Discontinued as of Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey -fb-survey,smoothed_wrestaurant_1d,TRUE,smoothed_restaurant_1d,FALSE,Restaurant (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wrestaurant_indoors_1d,FALSE,smoothed_wrestaurant_indoors_1d,FALSE,Restaurant Indoors (Last 24 Hours),FALSE,"Estimated percentage of respondents who went to an indoor ""bar, restaurant, or cafe"" in the past 24 hours","Estimated percentage of respondents who went to an indoor ""bar, restaurant, or cafe"" in the past 24 hours. - -This item was shown to respondents starting in Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey -fb-survey,smoothed_wrestaurant_indoors_1d,TRUE,smoothed_restaurant_indoors_1d,FALSE,Restaurant Indoors (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wscreening_tested_positive_14d,FALSE,smoothed_wscreening_tested_positive_14d,FALSE,Screening Tested Positive (Last 14 Days),FALSE,Estimated test positivity rate (percent) among people tested for COVID-19 in the past 14 days,"Estimated test positivity rate (percent) among people tested for COVID-19 in the past 14 days who were being screened with no symptoms or known exposure. - -Note: Until Wave 11 (May 19, 2021), this included people who said they were tested while receiving other medical care, because their employer or school required it, after attending a large outdoor gathering, or prior to visiting friends or family. After that date, this includes people who said they were tested while receiving other medical care, because their employer or school required it, prior to visiting friends or family, or prior to domestic or international travel.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-19,NA,2022-02-18,"End dates vary by geo: county 2022-02-16, hrr 2022-02-03, msa 2022-02-12, nation 2022-02-18, state 2022-02-16",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",ascertained (case),"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#testing-indicators,fb-survey -fb-survey,smoothed_wscreening_tested_positive_14d,TRUE,smoothed_screening_tested_positive_14d,FALSE,Screening Tested Positive (Last 14 Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-19,NA,2022-02-18,"End dates vary by geo: county 2022-02-16, hrr 2022-02-03, msa 2022-02-12, nation 2022-02-18, state 2022-02-16",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",ascertained (case),"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wshop_1d,FALSE,smoothed_wshop_1d,FALSE,Shop (Last 24 Hours),FALSE,"Estimated percentage of respondents who went to a ""market, grocery store, or pharmacy"" in the past 24 hours","Estimated percentage of respondents who went to a ""market, grocery store, or pharmacy"" in the past 24 hours - -Discontinued as of Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey -fb-survey,smoothed_wshop_1d,TRUE,smoothed_shop_1d,FALSE,Shop (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wshop_indoors_1d,FALSE,smoothed_wshop_indoors_1d,FALSE,Shop Indoors (Last 24 Hours),FALSE,"Estimated percentage of respondents who went to an ""indoor market, grocery store, or pharmacy"" in the past 24 hours","Estimated percentage of respondents who went to an ""indoor market, grocery store, or pharmacy"" in the past 24 hours - -This item was shown to respondents starting in Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey -fb-survey,smoothed_wshop_indoors_1d,TRUE,smoothed_shop_indoors_1d,FALSE,Shop Indoors (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wspent_time_1d,FALSE,smoothed_wspent_time_1d,FALSE,Spent Time (Last 24 Hours),FALSE,"Estimated percentage of respondents who ""spent time with someone who isn't currently staying with you"" in the past 24 hours","Estimated percentage of respondents who ""spent time with someone who isn't currently staying with you"" in the past 24 hours - -Discontinued as of Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey -fb-survey,smoothed_wspent_time_1d,TRUE,smoothed_spent_time_1d,FALSE,Spent Time (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wspent_time_indoors_1d,FALSE,smoothed_wspent_time_indoors_1d,FALSE,Spent Time Indoors (Last 24 Hours),FALSE,"Estimated percentage of respondents who ""spent time indoors with someone who isn't currently staying with you"" in the past 24 hours","Estimated percentage of respondents who ""spent time indoors with someone who isn't currently staying with you"" in the past 24 hours - -This item was shown to respondents starting in Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey -fb-survey,smoothed_wspent_time_indoors_1d,TRUE,smoothed_spent_time_indoors_1d,FALSE,Spent Time Indoors (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wtested_14d,FALSE,smoothed_wtested_14d,FALSE,Tested (Last 14 Days),FALSE,"Estimated percentage of people who were tested for COVID-19 in the past 14 days, regardless of their test result",NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#testing-indicators,fb-survey -fb-survey,smoothed_wtested_14d,TRUE,smoothed_tested_14d,FALSE,Tested (Last 14 Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wtested_positive_14d,FALSE,smoothed_wtested_positive_14d,FALSE,Tested Positive (Last 14 Days),FALSE,Estimated test positivity rate (percent) among people tested for COVID-19 in the past 14 days,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,"Start dates vary by geo: county 2020-09-08, hrr 2020-09-09, msa 2020-09-08, nation 2020-09-08, state 2020-09-08",2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",ascertained (case),"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#testing-indicators,fb-survey -fb-survey,smoothed_wtested_positive_14d,TRUE,smoothed_tested_positive_14d,FALSE,Tested Positive (Last 14 Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,"Start dates vary by geo: county 2020-09-08, hrr 2020-09-09, msa 2020-09-08, nation 2020-09-08, state 2020-09-08",2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",ascertained (case),"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wtravel_outside_state_5d,FALSE,smoothed_wtravel_outside_state_5d,FALSE,Travel Outside State (Last 5 Days),FALSE,Estimated percentage of respondents who report traveling outside their state in the past 5 days,"Estimated percentage of respondents who report traveling outside their state in the past 5 days - -Discontinued as of Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-06,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.",Data is available for about 45% of counties. Data is available for all states and some territories. Availability declines over time as survey response rate decreases,Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey -fb-survey,smoothed_wtravel_outside_state_5d,TRUE,smoothed_travel_outside_state_5d,FALSE,Travel Outside State (Last 5 Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-04-06,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.",Data is available for about 45% of counties. Data is available for all states and some territories. Availability declines over time as survey response rate decreases,Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wtravel_outside_state_7d,FALSE,smoothed_wtravel_outside_state_7d,FALSE,Travel Outside State (Last 7 Days),FALSE,Estimated percentage of respondents who report traveling outside their state in the past 7 days.,"Estimated percentage of respondents who report traveling outside their state in the past 7 days. - -This item was shown to respondents starting in Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-02-20,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-20, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey -fb-survey,smoothed_wtravel_outside_state_7d,TRUE,smoothed_travel_outside_state_7d,FALSE,Travel Outside State (Last 7 Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-02-20,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-20, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wtrust_covid_info_cdc,FALSE,smoothed_wtrust_covid_info_cdc,FALSE,Trust COVID Info From CDC,FALSE,Estimated percentage of respondents who trust the Centers for Disease Control (CDC) to provide accurate news and information about COVID-19.,"Estimated percentage of respondents who trust the Centers for Disease Control (CDC) to provide accurate news and information about COVID-19. - -Based on survey item I6. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey -fb-survey,smoothed_wtrust_covid_info_cdc,TRUE,smoothed_trust_covid_info_cdc,FALSE,Trust COVID Info From CDC (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wtrust_covid_info_doctors,FALSE,smoothed_wtrust_covid_info_doctors,FALSE,Trust COVID Info From Doctors,FALSE,Estimated percentage of respondents who trust doctors and other health professionals they go to for medical care to provide accurate news and information about COVID-19.,"Estimated percentage of respondents who trust doctors and other health professionals they go to for medical care to provide accurate news and information about COVID-19. - -Based on survey item I6. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey -fb-survey,smoothed_wtrust_covid_info_doctors,TRUE,smoothed_trust_covid_info_doctors,FALSE,Trust COVID Info From Doctors (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wtrust_covid_info_experts,FALSE,smoothed_wtrust_covid_info_experts,FALSE,Trust COVID Info From Scientists,FALSE,Estimated percentage of respondents who trust scientists and other health experts to provide accurate news and information about COVID-19.,"Estimated percentage of respondents who trust scientists and other health experts to provide accurate news and information about COVID-19. - -Based on survey item I6. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey -fb-survey,smoothed_wtrust_covid_info_experts,TRUE,smoothed_trust_covid_info_experts,FALSE,Trust COVID Info From Scientists (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wtrust_covid_info_friends,FALSE,smoothed_wtrust_covid_info_friends,FALSE,Trust COVID Info From Friends,FALSE,Estimated percentage of respondents who trust friends and family to provide accurate news and information about COVID-19.,"Estimated percentage of respondents who trust friends and family to provide accurate news and information about COVID-19. - -Based on survey item I6. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey -fb-survey,smoothed_wtrust_covid_info_friends,TRUE,smoothed_trust_covid_info_friends,FALSE,Trust COVID Info From Friends (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wtrust_covid_info_govt_health,FALSE,smoothed_wtrust_covid_info_govt_health,FALSE,Trust COVID Info From Health Officials,FALSE,Estimated percentage of respondents who trust government health officials to provide accurate news and information about COVID-19.,"Estimated percentage of respondents who trust government health officials to provide accurate news and information about COVID-19. - -Based on survey item I6. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey -fb-survey,smoothed_wtrust_covid_info_govt_health,TRUE,smoothed_trust_covid_info_govt_health,FALSE,Trust COVID Info From Health Officials (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wtrust_covid_info_journalists,FALSE,smoothed_wtrust_covid_info_journalists,FALSE,Trust COVID Info From Journalists,FALSE,Estimated percentage of respondents who trust journalists to provide accurate news and information about COVID-19.,"Estimated percentage of respondents who trust journalists to provide accurate news and information about COVID-19. - -Based on survey item I6. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey -fb-survey,smoothed_wtrust_covid_info_journalists,TRUE,smoothed_trust_covid_info_journalists,FALSE,Trust COVID Info From Journalists (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wtrust_covid_info_politicians,FALSE,smoothed_wtrust_covid_info_politicians,FALSE,Trust COVID Info From Politicians,FALSE,Estimated percentage of respondents who trust politicians to provide accurate news and information about COVID-19.,"Estimated percentage of respondents who trust politicians to provide accurate news and information about COVID-19. - -Based on survey item I6. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey -fb-survey,smoothed_wtrust_covid_info_politicians,TRUE,smoothed_trust_covid_info_politicians,FALSE,Trust COVID Info From Politicians (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wtrust_covid_info_religious,FALSE,smoothed_wtrust_covid_info_religious,FALSE,Trust COVID Info From Religious Leaders,FALSE,Estimated percentage of respondents who trust religious leaders to provide accurate news and information about COVID-19.,"Estimated percentage of respondents who trust religious leaders to provide accurate news and information about COVID-19. - -Based on survey item I6. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#sources-of-news,fb-survey -fb-survey,smoothed_wtrust_covid_info_religious,TRUE,smoothed_trust_covid_info_religious,FALSE,Trust COVID Info From Religious Leaders (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wtry_vaccinate_1m,FALSE,smoothed_wtry_vaccinate_1m,FALSE,Will Get COVID-19 Vaccine Within a Month,FALSE,"Estimated percentage of respondents who report that they will try to get the COVID-19 vaccine within a week to a month, among unvaccinated respondents who do not have a vaccination appointment and who are uncertain about getting vaccinated (i.e. did not say they definitely would get vaccinated, nor that they definitely would not).","Estimated percentage of respondents who report that they will try to get the COVID-19 vaccine within a week to a month, among unvaccinated respondents who do not have a vaccination appointment and who are uncertain about getting vaccinated (i.e. did not say they definitely would get vaccinated, nor that they definitely would not). - -Based on survey item V16. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,"Start dates vary by geo: county 2021-06-04, hrr 2021-06-06, msa 2021-06-04, nation 2021-06-04, state 2021-06-04",2022-06-25,"End dates vary by geo: county 2022-06-25, hrr 2022-02-24, msa 2022-05-24, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey -fb-survey,smoothed_wtry_vaccinate_1m,TRUE,smoothed_try_vaccinate_1m,FALSE,Will Get COVID-19 Vaccine Within a Month (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,"Start dates vary by geo: county 2021-06-04, hrr 2021-06-06, msa 2021-06-04, nation 2021-06-04, state 2021-06-04",2022-06-27,"End dates vary by geo: county 2022-06-27, hrr 2022-02-24, msa 2022-05-25, nation 2022-06-27, state 2022-06-27",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccinate_child_oldest,FALSE,smoothed_wvaccinate_child_oldest,FALSE,Will Vaccinate Oldest Child for COVID-19,FALSE,Estimated percentage of respondents with children who report that they will definitely or probably get the vaccine for their oldest child.,"Estimated percentage of respondents with children who report that they will definitely or probably get the vaccine for their oldest child. - -Based on survey item P3. This item was shown to respondents starting in Wave 12, December 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-19, hrr 2021-12-21, msa 2021-12-20, nation 2021-12-19, state 2021-12-19",2022-06-25,NA,day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey -fb-survey,smoothed_wvaccinate_child_oldest,TRUE,smoothed_vaccinate_child_oldest,FALSE,Will Vaccinate Oldest Child for COVID-19 (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-19, hrr 2021-12-21, msa 2021-12-20, nation 2021-12-19, state 2021-12-19",2022-06-27,NA,day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccinate_children,FALSE,smoothed_wvaccinate_children,FALSE,Will Vaccinate Children for COVID-19,FALSE,Estimated percentage of respondents with children who report that they will definitely or probably get the vaccine for their children.,"Estimated percentage of respondents with children who report that they will definitely or probably get the vaccine for their children. - -Based on survey item E4. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2021-12-25,"End dates vary by geo: county 2021-12-24, hrr 2021-12-23, msa 2021-12-24, nation 2021-12-25, state 2021-12-24",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#vaccination-indicators,fb-survey -fb-survey,smoothed_wvaccinate_children,TRUE,smoothed_vaccinate_children,FALSE,Will Vaccinate Children for COVID-19 (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2021-12-25,"End dates vary by geo: county 2021-12-24, hrr 2021-12-23, msa 2021-12-24, nation 2021-12-25, state 2021-12-24",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_appointment_location,FALSE,smoothed_wvaccine_barrier_appointment_location,FALSE,Vaccine Barrier: Appointment Locations,FALSE,"Estimated percentage of respondents who report available appointment locations as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report available appointment locations as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. - -Based on survey items V15a and V15b. This item was shown to respondents starting in Wave 12, December 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_appointment_location,TRUE,smoothed_vaccine_barrier_appointment_location,FALSE,Vaccine Barrier: Appointment Locations (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_appointment_location_has,FALSE,smoothed_wvaccine_barrier_appointment_location_has,FALSE,Vaccine Barrier (Among Vaccinated): Appointment Locations,FALSE,"Estimated percentage of respondents who report available appointment locations as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report available appointment locations as a barrier to getting the vaccine, among those who have already been vaccinated. - -Based on survey item V15a. This item was shown to respondents starting in Wave 12, December 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_appointment_location_has,TRUE,smoothed_vaccine_barrier_appointment_location_has,FALSE,Vaccine Barrier (Among Vaccinated): Appointment Locations (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,NA,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_appointment_location_tried,FALSE,smoothed_wvaccine_barrier_appointment_location_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Appointment Locations,FALSE,"Estimated percentage of respondents who report available appointment locations as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report available appointment locations as a barrier to getting the vaccine, among those who have tried to get vaccinated. - -Based on survey item V15b. This item was shown to respondents starting in Wave 12, December 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-24, nation 2021-12-19, state 2021-12-24",2022-06-25,NA,day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_appointment_location_tried,TRUE,smoothed_vaccine_barrier_appointment_location_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Appointment Locations (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-24, nation 2021-12-19, state 2021-12-24",2022-06-27,"End dates vary by geo: county 2022-06-25, nation 2022-06-27, state 2022-06-25",day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,NA,NA,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_appointment_time,FALSE,smoothed_wvaccine_barrier_appointment_time,FALSE,Vaccine Barrier: Appointment Times,FALSE,"Estimated percentage of respondents who report lack of vaccine or vaccine appointments as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report lack of vaccine or vaccine appointments as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. - -Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_appointment_time,TRUE,smoothed_vaccine_barrier_appointment_time,FALSE,Vaccine Barrier: Appointment Times (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_appointment_time_has,FALSE,smoothed_wvaccine_barrier_appointment_time_has,FALSE,Vaccine Barrier (Among Vaccinated): Appointment Times,FALSE,"Estimated percentage of respondents who report available appointment times as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report available appointment times as a barrier to getting the vaccine, among those who have already been vaccinated. - -Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_appointment_time_has,TRUE,smoothed_vaccine_barrier_appointment_time_has,FALSE,Vaccine Barrier (Among Vaccinated): Appointment Times (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_appointment_time_tried,FALSE,smoothed_wvaccine_barrier_appointment_time_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Appointment Times,FALSE,"Estimated percentage of respondents who report available appointment times as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report available appointment times as a barrier to getting the vaccine, among those who have tried to get vaccinated. - -Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_appointment_time_tried,TRUE,smoothed_vaccine_barrier_appointment_time_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Appointment Times (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_childcare,FALSE,smoothed_wvaccine_barrier_childcare,FALSE,Vaccine Barrier: Childcare,FALSE,"Estimated percentage of respondents who report lack of childcare as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report lack of childcare as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. - -Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_childcare,TRUE,smoothed_vaccine_barrier_childcare,FALSE,Vaccine Barrier: Childcare (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_childcare_has,FALSE,smoothed_wvaccine_barrier_childcare_has,FALSE,Vaccine Barrier (Among Vaccinated): Childcare,FALSE,"Estimated percentage of respondents who report lack of childcare as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report lack of childcare as a barrier to getting the vaccine, among those who have already been vaccinated. - -Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_childcare_has,TRUE,smoothed_vaccine_barrier_childcare_has,FALSE,Vaccine Barrier (Among Vaccinated): Childcare (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_childcare_tried,FALSE,smoothed_wvaccine_barrier_childcare_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Childcare,FALSE,"Estimated percentage of respondents who report lack of childcare as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report lack of childcare as a barrier to getting the vaccine, among those who have tried to get vaccinated. - -Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_childcare_tried,TRUE,smoothed_vaccine_barrier_childcare_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Childcare (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_document,FALSE,smoothed_wvaccine_barrier_document,FALSE,Vaccine Barrier: Documents,FALSE,"Estimated percentage of respondents who report inability to provide required documents as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report inability to provide required documents as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. - -Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_document,TRUE,smoothed_vaccine_barrier_document,FALSE,Vaccine Barrier: Documents (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_document_has,FALSE,smoothed_wvaccine_barrier_document_has,FALSE,Vaccine Barrier (Among Vaccinated): Documents,FALSE,"Estimated percentage of respondents who report inability to provide required documents as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report inability to provide required documents as a barrier to getting the vaccine, among those who have already been vaccinated. - -Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_document_has,TRUE,smoothed_vaccine_barrier_document_has,FALSE,Vaccine Barrier (Among Vaccinated): Documents (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_document_tried,FALSE,smoothed_wvaccine_barrier_document_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Documents,FALSE,"Estimated percentage of respondents who report inability to provide required documents as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report inability to provide required documents as a barrier to getting the vaccine, among those who have tried to get vaccinated. - -Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_document_tried,TRUE,smoothed_vaccine_barrier_document_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Documents (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_eligible,FALSE,smoothed_wvaccine_barrier_eligible,FALSE,Vaccine Barrier: Eligibility,FALSE,"Estimated percentage of respondents who report eligibility requirements as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report eligibility requirements as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. - -Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_eligible,TRUE,smoothed_vaccine_barrier_eligible,FALSE,Vaccine Barrier: Eligibility (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_eligible_has,FALSE,smoothed_wvaccine_barrier_eligible_has,FALSE,Vaccine Barrier (Among Vaccinated): Eligibility,FALSE,"Estimated percentage of respondents who report eligibility requirements as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report eligibility requirements as a barrier to getting the vaccine, among those who have already been vaccinated. - -Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_eligible_has,TRUE,smoothed_vaccine_barrier_eligible_has,FALSE,Vaccine Barrier (Among Vaccinated): Eligibility (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_eligible_tried,FALSE,smoothed_wvaccine_barrier_eligible_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Eligibility,FALSE,"Estimated percentage of respondents who report eligibility requirements as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report eligibility requirements as a barrier to getting the vaccine, among those who have tried to get vaccinated. - -Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_eligible_tried,TRUE,smoothed_vaccine_barrier_eligible_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Eligibility (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_language,FALSE,smoothed_wvaccine_barrier_language,FALSE,Vaccine Barrier: Language,FALSE,"Estimated percentage of respondents who report information not being available in their native language as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report information not being available in their native language as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. - -Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_language,TRUE,smoothed_vaccine_barrier_language,FALSE,Vaccine Barrier: Language (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_language_has,FALSE,smoothed_wvaccine_barrier_language_has,FALSE,Vaccine Barrier (Among Vaccinated): Language,FALSE,"Estimated percentage of respondents who report information not being available in their native language as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report information not being available in their native language as a barrier to getting the vaccine, among those who have already been vaccinated. - -Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_language_has,TRUE,smoothed_vaccine_barrier_language_has,FALSE,Vaccine Barrier (Among Vaccinated): Language (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_language_tried,FALSE,smoothed_wvaccine_barrier_language_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Language,FALSE,"Estimated percentage of respondents who report information not being available in their native language as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report information not being available in their native language as a barrier to getting the vaccine, among those who have tried to get vaccinated. - -Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_language_tried,TRUE,smoothed_vaccine_barrier_language_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Language (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_no_appointments,FALSE,smoothed_wvaccine_barrier_no_appointments,FALSE,Vaccine Barrier: No Appointments,FALSE,"Estimated percentage of respondents who report lack of vaccine or vaccine appointments as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report lack of vaccine or vaccine appointments as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. - -Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_no_appointments,TRUE,smoothed_vaccine_barrier_no_appointments,FALSE,Vaccine Barrier: No Appointments (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_no_appointments_has,FALSE,smoothed_wvaccine_barrier_no_appointments_has,FALSE,Vaccine Barrier (Among Vaccinated): No Appointments,FALSE,"Estimated percentage of respondents who report lack of vaccine or vaccine appointments as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report lack of vaccine or vaccine appointments as a barrier to getting the vaccine, among those who have already been vaccinated. - -Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_no_appointments_has,TRUE,smoothed_vaccine_barrier_no_appointments_has,FALSE,Vaccine Barrier (Among Vaccinated): No Appointments (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_no_appointments_tried,FALSE,smoothed_wvaccine_barrier_no_appointments_tried,FALSE,Vaccine Barrier (Among Unvaccinated): No Appointments,FALSE,"Estimated percentage of respondents who report lack of vaccine or vaccine appointments as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report lack of vaccine or vaccine appointments as a barrier to getting the vaccine, among those who have tried to get vaccinated. - -Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_no_appointments_tried,TRUE,smoothed_vaccine_barrier_no_appointments_tried,FALSE,Vaccine Barrier (Among Unvaccinated): No Appointments (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_none,FALSE,smoothed_wvaccine_barrier_none,FALSE,Vaccine Barrier: None of Above,FALSE,"Estimated percentage of respondents who report experiencing none of the listed barriers to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report experiencing none of the listed barriers to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. - -Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_none,TRUE,smoothed_vaccine_barrier_none,FALSE,Vaccine Barrier: None of Above (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_none_has,FALSE,smoothed_wvaccine_barrier_none_has,FALSE,Vaccine Barrier (Among Vaccinated): None of Above,FALSE,"Estimated percentage of respondents who report experiencing none of the listed barriers to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report experiencing none of the listed barriers to getting the vaccine, among those who have already been vaccinated. - -Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_none_has,TRUE,smoothed_vaccine_barrier_none_has,FALSE,Vaccine Barrier (Among Vaccinated): None of Above (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_none_tried,FALSE,smoothed_wvaccine_barrier_none_tried,FALSE,Vaccine Barrier (Among Unvaccinated): None of Above,FALSE,"Estimated percentage of respondents who report experiencing none of the listed barriers to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report experiencing none of the listed barriers to getting the vaccine, among those who have tried to get vaccinated. - -Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_none_tried,TRUE,smoothed_vaccine_barrier_none_tried,FALSE,Vaccine Barrier (Among Unvaccinated): None of Above (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_other,FALSE,smoothed_wvaccine_barrier_other,FALSE,Vaccine Barrier: Other,FALSE,"Estimated percentage of respondents who report experiencing some other barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report experiencing some other barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. - -Based on survey items V15a and V15b. This item was shown to respondents starting in Wave 12, December 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_other,TRUE,smoothed_vaccine_barrier_other,FALSE,Vaccine Barrier: Other (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_other_has,FALSE,smoothed_wvaccine_barrier_other_has,FALSE,Vaccine Barrier (Among Vaccinated): Other,FALSE,"Estimated percentage of respondents who report experiencing some other barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report experiencing some other barrier to getting the vaccine, among those who have already been vaccinated. - -Based on survey item V15a. This item was shown to respondents starting in Wave 12, December 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_other_has,TRUE,smoothed_vaccine_barrier_other_has,FALSE,Vaccine Barrier (Among Vaccinated): Other (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_other_tried,FALSE,smoothed_wvaccine_barrier_other_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Other,FALSE,"Estimated percentage of respondents who report experiencing some other barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report experiencing some other barrier to getting the vaccine, among those who have tried to get vaccinated. - -Based on survey item V15b. This item was shown to respondents starting in Wave 12, December 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-24, nation 2021-12-19, state 2021-12-24",2022-06-25,NA,day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_other_tried,TRUE,smoothed_vaccine_barrier_other_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Other (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), state (by Delphi), nation (by Delphi)",2021-12-19,"Start dates vary by geo: county 2021-12-24, nation 2021-12-19, state 2021-12-24",2022-06-27,"End dates vary by geo: county 2022-06-25, nation 2022-06-27, state 2022-06-25",day,Day,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_technical_difficulties,FALSE,smoothed_wvaccine_barrier_technical_difficulties,FALSE,Vaccine Barrier: Technical Problems,FALSE,"Estimated percentage of respondents who report technical difficulties with the website or phone line as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report technical difficulties with the website or phone line as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. - -Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_technical_difficulties,TRUE,smoothed_vaccine_barrier_technical_difficulties,FALSE,Vaccine Barrier: Technical Problems (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_technical_difficulties_has,FALSE,smoothed_wvaccine_barrier_technical_difficulties_has,FALSE,Vaccine Barrier (Among Vaccinated): Technical Problems,FALSE,"Estimated percentage of respondents who report technical difficulties with the website or phone line as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report technical difficulties with the website or phone line as a barrier to getting the vaccine, among those who have already been vaccinated. - -Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_technical_difficulties_has,TRUE,smoothed_vaccine_barrier_technical_difficulties_has,FALSE,Vaccine Barrier (Among Vaccinated): Technical Problems (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_technical_difficulties_tried,FALSE,smoothed_wvaccine_barrier_technical_difficulties_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Technical Problems,FALSE,"Estimated percentage of respondents who report technical difficulties with the website or phone line as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report technical difficulties with the website or phone line as a barrier to getting the vaccine, among those who have tried to get vaccinated. - -Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_technical_difficulties_tried,TRUE,smoothed_vaccine_barrier_technical_difficulties_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Technical Problems (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_technology_access,FALSE,smoothed_wvaccine_barrier_technology_access,FALSE,Vaccine Barrier: Technology Access,FALSE,"Estimated percentage of respondents who report limited access to internet or phone as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report limited access to internet or phone as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. - -Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_technology_access,TRUE,smoothed_vaccine_barrier_technology_access,FALSE,Vaccine Barrier: Technology Access (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_technology_access_has,FALSE,smoothed_wvaccine_barrier_technology_access_has,FALSE,Vaccine Barrier (Among Vaccinated): Technology Access,FALSE,"Estimated percentage of respondents who report limited access to internet or phone as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report limited access to internet or phone as a barrier to getting the vaccine, among those who have already been vaccinated. - -Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_technology_access_has,TRUE,smoothed_vaccine_barrier_technology_access_has,FALSE,Vaccine Barrier (Among Vaccinated): Technology Access (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_technology_access_tried,FALSE,smoothed_wvaccine_barrier_technology_access_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Technology Access,FALSE,"Estimated percentage of respondents who report limited access to internet or phone as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report limited access to internet or phone as a barrier to getting the vaccine, among those who have tried to get vaccinated. - -Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_technology_access_tried,TRUE,smoothed_vaccine_barrier_technology_access_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Technology Access (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_time,FALSE,smoothed_wvaccine_barrier_time,FALSE,Vaccine Barrier: Time Off,FALSE,"Estimated percentage of respondents who report difficulty getting time away from work or school as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report difficulty getting time away from work or school as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. - -Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_time,TRUE,smoothed_vaccine_barrier_time,FALSE,Vaccine Barrier: Time Off (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_time_has,FALSE,smoothed_wvaccine_barrier_time_has,FALSE,Vaccine Barrier (Among Vaccinated): Time Off,FALSE,"Estimated percentage of respondents who report difficulty getting time away from work or school as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report difficulty getting time away from work or school as a barrier to getting the vaccine, among those who have already been vaccinated. - -Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_time_has,TRUE,smoothed_vaccine_barrier_time_has,FALSE,Vaccine Barrier (Among Vaccinated): Time Off (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_time_tried,FALSE,smoothed_wvaccine_barrier_time_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Time Off,FALSE,"Estimated percentage of respondents who report difficulty getting time away from work or school as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report difficulty getting time away from work or school as a barrier to getting the vaccine, among those who have tried to get vaccinated. - -Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_time_tried,TRUE,smoothed_vaccine_barrier_time_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Time Off (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_travel,FALSE,smoothed_wvaccine_barrier_travel,FALSE,Vaccine Barrier: Travel,FALSE,"Estimated percentage of respondents who report difficulty traveling to vaccination sites as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report difficulty traveling to vaccination sites as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. - -Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_travel,TRUE,smoothed_vaccine_barrier_travel,FALSE,Vaccine Barrier: Travel (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_travel_has,FALSE,smoothed_wvaccine_barrier_travel_has,FALSE,Vaccine Barrier (Among Vaccinated): Travel,FALSE,"Estimated percentage of respondents who report difficulty traveling to vaccination sites as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report difficulty traveling to vaccination sites as a barrier to getting the vaccine, among those who have already been vaccinated. - -Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_travel_has,TRUE,smoothed_vaccine_barrier_travel_has,FALSE,Vaccine Barrier (Among Vaccinated): Travel (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_travel_tried,FALSE,smoothed_wvaccine_barrier_travel_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Travel,FALSE,"Estimated percentage of respondents who report difficulty traveling to vaccination sites as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report difficulty traveling to vaccination sites as a barrier to getting the vaccine, among those who have tried to get vaccinated. - -Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_travel_tried,TRUE,smoothed_vaccine_barrier_travel_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Travel (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_type,FALSE,smoothed_wvaccine_barrier_type,FALSE,Vaccine Barrier: Vaccine Type,FALSE,"Estimated percentage of respondents who report available vaccine type as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated.","Estimated percentage of respondents who report available vaccine type as a barrier to getting the vaccine, among those who have already been vaccinated or have tried to get vaccinated. - -Based on survey items V15a and V15b. These items were shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_type,TRUE,smoothed_vaccine_barrier_type,FALSE,Vaccine Barrier: Vaccine Type (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-06-04,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_type_has,FALSE,smoothed_wvaccine_barrier_type_has,FALSE,Vaccine Barrier (Among Vaccinated): Vaccine Type,FALSE,"Estimated percentage of respondents who report available vaccine type as a barrier to getting the vaccine, among those who have already been vaccinated.","Estimated percentage of respondents who report available vaccine type as a barrier to getting the vaccine, among those who have already been vaccinated. - -Based on survey item V15a. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_type_has,TRUE,smoothed_vaccine_barrier_type_has,FALSE,Vaccine Barrier (Among Vaccinated): Vaccine Type (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,NA,2022-02-19,"End dates vary by geo: county 2022-02-18, hrr 2022-02-17, msa 2022-02-18, nation 2022-02-19, state 2022-02-18",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_barrier_type_tried,FALSE,smoothed_wvaccine_barrier_type_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Vaccine Type,FALSE,"Estimated percentage of respondents who report available vaccine type as a barrier to getting the vaccine, among those who have tried to get vaccinated.","Estimated percentage of respondents who report available vaccine type as a barrier to getting the vaccine, among those who have tried to get vaccinated. - -Based on survey item V15b. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-25,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-25, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#barriers-to-accessing-vaccination,fb-survey -fb-survey,smoothed_wvaccine_barrier_type_tried,TRUE,smoothed_vaccine_barrier_type_tried,FALSE,Vaccine Barrier (Among Unvaccinated): Vaccine Type (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-07-30,"Start dates vary by geo: county 2021-08-03, msa 2021-08-08, nation 2021-07-30, state 2021-08-03",2022-06-27,"End dates vary by geo: county 2022-06-25, msa 2021-09-19, nation 2022-06-27, state 2022-06-25",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_likely_doctors,FALSE,smoothed_wvaccine_likely_doctors,FALSE,Vaccine Likely: Doctors,FALSE,Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by doctors and other health professionals they go to for medical care,"Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by doctors and other health professionals they go to for medical care, among respondents who have not yet been vaccinated. - -Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#outreach-and-image,fb-survey -fb-survey,smoothed_wvaccine_likely_doctors,TRUE,smoothed_vaccine_likely_doctors,FALSE,Vaccine Likely: Doctors (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_likely_friends,FALSE,smoothed_wvaccine_likely_friends,FALSE,Vaccine Likely: Friends,FALSE,Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by friends and family,"Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by friends and family, among respondents who have not yet been vaccinated. - -Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#outreach-and-image,fb-survey -fb-survey,smoothed_wvaccine_likely_friends,TRUE,smoothed_vaccine_likely_friends,FALSE,Vaccine Likely: Friends (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_likely_govt_health,FALSE,smoothed_wvaccine_likely_govt_health,FALSE,Vaccine Likely: Government Health,FALSE,Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by government health officials,"Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by government health officials, among respondents who have not yet been vaccinated. - -Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#outreach-and-image,fb-survey -fb-survey,smoothed_wvaccine_likely_govt_health,TRUE,smoothed_vaccine_likely_govt_health,FALSE,Vaccine Likely: Government Health (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_likely_local_health,FALSE,smoothed_wvaccine_likely_local_health,FALSE,Vaccine Likely: Local Health,FALSE,Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by local health workers,"Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by local health workers, among respondents who have not yet been vaccinated. - -Discontinued as of Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-03-16,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#outreach-and-image,fb-survey -fb-survey,smoothed_wvaccine_likely_local_health,TRUE,smoothed_vaccine_likely_local_health,FALSE,Vaccine Likely: Local Health (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-03-16,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_likely_politicians,FALSE,smoothed_wvaccine_likely_politicians,FALSE,Vaccine Likely: Politicians,FALSE,Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by politicians,"Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by politicians, among respondents who have not yet been vaccinated. - -Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#outreach-and-image,fb-survey -fb-survey,smoothed_wvaccine_likely_politicians,TRUE,smoothed_vaccine_likely_politicians,FALSE,Vaccine Likely: Politicians (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wvaccine_likely_who,FALSE,smoothed_wvaccine_likely_who,FALSE,Vaccine Likely: WHO,FALSE,Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by the World Health Organization,"Estimated percentage of respondents who would be more likely to get a COVID-19 vaccine if it were recommended to them by the World Health Organization, among respondents who have not yet been vaccinated. - -Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#outreach-and-image,fb-survey -fb-survey,smoothed_wvaccine_likely_who,TRUE,smoothed_vaccine_likely_who,FALSE,Vaccine Likely: WHO (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-12-20,NA,2021-08-08,"End dates vary by geo: county 2021-08-08, hrr 2021-08-06, msa 2021-08-07, nation 2021-08-08, state 2021-08-08",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wwant_info_children_education,FALSE,smoothed_wwant_info_children_education,FALSE,Want Information: Education,FALSE,Estimated percentage of people who want more information about how to support their children’s education.,"Estimated percentage of people who want more information about how to support their children’s education. - -Based on survey item I7. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#desired-information,fb-survey -fb-survey,smoothed_wwant_info_children_education,TRUE,smoothed_want_info_children_education,FALSE,Want Information: Education (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wwant_info_covid_treatment,FALSE,smoothed_wwant_info_covid_treatment,FALSE,Want Information: COVID Treatment,FALSE,Estimated percentage of people who want more information about the treatment of COVID-19.,"Estimated percentage of people who want more information about the treatment of COVID-19. - -Based on survey item I7. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#desired-information,fb-survey -fb-survey,smoothed_wwant_info_covid_treatment,TRUE,smoothed_want_info_covid_treatment,FALSE,Want Information: COVID Treatment (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wwant_info_covid_variants,FALSE,smoothed_wwant_info_covid_variants,FALSE,Want Information: COVID Variants,FALSE,Estimated percentage of people who want more information about COVID-19 variants and mutations.,"Estimated percentage of people who want more information about COVID-19 variants and mutations. - -Based on survey item I7. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#desired-information,fb-survey -fb-survey,smoothed_wwant_info_covid_variants,TRUE,smoothed_want_info_covid_variants,FALSE,Want Information: COVID Variants (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wwant_info_employment,FALSE,smoothed_wwant_info_employment,FALSE,Want Information: Employment,FALSE,Estimated percentage of people who want more information about employment and other economic and financial issues.,"Estimated percentage of people who want more information about employment and other economic and financial issues. - -Based on survey item I7. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#desired-information,fb-survey -fb-survey,smoothed_wwant_info_employment,TRUE,smoothed_want_info_employment,FALSE,Want Information: Employment (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wwant_info_mental_health,FALSE,smoothed_wwant_info_mental_health,FALSE,Want Information: Mental Health,FALSE,Estimated percentage of people who want more information about how to maintain their mental health.,"Estimated percentage of people who want more information about how to maintain their mental health. - -Based on survey item I7. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#desired-information,fb-survey -fb-survey,smoothed_wwant_info_mental_health,TRUE,smoothed_want_info_mental_health,FALSE,Want Information: Mental Health (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wwant_info_none,FALSE,smoothed_wwant_info_none,FALSE,Want Information: None of Above,FALSE,Estimated percentage of people who want more information about none of the listed topics.,"Estimated percentage of people who want more information about none of the listed topics. - -Based on survey item I7. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#desired-information,fb-survey -fb-survey,smoothed_wwant_info_none,TRUE,smoothed_want_info_none,FALSE,Want Information: None of Above (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wwant_info_relationships,FALSE,smoothed_wwant_info_relationships,FALSE,Want Information: Relationships,FALSE,Estimated percentage of people who want more information about how to maintain their social relationships despite physical distancing.,"Estimated percentage of people who want more information about how to maintain their social relationships despite physical distancing. - -Based on survey item I7. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#desired-information,fb-survey -fb-survey,smoothed_wwant_info_relationships,TRUE,smoothed_want_info_relationships,FALSE,Want Information: Relationships (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wwant_info_vaccine_access,FALSE,smoothed_wwant_info_vaccine_access,FALSE,Want Information: Vaccine Access,FALSE,Estimated percentage of people who want more information about how to get a COVID-19 vaccine.,"Estimated percentage of people who want more information about how to get a COVID-19 vaccine. - -Based on survey item I7. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#desired-information,fb-survey -fb-survey,smoothed_wwant_info_vaccine_access,TRUE,smoothed_want_info_vaccine_access,FALSE,Want Information: Vaccine Access (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wwant_info_vaccine_types,FALSE,smoothed_wwant_info_vaccine_types,FALSE,Want Information: Vaccine Types,FALSE,Estimated percentage of people who want more information about different types of COVID-19 vaccines.,"Estimated percentage of people who want more information about different types of COVID-19 vaccines. - -Based on survey item I7. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#desired-information,fb-survey -fb-survey,smoothed_wwant_info_vaccine_types,TRUE,smoothed_want_info_vaccine_types,FALSE,Want Information: Vaccine Types (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wwanted_test_14d,FALSE,smoothed_wwanted_test_14d,FALSE,Wanted Test (Last 14 Days),FALSE,"Estimated percentage of people who wanted to be tested for COVID-19 in the past 14 days, out of people who were not tested in that time","Estimated percentage of people who wanted to be tested for COVID-19 in the past 14 days, out of people who were not tested in that time. - -Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-08-08,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#testing-indicators,fb-survey -fb-survey,smoothed_wwanted_test_14d,TRUE,smoothed_wanted_test_14d,FALSE,Wanted Test (Last 14 Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-08-08,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wwearing_mask,FALSE,smoothed_wwearing_mask,FALSE,People Wearing Masks (Last 5 Days),FALSE,Estimated percentage of people who wore a mask for most or all of the time while in public in the past 5 days; those not in public in the past 5 days are not counted.,"Estimated percentage of people who wore a mask for most or all of the time while in public in the past 5 days; those not in public in the past 5 days are not counted. - -Discontinued as of Wave 8, February 8, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-02-22,"End dates vary by geo: county 2021-02-21, hrr 2021-02-20, msa 2021-02-21, nation 2021-02-22, state 2021-02-21",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,"[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mask-use) -[Interpreting mask use in context](https://delphi.cmu.edu/blog/2020/12/13/are-masks-widely-used-in-public/) -[Wave 10 revision updates](https://cmu-delphi.github.io/delphi-epidata/symptom-survey/coding.html#wave-10)",fb-survey -fb-survey,smoothed_wwearing_mask,TRUE,smoothed_wearing_mask,FALSE,People Wearing Masks (Last 5 Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-02-22,"End dates vary by geo: county 2021-02-21, hrr 2021-02-20, msa 2021-02-21, nation 2021-02-22, state 2021-02-21",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wwearing_mask_7d,FALSE,smoothed_wwearing_mask_7d,FALSE,People Wearing Masks (Last 7 Days),FALSE,Estimated percentage of people who wore a mask for most or all of the time while in public in the past 7 days; those not in public in the past 7 days are not counted.,"{source_description} We also ask them if they wear a mask when they are in public. For this signal, we estimate the percentage of people who say they wear a mask most or all of the time when they are in public. - -This item was shown to respondents starting in Wave 8, February 8, 2021, replacing a 5-day version of the same question.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,"[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mask-use) -[Interpreting mask use in context](https://delphi.cmu.edu/blog/2020/12/13/are-masks-widely-used-in-public/) -[Wave 10 revision updates](https://cmu-delphi.github.io/delphi-epidata/symptom-survey/coding.html#wave-10)",fb-survey -fb-survey,smoothed_wwearing_mask_7d,TRUE,smoothed_wearing_mask_7d,FALSE,People Wearing Masks (Last 7 Days) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-02-09,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,good,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wwork_outside_home_1d,FALSE,smoothed_wwork_outside_home_1d,FALSE,Work Outside Home (Last 24 Hours),FALSE,Estimated percentage of respondents who worked or went to school outside their home in the past 24 hours,"Estimated percentage of respondents who worked or went to school outside their home in the past 24 hours. - -This item was shown to respondents starting in Wave 4, September 8, 2020. - -Discontinued as of Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey -fb-survey,smoothed_wwork_outside_home_1d,TRUE,smoothed_work_outside_home_1d,FALSE,Work Outside Home (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-03-18,"End dates vary by geo: county 2021-03-15, hrr 2021-03-11, msa 2021-03-14, nation 2021-03-18, state 2021-03-15",day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wwork_outside_home_indoors_1d,FALSE,smoothed_wwork_outside_home_indoors_1d,FALSE,Work Outside Home Indoors (Last 24 Hours),FALSE,Estimated percentage of respondents who worked or went to school outside their home in an indoor setting in the past 24 hours,"Estimated percentage of respondents who worked or went to school outside their home in an indoor setting in the past 24 hours. - -This item was shown to respondents starting in Wave 10, March 2, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#social-distancing-and-travel,fb-survey -fb-survey,smoothed_wwork_outside_home_indoors_1d,TRUE,smoothed_work_outside_home_indoors_1d,FALSE,Work Outside Home Indoors (Last 24 Hours) (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-03-02,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wworried_become_ill,FALSE,smoothed_wworried_become_ill,FALSE,Worried Become Ill,FALSE,"Estimated percentage of respondents who reported feeling very or somewhat worried that ""you or someone in your immediate family might become seriously ill from COVID-19""","Estimated percentage of respondents who reported feeling very or somewhat worried that ""you or someone in your immediate family might become seriously ill from COVID-19"". - -Discontinued as of Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-08-08,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mental-health-indicators,fb-survey -fb-survey,smoothed_wworried_become_ill,TRUE,smoothed_worried_become_ill,FALSE,Worried Become Ill (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2021-08-08,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wworried_catch_covid,FALSE,smoothed_wworried_catch_covid,FALSE,Worried About Catching COVID,FALSE,Estimated percentage of respondents worrying either a great deal or a moderate amount about catching COVID-19.,"Estimated percentage of respondents worrying either a great deal or a moderate amount about catching COVID-19. - -Based on survey item G1. This item was shown to respondents starting in Wave 11, May 19, 2021.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#desired-information,fb-survey -fb-survey,smoothed_wworried_catch_covid,TRUE,smoothed_worried_catch_covid,FALSE,Worried About Catching COVID (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-05-20,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,neutral,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wworried_finances,FALSE,smoothed_wworried_finances,FALSE,Worried Finances,FALSE,"Estimated percentage of respondents who report being very or somewhat worried about their ""household's finances for the next month""",NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#mental-health-indicators,fb-survey -fb-survey,smoothed_wworried_finances,TRUE,smoothed_worried_finances,FALSE,Worried Finances (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2020-09-08,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -fb-survey,smoothed_wworried_vaccine_side_effects,FALSE,smoothed_wworried_vaccine_side_effects,FALSE,Worried Vaccine Side Effects,FALSE,"Estimated percentage of respondents who are very or moderately concerned that they would ""experience a side effect from a COVID-19 vaccination.""","Estimated percentage of respondents who are very or moderately concerned that they would ""experience a side effect from a COVID-19 vaccination."" - -Note: Until Wave 10, March 2, 2021, all respondents answered this question, including those who had already received one or more doses of a COVID-19 vaccine; beginning on that date, only respondents who said they have not received a COVID vaccine are asked this question.",Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-01-13,NA,2022-06-25,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,TRUE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/fb-survey.html#reasons-for-hesitancy,fb-survey -fb-survey,smoothed_wworried_vaccine_side_effects,TRUE,smoothed_worried_vaccine_side_effects,FALSE,Worried Vaccine Side Effects (Unweighted),FALSE,NA,NA,Delphi US COVID-19 Trends and Impact Survey,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), nation (by Delphi)",2021-01-13,NA,2022-06-27,NA,day,Date,daily,1 day,"Daily, for 5 consecutive issues for each report date",Adult Facebook users,"None. However, contingency tables containing demographic breakdowns of survey data are available for download (https://cmu-delphi.github.io/delphi-epidata/symptom-survey/contingency-tables.html).",population,"Discarded if an estimate is based on fewer than 100 survey responses. For signals reported using a 7-day average (those beginning with 'smoothed_'), this means a geographic area must have at least 100 responses in 7 days to be reported. - - This affects some items more than others. For instance, some survey items are only asked of a subset of survey respondents. It also affects some geographic areas more than others, particularly rural areas with low population densities. When doing analysis of county-level data, one should be aware that missing counties are typically more rural and less populous than those present in the data, which may introduce bias into the analysis.","Geographic coverage varies widely by signal, with anywhere from 0.4% to 25% of counties available and 15% to 100% of states. A handful of signals are available for 40-50% of counties, and all states and some territories. Signals based on questions that were asked to a subset of survey respondents are available for fewer locations. Availability declines over time as survey response rate decreases. A missing value indicates no valid data OR, for test positivity, that the value was censored due to small sample size (<= 5)",Percentage,percent,public,bad,TRUE,FALSE,FALSE,TRUE,TRUE,public,public,CC BY,Delphi aggregated data has no use restrictions (CC BY). Raw data users must sign DUA with Delphi. Research purpose for all survey waves must be consistent with the consent language used in Wave 1. Part- or full-time Facebook employees not eligible to receive data access.,NA,NA,fb-survey -ght,raw_search,NA,raw_search,FALSE,COVID-Related Searches,FALSE,"Google search volume for COVID-related searches, in arbitrary units that are normalized for population","Google search volume for COVID-related searches, in arbitrary units that are normalized for population - -Discontinued March 8, 2021.",Google Health Trends,covid,Search volume,USA,"hrr (by Delphi), msa (by Delphi), dma, state",2020-02-01,NA,2021-03-04,NA,day,Date,daily,4-5 days,None,Google search users,None,population,"Reported as 0 query when search volume is below a certain threshold, as set by Google. Areas with low query volume hence exhibit jumps and zero-inflation, as small variations in the signal can cause it to be sometimes truncated to 0 and sometimes reported at its actual level",Data is available for all states.,Value,raw,public,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/ght.html,ght -ght,raw_search,NA,smoothed_search,FALSE,COVID-Related Searches (Gaussian smoothed),FALSE,NA,"{base_short_description), smoothed in time using a Gaussian linear smoother. - -Discontinued March 8, 2021.",Google Health Trends,covid,Search volume,USA,"hrr (by Delphi), msa (by Delphi), dma, state",2020-02-01,NA,2021-03-04,NA,day,Date,daily,4-5 days,None,Google search users,None,population,"Reported as 0 query when search volume is below a certain threshold, as set by Google. Areas with low query volume hence exhibit jumps and zero-inflation, as small variations in the signal can cause it to be sometimes truncated to 0 and sometimes reported at its actual level",Data is available for all states.,Value,raw,public,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,ght -google-survey,raw_cli,FALSE,raw_cli,FALSE,COVID-Like Illness,FALSE,Estimated percentage of people who know someone in their community with COVID-like illness.,"Estimated percentage of people who know someone in their community with COVID-like illness. - -Discontinued May 16, 2020.",Google Symptom Surveys,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi)",2020-04-11,NA,2020-05-14,NA,day,Date,daily,1-2 days,"Daily, for 3 consecutive issues for each report date","Google ad publisher website, Google's Opinions Reward app, and similar application users",None,symptomatic,Discarded when an estimate is based on fewer than 100 survey responses,Data is available for about 20% of counties Data is available for all states.,Value,raw,early,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-survey.html,google-survey -google-survey,raw_cli,TRUE,smoothed_cli,FALSE,COVID-Like Illness (7-day average),FALSE,NA,NA,Google Symptom Surveys,covid,Self-reported (survey),USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi)",2020-04-11,NA,2020-05-14,NA,day,Date,daily,1-2 days,"Daily, for 3 consecutive issues for each report date","Google ad publisher website, Google's Opinions Reward app, and similar application users",None,symptomatic,Discarded when an estimate is based on fewer than 100 survey responses,Data is available for about 20% of counties Data is available for all states.,Value,raw,early,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,google-survey -google-symptoms,ageusia_raw_search,FALSE,ageusia_raw_search,FALSE,Ageusia Searches,FALSE,"Google search volume for ageusia-related searches, in arbitrary units that are normalized for overall search users",NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-13,"Start dates vary by geo: county 2020-02-13, hhs 2020-02-14, hrr 2020-02-13, msa 2020-02-13, nation 2020-02-14, state 2020-02-13",2022-01-20,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 3-4% of counties. Data is available for about 85% of states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-symptoms.html,google-symptoms -google-symptoms,ageusia_raw_search,TRUE,ageusia_smoothed_search,TRUE,Ageusia Searches (7-day average),FALSE,NA,NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,2022-01-20,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 3-4% of counties. Data is available for about 85% of states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,google-symptoms -google-symptoms,anosmia_raw_search,FALSE,anosmia_raw_search,FALSE,Anosmia Searches,FALSE,"Google search volume for anosmia-related searches, in arbitrary units that are normalized for overall search users",NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-13,"Start dates vary by geo: county 2020-02-13, hhs 2020-02-14, hrr 2020-02-13, msa 2020-02-13, nation 2020-02-14, state 2020-02-13",2022-01-20,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 3-4% of counties. Data is available for about 85% of states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-symptoms.html,google-symptoms -google-symptoms,anosmia_raw_search,TRUE,anosmia_smoothed_search,TRUE,Anosmia Searches (7-day average),FALSE,NA,NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,2022-01-20,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 3-4% of counties. Data is available for about 85% of states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,google-symptoms -google-symptoms,s01_raw_search,FALSE,s01_raw_search,FALSE,"Searches for: Cough, Phlegm, Sputum, Upper respiratory tract infection",TRUE,"The average relative frequency of searches for Cough, Phlegm, Sputum, and Upper respiratory tract infection, in arbitrary units that are normalized against overall search patterns within each region.","The average relative frequency of searches for Cough, Phlegm, Sputum, and Upper respiratory tract infection, in arbitrary units that are normalized against overall search patterns within each region. - -The symptoms in this set showed positive correlation with cases, especially after Omicron was declared a variant of concern by the WHO.",Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-14,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 50% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-symptoms.html,google-symptoms -google-symptoms,s01_raw_search,TRUE,s01_smoothed_search,FALSE,"Searches for: Cough, Phlegm, Sputum, Upper respiratory tract infection (7-day average)",TRUE,NA,NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 50% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,google-symptoms -google-symptoms,s02_raw_search,FALSE,s02_raw_search,FALSE,"Searches for: Nasal congestion, Post nasal drip, Rhinorrhea, Sinusitis, Rhinitis, Common cold",TRUE,"The average relative frequency of searches for Nasal congestion, Post nasal drip, Rhinorrhea, Sinusitis, Rhinitis, and Common cold, in arbitrary units that are normalized against overall search patterns within each region.","The average relative frequency of searches for Nasal congestion, Post nasal drip, Rhinorrhea, Sinusitis, Rhinitis, and Common cold, in arbitrary units that are normalized against overall search patterns within each region. - -The symptoms in this set showed positive correlation with cases, especially after Omicron was declared a variant of concern by the WHO.",Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-14,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 65% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-symptoms.html,google-symptoms -google-symptoms,s02_raw_search,TRUE,s02_smoothed_search,FALSE,"Searches for: Nasal congestion, Post nasal drip, Rhinorrhea, Sinusitis, Rhinitis, Common cold (7-day average)",TRUE,NA,NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 65% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,google-symptoms -google-symptoms,s03_raw_search,FALSE,s03_raw_search,FALSE,"Searches for: Fever, Hyperthermia, Chills, Shivering, Low grade fever",TRUE,"The average relative frequency of searches for Fever, Hyperthermia, Chills, Shivering, and Low grade fever, in arbitrary units that are normalized against overall search patterns within each region.","The average relative frequency of searches for Fever, Hyperthermia, Chills, Shivering, and Low grade fever, in arbitrary units that are normalized against overall search patterns within each region. - -The symptoms in this set showed positive correlation with cases, especially after Omicron was declared a variant of concern by the WHO.",Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-14,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 50% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-symptoms.html,google-symptoms -google-symptoms,s03_raw_search,TRUE,s03_smoothed_search,FALSE,"Searches for: Fever, Hyperthermia, Chills, Shivering, Low grade fever (7-day average)",TRUE,NA,NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 50% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,google-symptoms -google-symptoms,s04_raw_search,FALSE,s04_raw_search,FALSE,"Searches for: Shortness of breath, Wheeze, Croup, Pneumonia, Asthma, Crackles, Acute bronchitis, Bronchitis",TRUE,"The average relative frequency of searches for Shortness of breath, Wheeze, Croup, Pneumonia, Asthma, Crackles, Acute bronchitis, and Bronchitis, in arbitrary units that are normalized against overall search patterns within each region.","The average relative frequency of searches for Shortness of breath, Wheeze, Croup, Pneumonia, Asthma, Crackles, Acute bronchitis, and Bronchitis, in arbitrary units that are normalized against overall search patterns within each region. - -The symptoms in this set showed positive correlation with cases, especially after Omicron was declared a variant of concern by the WHO.",Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-14,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 30% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-symptoms.html,google-symptoms -google-symptoms,s04_raw_search,TRUE,s04_smoothed_search,FALSE,"Searches for: Shortness of breath, Wheeze, Croup, Pneumonia, Asthma, Crackles, Acute bronchitis, Bronchitis (7-day average)",TRUE,NA,NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 30% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,google-symptoms -google-symptoms,s05_raw_search,FALSE,s05_raw_search,FALSE,"Searches for: Anosmia, Dysgeusia, Ageusia",TRUE,"The average relative frequency of searches for Anosmia, Dysgeusia, and Ageusia, in arbitrary units that are normalized against overall search patterns within each region.","The average relative frequency of searches for Anosmia, Dysgeusia, and Ageusia, in arbitrary units that are normalized against overall search patterns within each region. - -The symptoms in this set showed positive correlation with cases, especially after Omicron was declared a variant of concern by the WHO.",Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-14,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 3-4% of counties. Data is available for about 90% of states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-symptoms.html,google-symptoms -google-symptoms,s05_raw_search,TRUE,s05_smoothed_search,FALSE,"Searches for: Anosmia, Dysgeusia, Ageusia (7-day average)",TRUE,NA,NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 3-4% of counties. Data is available for about 90% of states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,google-symptoms -google-symptoms,s06_raw_search,FALSE,s06_raw_search,FALSE,"Searches for: Laryngitis, Sore throat, Throat irritation",TRUE,"The average relative frequency of searches for Laryngitis, Sore throat, and Throat irritation, in arbitrary units that are normalized against overall search patterns within each region.","The average relative frequency of searches for Laryngitis, Sore throat, and Throat irritation, in arbitrary units that are normalized against overall search patterns within each region. - -The symptoms in this set showed positive correlation with cases, especially after Omicron was declared a variant of concern by the WHO.",Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-14,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 30% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-symptoms.html,google-symptoms -google-symptoms,s06_raw_search,TRUE,s06_smoothed_search,FALSE,"Searches for: Laryngitis, Sore throat, Throat irritation (7-day average)",TRUE,NA,NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 30% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,google-symptoms -google-symptoms,scontrol_raw_search,FALSE,scontrol_raw_search,FALSE,"Searches for: Type 2 diabetes, Urinary tract infection, Hair loss, Candidiasis, Weight gain",TRUE,"The average relative frequency of searches for Type 2 diabetes, Urinary tract infection, Hair loss, Candidiasis, and Weight gain, in arbitrary units that are normalized against overall search patterns within each region.","The average relative frequency of searches for Type 2 diabetes, Urinary tract infection, Hair loss, Candidiasis, and Weight gain, in arbitrary units that are normalized against overall search patterns within each region. - -The symptoms in this set are not COVID-19 related. This signal is intended to be used as a negative control.",Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-14,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 45% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-symptoms.html,google-symptoms -google-symptoms,scontrol_raw_search,TRUE,scontrol_smoothed_search,FALSE,"Searches for: Type 2 diabetes, Urinary tract infection, Hair loss, Candidiasis, Weight gain (7-day average)",TRUE,NA,NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,Ongoing,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 45% of counties. Data is available for all states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,neutral,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,google-symptoms -google-symptoms,sum_anosmia_ageusia_raw_search,FALSE,sum_anosmia_ageusia_raw_search,FALSE,Sum Anosmia Ageusia Searches,FALSE,"The sum of Google search volume for anosmia and ageusia related searches, in arbitrary units that are normalized for overall search users",NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-13,"Start dates vary by geo: county 2020-02-13, hhs 2020-02-14, hrr 2020-02-13, msa 2020-02-13, nation 2020-02-14, state 2020-02-13",2022-01-20,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 3-4% of counties. Data is available for about 85% of states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/google-symptoms.html,google-symptoms -google-symptoms,sum_anosmia_ageusia_raw_search,TRUE,sum_anosmia_ageusia_smoothed_search,TRUE,Sum Anosmia Ageusia Searches (7-day average),FALSE,NA,NA,Google Symptoms Search Trends,covid,Search volume,USA,"county, hrr (by Delphi), msa (by Delphi), state, hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,2022-01-20,NA,day,Date,daily,4-7 days,None,Google search users,None,symptomatic,"Unavailable when daily volume in a region does not meet quality or privacy thresholds, as set by Google. Google also uses differential privacy, which adds artificial noise to the incoming data","Data is available for about 3-4% of counties. Data is available for about 85% of states. Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason",Value,raw,public,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Google Terms of Service (https://policies.google.com/terms),Google Terms of Service (https://policies.google.com/terms),NA,NA,google-symptoms -hhs,confirmed_admissions_covid_1d,FALSE,confirmed_admissions_covid_1d,FALSE,Confirmed COVID-19 Admissions per day,TRUE,Sum of adult and pediatric confirmed COVID-19 hospital admissions occurring each day.,The U.S. Department of Health & Human Services (HHS) receives reports from hospital systems on their capacity and admissions. This signal reports the number of adult and pediatric hospital admissions with confirmed COVID-19 occurring each day,U.S. Department of Health & Human Services,covid,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2019-12-31,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/hhs.html,hhs -hhs,confirmed_admissions_covid_1d,TRUE,confirmed_admissions_covid_1d_prop,FALSE,Confirmed COVID-19 Admissions per day (per 100k people),TRUE,NA,NA,U.S. Department of Health & Human Services,covid,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2019-12-31,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,NA,hhs -hhs,confirmed_admissions_covid_1d,NA,confirmed_admissions_covid_1d_7dav,TRUE,Confirmed COVID-19 Admissions per day (7-day average),TRUE,NA,NA,U.S. Department of Health & Human Services,covid,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2020-01-06,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,count,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,NA,hhs -hhs,confirmed_admissions_covid_1d,NA,confirmed_admissions_covid_1d_prop_7dav,FALSE,"Confirmed COVID-19 Admissions per day (7-day average, per 100k people)",TRUE,NA,NA,U.S. Department of Health & Human Services,covid,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2020-01-06,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,per100k,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,NA,hhs -hhs,confirmed_admissions_influenza_1d,NA,confirmed_admissions_influenza_1d,FALSE,Confirmed Influenza Admissions per day,TRUE,All confirmed influenza hospital admissions occurring each day.,The U.S. Department of Health & Human Services (HHS) receives reports from hospital systems on their capacity and admissions. This signal reports the number of adult and pediatric hospital admissions with confirmed influenza occurring each day,U.S. Department of Health & Human Services,flu,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2019-12-31,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/hhs.html,hhs -hhs,confirmed_admissions_influenza_1d,NA,confirmed_admissions_influenza_1d_7dav,FALSE,Confirmed Influenza Admissions per day (7-day average),TRUE,NA,NA,U.S. Department of Health & Human Services,flu,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2020-01-06,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,count,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,NA,hhs -hhs,confirmed_admissions_influenza_1d,NA,confirmed_admissions_influenza_1d_prop,FALSE,Confirmed Influenza Admissions per day (per 100k people),TRUE,NA,NA,U.S. Department of Health & Human Services,flu,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2019-12-31,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,NA,hhs -hhs,confirmed_admissions_influenza_1d,NA,confirmed_admissions_influenza_1d_prop_7dav,FALSE,"Confirmed Influenza Admissions per day (7-day average, per 100k people)",TRUE,NA,NA,U.S. Department of Health & Human Services,flu,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2020-01-06,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,per100k,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,NA,hhs -hhs,sum_confirmed_suspected_admissions_covid_1d,FALSE,sum_confirmed_suspected_admissions_covid_1d,FALSE,Confirmed and Suspected COVID-19 Admissions per day,TRUE,Sum of adult and pediatric confirmed and suspected COVID-19 hospital admissions occurring each day.,The U.S. Department of Health & Human Services (HHS) receives reports from hospital systems on their capacity and admissions. This signal reports the number of adult and pediatric hospital admissions with suspected COVID-19 occurring each day,U.S. Department of Health & Human Services,covid,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2019-12-31,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/hhs.html,hhs -hhs,sum_confirmed_suspected_admissions_covid_1d,TRUE,sum_confirmed_suspected_admissions_covid_1d_prop,FALSE,Confirmed and Suspected COVID-19 Admissions per day (per 100k people),TRUE,NA,NA,U.S. Department of Health & Human Services,covid,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2019-12-31,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,NA,hhs -hhs,sum_confirmed_suspected_admissions_covid_1d,NA,sum_confirmed_suspected_admissions_covid_1d_7dav,TRUE,Confirmed and Suspected COVID-19 Admissions per day (7-day average),TRUE,NA,NA,U.S. Department of Health & Human Services,covid,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2020-01-06,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,count,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,NA,hhs -hhs,sum_confirmed_suspected_admissions_covid_1d,NA,sum_confirmed_suspected_admissions_covid_1d_prop_7dav,FALSE,"Confirmed and Suspected COVID-19 Admissions per day (7-day average, per 100k people)",TRUE,NA,NA,U.S. Department of Health & Human Services,covid,Hospitalizations,USA,"state, hhs (by Delphi), nation (by Delphi)",2020-01-06,NA,Ongoing,NA,day,Date,weekly,5-11 days,"Monthly. Backfill is relatively uncommon in this dataset (80% of dates from November 1, 2020 onward are never touched after their first issue) and most such updates occur one to two weeks after information about a date is first published. In rare instances, a value may be updated 10 weeks or more after it is first published.",All,None,hospitalized,None,Data is available for all states and some territories.,Value,per100k,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,Public Domain US Government (https://www.usa.gov/government-works),Public Domain US Government (https://www.usa.gov/government-works),NA,NA,hhs -hospital-admissions,smoothed_covid19,FALSE,smoothed_covid19,FALSE,COVID-19 Admissions (EMR and Claims),FALSE,Estimated percentage of new hospital admissions with COVID-associated diagnoses,"Estimated percentage of new hospital admissions with COVID-associated diagnoses, based on counts of electronic medical records and claims from health system partners, smoothed in time using a Gaussian linear smoother. - -Discontinued October 1, 2020.",Hospital Admissions From Claims,covid,Inpatient insurance claims,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi)",2020-02-01,NA,2020-09-27,NA,day,Date,daily,3-4 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 7-13 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 57 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Optum network,None,hospitalized,Discarded if over a given 7-day period an estimate is computed with 500 or fewer observations,Data is available for about 35% of counties Data is available for all states.,Percentage,percent,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/hospital-admissions.html,hospital-admissions -hospital-admissions,smoothed_covid19,TRUE,smoothed_adj_covid19,FALSE,COVID-19 Admissions (EMR and Claims) (Day-adjusted),FALSE,NA,"{base_short_description}, based on counts of electronic medical records and claims from health system partners, smoothed in time using a Gaussian linear smoother, and adjusted to reduce day-of-week effects. - -Discontinued October 1, 2020.",Hospital Admissions From Claims,covid,Inpatient insurance claims,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi)",2020-02-01,NA,2020-09-27,NA,day,Date,daily,3-4 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 7-13 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 57 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Optum network,None,hospitalized,Discarded if over a given 7-day period an estimate is computed with 500 or fewer observations,Data is available for about 35% of counties Data is available for all states.,Percentage,percent,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf,NA,hospital-admissions -hospital-admissions,smoothed_covid19_from_claims,FALSE,smoothed_covid19_from_claims,FALSE,COVID-19 Admissions (Claims),TRUE,Estimated percentage of new hospital admissions with COVID-associated diagnoses,"Estimated percentage of new hospital admissions with COVID-associated diagnoses, based on counts of claims from health system partners, smoothed in time using a Gaussian linear smoother.",Hospital Admissions From Claims,covid,Inpatient insurance claims,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,Ongoing,NA,day,Date,daily,3-4 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 7-13 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 57 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Optum network,None,hospitalized,Discarded if over a given 7-day period an estimate is computed with 500 or fewer observations,Data is available for about 35% of counties Data is available for all states.,Percentage,percent,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/hospital-admissions.html,hospital-admissions -hospital-admissions,smoothed_covid19_from_claims,TRUE,smoothed_adj_covid19_from_claims,FALSE,COVID-19 Admissions (Claims) (Day-adjusted),TRUE,NA,"{base_short_description}, based on counts of claims from health system partners, smoothed in time using a Gaussian linear smoother, and adjusted to reduce day-of-week effects.",Hospital Admissions From Claims,covid,Inpatient insurance claims,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,Ongoing,NA,day,Date,daily,3-4 days,"Daily. The source experiences heavy backfill with data delayed for a couple of weeks. We expect estimates available for the most recent 7-13 days to change substantially in later data revisions (having a median delta of 10% or more). Estimates for dates more than 57 days in the past are expected to remain fairly static (having a median delta of 1% or less), as most major revisions have already occurred.",Nationwide Optum network,None,hospitalized,Discarded if over a given 7-day period an estimate is computed with 500 or fewer observations,Data is available for about 35% of counties Data is available for all states.,Percentage,percent,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf,NA,hospital-admissions -indicator-combination-cases-deaths,confirmed_cumulative_num,FALSE,confirmed_cumulative_num,FALSE,Confirmed COVID Cases (Cumulative),FALSE,Cumulative confirmed COVID cases,Confirmed COVID-19 cases as reported by [USAFacts](https://usafacts.org/visualizations/coronavirus-covid-19-spread-map/) and [JHU-CSSE](https://github.com/CSSEGISandData/COVID-19),Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,ascertained (case),None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,cases_testing,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/indicator-combination-inactive.html#compositional-signals-confirmed-cases-and-deaths,indicator-combination -indicator-combination-cases-deaths,confirmed_cumulative_num,TRUE,confirmed_7dav_incidence_num,TRUE,"Confirmed COVID Cases (Daily new, 7-day average)",FALSE,"Daily new confirmed COVID cases, 7-day average",NA,Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,ascertained (case),None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,cases_testing,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",NA,indicator-combination -indicator-combination-cases-deaths,confirmed_cumulative_num,TRUE,confirmed_7dav_incidence_prop,FALSE,"Confirmed COVID Cases (Daily new, 7-day average, per 100k people)",FALSE,"Daily new confirmed COVID cases, 7-day average, per 100k people",NA,Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,ascertained (case),None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,cases_testing,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",NA,indicator-combination -indicator-combination-cases-deaths,confirmed_cumulative_num,TRUE,confirmed_cumulative_prop,FALSE,"Confirmed COVID Cases (Cumulative, per 100k people)",FALSE,"Cumulative confirmed COVID cases, per 100k people",NA,Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,ascertained (case),None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,cases_testing,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",NA,indicator-combination -indicator-combination-cases-deaths,confirmed_cumulative_num,TRUE,confirmed_incidence_num,TRUE,Confirmed COVID Cases (Daily new),FALSE,Daily new confirmed COVID cases,NA,Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,ascertained (case),None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,cases_testing,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",NA,indicator-combination -indicator-combination-cases-deaths,confirmed_cumulative_num,TRUE,confirmed_incidence_prop,FALSE,"Confirmed COVID Cases (Daily new, per 100k people)",FALSE,"Daily new confirmed COVID cases, per 100k people",NA,Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,ascertained (case),None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,cases_testing,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",NA,indicator-combination -indicator-combination-cases-deaths,deaths_cumulative_num,FALSE,deaths_cumulative_num,FALSE,Confirmed COVID Deaths (Cumulative),FALSE,Cumulative confirmed COVID deaths,Confirmed COVID-19 deaths as reported by [USAFacts](https://usafacts.org/visualizations/coronavirus-covid-19-spread-map/) and [JHU-CSSE](https://github.com/CSSEGISandData/COVID-19),Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,dead,None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,cases_testing,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/indicator-combination-inactive.html#compositional-signals-confirmed-cases-and-deaths,indicator-combination -indicator-combination-cases-deaths,deaths_cumulative_num,TRUE,deaths_7dav_incidence_num,TRUE,"Confirmed COVID Deaths (Daily new, 7-day average)",FALSE,"Daily new confirmed COVID deaths, 7-day average",NA,Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,dead,None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,cases_testing,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",NA,indicator-combination -indicator-combination-cases-deaths,deaths_cumulative_num,TRUE,deaths_7dav_incidence_prop,FALSE,"Confirmed COVID Deaths (Daily new, 7-day average, per 100k people)",FALSE,"Daily new confirmed COVID deaths, 7-day average, per 100k people",NA,Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,dead,None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,cases_testing,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",NA,indicator-combination -indicator-combination-cases-deaths,deaths_cumulative_num,TRUE,deaths_cumulative_prop,FALSE,"Confirmed COVID Deaths (Cumulative, per 100k people)",FALSE,"Cumulative confirmed COVID deaths, per 100k people",NA,Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,dead,None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,cases_testing,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",NA,indicator-combination -indicator-combination-cases-deaths,deaths_cumulative_num,TRUE,deaths_incidence_num,TRUE,Confirmed COVID Deaths (Daily new),FALSE,Daily new confirmed COVID deaths,NA,Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,dead,None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,cases_testing,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",NA,indicator-combination -indicator-combination-cases-deaths,deaths_cumulative_num,TRUE,deaths_incidence_prop,FALSE,"Confirmed COVID Deaths (Daily new, per 100k people)",FALSE,"Daily new confirmed COVID deaths, per 100k people",NA,Composite COVID Cases & Deaths,covid,Deaths,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,"Start dates vary by geo: county 2020-02-20, hhs 2020-04-01, hrr 2020-02-20, msa 2020-02-20, nation 2020-04-01, state 2020-02-20",2021-11-12,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,dead,None. However underlying signals may perform their own censoring,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,cases_testing,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",NA,indicator-combination -indicator-combination-nmf,nmf_day_doc_fbc_fbs_ght,nmf_day_doc_fbc_fbs_ght,nmf_day_doc_fbc_fbs_ght,FALSE,NMF Combination (with community symptoms),FALSE,Rank-1 NMF approximation to reconstruct 4 other signals.,"This signal uses a rank-1 approximation, from a nonnegative matrix factorization approach, to identify an underlying signal that best reconstructs the Doctor Visits (smoothed_adj_cli), Facebook Symptoms surveys (smoothed_cli), Facebook Symptoms in Community surveys (smoothed_hh_cmnty_cli), and Search Trends (smoothed_search) indicators. It does not include official reports (cases and deaths from the jhu-csse source). Higher values of the combined signal correspond to higher values of the other indicators, but the scale (units) of the combination is arbitrary. Note that the Search Trends source is not available at the county level, so county values of this signal do not use it. - -Discontinued March 17, 2021.",Statistical Combination (NMF),covid,NA,USA,"county (by Delphi), msa (by Delphi), state (by Delphi)",2020-04-15,NA,2021-03-16,"End dates vary by geo: county 2021-03-16, msa 2021-03-16, state 2021-03-15",day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,infected,None. However underlying signals may perform their own censoring,Data is available for about 80% of counties Data is available for all states and some territories.,Value,raw,early,bad,FALSE,FALSE,FALSE,TRUE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/indicator-combination-inactive.html#statistical-combination-signals,indicator-combination -indicator-combination-nmf,nmf_day_doc_fbs_ght,nmf_day_doc_fbs_ght,nmf_day_doc_fbs_ght,FALSE,NMF Combination (without community symptoms),FALSE,Rank-1 NMF approximation to reconstruct 3 other signals.,"This signal uses a rank-1 approximation, from a nonnegative matrix factorization approach, to identify an underlying signal that best reconstructs the Doctor Visits (doctor-visits:smoothed_cli), Facebook Symptoms surveys (fb-surveys:smoothed_cli), and Search Trends (ght:smoothed_search) indicators. It does not include official reports (cases and deaths from the jhu-csse source). Higher values of the combined signal correspond to higher values of the other indicators, but the scale (units) of the combination is arbitrary. Note that the Search Trends source is not available at the county level, so county values of this signal do not use it. - -Discontinued May 28, 2020.",Statistical Combination (NMF),covid,NA,USA,"county (by Delphi), msa (by Delphi), state (by Delphi)",2020-04-06,NA,2020-05-26,NA,day,Date,NA,1-3 days,Daily,"This source is a combination of several signals representing different populations, and doesn't correspond to a single demographic group",None,infected,None. However underlying signals may perform their own censoring,Data is available for about 70% of counties Data is available for all states and some territories.,Value,raw,early,bad,FALSE,FALSE,FALSE,TRUE,FALSE,public,public,CC BY,CC BY,"see Doctor Visits, Facebook Survey, and Google Health Trends",https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/indicator-combination-inactive.html#statistical-combination-signals,indicator-combination -jhu-csse,confirmed_cumulative_num,FALSE,confirmed_cumulative_num,FALSE,Confirmed COVID Cases (Cumulative),FALSE,Cumulative confirmed COVID cases,Confirmed COVID-19 cases as reported by [JHU-CSSE](https://github.com/CSSEGISandData/COVID-19),Johns Hopkins University,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-22,"Start dates vary by geo: county 2020-01-22, hhs 2020-02-20, hrr 2020-01-22, msa 2020-01-22, nation 2020-02-20, state 2020-01-22",2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which - Delphi diffs to compute incidence. Raw cumulative figures are sometimes - corrected by adjusting the reported value for a single day, but revisions - do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,cases_testing,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/jhu-csse.html,jhu-csse -jhu-csse,confirmed_cumulative_num,TRUE,confirmed_7dav_incidence_num,TRUE,"Confirmed COVID Cases (Daily new, 7-day average)",FALSE,"Daily new confirmed COVID cases, 7-day average",NA,Johns Hopkins University,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which - Delphi diffs to compute incidence. Raw cumulative figures are sometimes - corrected by adjusting the reported value for a single day, but revisions - do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,cases_testing,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,jhu-csse -jhu-csse,confirmed_cumulative_num,TRUE,confirmed_7dav_incidence_prop,FALSE,"Confirmed COVID Cases (Daily new, 7-day average, per 100k people)",FALSE,"Daily new confirmed COVID cases, 7-day average, per 100k people",NA,Johns Hopkins University,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which - Delphi diffs to compute incidence. Raw cumulative figures are sometimes - corrected by adjusting the reported value for a single day, but revisions - do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,cases_testing,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,jhu-csse -jhu-csse,confirmed_cumulative_num,TRUE,confirmed_cumulative_prop,FALSE,"Confirmed COVID Cases (Cumulative, per 100k people)",FALSE,"Cumulative confirmed COVID cases, per 100k people",NA,Johns Hopkins University,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-22,"Start dates vary by geo: county 2020-01-22, hhs 2020-02-20, hrr 2020-01-22, msa 2020-01-22, nation 2020-02-20, state 2020-01-22",2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which - Delphi diffs to compute incidence. Raw cumulative figures are sometimes - corrected by adjusting the reported value for a single day, but revisions - do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,cases_testing,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,jhu-csse -jhu-csse,confirmed_cumulative_num,TRUE,confirmed_incidence_num,TRUE,Confirmed COVID Cases (Daily new),FALSE,Daily new confirmed COVID cases,NA,Johns Hopkins University,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-22,"Start dates vary by geo: county 2020-01-22, hhs 2020-02-20, hrr 2020-01-22, msa 2020-01-22, nation 2020-02-20, state 2020-01-22",2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which - Delphi diffs to compute incidence. Raw cumulative figures are sometimes - corrected by adjusting the reported value for a single day, but revisions - do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,cases_testing,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,jhu-csse -jhu-csse,confirmed_cumulative_num,TRUE,confirmed_incidence_prop,FALSE,"Confirmed COVID Cases (Daily new, per 100k people)",FALSE,"Daily new confirmed COVID cases, per 100k people",NA,Johns Hopkins University,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-22,"Start dates vary by geo: county 2020-01-22, hhs 2020-02-20, hrr 2020-01-22, msa 2020-01-22, nation 2020-02-20, state 2020-01-22",2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which - Delphi diffs to compute incidence. Raw cumulative figures are sometimes - corrected by adjusting the reported value for a single day, but revisions - do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,cases_testing,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,jhu-csse -jhu-csse,deaths_cumulative_num,FALSE,deaths_cumulative_num,FALSE,Confirmed COVID Deaths (Cumulative),FALSE,Cumulative confirmed COVID deaths,Confirmed COVID-19 deaths as reported by [JHU-CSSE](https://github.com/CSSEGISandData/COVID-19),Johns Hopkins University,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-22,"Start dates vary by geo: county 2020-01-22, hhs 2020-02-20, hrr 2020-01-22, msa 2020-01-22, nation 2020-02-20, state 2020-01-22",2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which - Delphi diffs to compute incidence. Raw cumulative figures are sometimes - corrected by adjusting the reported value for a single day, but revisions - do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,NA,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/jhu-csse.html,jhu-csse -jhu-csse,deaths_cumulative_num,TRUE,deaths_7dav_incidence_num,TRUE,"Confirmed COVID Deaths (Daily new, 7-day average)",FALSE,"Daily new confirmed COVID deaths, 7-day average",NA,Johns Hopkins University,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which - Delphi diffs to compute incidence. Raw cumulative figures are sometimes - corrected by adjusting the reported value for a single day, but revisions - do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,jhu-csse -jhu-csse,deaths_cumulative_num,TRUE,deaths_7dav_incidence_prop,FALSE,"Confirmed COVID Deaths (Daily new, 7-day average, per 100k people)",FALSE,"Daily new confirmed COVID deaths, 7-day average, per 100k people",NA,Johns Hopkins University,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-20,NA,2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which - Delphi diffs to compute incidence. Raw cumulative figures are sometimes - corrected by adjusting the reported value for a single day, but revisions - do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,jhu-csse -jhu-csse,deaths_cumulative_num,TRUE,deaths_cumulative_prop,FALSE,"Confirmed COVID Deaths (Cumulative, per 100k people)",FALSE,"Cumulative confirmed COVID deaths, per 100k people",NA,Johns Hopkins University,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-22,"Start dates vary by geo: county 2020-01-22, hhs 2020-02-20, hrr 2020-01-22, msa 2020-01-22, nation 2020-02-20, state 2020-01-22",2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which - Delphi diffs to compute incidence. Raw cumulative figures are sometimes - corrected by adjusting the reported value for a single day, but revisions - do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,jhu-csse -jhu-csse,deaths_cumulative_num,TRUE,deaths_incidence_num,TRUE,Confirmed COVID Deaths (Daily new),FALSE,Daily new confirmed COVID deaths,NA,Johns Hopkins University,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-22,"Start dates vary by geo: county 2020-01-22, hhs 2020-02-20, hrr 2020-01-22, msa 2020-01-22, nation 2020-02-20, state 2020-01-22",2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which - Delphi diffs to compute incidence. Raw cumulative figures are sometimes - corrected by adjusting the reported value for a single day, but revisions - do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,jhu-csse -jhu-csse,deaths_cumulative_num,TRUE,deaths_incidence_prop,FALSE,"Confirmed COVID Deaths (Daily new, per 100k people)",FALSE,"Daily new confirmed COVID deaths, per 100k people",NA,Johns Hopkins University,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-22,"Start dates vary by geo: county 2020-01-22, hhs 2020-02-20, hrr 2020-01-22, msa 2020-01-22, nation 2020-02-20, state 2020-01-22",2023-03-09,NA,day,Date,daily,1 day,"None. The raw data reports cumulative cases and deaths, which - Delphi diffs to compute incidence. Raw cumulative figures are sometimes - corrected by adjusting the reported value for a single day, but revisions - do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,jhu-csse -nchs-mortality,deaths_allcause_incidence_num,FALSE,deaths_allcause_incidence_num,FALSE,All Causes Deaths (Weekly new),TRUE,Number of weekly new deaths from all causes,"Number of weekly new deaths from all causes. - -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,n/a,Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html,nchs-mortality -nchs-mortality,deaths_allcause_incidence_num,TRUE,deaths_allcause_incidence_prop,FALSE,"All Causes Deaths (Weekly new, per 100k people)",TRUE,"Number of weekly new deaths from all causes, per 100k people","Number of weekly new deaths from all causes, per 100k people. - -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,n/a,Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,NA,nchs-mortality -nchs-mortality,deaths_covid_and_pneumonia_notflu_incidence_num,FALSE,deaths_covid_and_pneumonia_notflu_incidence_num,FALSE,COVID and Pneumonia excl. Influenza Deaths (Weekly new),TRUE,"Number of weekly new deaths involving COVID-19 and Pneumonia, excluding Influenza","Number of weekly new deaths involving COVID-19 and Pneumonia, excluding Influenza . - -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,"covid, pneumonia",Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html,nchs-mortality -nchs-mortality,deaths_covid_and_pneumonia_notflu_incidence_num,TRUE,deaths_covid_and_pneumonia_notflu_incidence_prop,FALSE,"COVID and Pneumonia excl. Influenza Deaths (Weekly new, per 100k people)",TRUE,"Number of weekly new deaths involving COVID-19 and Pneumonia, excluding Influenza, per 100k people","Number of weekly new deaths involving COVID-19 and Pneumonia, excluding Influenza, per 100k people. - -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,covid,Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,NA,nchs-mortality -nchs-mortality,deaths_covid_incidence_num,FALSE,deaths_covid_incidence_num,FALSE,Confirmed or Presumed COVID Deaths (Weekly new),TRUE,Number of weekly new deaths with confirmed or presumed COVID-19,"Number of weekly new deaths with confirmed or presumed COVID-19 . - -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,covid,Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html,nchs-mortality -nchs-mortality,deaths_covid_incidence_num,TRUE,deaths_covid_incidence_prop,FALSE,"Confirmed or Presumed COVID Deaths (Weekly new, per 100k people)",TRUE,"Number of weekly new deaths with confirmed or presumed COVID-19, per 100k people","Number of weekly new deaths with confirmed or presumed COVID-19, per 100k people. - -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,covid,Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,NA,nchs-mortality -nchs-mortality,deaths_flu_incidence_num,FALSE,deaths_flu_incidence_num,FALSE,Influenza Deaths (Weekly new),TRUE,"Number of weekly new deaths involving Influenza and at least one of (Pneumonia, COVID-19)","Number of weekly new deaths involving Influenza and at least one of (Pneumonia, COVID-19). - -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,flu,Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html,nchs-mortality -nchs-mortality,deaths_flu_incidence_num,TRUE,deaths_flu_incidence_prop,FALSE,"Influenza Deaths (Weekly new, per 100k people)",TRUE,"Number of weekly new deaths involving Influenza and at least one of (Pneumonia, COVID-19), per 100k people","Number of weekly new deaths involving Influenza and at least one of (Pneumonia, COVID-19), per 100k people. - -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,flu,Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,NA,nchs-mortality -nchs-mortality,deaths_percent_of_expected,FALSE,deaths_percent_of_expected,FALSE,Percentage of Expected Deaths,TRUE,Weekly new deaths for all causes in 2020 as a percentage of the average number across the same week in 2017-2019.,"Weekly new deaths for all causes in 2020 as a percentage of the average number across the same week in 2017-2019.. - -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,n/a,Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Percentage,percent,late,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html,nchs-mortality -nchs-mortality,deaths_pneumonia_notflu_incidence_num,FALSE,deaths_pneumonia_notflu_incidence_num,FALSE,Pneumonia excl. Influenza Deaths (Weekly new),TRUE,"Number of weekly new deaths involving Pneumonia, excluding Influenza deaths","Number of weekly new deaths involving Pneumonia, excluding Influenza deaths . - -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,pneumonia,Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html,nchs-mortality -nchs-mortality,deaths_pneumonia_notflu_incidence_num,TRUE,deaths_pneumonia_notflu_incidence_prop,FALSE,"Pneumonia excl. Influenza Deaths (Weekly new, per 100k people)",TRUE,"Number of weekly new deaths involving Pneumonia, excluding Influenza deaths, per 100k people","Number of weekly new deaths involving Pneumonia, excluding Influenza deaths, per 100k people. - -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,pneumonia,Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,NA,nchs-mortality -nchs-mortality,deaths_pneumonia_or_flu_or_covid_incidence_num,FALSE,deaths_pneumonia_or_flu_or_covid_incidence_num,FALSE,"COVID, Pneumonia or Influenza Deaths (Weekly new)",TRUE,"Number of weekly new deaths involving Pneumonia, Influenza, or COVID-19","Number of weekly new deaths involving Pneumonia, Influenza, or COVID-19 . - -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,"pneumonia, flu, covid",Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html,nchs-mortality -nchs-mortality,deaths_pneumonia_or_flu_or_covid_incidence_num,TRUE,deaths_pneumonia_or_flu_or_covid_incidence_prop,FALSE,"COVID, Pneumonia or Influenza Deaths (Weekly new, per 100k people)",TRUE,"Number of weekly new deaths involving Pneumonia, Influenza, or COVID-19, per 100k people","Number of weekly new deaths involving Pneumonia, Influenza, or COVID-19, per 100k people. - -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,"pneumonia, flu, covid",Deaths,USA,"state, nation",2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),https://www.cdc.gov/nchs/data_access/restrictions.htm,NA,nchs-mortality -quidel-covid-ag,covid_ag_raw_pct_positive,FALSE,covid_ag_raw_pct_positive,FALSE,COVID-19 Antigen Tests: Percent Positive,TRUE,Percentage of antigen tests that were positive for COVID-19,"When a patient (whether at a doctor's office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19.",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests),quidel -quidel-covid-ag,covid_ag_raw_pct_positive,TRUE,covid_ag_smoothed_pct_positive,FALSE,COVID-19 Antigen Tests: Percent Positive (7-day average),TRUE,NA,NA,Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,NA,quidel -quidel-covid-ag,covid_ag_raw_pct_positive_age_0_17,FALSE,covid_ag_raw_pct_positive_age_0_17,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 0-17",TRUE,Percentage of antigen tests that were positive for COVID-19 among people ages 0-17,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 0-17",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests),quidel -quidel-covid-ag,covid_ag_raw_pct_positive_age_0_17,TRUE,covid_ag_smoothed_pct_positive_age_0_17,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 0-17 (Smoothed)",TRUE,NA,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 0-17, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,NA,quidel -quidel-covid-ag,covid_ag_raw_pct_positive_age_0_4,FALSE,covid_ag_raw_pct_positive_age_0_4,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 0-4",TRUE,Percentage of antigen tests that were positive for COVID-19 among people ages 0-4,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 0-4",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,"End dates vary by geo: county 2024-05-03, hhs 2024-05-03, hrr 2024-04-27, msa 2024-04-27, nation 2024-05-03, state 2024-05-03",day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests),quidel -quidel-covid-ag,covid_ag_raw_pct_positive_age_0_4,TRUE,covid_ag_smoothed_pct_positive_age_0_4,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 0-4 (Smoothed)",TRUE,NA,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 0-4, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,NA,quidel -quidel-covid-ag,covid_ag_raw_pct_positive_age_18_49,FALSE,covid_ag_raw_pct_positive_age_18_49,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 18-49",TRUE,Percentage of antigen tests that were positive for COVID-19 among people ages 18-49,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 18-49",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,"End dates vary by geo: county 2024-05-02, hhs 2024-05-02, hrr 2024-05-01, msa 2024-05-01, nation 2024-05-03, state 2024-05-02",day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests),quidel -quidel-covid-ag,covid_ag_raw_pct_positive_age_18_49,TRUE,covid_ag_smoothed_pct_positive_age_18_49,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 18-49 (Smoothed)",TRUE,NA,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 18-49, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,NA,quidel -quidel-covid-ag,covid_ag_raw_pct_positive_age_5_17,FALSE,covid_ag_raw_pct_positive_age_5_17,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 5-17",TRUE,Percentage of antigen tests that were positive for COVID-19 among people ages 5-17,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 5-17",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests),quidel -quidel-covid-ag,covid_ag_raw_pct_positive_age_5_17,TRUE,covid_ag_smoothed_pct_positive_age_5_17,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 5-17 (Smoothed)",TRUE,NA,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 5-17, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,NA,quidel -quidel-covid-ag,covid_ag_raw_pct_positive_age_50_64,FALSE,covid_ag_raw_pct_positive_age_50_64,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 50-64",TRUE,Percentage of antigen tests that were positive for COVID-19 among people ages 50-64,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 50-64",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,"End dates vary by geo: county 2024-05-01, hhs 2024-05-01, hrr 2024-05-01, msa 2024-05-01, nation 2024-05-03, state 2024-05-01",day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests),quidel -quidel-covid-ag,covid_ag_raw_pct_positive_age_50_64,TRUE,covid_ag_smoothed_pct_positive_age_50_64,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 50-64 (Smoothed)",TRUE,NA,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 50-64, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,NA,quidel -quidel-covid-ag,covid_ag_raw_pct_positive_age_65plus,FALSE,covid_ag_raw_pct_positive_age_65plus,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 65+",TRUE,Percentage of antigen tests that were positive for COVID-19 among people age 65 and above,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 65 and above",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,"End dates vary by geo: county 2024-04-19, hhs 2024-05-01, hrr 2024-04-19, msa 2024-04-19, nation 2024-05-03, state 2024-04-19",day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests),quidel -quidel-covid-ag,covid_ag_raw_pct_positive_age_65plus,TRUE,covid_ag_smoothed_pct_positive_age_65plus,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 65+ (Smoothed)",TRUE,NA,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 65 and above, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,NA,quidel -quidel-flu,raw_pct_negative,FALSE,raw_pct_negative,FALSE,Flu Tests: Percent Negative,FALSE,"The percentage of flu tests that are negative, suggesting the patient's illness has another cause, possibly COVID-19","The percentage of flu tests that are negative, suggesting the patient's illness has another cause, possibly COVID-19 . - -Discontinued May 19, 2020.",Quidel Inc. (Flu),flu,Testing,USA,"msa (by Delphi), state (by Delphi)",2020-01-31,NA,2020-05-10,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,None,population,"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,late,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#flu-tests,quidel -quidel-flu,raw_pct_negative,TRUE,smoothed_pct_negative,FALSE,Flu Tests: Percent Negative (7-day average),FALSE,NA,NA,Quidel Inc. (Flu),flu,Testing,USA,"msa (by Delphi), state (by Delphi)",2020-01-31,NA,2020-05-10,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,None,population,"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Percentage,percent,late,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,NA,quidel -quidel-flu,raw_tests_per_device,FALSE,raw_tests_per_device,FALSE,Flu Tests: Tests Per Device,FALSE,The average number of flu tests conducted by each testing device; measures volume of testing,"The average number of flu tests conducted by each testing device; measures volume of testing . - -Discontinued May 19, 2020.",Quidel Inc. (Flu),flu,Testing,USA,"msa (by Delphi), state (by Delphi)",2020-01-31,NA,2020-05-10,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,None,population,"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Number of Tests,count,late,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#flu-tests,quidel -quidel-flu,raw_tests_per_device,TRUE,smoothed_tests_per_device,FALSE,Flu Tests: Tests Per Device (7-day average),FALSE,NA,NA,Quidel Inc. (Flu),flu,Testing,USA,"msa (by Delphi), state (by Delphi)",2020-01-31,NA,2020-05-10,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,None,population,"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.",Number of Tests,count,late,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,NA,quidel -safegraph-daily,completely_home_prop,FALSE,completely_home_prop,FALSE,Completely Home,FALSE,The fraction of mobile devices that did not leave the immediate area of their home,"The fraction of mobile devices that did not leave the immediate area of their home. This is SafeGraph’s completely_home_device_count / device_count. - -Discontinued April 19th, 2021.",SafeGraph (Daily),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-12-01, hrr 2019-01-01, msa 2019-01-01, nation 2020-12-01, state 2019-01-01",2021-04-16,NA,day,Date,daily,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,public,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph -safegraph-daily,completely_home_prop,TRUE,completely_home_prop_7dav,FALSE,Completely Home (7-day average),FALSE,NA,NA,SafeGraph (Daily),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-12-01, hrr 2019-01-01, msa 2019-01-01, nation 2020-12-01, state 2019-01-01",2021-04-16,NA,day,Date,daily,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,public,neutral,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph -safegraph-daily,full_time_work_prop,FALSE,full_time_work_prop,FALSE,Full Time Work/School,FALSE,The fraction of mobile devices that spent more than 6 hours at one location other than their home during the daytime,"The fraction of mobile devices that spent more than 6 hours at one location other than their home during the daytime. This is SafeGraph’s full_time_work_behavior_devices / device_count. - -Discontinued April 19th, 2021.",SafeGraph (Daily),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-12-01, hrr 2019-01-01, msa 2019-01-01, nation 2020-12-01, state 2019-01-01",2021-04-16,NA,day,Date,daily,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,public,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph -safegraph-daily,full_time_work_prop,TRUE,full_time_work_prop_7dav,FALSE,Full Time Work/School (7-day average),FALSE,NA,NA,SafeGraph (Daily),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-12-01, hrr 2019-01-01, msa 2019-01-01, nation 2020-12-01, state 2019-01-01",2021-04-16,NA,day,Date,daily,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,public,neutral,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph -safegraph-daily,median_home_dwell_time,FALSE,median_home_dwell_time,FALSE,Median Home Dwell Time,FALSE,"The median time spent at home for all devices at this location for this time period, in minutes","The median time spent at home for all devices at this location for this time period, in minutes. - -Discontinued April 19th, 2021.",SafeGraph (Daily),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-12-01, hrr 2019-01-01, msa 2019-01-01, nation 2020-12-01, state 2019-01-01",2021-04-16,NA,day,Date,daily,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,public,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph -safegraph-daily,median_home_dwell_time,TRUE,median_home_dwell_time_7dav,FALSE,Median Home Dwell Time (7-day average),FALSE,NA,NA,SafeGraph (Daily),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-12-01, hrr 2019-01-01, msa 2019-01-01, nation 2020-12-01, state 2019-01-01",2021-04-16,NA,day,Date,daily,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,count,public,neutral,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph -safegraph-daily,part_time_work_prop,FALSE,part_time_work_prop,FALSE,Part Time Work/School,FALSE,The fraction of devices that spent between 3 and 6 hours at one location other than their home during the daytime,"The fraction of devices that spent between 3 and 6 hours at one location other than their home during the daytime. This is SafeGraph’s part_time_work_behavior_devices / device_count. - -Discontinued April 19th, 2021.",SafeGraph (Daily),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-12-01, hrr 2019-01-01, msa 2019-01-01, nation 2020-12-01, state 2019-01-01",2021-04-16,NA,day,Date,daily,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,public,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph -safegraph-daily,part_time_work_prop,TRUE,part_time_work_prop_7dav,FALSE,Part Time Work/School (7-day average),FALSE,NA,NA,SafeGraph (Daily),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-12-01, hrr 2019-01-01, msa 2019-01-01, nation 2020-12-01, state 2019-01-01",2021-04-16,NA,day,Date,daily,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,public,neutral,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph -safegraph-weekly,bars_visit_num,FALSE,bars_visit_num,FALSE,Bar Visits,FALSE,"Daily number of visits to bars, based on SafeGraph's Weekly Patterns dataset","Delphi receives data from [SafeGraph](https://docs.safegraph.com/docs/weekly-patterns), which collects weekly insights on Points of Interest (POI) using anonymized location data from mobile phones. We select locations that qualify as ""Drinking Places (alcoholic beverages)"" from all the [core places](https://docs.safegraph.com/v4.0/docs/places-manual#section-core-places), then count the number of visits. - -Note that these counts only include people whose visits are tracked because they are in SafeGraph's panel; they do not include all bar visits by everyone in the population.",SafeGraph (Weekly),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-11-23, hrr 2019-01-01, msa 2019-01-01, nation 2020-11-23, state 2019-01-01",2022-05-01,NA,day,Date,weekly,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for about 10% of counties. Data is available for about 90% of states,Visits,count,public,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph -safegraph-weekly,bars_visit_num,TRUE,bars_visit_prop,FALSE,Bar Visits (per 100k people),FALSE,NA,NA,SafeGraph (Weekly),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-11-23, hrr 2019-01-01, msa 2019-01-01, nation 2020-11-23, state 2019-01-01",2022-05-01,NA,day,Date,weekly,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for about 10% of counties. Data is available for about 90% of states,"Visits per 100,000 people",per100k,public,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph -safegraph-weekly,restaurants_visit_num,FALSE,restaurants_visit_num,FALSE,Restaurant Visits,FALSE,"Daily number of visits to restaurants, based on SafeGraph's Weekly Patterns dataset","Delphi receives data from [SafeGraph](https://docs.safegraph.com/docs/weekly-patterns), which collects weekly insights on Points of Interest (POI) using anonymized location data from mobile phones. We select locations that qualify as ""Full-Service Restaurants"" from all the [core places](https://docs.safegraph.com/v4.0/docs/places-manual#section-core-places), then count the number of visits. - -Note that these counts only include people whose visits are tracked because they are in SafeGraph's panel; they do not include all restaurant visits by everyone in the population.",SafeGraph (Weekly),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-11-23, hrr 2019-01-01, msa 2019-01-01, nation 2020-11-23, state 2019-01-01",2022-05-01,NA,day,Date,weekly,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for about 80% of counties Data is available for all states and some territories.,Visits,count,public,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph -safegraph-weekly,restaurants_visit_num,TRUE,restaurants_visit_prop,FALSE,Restaurant Visits (per 100k people),FALSE,NA,NA,SafeGraph (Weekly),n/a,Mobility,USA,"county (by Delphi), hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-11-23, hrr 2019-01-01, msa 2019-01-01, nation 2020-11-23, state 2019-01-01",2022-05-01,NA,day,Date,weekly,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for about 80% of counties Data is available for all states and some territories.,"Visits per 100,000 people",per100k,public,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x,NA,safegraph -usa-facts,confirmed_cumulative_num,FALSE,confirmed_cumulative_num,FALSE,Confirmed COVID Cases (Cumulative),FALSE,Cumulative confirmed COVID cases,Confirmed COVID-19 cases as reported by [USAFacts](https://usafacts.org/visualizations/coronavirus-covid-19-spread-map/),USAFacts,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-25,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,count,cases_testing,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts -usa-facts,confirmed_cumulative_num,TRUE,confirmed_7dav_incidence_num,TRUE,"Confirmed COVID Cases (Daily new, 7-day average)",FALSE,"Daily new confirmed COVID cases, 7-day average",NA,USAFacts,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,count,cases_testing,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts -usa-facts,confirmed_cumulative_num,TRUE,confirmed_7dav_incidence_prop,FALSE,"Confirmed COVID Cases (Daily new, 7-day average, per 100k people)",FALSE,"Daily new confirmed COVID cases, 7-day average, per 100k people",NA,USAFacts,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,per100k,cases_testing,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts -usa-facts,confirmed_cumulative_num,TRUE,confirmed_cumulative_prop,FALSE,"Confirmed COVID Cases (Cumulative, per 100k people)",FALSE,"Cumulative confirmed COVID cases, per 100k people",NA,USAFacts,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-25,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,per100k,cases_testing,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts -usa-facts,confirmed_cumulative_num,TRUE,confirmed_incidence_num,TRUE,Confirmed COVID Cases (Daily new),FALSE,Daily new confirmed COVID cases,NA,USAFacts,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-25,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,count,cases_testing,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts -usa-facts,confirmed_cumulative_num,TRUE,confirmed_incidence_prop,FALSE,"Confirmed COVID Cases (Daily new, per 100k people)",FALSE,"Daily new confirmed COVID cases, per 100k people",NA,USAFacts,covid,Cases,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-25,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,ascertained (case),None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,per100k,cases_testing,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts -usa-facts,deaths_cumulative_num,FALSE,deaths_cumulative_num,FALSE,Confirmed COVID Deaths (Cumulative),FALSE,Cumulative confirmed COVID deaths,Confirmed COVID-19 deaths as reported by [USAFacts](https://usafacts.org/visualizations/coronavirus-covid-19-spread-map/),USAFacts,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-25,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,count,late,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts -usa-facts,deaths_cumulative_num,TRUE,deaths_7dav_incidence_num,TRUE,"Confirmed COVID Deaths (Daily new, 7-day average)",FALSE,"Daily new confirmed COVID deaths, 7-day average",NA,USAFacts,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,count,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts -usa-facts,deaths_cumulative_num,TRUE,deaths_7dav_incidence_prop,FALSE,"Confirmed COVID Deaths (Daily new, 7-day average, per 100k people)",FALSE,"Daily new confirmed COVID deaths, 7-day average, per 100k people",NA,USAFacts,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-02-01,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,per100k,late,bad,TRUE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts -usa-facts,deaths_cumulative_num,TRUE,deaths_cumulative_prop,FALSE,"Confirmed COVID Deaths (Cumulative, per 100k people)",FALSE,"Cumulative confirmed COVID deaths, per 100k people",NA,USAFacts,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-25,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,per100k,late,bad,FALSE,FALSE,TRUE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts -usa-facts,deaths_cumulative_num,TRUE,deaths_incidence_num,TRUE,Confirmed COVID Deaths (Daily new),FALSE,Daily new confirmed COVID deaths,NA,USAFacts,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-25,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts -usa-facts,deaths_cumulative_num,TRUE,deaths_incidence_prop,FALSE,"Confirmed COVID Deaths (Daily new, per 100k people)",FALSE,"Daily new confirmed COVID deaths, per 100k people",NA,USAFacts,covid,Deaths,USA,"county, hrr (by Delphi), msa (by Delphi), state (by Delphi), hhs (by Delphi), nation (by Delphi)",2020-01-25,NA,2023-01-02,NA,day,Date,daily,2-8 days,"None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,CC BY,NA,NA,usa-facts From 2f76a76a3f2b5baac49b853b354b5f10cbb3263e Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Thu, 9 May 2024 12:19:24 -0400 Subject: [PATCH 12/30] merge dua changes --- scripts/signal_spreadsheet_updater.R | 94 ++++++++++++---------------- 1 file changed, 40 insertions(+), 54 deletions(-) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index 0ffbe3450..2ced6d536 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -10,7 +10,7 @@ suppressPackageStartupMessages({ options(warn = 1) -# TODO all info for youtube-survey +# TODO all info for youtube-survey. Information is hard to find. Filled out some fields based on https://github.com/cmu-delphi/covid-19/tree/main/youtube # COVIDcast metadata # Metadata documentation: https://cmu-delphi.github.io/delphi-epidata/api/covidcast_meta.html @@ -110,14 +110,14 @@ new_fields <- c( "Temporal Scope Start", "Temporal Scope End", "Reporting Cadence", - "Reporting Lag", - "Revision Cadence", + "Typical Reporting Lag", #originally Reporting Lag + "Typical Revision Cadence", #originally Revision Cadence "Demographic Scope", - "Demographic Disaggregation", ###Change to "Demographic Breakdowns" when granted sheet access + "Demographic Breakdowns", "Severity Pyramid Rungs", "Data Censoring", "Missingness", - "Who may Access this signal?", + "Who may access this signal?", "Who may be told about this signal?", "Use Restrictions", "Link to DUA" @@ -190,7 +190,7 @@ source5 <- source4 %>% # Inactive data_sources list inactive_sources <- c( "jhu-csse", "dsew-cpr", "fb-survey", "covid-act-now", "ght", "google-survey", - "indicator-combination", "safegraph", "usa-facts" + "indicator-combination", "safegraph", "usa-facts", "youtube-survey" ) # Inactive signals list, where some signals for a given data source are active @@ -310,7 +310,7 @@ geo_scope <- c( "quidel" = "USA", "safegraph" = "USA", "usa-facts" = "USA", - "youtube-survey" = NA_character_ + "youtube-survey" = "USA" ) source_updated[, col] <- geo_scope[source_updated$data_source] @@ -370,9 +370,7 @@ avail_geos <- c( "indicator-combination" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), "jhu-csse" = glue("county, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), "nchs-mortality" = glue("state, nation"), - - # TODO check against actual data. Or maybe there's an internal/private version of metadata that includes Quidel stats? - # this is quidel non-flu signals, other is flu + # Quidel non-flu signals "quidel" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), "safegraph" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), "usa-facts" = glue("county, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), @@ -432,8 +430,6 @@ leftover_signal_geos_manual <- tibble::tribble( "indicator-combination", "nmf_day_doc_fbs_ght", combo_geos, # Quidel flu signals - # TODO check against actual data. Or maybe there's an internal/private version of metadata that includes Quidel stats? Nat was only looking at metadata - #for each of these quidel signals, make request to API for each possible geotype (county, hrr, etc) to see if data comes back "quidel", "raw_pct_negative", quidel_geos, "quidel", "smoothed_pct_negative", quidel_geos, "quidel", "raw_tests_per_device", quidel_geos, @@ -477,7 +473,7 @@ avail_geos <- c( "quidel" = "daily", "safegraph" = "weekly", "usa-facts" = "weekly", - "youtube-survey" = NA_character_ + "youtube-survey" = NA_character_ # See https://github.com/cmu-delphi/covid-19/tree/main/youtube ) # # Tool: Investigate reporting lag and revision cadence @@ -593,7 +589,7 @@ reporting_lag <- c( "quidel" = "5-6 days", "safegraph" = "3-11 days", "usa-facts" = "2-8 days", - "youtube-survey" = NA_character_ + "youtube-survey" = NA_character_ # See https://github.com/cmu-delphi/covid-19/tree/main/youtube ) # Index (using `[]`) into the map using the data_source (or source division) @@ -623,10 +619,10 @@ revision_cadence <- c( corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.", "nchs-mortality" = "Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7)", - "quidel" = NA_character_, # Happens, up to 6+ weeks after the report date. # TODO + "quidel" = "Weekly. Happens, up to 6+ weeks after the report date.", "safegraph" = "None", "usa-facts" = "None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.", - "youtube-survey" = NA_character_ + "youtube-survey" = NA_character_ # See https://github.com/cmu-delphi/covid-19/tree/main/youtube ) source_updated[, col] <- revision_cadence[source_updated$data_source] @@ -652,7 +648,7 @@ demo_scope <- c( "quidel" = "Nationwide Quidel testing equipment network", "safegraph" = "Safegraph panel members who use mobile devices", "usa-facts" = "All", - "youtube-survey" = NA_character_ + "youtube-survey" = NA_character_ # See https://github.com/cmu-delphi/covid-19/tree/main/youtube ) source_updated[, col] <- demo_scope[source_updated$data_source] @@ -684,11 +680,11 @@ demo_breakdowns <- c( "quidel" = "age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)", "safegraph" = "None", "usa-facts" = "None", - "youtube-survey" = NA_character_ + "youtube-survey" = NA_character_ # See https://github.com/cmu-delphi/covid-19/tree/main/youtube ) source_updated[, col] <- demo_breakdowns[source_updated$data_source] # Quidel covid has age bands, but quidel flu doesn't. -source_updated[source_update$`Source Subdivision` == "quidel-flu", col] <- "None" +source_updated[source_updated$`Source Subdivision` == "quidel-flu", col] <- "None" col <- "Severity Pyramid Rungs" @@ -720,7 +716,7 @@ data_censoring <- c( "quidel" = "Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests", "safegraph" = "None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details", "usa-facts" = "None", - "youtube-survey" = NA_character_ + "youtube-survey" = NA_character_ # See https://github.com/cmu-delphi/covid-19/tree/main/youtube ) signal_specific_censoring <- tibble::tribble( ~data_source, ~signal, ~note, @@ -820,10 +816,10 @@ missingness <- c( "indicator-combination" = paste(all_counties_terr, all_states_terr), "jhu-csse" = paste(all_counties_terr, all_states_terr), "nchs-mortality" = paste(all_states_terr), - "quidel" = "Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.", # TODO + "quidel" = "Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.", "safegraph" = paste(all_counties_terr, all_states_terr), "usa-facts" = paste(all_counties_terr, all_states), - "youtube-survey" = NA_character_ # below + "youtube-survey" = NA_character_ # See https://github.com/cmu-delphi/covid-19/tree/main/youtube # below ) source_updated[, col] <- missingness[source_updated$data_source] @@ -905,7 +901,7 @@ orgs_allowed_access <- c( "quidel" = "Delphi", "safegraph" = "public", "usa-facts" = "public", - "youtube-survey" = NA_character_ + "youtube-survey" = NA_character_ # See https://github.com/cmu-delphi/covid-19/tree/main/youtube ) source_updated[, col] <- orgs_allowed_access[source_updated$data_source] @@ -928,7 +924,7 @@ orgs_allowed_know <- c( "quidel" = "public", "safegraph" = "public", "usa-facts" = "public", - "youtube-survey" = NA_character_ + "youtube-survey" = NA_character_ # See https://github.com/cmu-delphi/covid-19/tree/main/youtube ) source_updated[, col] <- orgs_allowed_know[source_updated$data_source] @@ -951,64 +947,54 @@ license <- c( "quidel" = "CC BY", "safegraph" = "CC BY", "usa-facts" = "CC BY", - "youtube-survey" = NA_character_ + "youtube-survey" = NA_character_ # See https://github.com/cmu-delphi/covid-19/tree/main/youtube ) source_updated[, col] <- license[source_updated$data_source] -# TODO col <- "Use Restrictions" # Any important DUA restrictions on use, publication, sharing, linkage, etc.? use_restrictions <- c( - "chng" = NA_character_, #change DUA in confidential Google drive, generic contract terms - "covid-act-now" = NA_character_, #public - "doctor-visits" = NA_character_, #optum DUA in confidential Google drive, generic contract terms - "dsew-cpr" = NA_character_, #public - "fb-survey" = NA_character_, # - "ght" = NA_character_, + "chng" = "See license. DUA uses generic contract terms.", #DUA in confidential Google drive, generic contract terms + "covid-act-now" = "See license", #public + "doctor-visits" = "See license. DUA uses generic contract terms.", #optum DUA in confidential Google drive, generic contract terms + "dsew-cpr" = "See license", #public + "fb-survey" = "Delphi aggregated data has no use restrictions. Raw data users must sign DUA with Delphi, and the proposed research purpose must be consistent with the consent language used in Wave 1, regardless of which survey wave the data they're using comes from. Part- or full-time Facebook employees are not eligible to receive data access.", # @AlexR + "ght" = "See license", #public, no Delphi documentation, "google-survey" = NA_character_, - "google-symptoms" = NA_character_, - "hhs" = NA_character_, - "hospital-admissions" = NA_character_, #optum DUA in confidential Google drive, generic contract terms + "google-symptoms" = "See license", + "hhs" = "See license", + "hospital-admissions" = "See license. DUA uses generic contract terms.", #optum DUA in confidential Google drive, generic contract terms "indicator-combination" = NA_character_, - "jhu-csse" = NA_character_, - "nchs-mortality" = NA_character_, - "quidel" = "Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics.", #Quidel DUA in confidential Google drive, + "jhu-csse" = "See license", + "nchs-mortality" = "See license", + "quidel" = "Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).", #Quidel DUA in confidential Google drive, "safegraph" = NA_character_, - "usa-facts" = NA_character_, - "youtube-survey" = NA_character_ + "usa-facts" = "See license", + "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube ) source_updated[, col] <- use_restrictions[source_updated$data_source] -#aa <- epidatr::covidcast_epidata() -#aa$sources$`jhu-csse`$dua - -#purrr::map(aa$sources, ~ .x$license) - -#bb <- aa$sources$`fb-survey`$signals %>% tibble::as_tibble() -#bb - -# TODO col <- "Link to DUA" dua_link <- c( "chng" = "https://drive.google.com/drive/u/1/folders/1GKYSFb6C_8jSHTg-65eVzSOT433oIDrf", #"https://cmu.box.com/s/cto4to822zecr3oyq1kkk9xmzhtq9tl2" "covid-act-now" = NA_character_, #public, maybe contract for other specific project #@Carlyn - "doctor-visits" = "https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf", #"https://cmu.box.com/s/l2tz6kmiws6jyty2azwb43poiepz0565", + "doctor-visits" = "https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf", #"https://cmu.box.com/s/l2tz6kmiws6jyty2azwb43poiepz0565" "dsew-cpr" = NA_character_, #public - "fb-survey" = "https://cmu.box.com/s/qfxplcdrcn9retfzx4zniyugbd9h3bos",#@Alex R. - "ght" = NA_character_, #public, has an API doesn't require password + "fb-survey" = "https://cmu.box.com/s/qfxplcdrcn9retfzx4zniyugbd9h3bos", + "ght" = NA_character_, #public, has an API doesn't require password. No Delphi documentation. See "google-survey" = NA_character_, #@Carlyn has requested DUA from Roni "google-symptoms" = NA_character_, #public "hhs" = NA_character_, #public gov't - "hospital-admissions" = "https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf", #"https://cmu.box.com/s/l2tz6kmiws6jyty2azwb43poiepz0565", + "hospital-admissions" = "https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf", #"https://cmu.box.com/s/l2tz6kmiws6jyty2azwb43poiepz0565" "indicator-combination" = "see Doctor Visits, Facebook Survey, and Google Health Trends", "jhu-csse" = NA_character_, #public "nchs-mortality" = "https://www.cdc.gov/nchs/data_access/restrictions.htm", "quidel" = "https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS", "safegraph" = "https://drive.google.com/drive/u/1/folders/1qkcUpdkJOkbSBBszrSCA4n1vSQKSlv3x", "usa-facts" = NA_character_, #public - "youtube-survey" = NA_character_ #looking for contract, https://github.com/cmu-delphi/covid-19/tree/main/youtube + "youtube-survey" = NA_character_ # contract expected, but not found ) source_updated[, col] <- dua_link[source_updated$data_source] From 71db9d6258769a06b684771a93730ed51b09c9ce Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Thu, 9 May 2024 12:42:02 -0400 Subject: [PATCH 13/30] fb dua clarification --- scripts/signal_spreadsheet_updater.R | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index 2ced6d536..f909b6465 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -959,7 +959,7 @@ use_restrictions <- c( "covid-act-now" = "See license", #public "doctor-visits" = "See license. DUA uses generic contract terms.", #optum DUA in confidential Google drive, generic contract terms "dsew-cpr" = "See license", #public - "fb-survey" = "Delphi aggregated data has no use restrictions. Raw data users must sign DUA with Delphi, and the proposed research purpose must be consistent with the consent language used in Wave 1, regardless of which survey wave the data they're using comes from. Part- or full-time Facebook employees are not eligible to receive data access.", # @AlexR + "fb-survey" = "Aggregationed signals must be based on 100 or more survey responses. Delphi aggregated data has no use restrictions. Raw data users must sign DUA with Delphi, and the proposed research purpose must be consistent with the consent language used in Wave 1, regardless of which survey wave the data they're using comes from. Part- or full-time Facebook employees are not eligible to receive data access.", # @AlexR "ght" = "See license", #public, no Delphi documentation, "google-survey" = NA_character_, "google-symptoms" = "See license", @@ -988,7 +988,7 @@ dua_link <- c( "google-symptoms" = NA_character_, #public "hhs" = NA_character_, #public gov't "hospital-admissions" = "https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf", #"https://cmu.box.com/s/l2tz6kmiws6jyty2azwb43poiepz0565" - "indicator-combination" = "see Doctor Visits, Facebook Survey, and Google Health Trends", + "indicator-combination" = "See Doctor Visits, Facebook Survey, and Google Health Trends", "jhu-csse" = NA_character_, #public "nchs-mortality" = "https://www.cdc.gov/nchs/data_access/restrictions.htm", "quidel" = "https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS", From 120e4e5b0f560d4e747c98d1d500dafaab627c7f Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Thu, 9 May 2024 13:05:38 -0400 Subject: [PATCH 14/30] cleanup --- scripts/signal_spreadsheet_updater.R | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index f909b6465..3c63e5198 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -166,6 +166,8 @@ source3 <- left_join( # also convert min_time col to character (easier to move times over to google spreadsheet without corrupting) # *only in dplyr can you use col names without quotations, as.character is base function # *min_time, we can just use the earliest date available and not specify each geo's different dates + +# TODO: fill in Temporal Scope Start/End for quidel signals. Can't get them from metadata. source4 <- mutate( source3, `Temporal Scope Start Note` = min_time_notes, @@ -340,9 +342,8 @@ auto_geo_list_by_signal <- arrange( # Tool: Are there any data sources where geos_list is different for different signal? different_geos_by_signal <- count(auto_geo_list_by_signal, data_source, geos_list, name = "n_signals") -different_geos_by_signal +# different_geos_by_signal # which(duplicated(select(different_geos_by_signal, data_source))) -# # [1] 2 6 8 9 15 17 # Keep most common geos_list for each data source. most_common_geos_list <- group_by(different_geos_by_signal, data_source) %>% @@ -456,7 +457,7 @@ source_updated <- left_join( col <- "Reporting Cadence" # E.g. daily, weekly, etc. Might not be the same as Temporal Granularity -avail_geos <- c( +cadence_map <- c( "chng" = "daily", "covid-act-now" = "daily", "doctor-visits" = "daily", @@ -475,6 +476,7 @@ avail_geos <- c( "usa-facts" = "weekly", "youtube-survey" = NA_character_ # See https://github.com/cmu-delphi/covid-19/tree/main/youtube ) +source_updated[, col] <- cadence_map[source_updated$data_source] # # Tool: Investigate reporting lag and revision cadence # source <- "indicator-combination-nmf" From 99f9292ab7cb5745ec088457d10870435a6f27bf Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Thu, 9 May 2024 13:16:01 -0400 Subject: [PATCH 15/30] intro to script --- scripts/signal_spreadsheet_updater.R | 18 ++++++++++++++++++ 1 file changed, 18 insertions(+) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index 3c63e5198..ef4cae944 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -1,3 +1,21 @@ +# This is a helper script for updating the signal spreadsheet "Signals" tab +# (https://docs.google.com/spreadsheets/d/1zb7ItJzY5oq1n-2xtvnPBiJu2L3AqmCKubrLkKJZVHs/edit#gid=329338228) +# semi-programmatically. +# +# To run this, you need to have the Signals tab and the Sources tab saved +# locally as CSVs. The script loads and modifies the data from the Signals tab. +# +# To update a given field, we define a map between data source names and a set +# of values, use the data source column to index into the map, and save the +# result to the spreadsheet. There is some additional logic, depending on the +# field to be updated, to handle certain signals and cases (active/inactive +# signals) separately. +# +# The updated spreadsheet is saved to disk as a CSV. Any updated columns must be +# manually pasted into the online spreadsheet. This script checks that the +# original sort order is the same as that of the updated spreadsheet. + + # Load packages suppressPackageStartupMessages({ library(epidatr) # Access Delphi API From 830657234d2cf739c028321e210f476bb941faa7 Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Thu, 9 May 2024 13:18:44 -0400 Subject: [PATCH 16/30] safegraph use restrictions --- scripts/signal_spreadsheet_updater.R | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index ef4cae944..39cef900e 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -989,7 +989,8 @@ use_restrictions <- c( "jhu-csse" = "See license", "nchs-mortality" = "See license", "quidel" = "Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).", #Quidel DUA in confidential Google drive, - "safegraph" = NA_character_, + "safegraph" = "Delphi is free to publish and otherwise disclose the results of its Research (including but not limited to reports and papers and other activities conducted under the Research), including analyses and/or aggregated reporting of the Data. However, the underlying raw Data may not be published +without Licensor’s consent.", "usa-facts" = "See license", "youtube-survey" = NA_character_ #https://github.com/cmu-delphi/covid-19/tree/main/youtube ) From 38148990525e16d4d560561ee200cfe3407b9255 Mon Sep 17 00:00:00 2001 From: Tina Townes Date: Thu, 9 May 2024 23:26:40 -0400 Subject: [PATCH 17/30] updated Facebook DUA line 1008 with clarification Clarification: API users won't need a DUA as they won't have access to raw facebook data. What's available to users is aggregated Delphi data. (According to @AlexReinhart and Geographically aggregated data from this survey is publicly available through the COVIDcast API as the fb-survey data source .) --- scripts/signal_spreadsheet_updater.R | 42 +++++++++++++++------------- 1 file changed, 22 insertions(+), 20 deletions(-) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index 39cef900e..ec302a55b 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -502,7 +502,7 @@ source_updated[, col] <- cadence_map[source_updated$data_source] # # Not available for all indicators. Try nation. Avoid smaller geos because # # processing later will take a while. # geo_type <- "state" -# +# # # Consider a range of issues. About 2 weeks is probably fine. Not all indicators # # are available in this time range, so you may need to make another range of # # dates that is years or months different. @@ -523,8 +523,8 @@ source_updated[, col] <- cadence_map[source_updated$data_source] # "2021-02-15", # "2021-02-16" # ) -# -# +# +# # epidata <- pub_covidcast( # source, # signal, @@ -533,16 +533,16 @@ source_updated[, col] <- cadence_map[source_updated$data_source] # time_type = "day", # issues = about_2weeks_issues # ) -# -# +# +# # # Make sure data is looking reasonable # # Number of reference dates reported in each issue # count(epidata, issue) -# +# # # Number of locations reported for each issue and reference date # count(epidata, issue, time_value) -# -# +# +# # ## Revision cadence # # For each location and reference date, are all reported values the same across # # all lags we're checking? @@ -559,17 +559,19 @@ source_updated[, col] <- cadence_map[source_updated$data_source] # ) # # Are all reference dates without any lag? # all(revision_comparison$no_backfill == "TRUE") +# #all(revision_comparison[revision_comparison$no_backfill != "TRUE", ]) +# revision_comparison[revision_comparison$no_backfill != "TRUE", ] # View(revision_comparison) -# -# -# ## Reporting lag -# # Find how lagged the newest reported value is for each issue. -# epidata_slice <- epidata %>% group_by(issue) %>% slice_min(lag) -# # Find the most common min lag. We expect a relatively narrow range of lags. At -# # most, a data source should be updated weekly such that it has a range of lags -# # of 7 days (e.g. 5-12 days). For data updated daily, we expect a range of lags -# # of only a few days (e.g. 2-4 days or even 2-3 days). -# table(epidata_slice$lag) + + +## Reporting lag +# Find how lagged the newest reported value is for each issue. +epidata_slice <- epidata %>% group_by(issue) %>% slice_min(lag) +# Find the most common min lag. We expect a relatively narrow range of lags. At +# most, a data source should be updated weekly such that it has a range of lags +# of 7 days (e.g. 5-12 days). For data updated daily, we expect a range of lags +# of only a few days (e.g. 2-4 days or even 2-3 days). +table(epidata_slice$lag) col <- "Typical Reporting Lag" @@ -1003,9 +1005,9 @@ dua_link <- c( "covid-act-now" = NA_character_, #public, maybe contract for other specific project #@Carlyn "doctor-visits" = "https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf", #"https://cmu.box.com/s/l2tz6kmiws6jyty2azwb43poiepz0565" "dsew-cpr" = NA_character_, #public - "fb-survey" = "https://cmu.box.com/s/qfxplcdrcn9retfzx4zniyugbd9h3bos", + "fb-survey" = NA_character_, #@AlexR public aggregated by Delphi, but raw data requires DUA "https://cmu.box.com/s/qfxplcdrcn9retfzx4zniyugbd9h3bos", "ght" = NA_character_, #public, has an API doesn't require password. No Delphi documentation. See - "google-survey" = NA_character_, #@Carlyn has requested DUA from Roni + "google-survey" = NA_character_, #@Carlyn has requested DUA from Roni, waiting. "google-symptoms" = NA_character_, #public "hhs" = NA_character_, #public gov't "hospital-admissions" = "https://drive.google.com/drive/u/1/folders/11kvTzVR5Yd3lVszxmPHxFZcAYjIpoLcf", #"https://cmu.box.com/s/l2tz6kmiws6jyty2azwb43poiepz0565" From 13d0135e8fa15e8dc1d759b4dc676c4af8d3212c Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Fri, 10 May 2024 13:18:44 -0400 Subject: [PATCH 18/30] quidel signal-specific missingness --- scripts/signal_spreadsheet_updater.R | 31 +++++++++++++++++++++++++++- 1 file changed, 30 insertions(+), 1 deletion(-) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index ec302a55b..44e6703a2 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -838,7 +838,7 @@ missingness <- c( "indicator-combination" = paste(all_counties_terr, all_states_terr), "jhu-csse" = paste(all_counties_terr, all_states_terr), "nchs-mortality" = paste(all_states_terr), - "quidel" = "Geographic coverage for some age groups (e.g. age 0-4 and age 65+) are extremely limited at HRR and MSA level, and can even be limited at state level on weekends.", + "quidel" = NA_character_, # below "safegraph" = paste(all_counties_terr, all_states_terr), "usa-facts" = paste(all_counties_terr, all_states), "youtube-survey" = NA_character_ # See https://github.com/cmu-delphi/covid-19/tree/main/youtube # below @@ -846,6 +846,13 @@ missingness <- c( source_updated[, col] <- missingness[source_updated$data_source] google_symptoms_note <- "Signals associated with rarer symptoms (e.g. ageusia) will tend to have fewer locations available, due to upstream privacy censoring. Locations with lower populations will tend to be less available for the same reason" + +# Quidel +smoothed_nonage_groups <- "Data is available for about 50% of counties, and all or nearly all states." +raw_nonage_groups <- "Data is available for about 7% of counties, half that on weekends. Data is available for about 90% of states, about 70% on weekends" +smoothed_age_groups <- "Data is available for about 5-15% of counties. 65-95% of states." +raw_age_groups <- "Data is available for about 0.7-2% of counties, half that on weekends. Data is available for about 30-45% of states, half that on weekends. Geographic coverage for smaller age groups (age 0-4 and age 65+) are also extremely limited at the HRR and MSA levels" + signal_specific_missingness <- tibble::tribble( ~data_source, ~signal, ~note, "indicator-combination", "nmf_day_doc_fbc_fbs_ght", paste("Data is available for about 80% of counties", all_states_terr), @@ -892,6 +899,28 @@ signal_specific_missingness <- tibble::tribble( "google-symptoms", "scontrol_smoothed_search", paste("Data is available for about 45% of counties.", all_states, google_symptoms_note), "google-symptoms", "sum_anosmia_ageusia_raw_search", paste("Data is available for about 3-4% of counties. Data is available for about 85% of states.", google_symptoms_note), "google-symptoms", "sum_anosmia_ageusia_smoothed_search", paste("Data is available for about 3-4% of counties. Data is available for about 85% of states.", google_symptoms_note), + + # covid + "quidel", "covid_ag_raw_pct_positive", raw_nonage_groups, + "quidel", "covid_ag_smoothed_pct_positive", smoothed_nonage_groups, + "quidel", "covid_ag_raw_pct_positive_age_0_17", raw_age_groups, + "quidel", "covid_ag_smoothed_pct_positive_age_0_17", smoothed_age_groups, + "quidel", "covid_ag_raw_pct_positive_age_0_4", raw_age_groups, + "quidel", "covid_ag_smoothed_pct_positive_age_0_4", smoothed_age_groups, + "quidel", "covid_ag_raw_pct_positive_age_18_49", raw_age_groups, + "quidel", "covid_ag_smoothed_pct_positive_age_18_49", smoothed_age_groups, + "quidel", "covid_ag_raw_pct_positive_age_5_17", raw_age_groups, + "quidel", "covid_ag_smoothed_pct_positive_age_5_17", smoothed_age_groups, + "quidel", "covid_ag_raw_pct_positive_age_50_64", raw_age_groups, + "quidel", "covid_ag_smoothed_pct_positive_age_50_64", smoothed_age_groups, + "quidel", "covid_ag_raw_pct_positive_age_65plus", raw_age_groups, + "quidel", "covid_ag_smoothed_pct_positive_age_65plus", smoothed_age_groups, + + # flu + "quidel", "raw_pct_negative", raw_nonage_groups, + "quidel", "smoothed_pct_negative", smoothed_nonage_groups, + "quidel", "raw_tests_per_device", raw_nonage_groups, + "quidel", "smoothed_tests_per_device", smoothed_nonage_groups, ) # Add signal-specific missingness From cf5a4404c0f3ed3f019c879f4bc3e443f9497ccd Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Fri, 10 May 2024 13:22:13 -0400 Subject: [PATCH 19/30] quidel TODO --- scripts/signal_spreadsheet_updater.R | 1 + 1 file changed, 1 insertion(+) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index 44e6703a2..7e13f9f43 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -29,6 +29,7 @@ options(warn = 1) # TODO all info for youtube-survey. Information is hard to find. Filled out some fields based on https://github.com/cmu-delphi/covid-19/tree/main/youtube +# TODO some info for quidel. # COVIDcast metadata # Metadata documentation: https://cmu-delphi.github.io/delphi-epidata/api/covidcast_meta.html From 9b5c16b2ab781c8eeab7a1cc3b59f6227f67b15a Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Fri, 10 May 2024 17:46:26 -0400 Subject: [PATCH 20/30] quidel TODO --- scripts/signal_spreadsheet_updater.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index 7e13f9f43..8724fea21 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -186,7 +186,7 @@ source3 <- left_join( # *only in dplyr can you use col names without quotations, as.character is base function # *min_time, we can just use the earliest date available and not specify each geo's different dates -# TODO: fill in Temporal Scope Start/End for quidel signals. Can't get them from metadata. +# TODO: fill in Temporal Scope Start/End for quidel signals by coalescing the existing column with the new data; quidel dates have already been filled in manually in the spreadsheet. source4 <- mutate( source3, `Temporal Scope Start Note` = min_time_notes, From 999273d9a7c78237eca4ac3bd6fc598b71b80526 Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Tue, 28 May 2024 15:46:43 -0400 Subject: [PATCH 21/30] for quidel signals, use existing start/end times --- scripts/signal_spreadsheet_updater.R | 14 +++++++++++--- 1 file changed, 11 insertions(+), 3 deletions(-) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index 8724fea21..03c63dcde 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -180,13 +180,21 @@ source3 <- left_join( by = c("Signal" = "signal", "data_source") ) -# select: source subdivision, signal, scope start, scope end, min_time, max_time +# Fill in Temporal Scope Start/End for quidel signals by coalescing the existing +# column with the new data; quidel dates have already been filled in manually in +# the spreadsheet. +source3$min_time <- case_when( + source3$data_source == "quidel" ~ coalesce(source3$min_time, source3$`Temporal Scope Start`) +) +source3$max_time <- case_when( + source3$data_source == "quidel" ~ coalesce(source3$max_time, source3$`Temporal Scope Start`) +) + +# Select relevant columns # first reformat max_time col to character for compatibility # also convert min_time col to character (easier to move times over to google spreadsheet without corrupting) # *only in dplyr can you use col names without quotations, as.character is base function # *min_time, we can just use the earliest date available and not specify each geo's different dates - -# TODO: fill in Temporal Scope Start/End for quidel signals by coalescing the existing column with the new data; quidel dates have already been filled in manually in the spreadsheet. source4 <- mutate( source3, `Temporal Scope Start Note` = min_time_notes, From 96da3bb08e054b0879415342ffcb874976972b9f Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Tue, 28 May 2024 16:04:03 -0400 Subject: [PATCH 22/30] verify quidel geo availability --- scripts/signal_spreadsheet_updater.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index 03c63dcde..ca8995f95 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -859,7 +859,7 @@ google_symptoms_note <- "Signals associated with rarer symptoms (e.g. ageusia) w # Quidel smoothed_nonage_groups <- "Data is available for about 50% of counties, and all or nearly all states." raw_nonage_groups <- "Data is available for about 7% of counties, half that on weekends. Data is available for about 90% of states, about 70% on weekends" -smoothed_age_groups <- "Data is available for about 5-15% of counties. 65-95% of states." +smoothed_age_groups <- "Data is available for about 5-15% of counties. Data is available for about 65-95% of states." raw_age_groups <- "Data is available for about 0.7-2% of counties, half that on weekends. Data is available for about 30-45% of states, half that on weekends. Geographic coverage for smaller age groups (age 0-4 and age 65+) are also extremely limited at the HRR and MSA levels" signal_specific_missingness <- tibble::tribble( From e71211b3ee12c0c47eff0378e44da2031b6d05cc Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Wed, 29 May 2024 11:12:41 -0400 Subject: [PATCH 23/30] note geos we created in separate col --- scripts/signal_spreadsheet_updater.R | 213 +++++++++++++++++++-------- 1 file changed, 155 insertions(+), 58 deletions(-) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index ca8995f95..8456fa736 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -126,6 +126,7 @@ signal_sheet <- suppressMessages(read_csv("delphi-eng-covidcast-data-sources-sig # Fields we want to add. new_fields <- c( "Geographic Scope", + "Delphi-Aggregated Geography", "Temporal Scope Start", "Temporal Scope End", "Reporting Cadence", @@ -344,74 +345,169 @@ geo_scope <- c( source_updated[, col] <- geo_scope[source_updated$data_source] + + col <- "Available Geography" -# List all available geo-levels. If a geo-level was created by Delphi -# aggregation (as opposed to being ingested directly from the data source), -# indicate this as per this example: county, state (by Delphi), National -# (by Delphi). - -# Tool: Create lists of geos for each data source-signal combo based on what is reported in metadata (does not include quidel, at least with). -metadata_factorgeo <- metadata -metadata_factorgeo$geo_type <- factor(metadata_factorgeo$geo_type, levels = c("county", "hrr", "msa", "dma", "state", "hhs", "nation")) -auto_geo_list_by_signal <- arrange( - metadata_factorgeo, - geo_type -) %>% - group_by( - data_source, - signal - ) %>% - summarize( - geos_list = paste(geo_type, collapse = ", "), - .groups = "keep" - ) %>% - ungroup() +# List all available geo-levels, e.g: county,state,nation + +# # Tool: Create lists of geos for each data source-signal combo based on what is +# # reported in metadata (does not include quidel). +# metadata_factorgeo <- metadata +# metadata_factorgeo$geo_type <- factor(metadata_factorgeo$geo_type, levels = c("county", "hrr", "msa", "dma", "state", "hhs", "nation")) +# auto_geo_list_by_signal <- arrange( +# metadata_factorgeo, +# geo_type +# ) %>% +# group_by( +# data_source, +# signal +# ) %>% +# summarize( +# geos_list = paste(geo_type, collapse = ", "), +# .groups = "keep" +# ) %>% +# ungroup() + +# # Tool: Are there any data sources where geos_list is different for different signal? +# different_geos_by_signal <- count(auto_geo_list_by_signal, data_source, geos_list, name = "n_signals") +# # different_geos_by_signal +# # which(duplicated(select(different_geos_by_signal, data_source))) + +# # Keep most common geos_list for each data source. +# most_common_geos_list <- group_by(different_geos_by_signal, data_source) %>% +# slice_max(n_signals, with_ties = FALSE) +# # most_common_geos_list +# leftover_datasource_geos <- anti_join(different_geos_by_signal, most_common_geos_list) +# # leftover_datasource_geos +# leftover_signal_geos <- semi_join(auto_geo_list_by_signal, leftover_datasource_geos) +# # leftover_signal_geos + +# These values are applied first. They are the default (most common) geos for each data source. +avail_geos <- c( + "chng" = glue("county,hrr,msa,state,hhs,nation"), + "covid-act-now" = glue("county,hrr,msa,state,hhs,nation"), + "doctor-visits" = glue("county,hrr,msa,state,hhs,nation"), + "dsew-cpr" = glue("county,msa,state,hhs,nation"), + "fb-survey" = glue("county,hrr,msa,state,nation"), + "ght" = glue("hrr,msa,dma,state"), + "google-survey" = glue("county,hrr,msa,state"), + "google-symptoms" = glue("county,hrr,msa,state,hhs,nation"), + "hhs" = glue("state,hhs,nation"), + "hospital-admissions" = glue("county,hrr,msa,state,hhs,nation"), + "indicator-combination" = glue("county,hrr,msa,state,hhs,nation"), + "jhu-csse" = glue("county,hrr,msa,state,hhs,nation"), + "nchs-mortality" = glue("state,nation"), + # Quidel non-flu signals + "quidel" = glue("county,hrr,msa,state,hhs,nation"), + "safegraph" = glue("county,hrr,msa,state,hhs,nation"), + "usa-facts" = glue("county,hrr,msa,state,hhs,nation"), + "youtube-survey" = "state" +) + +# These are signal-specific geo lists. These are less common and are applied as a patch. +dsew_geos <- glue("state,hhs,nation") +fb_geos1 <- glue("county,state,nation") +fb_geos2 <- glue("county,msa,state,nation") +hosp_geos <- glue("county,hrr,msa,state") +combo_geos <- glue("county,msa,state") +quidel_geos <- glue("msa,state") +leftover_signal_geos_manual <- tibble::tribble( + ~data_source, ~signal, ~geos_list, + "chng", "7dav_inpatient_covid", "state", + "chng", "7dav_outpatient_covid", "state", + + "dsew-cpr", "booster_doses_admin_7dav", dsew_geos, + "dsew-cpr", "doses_admin_7dav", dsew_geos, + "dsew-cpr", "people_booster_doses", dsew_geos, + + "fb-survey", "smoothed_vaccine_barrier_appointment_location_tried", fb_geos1, + "fb-survey", "smoothed_vaccine_barrier_other_tried", fb_geos1, + "fb-survey", "smoothed_wvaccine_barrier_appointment_location_tried", fb_geos1, + "fb-survey", "smoothed_wvaccine_barrier_other_tried", fb_geos1, + + "fb-survey", "smoothed_vaccine_barrier_appointment_time_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_childcare_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_document_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_eligible_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_language_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_no_appointments_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_none_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_technical_difficulties_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_technology_access_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_time_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_travel_tried", fb_geos2, + "fb-survey", "smoothed_vaccine_barrier_type_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_appointment_time_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_childcare_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_document_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_eligible_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_language_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_no_appointments_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_none_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_technical_difficulties_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_technology_access_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_time_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_travel_tried", fb_geos2, + "fb-survey", "smoothed_wvaccine_barrier_type_tried", fb_geos2, + + "hospital-admissions", "smoothed_adj_covid19", hosp_geos, + "hospital-admissions", "smoothed_covid19", hosp_geos, + + "indicator-combination", "nmf_day_doc_fbc_fbs_ght", combo_geos, + "indicator-combination", "nmf_day_doc_fbs_ght", combo_geos, + + # Quidel flu signals + "quidel", "raw_pct_negative", quidel_geos, + "quidel", "smoothed_pct_negative", quidel_geos, + "quidel", "raw_tests_per_device", quidel_geos, + "quidel", "smoothed_tests_per_device", quidel_geos +) -# Tool: Are there any data sources where geos_list is different for different signal? -different_geos_by_signal <- count(auto_geo_list_by_signal, data_source, geos_list, name = "n_signals") -# different_geos_by_signal -# which(duplicated(select(different_geos_by_signal, data_source))) +source_updated[, col] <- coalesce(avail_geos[source_updated$data_source], source_updated[[col]]) + +source_updated <- left_join( + source_updated, leftover_signal_geos_manual, + by = c("Signal" = "signal", "data_source") +) %>% + mutate(`Available Geography` = coalesce(geos_list, `Available Geography`)) %>% + select(-geos_list) -# Keep most common geos_list for each data source. -most_common_geos_list <- group_by(different_geos_by_signal, data_source) %>% - slice_max(n_signals, with_ties = FALSE) -# most_common_geos_list -leftover_datasource_geos <- anti_join(different_geos_by_signal, most_common_geos_list) -# leftover_datasource_geos -leftover_signal_geos <- semi_join(auto_geo_list_by_signal, leftover_datasource_geos) -# leftover_signal_geos -delphi_agg_text <- " (by Delphi)" +col <- "Delphi-Aggregated Geography" +# List available geo-levels that were created by Delphi (as opposed to being +# ingested directly from the data source), e.g. if available at the county, +# state, and nation levels but state and nation were aggregated by us from +# provided county data: state,nation # These values are applied first. They are the default (most common) geos for each data source. avail_geos <- c( - "chng" = glue("county, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), - "covid-act-now" = glue("county, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), - "doctor-visits" = glue("county, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), - "dsew-cpr" = glue("county, msa, state, hhs, nation{delphi_agg_text}"), - "fb-survey" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, nation{delphi_agg_text}"), - "ght" = glue("hrr{delphi_agg_text}, msa{delphi_agg_text}, dma, state"), - "google-survey" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}"), - "google-symptoms" = glue("county, hrr{delphi_agg_text}, msa{delphi_agg_text}, state, hhs{delphi_agg_text}, nation{delphi_agg_text}"), - "hhs" = glue("state, hhs{delphi_agg_text}, nation{delphi_agg_text}"), - "hospital-admissions" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), - "indicator-combination" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), - "jhu-csse" = glue("county, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), - "nchs-mortality" = glue("state, nation"), + "chng" = glue("hrr,msa,state,hhs,nation"), + "covid-act-now" = glue("hrr,msa,state,hhs,nation"), + "doctor-visits" = glue("hrr,msa,state,hhs,nation"), + "dsew-cpr" = glue("nation"), + "fb-survey" = glue("county,hrr,msa,state,nation"), + "ght" = glue("hrr,msa"), + "google-survey" = glue("county,hrr,msa,state"), + "google-symptoms" = glue("hrr,msa,hhs,nation"), + "hhs" = glue("hhs,nation"), + "hospital-admissions" = glue("county,hrr,msa,state,hhs,nation"), + "indicator-combination" = glue("county,hrr,msa,state,hhs,nation"), + "jhu-csse" = glue("hrr,msa,state,hhs,nation"), + "nchs-mortality" = NA_character_, # Quidel non-flu signals - "quidel" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), - "safegraph" = glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), - "usa-facts" = glue("county, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, hhs{delphi_agg_text}, nation{delphi_agg_text}"), - "youtube-survey" = "state{delphi_agg_text}" + "quidel" = glue("county,hrr,msa,state,hhs,nation"), + "safegraph" = glue("county,hrr,msa,state,hhs,nation"), + "usa-facts" = glue("hrr,msa,state,hhs,nation"), + "youtube-survey" = "state" ) # These are signal-specific geo lists. These are less common and are applied as a patch. -dsew_geos <- glue("state, hhs, nation{delphi_agg_text}") -fb_geos1 <- glue("county{delphi_agg_text}, state{delphi_agg_text}, nation{delphi_agg_text}") -fb_geos2 <- glue("county{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}, nation{delphi_agg_text}") -hosp_geos <- glue("county{delphi_agg_text}, hrr{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}") -combo_geos <- glue("county{delphi_agg_text}, msa{delphi_agg_text}, state{delphi_agg_text}") -quidel_geos <- glue("msa{delphi_agg_text}, state{delphi_agg_text}") +dsew_geos <- glue("nation") +fb_geos1 <- glue("county,state,nation") +fb_geos2 <- glue("county,msa,state,nation") +hosp_geos <- glue("county,hrr,msa,state") +combo_geos <- glue("county,msa,state") +quidel_geos <- glue("msa,state") leftover_signal_geos_manual <- tibble::tribble( ~data_source, ~signal, ~geos_list, "chng", "7dav_inpatient_covid", "state", @@ -470,10 +566,11 @@ source_updated <- left_join( source_updated, leftover_signal_geos_manual, by = c("Signal" = "signal", "data_source") ) %>% - mutate(`Available Geography` = coalesce(geos_list, `Available Geography`)) %>% + mutate(`Delphi-Aggregated Geography` = coalesce(geos_list, `Delphi-Aggregated Geography`)) %>% select(-geos_list) + # Temporal Scope Start # Above. YYYY-MM-DD, with epiweeks as YYYY-WW. Formatted as a string From 59d37341aef45bf488f2c5ceda9c541f4cce114e Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Wed, 29 May 2024 11:52:06 -0400 Subject: [PATCH 24/30] generalize coalesce for start/end dates --- scripts/signal_spreadsheet_updater.R | 15 +++++---------- 1 file changed, 5 insertions(+), 10 deletions(-) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index 8456fa736..19dcb3626 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -181,15 +181,10 @@ source3 <- left_join( by = c("Signal" = "signal", "data_source") ) -# Fill in Temporal Scope Start/End for quidel signals by coalescing the existing -# column with the new data; quidel dates have already been filled in manually in -# the spreadsheet. -source3$min_time <- case_when( - source3$data_source == "quidel" ~ coalesce(source3$min_time, source3$`Temporal Scope Start`) -) -source3$max_time <- case_when( - source3$data_source == "quidel" ~ coalesce(source3$max_time, source3$`Temporal Scope Start`) -) +# Assume new values for Temporal Scope Start/End are correct, but use previous +# (manual) values as backup. +source3$min_time <- coalesce(source3$min_time, source3$`Temporal Scope Start`) +source3$max_time <- coalesce(source3$max_time, source3$`Temporal Scope End`) # Select relevant columns # first reformat max_time col to character for compatibility @@ -566,7 +561,7 @@ source_updated <- left_join( source_updated, leftover_signal_geos_manual, by = c("Signal" = "signal", "data_source") ) %>% - mutate(`Delphi-Aggregated Geography` = coalesce(geos_list, `Delphi-Aggregated Geography`)) %>% + mutate(`Delphi-Aggregated Geography` = geos_list) %>% select(-geos_list) From 73d78cd405d58284d30b5334f4bbda07059d65ec Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Wed, 29 May 2024 12:31:26 -0400 Subject: [PATCH 25/30] quidel revision cadence and TODO --- scripts/signal_spreadsheet_updater.R | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/scripts/signal_spreadsheet_updater.R b/scripts/signal_spreadsheet_updater.R index 19dcb3626..a109ccf16 100644 --- a/scripts/signal_spreadsheet_updater.R +++ b/scripts/signal_spreadsheet_updater.R @@ -29,7 +29,6 @@ options(warn = 1) # TODO all info for youtube-survey. Information is hard to find. Filled out some fields based on https://github.com/cmu-delphi/covid-19/tree/main/youtube -# TODO some info for quidel. # COVIDcast metadata # Metadata documentation: https://cmu-delphi.github.io/delphi-epidata/api/covidcast_meta.html @@ -742,7 +741,7 @@ revision_cadence <- c( corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.", "nchs-mortality" = "Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7)", - "quidel" = "Weekly. Happens, up to 6+ weeks after the report date.", + "quidel" = "Daily. Happens up to 6+ weeks after the report date. Revised values vary -3.5 to 1.8% around the final value for a given date and location.", "safegraph" = "None", "usa-facts" = "None. The raw data reports cumulative cases and deaths, which Delphi diffs to compute incidence. Raw cumulative figures are sometimes corrected by adjusting the reported value for a single day, but revisions do not affect past report dates.", "youtube-survey" = NA_character_ # See https://github.com/cmu-delphi/covid-19/tree/main/youtube From 70e98166b1eff258dba0c804fb44d57494b28db5 Mon Sep 17 00:00:00 2001 From: nmdefries Date: Wed, 29 May 2024 16:50:32 +0000 Subject: [PATCH 26/30] chore: update docs --- .../endpoints/covidcast_utils/db_signals.csv | 62 +++++++++---------- 1 file changed, 31 insertions(+), 31 deletions(-) diff --git a/src/server/endpoints/covidcast_utils/db_signals.csv b/src/server/endpoints/covidcast_utils/db_signals.csv index 905c8a10d..bcddbc442 100644 --- a/src/server/endpoints/covidcast_utils/db_signals.csv +++ b/src/server/endpoints/covidcast_utils/db_signals.csv @@ -1454,65 +1454,65 @@ jhu-csse,deaths_cumulative_num,TRUE,deaths_incidence_prop,FALSE,"Confirmed COVID do not affect past report dates.",All,None,dead,None,Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,See license,NA, nchs-mortality,deaths_allcause_incidence_num,FALSE,deaths_allcause_incidence_num,FALSE,All Causes Deaths (Weekly new),TRUE,Number of weekly new deaths from all causes,"Number of weekly new deaths from all causes. -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,n/a,Deaths,USA,"state,nation",nation,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,n/a,Deaths,USA,"state,nation",,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html nchs-mortality,deaths_allcause_incidence_num,TRUE,deaths_allcause_incidence_prop,FALSE,"All Causes Deaths (Weekly new, per 100k people)",TRUE,"Number of weekly new deaths from all causes, per 100k people","Number of weekly new deaths from all causes, per 100k people. -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,n/a,Deaths,USA,"state,nation",nation,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm, +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,n/a,Deaths,USA,"state,nation",,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm, nchs-mortality,deaths_covid_and_pneumonia_notflu_incidence_num,FALSE,deaths_covid_and_pneumonia_notflu_incidence_num,FALSE,COVID and Pneumonia excl. Influenza Deaths (Weekly new),TRUE,"Number of weekly new deaths involving COVID-19 and Pneumonia, excluding Influenza ","Number of weekly new deaths involving COVID-19 and Pneumonia, excluding Influenza . -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,"covid, pneumonia",Deaths,USA,"state,nation",nation,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,"covid, pneumonia",Deaths,USA,"state,nation",,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html nchs-mortality,deaths_covid_and_pneumonia_notflu_incidence_num,TRUE,deaths_covid_and_pneumonia_notflu_incidence_prop,FALSE,"COVID and Pneumonia excl. Influenza Deaths (Weekly new, per 100k people)",TRUE,"Number of weekly new deaths involving COVID-19 and Pneumonia, excluding Influenza, per 100k people","Number of weekly new deaths involving COVID-19 and Pneumonia, excluding Influenza, per 100k people. -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,covid,Deaths,USA,"state,nation",nation,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm, +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,covid,Deaths,USA,"state,nation",,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm, nchs-mortality,deaths_covid_incidence_num,FALSE,deaths_covid_incidence_num,FALSE,Confirmed or Presumed COVID Deaths (Weekly new),TRUE,Number of weekly new deaths with confirmed or presumed COVID-19 ,"Number of weekly new deaths with confirmed or presumed COVID-19 . -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,covid,Deaths,USA,"state,nation",nation,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,covid,Deaths,USA,"state,nation",,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html nchs-mortality,deaths_covid_incidence_num,TRUE,deaths_covid_incidence_prop,FALSE,"Confirmed or Presumed COVID Deaths (Weekly new, per 100k people)",TRUE,"Number of weekly new deaths with confirmed or presumed COVID-19, per 100k people","Number of weekly new deaths with confirmed or presumed COVID-19, per 100k people. -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,covid,Deaths,USA,"state,nation",nation,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm, +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,covid,Deaths,USA,"state,nation",,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm, nchs-mortality,deaths_flu_incidence_num,FALSE,deaths_flu_incidence_num,FALSE,Influenza Deaths (Weekly new),TRUE,"Number of weekly new deaths involving Influenza and at least one of (Pneumonia, COVID-19)","Number of weekly new deaths involving Influenza and at least one of (Pneumonia, COVID-19). -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,flu,Deaths,USA,"state,nation",nation,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,flu,Deaths,USA,"state,nation",,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html nchs-mortality,deaths_flu_incidence_num,TRUE,deaths_flu_incidence_prop,FALSE,"Influenza Deaths (Weekly new, per 100k people)",TRUE,"Number of weekly new deaths involving Influenza and at least one of (Pneumonia, COVID-19), per 100k people","Number of weekly new deaths involving Influenza and at least one of (Pneumonia, COVID-19), per 100k people. -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,flu,Deaths,USA,"state,nation",nation,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm, +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,flu,Deaths,USA,"state,nation",,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm, nchs-mortality,deaths_percent_of_expected,FALSE,deaths_percent_of_expected,FALSE,Percentage of Expected Deaths,TRUE,Weekly new deaths for all causes in 2020 as a percentage of the average number across the same week in 2017-2019.,"Weekly new deaths for all causes in 2020 as a percentage of the average number across the same week in 2017-2019.. -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,n/a,Deaths,USA,"state,nation",nation,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Percentage,percent,late,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,n/a,Deaths,USA,"state,nation",,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Percentage,percent,late,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html nchs-mortality,deaths_pneumonia_notflu_incidence_num,FALSE,deaths_pneumonia_notflu_incidence_num,FALSE,Pneumonia excl. Influenza Deaths (Weekly new),TRUE,"Number of weekly new deaths involving Pneumonia, excluding Influenza deaths ","Number of weekly new deaths involving Pneumonia, excluding Influenza deaths . -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,pneumonia,Deaths,USA,"state,nation",nation,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,pneumonia,Deaths,USA,"state,nation",,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html nchs-mortality,deaths_pneumonia_notflu_incidence_num,TRUE,deaths_pneumonia_notflu_incidence_prop,FALSE,"Pneumonia excl. Influenza Deaths (Weekly new, per 100k people)",TRUE,"Number of weekly new deaths involving Pneumonia, excluding Influenza deaths, per 100k people","Number of weekly new deaths involving Pneumonia, excluding Influenza deaths, per 100k people. -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,pneumonia,Deaths,USA,"state,nation",nation,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm, +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,pneumonia,Deaths,USA,"state,nation",,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm, nchs-mortality,deaths_pneumonia_or_flu_or_covid_incidence_num,FALSE,deaths_pneumonia_or_flu_or_covid_incidence_num,FALSE,"COVID, Pneumonia or Influenza Deaths (Weekly new)",TRUE,"Number of weekly new deaths involving Pneumonia, Influenza, or COVID-19 ","Number of weekly new deaths involving Pneumonia, Influenza, or COVID-19 . -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,"pneumonia, flu, covid",Deaths,USA,"state,nation",nation,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,"pneumonia, flu, covid",Deaths,USA,"state,nation",,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,count,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/nchs-mortality.html nchs-mortality,deaths_pneumonia_or_flu_or_covid_incidence_num,TRUE,deaths_pneumonia_or_flu_or_covid_incidence_prop,FALSE,"COVID, Pneumonia or Influenza Deaths (Weekly new, per 100k people)",TRUE,"Number of weekly new deaths involving Pneumonia, Influenza, or COVID-19, per 100k people","Number of weekly new deaths involving Pneumonia, Influenza, or COVID-19, per 100k people. -National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,"pneumonia, flu, covid",Deaths,USA,"state,nation",nation,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm, -quidel-covid-ag,covid_ag_raw_pct_positive,FALSE,covid_ag_raw_pct_positive,FALSE,COVID-19 Antigen Tests: Percent Positive,TRUE,Percentage of antigen tests that were positive for COVID-19,"When a patient (whether at a doctor's office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19.",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 7% of counties, half that on weekends. Data is available for about 90% of states, about 70% on weekends",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests) -quidel-covid-ag,covid_ag_raw_pct_positive,TRUE,covid_ag_smoothed_pct_positive,FALSE,COVID-19 Antigen Tests: Percent Positive (7-day average),TRUE,,,Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 50% of counties, and all or nearly all states.",Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS, -quidel-covid-ag,covid_ag_raw_pct_positive_age_0_17,FALSE,covid_ag_raw_pct_positive_age_0_17,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 0-17",TRUE,Percentage of antigen tests that were positive for COVID-19 among people ages 0-17,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 0-17",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 0.7-2% of counties, half that on weekends. Data is available for about 30-45% of states, half that on weekends. Geographic coverage for smaller age groups (age 0-4 and age 65+) are also extremely limited at the HRR and MSA levels",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests) -quidel-covid-ag,covid_ag_raw_pct_positive_age_0_17,TRUE,covid_ag_smoothed_pct_positive_age_0_17,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 0-17 (Smoothed)",TRUE,,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 0-17, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests",Data is available for about 5-15% of counties. 65-95% of states.,Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS, -quidel-covid-ag,covid_ag_raw_pct_positive_age_0_4,FALSE,covid_ag_raw_pct_positive_age_0_4,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 0-4",TRUE,Percentage of antigen tests that were positive for COVID-19 among people ages 0-4,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 0-4",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 0.7-2% of counties, half that on weekends. Data is available for about 30-45% of states, half that on weekends. Geographic coverage for smaller age groups (age 0-4 and age 65+) are also extremely limited at the HRR and MSA levels",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests) -quidel-covid-ag,covid_ag_raw_pct_positive_age_0_4,TRUE,covid_ag_smoothed_pct_positive_age_0_4,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 0-4 (Smoothed)",TRUE,,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 0-4, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests",Data is available for about 5-15% of counties. 65-95% of states.,Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS, -quidel-covid-ag,covid_ag_raw_pct_positive_age_18_49,FALSE,covid_ag_raw_pct_positive_age_18_49,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 18-49",TRUE,Percentage of antigen tests that were positive for COVID-19 among people ages 18-49,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 18-49",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 0.7-2% of counties, half that on weekends. Data is available for about 30-45% of states, half that on weekends. Geographic coverage for smaller age groups (age 0-4 and age 65+) are also extremely limited at the HRR and MSA levels",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests) -quidel-covid-ag,covid_ag_raw_pct_positive_age_18_49,TRUE,covid_ag_smoothed_pct_positive_age_18_49,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 18-49 (Smoothed)",TRUE,,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 18-49, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests",Data is available for about 5-15% of counties. 65-95% of states.,Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS, -quidel-covid-ag,covid_ag_raw_pct_positive_age_5_17,FALSE,covid_ag_raw_pct_positive_age_5_17,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 5-17",TRUE,Percentage of antigen tests that were positive for COVID-19 among people ages 5-17,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 5-17",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 0.7-2% of counties, half that on weekends. Data is available for about 30-45% of states, half that on weekends. Geographic coverage for smaller age groups (age 0-4 and age 65+) are also extremely limited at the HRR and MSA levels",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests) -quidel-covid-ag,covid_ag_raw_pct_positive_age_5_17,TRUE,covid_ag_smoothed_pct_positive_age_5_17,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 5-17 (Smoothed)",TRUE,,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 5-17, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests",Data is available for about 5-15% of counties. 65-95% of states.,Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS, -quidel-covid-ag,covid_ag_raw_pct_positive_age_50_64,FALSE,covid_ag_raw_pct_positive_age_50_64,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 50-64",TRUE,Percentage of antigen tests that were positive for COVID-19 among people ages 50-64,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 50-64",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 0.7-2% of counties, half that on weekends. Data is available for about 30-45% of states, half that on weekends. Geographic coverage for smaller age groups (age 0-4 and age 65+) are also extremely limited at the HRR and MSA levels",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests) -quidel-covid-ag,covid_ag_raw_pct_positive_age_50_64,TRUE,covid_ag_smoothed_pct_positive_age_50_64,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 50-64 (Smoothed)",TRUE,,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 50-64, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests",Data is available for about 5-15% of counties. 65-95% of states.,Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS, -quidel-covid-ag,covid_ag_raw_pct_positive_age_65plus,FALSE,covid_ag_raw_pct_positive_age_65plus,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 65+",TRUE,Percentage of antigen tests that were positive for COVID-19 among people age 65 and above,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 65 and above",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 0.7-2% of counties, half that on weekends. Data is available for about 30-45% of states, half that on weekends. Geographic coverage for smaller age groups (age 0-4 and age 65+) are also extremely limited at the HRR and MSA levels",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests) -quidel-covid-ag,covid_ag_raw_pct_positive_age_65plus,TRUE,covid_ag_smoothed_pct_positive_age_65plus,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 65+ (Smoothed)",TRUE,,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 65 and above, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests",Data is available for about 5-15% of counties. 65-95% of states.,Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS, +National provisional death counts is based on death certificate data received and coded by the National Center for Health Statistics ([NCHS](https://www.cdc.gov/nchs/nvss/vsrr/COVID19/index.htm))",NCHS Mortality Data,"pneumonia, flu, covid",Deaths,USA,"state,nation",,2020-05,"Start dates vary by geo: nation 2020-06, state 2020-05",Ongoing,NA,week,Week,weekly,11-17 days,Weekly. All-cause mortality takes ~6 weeks on average to achieve 99% of its final value (https://link.springer.com/article/10.1057/s41271-021-00309-7),All,None,dead,"Unavailable by NCHS when counts are between 1 and 9, and for weeks where the counts are less than 50% of the expected number, since these provisional counts are highly incomplete and potentially misleading",Data is available for all states and some territories.,Value,per100k,late,bad,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,NCHS Data Use Agreement (https://www.cdc.gov/nchs/data_access/restrictions.htm),See license,https://www.cdc.gov/nchs/data_access/restrictions.htm, +quidel-covid-ag,covid_ag_raw_pct_positive,FALSE,covid_ag_raw_pct_positive,FALSE,COVID-19 Antigen Tests: Percent Positive,TRUE,Percentage of antigen tests that were positive for COVID-19,"When a patient (whether at a doctor's office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19.",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,Daily. Happens up to 6+ weeks after the report date. Revised values vary -3.5 to 1.8% around the final value for a given date and location.,Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 7% of counties, half that on weekends. Data is available for about 90% of states, about 70% on weekends",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests) +quidel-covid-ag,covid_ag_raw_pct_positive,TRUE,covid_ag_smoothed_pct_positive,FALSE,COVID-19 Antigen Tests: Percent Positive (7-day average),TRUE,,,Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,Daily. Happens up to 6+ weeks after the report date. Revised values vary -3.5 to 1.8% around the final value for a given date and location.,Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 50% of counties, and all or nearly all states.",Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS, +quidel-covid-ag,covid_ag_raw_pct_positive_age_0_17,FALSE,covid_ag_raw_pct_positive_age_0_17,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 0-17",TRUE,Percentage of antigen tests that were positive for COVID-19 among people ages 0-17,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 0-17",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,Daily. Happens up to 6+ weeks after the report date. Revised values vary -3.5 to 1.8% around the final value for a given date and location.,Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 0.7-2% of counties, half that on weekends. Data is available for about 30-45% of states, half that on weekends. Geographic coverage for smaller age groups (age 0-4 and age 65+) are also extremely limited at the HRR and MSA levels",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests) +quidel-covid-ag,covid_ag_raw_pct_positive_age_0_17,TRUE,covid_ag_smoothed_pct_positive_age_0_17,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 0-17 (Smoothed)",TRUE,,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 0-17, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,Daily. Happens up to 6+ weeks after the report date. Revised values vary -3.5 to 1.8% around the final value for a given date and location.,Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests",Data is available for about 5-15% of counties. Data is available for about 65-95% of states.,Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS, +quidel-covid-ag,covid_ag_raw_pct_positive_age_0_4,FALSE,covid_ag_raw_pct_positive_age_0_4,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 0-4",TRUE,Percentage of antigen tests that were positive for COVID-19 among people ages 0-4,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 0-4",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,Daily. Happens up to 6+ weeks after the report date. Revised values vary -3.5 to 1.8% around the final value for a given date and location.,Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 0.7-2% of counties, half that on weekends. Data is available for about 30-45% of states, half that on weekends. Geographic coverage for smaller age groups (age 0-4 and age 65+) are also extremely limited at the HRR and MSA levels",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests) +quidel-covid-ag,covid_ag_raw_pct_positive_age_0_4,TRUE,covid_ag_smoothed_pct_positive_age_0_4,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 0-4 (Smoothed)",TRUE,,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 0-4, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,Daily. Happens up to 6+ weeks after the report date. Revised values vary -3.5 to 1.8% around the final value for a given date and location.,Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests",Data is available for about 5-15% of counties. Data is available for about 65-95% of states.,Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS, +quidel-covid-ag,covid_ag_raw_pct_positive_age_18_49,FALSE,covid_ag_raw_pct_positive_age_18_49,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 18-49",TRUE,Percentage of antigen tests that were positive for COVID-19 among people ages 18-49,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 18-49",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,Daily. Happens up to 6+ weeks after the report date. Revised values vary -3.5 to 1.8% around the final value for a given date and location.,Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 0.7-2% of counties, half that on weekends. Data is available for about 30-45% of states, half that on weekends. Geographic coverage for smaller age groups (age 0-4 and age 65+) are also extremely limited at the HRR and MSA levels",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests) +quidel-covid-ag,covid_ag_raw_pct_positive_age_18_49,TRUE,covid_ag_smoothed_pct_positive_age_18_49,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 18-49 (Smoothed)",TRUE,,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 18-49, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,Daily. Happens up to 6+ weeks after the report date. Revised values vary -3.5 to 1.8% around the final value for a given date and location.,Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests",Data is available for about 5-15% of counties. Data is available for about 65-95% of states.,Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS, +quidel-covid-ag,covid_ag_raw_pct_positive_age_5_17,FALSE,covid_ag_raw_pct_positive_age_5_17,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 5-17",TRUE,Percentage of antigen tests that were positive for COVID-19 among people ages 5-17,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 5-17",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,Daily. Happens up to 6+ weeks after the report date. Revised values vary -3.5 to 1.8% around the final value for a given date and location.,Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 0.7-2% of counties, half that on weekends. Data is available for about 30-45% of states, half that on weekends. Geographic coverage for smaller age groups (age 0-4 and age 65+) are also extremely limited at the HRR and MSA levels",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests) +quidel-covid-ag,covid_ag_raw_pct_positive_age_5_17,TRUE,covid_ag_smoothed_pct_positive_age_5_17,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 5-17 (Smoothed)",TRUE,,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 5-17, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,Daily. Happens up to 6+ weeks after the report date. Revised values vary -3.5 to 1.8% around the final value for a given date and location.,Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests",Data is available for about 5-15% of counties. Data is available for about 65-95% of states.,Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS, +quidel-covid-ag,covid_ag_raw_pct_positive_age_50_64,FALSE,covid_ag_raw_pct_positive_age_50_64,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 50-64",TRUE,Percentage of antigen tests that were positive for COVID-19 among people ages 50-64,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 50-64",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,Daily. Happens up to 6+ weeks after the report date. Revised values vary -3.5 to 1.8% around the final value for a given date and location.,Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 0.7-2% of counties, half that on weekends. Data is available for about 30-45% of states, half that on weekends. Geographic coverage for smaller age groups (age 0-4 and age 65+) are also extremely limited at the HRR and MSA levels",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests) +quidel-covid-ag,covid_ag_raw_pct_positive_age_50_64,TRUE,covid_ag_smoothed_pct_positive_age_50_64,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 50-64 (Smoothed)",TRUE,,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 50-64, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,Daily. Happens up to 6+ weeks after the report date. Revised values vary -3.5 to 1.8% around the final value for a given date and location.,Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests",Data is available for about 5-15% of counties. Data is available for about 65-95% of states.,Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS, +quidel-covid-ag,covid_ag_raw_pct_positive_age_65plus,FALSE,covid_ag_raw_pct_positive_age_65plus,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 65+",TRUE,Percentage of antigen tests that were positive for COVID-19 among people age 65 and above,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 65 and above",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,Daily. Happens up to 6+ weeks after the report date. Revised values vary -3.5 to 1.8% around the final value for a given date and location.,Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 0.7-2% of counties, half that on weekends. Data is available for about 30-45% of states, half that on weekends. Geographic coverage for smaller age groups (age 0-4 and age 65+) are also extremely limited at the HRR and MSA levels",Percentage,percent,cases_testing,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,[Technical description](https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#covid-19-tests) +quidel-covid-ag,covid_ag_raw_pct_positive_age_65plus,TRUE,covid_ag_smoothed_pct_positive_age_65plus,FALSE,"COVID-19 Antigen Tests: Percent Positive, Ages 65+ (Smoothed)",TRUE,,"When a patient (whether at a doctor’s office, clinic, or hospital) has COVID-like symptoms, doctors may order an antigen test. An antigen test can detect parts of the virus that are present during an active infection. This is in contrast with antibody tests, which detect parts of the immune system that react to the virus, but which persist long after the infection has passed. For this signal, we compute the percentage of antigen tests performed that were positive for COVID-19 among people ages 65 and above, smoothed using a 7-day moving average and geographical pooling",Quidel Inc. (COVID),covid,Testing,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2020-05-26,NA,Ongoing,NA,day,Date,daily,5-6 days,Daily. Happens up to 6+ weeks after the report date. Revised values vary -3.5 to 1.8% around the final value for a given date and location.,Nationwide Quidel testing equipment network,"age (0-17, 0-4, 5-17, 18-49, 50-64, 65+)",ascertained (case),"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests",Data is available for about 5-15% of counties. Data is available for about 65-95% of states.,Percentage,percent,cases_testing,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS, quidel-flu,raw_pct_negative,FALSE,raw_pct_negative,FALSE,Flu Tests: Percent Negative,FALSE,"The percentage of flu tests that are negative, suggesting the patient's illness has another cause, possibly COVID-19 ","The percentage of flu tests that are negative, suggesting the patient's illness has another cause, possibly COVID-19 . -Discontinued May 19, 2020.",Quidel Inc. (Flu),flu,Testing,USA,"msa,state","msa,state",2020-01-31,NA,2020-05-10,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,None,population,"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 7% of counties, half that on weekends. Data is available for about 90% of states, about 70% on weekends",Percentage,percent,late,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#flu-tests -quidel-flu,raw_pct_negative,TRUE,smoothed_pct_negative,FALSE,Flu Tests: Percent Negative (7-day average),FALSE,,,Quidel Inc. (Flu),flu,Testing,USA,"msa,state","msa,state",2020-01-31,NA,2020-05-10,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,None,population,"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 50% of counties, and all or nearly all states.",Percentage,percent,late,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS, +Discontinued May 19, 2020.",Quidel Inc. (Flu),flu,Testing,USA,"msa,state","msa,state",2020-01-31,NA,2020-05-10,NA,day,Date,daily,5-6 days,Daily. Happens up to 6+ weeks after the report date. Revised values vary -3.5 to 1.8% around the final value for a given date and location.,Nationwide Quidel testing equipment network,None,population,"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 7% of counties, half that on weekends. Data is available for about 90% of states, about 70% on weekends",Percentage,percent,late,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#flu-tests +quidel-flu,raw_pct_negative,TRUE,smoothed_pct_negative,FALSE,Flu Tests: Percent Negative (7-day average),FALSE,,,Quidel Inc. (Flu),flu,Testing,USA,"msa,state","msa,state",2020-01-31,NA,2020-05-10,NA,day,Date,daily,5-6 days,Daily. Happens up to 6+ weeks after the report date. Revised values vary -3.5 to 1.8% around the final value for a given date and location.,Nationwide Quidel testing equipment network,None,population,"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 50% of counties, and all or nearly all states.",Percentage,percent,late,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS, quidel-flu,raw_tests_per_device,FALSE,raw_tests_per_device,FALSE,Flu Tests: Tests Per Device,FALSE,The average number of flu tests conducted by each testing device; measures volume of testing ,"The average number of flu tests conducted by each testing device; measures volume of testing . -Discontinued May 19, 2020.",Quidel Inc. (Flu),flu,Testing,USA,"msa,state","msa,state",2020-01-31,NA,2020-05-10,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,None,population,"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 7% of counties, half that on weekends. Data is available for about 90% of states, about 70% on weekends",Number of Tests,count,late,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#flu-tests -quidel-flu,raw_tests_per_device,TRUE,smoothed_tests_per_device,FALSE,Flu Tests: Tests Per Device (7-day average),FALSE,,,Quidel Inc. (Flu),flu,Testing,USA,"msa,state","msa,state",2020-01-31,NA,2020-05-10,NA,day,Date,daily,5-6 days,"Weekly. Happens, up to 6+ weeks after the report date.",Nationwide Quidel testing equipment network,None,population,"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 50% of counties, and all or nearly all states.",Number of Tests,count,late,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS, +Discontinued May 19, 2020.",Quidel Inc. (Flu),flu,Testing,USA,"msa,state","msa,state",2020-01-31,NA,2020-05-10,NA,day,Date,daily,5-6 days,Daily. Happens up to 6+ weeks after the report date. Revised values vary -3.5 to 1.8% around the final value for a given date and location.,Nationwide Quidel testing equipment network,None,population,"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 7% of counties, half that on weekends. Data is available for about 90% of states, about 70% on weekends",Number of Tests,count,late,bad,FALSE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS,https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/quidel.html#flu-tests +quidel-flu,raw_tests_per_device,TRUE,smoothed_tests_per_device,FALSE,Flu Tests: Tests Per Device (7-day average),FALSE,,,Quidel Inc. (Flu),flu,Testing,USA,"msa,state","msa,state",2020-01-31,NA,2020-05-10,NA,day,Date,daily,5-6 days,Daily. Happens up to 6+ weeks after the report date. Revised values vary -3.5 to 1.8% around the final value for a given date and location.,Nationwide Quidel testing equipment network,None,population,"Discarded when an estimate is based on fewer than 50 tests. For smoothed signals at the county, MSA, and HRR levels with between 25 and 50 tests, the estimate is computed with the original N tests and 50-N synthetic tests that have the same test positivity rate as the parent state (state with the largest proportion of the population in this region); estimates are entirely discarded when based on fewer than 25 tests","Data is available for about 50% of counties, and all or nearly all states.",Number of Tests,count,late,bad,TRUE,FALSE,FALSE,TRUE,TRUE,Delphi,public,CC BY,Quidel provides Delphi data solely for internal research use and non-commercial research and analytics purposes for developing models for forecasting influenza-like epidemics and pandemics (CC BY).,https://drive.google.com/drive/u/1/folders/1HhOEbXlZXN9YpHBWOfrY7Wo2USVVfJVS, safegraph-daily,completely_home_prop,FALSE,completely_home_prop,FALSE,Completely Home,FALSE,The fraction of mobile devices that did not leave the immediate area of their home,"The fraction of mobile devices that did not leave the immediate area of their home. This is SafeGraph’s completely_home_device_count / device_count. Discontinued April 19th, 2021.",SafeGraph (Daily),n/a,Mobility,USA,"county,hrr,msa,state,hhs,nation","county,hrr,msa,state,hhs,nation",2019-01-01,"Start dates vary by geo: county 2019-01-01, hhs 2020-12-01, hrr 2019-01-01, msa 2019-01-01, nation 2020-12-01, state 2019-01-01",2021-04-16,NA,day,Date,weekly,3-11 days,None,Safegraph panel members who use mobile devices,None,population,"None. However, Safegraph uses differential privacy, which adds artificial noise to the incoming data. See https://docs.safegraph.com/docs/social-distancing-metrics for details",Data is available for all counties and some territorial county equivalents. Data is available for all states and some territories.,Value,per100k,public,neutral,FALSE,FALSE,FALSE,FALSE,FALSE,public,public,CC BY,"Delphi is free to publish and otherwise disclose the results of its Research (including but not limited to reports and papers and other activities conducted under the Research), including analyses and/or aggregated reporting of the Data. However, the underlying raw Data may not be published From 7eadc13d3b49afe2c445df2a947966fed7d5fdb8 Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Wed, 29 May 2024 15:49:44 -0400 Subject: [PATCH 27/30] state epidatr is ready --- docs/api/client_libraries.md | 34 ++++++++++++++++++++++++---------- 1 file changed, 24 insertions(+), 10 deletions(-) diff --git a/docs/api/client_libraries.md b/docs/api/client_libraries.md index 8bea7f667..d7bbc142b 100644 --- a/docs/api/client_libraries.md +++ b/docs/api/client_libraries.md @@ -8,11 +8,13 @@ nav_order: 1 For anyone looking for COVIDCast data, please visit our [COVIDCast Libraries](covidcast_clients.md). -We are currently working on fully-featured Epidata clients for R and Python. They are not ready -for release yet, but you can track our development progress and help us test them out at: +A full-featured Epidata client for R is available at +[epidatr](https://github.com/cmu-delphi/epidatr) and +[also on CRAN](https://cran.r-project.org/web/packages/epidatr/index.html). -* [epidatr](https://github.com/cmu-delphi/epidatr) -* [epidatpy](https://github.com/cmu-delphi/epidatpy) +We are currently working on a new full-featured Epidata client for Python. It is not ready +for release yet, but you can track our development progress and help us test it out at +[epidatpy](https://github.com/cmu-delphi/epidatpy). In the meantime, minimalist Epidata clients remain available for [JavaScript](https://github.com/cmu-delphi/delphi-epidata/blob/master/src/client/delphi_epidata.js), @@ -20,9 +22,23 @@ In the meantime, minimalist Epidata clients remain available for and [R](https://github.com/cmu-delphi/delphi-epidata/blob/master/src/client/delphi_epidata.R). The following samples show how to import the library and fetch Delphi's COVID-19 -Surveillance Streams from Facebook Survey CLI for county 06001 and days +Surveillance Streams from Facebook Survey CLI for county 06001, and days `20200401` and `20200405-20200414` (11 days total). +### R + +````R +# [Optional] configure your API key, if desired +# Interactive. See https://cmu-delphi.github.io/epidatr/articles/epidatr.html#api-keys for details. +#save_api_key() +# Import +library(epidatr) +# Fetch data +res <- pub_covidcast('fb-survey', 'smoothed_cli', 'county', 'day', geo_values = '06001', + time_values = c(20200401, 20200405:20200414)) +cat(res) +```` + ### JavaScript (in a web browser) The minimalist JavaScript client does not currently support API keys. If you need API key support in JavaScript, contact delphi-support+privacy@andrew.cmu.edu. @@ -40,7 +56,6 @@ The minimalist JavaScript client does not currently support API keys. If you nee ### Python - Optionally install the [package from PyPI](https://pypi.org/project/delphi-epidata/) using pip(env): ````bash pip install delphi-epidata @@ -60,10 +75,9 @@ res = Epidata.covidcast('fb-survey', 'smoothed_cli', 'day', 'county', [20200401, print(res['result'], res['message'], len(res['epidata'])) ```` -### R - +### R (legacy) -````R +```R # [Optional] configure your API key, if desired #option('epidata.auth', ) # Import @@ -71,4 +85,4 @@ source('delphi_epidata.R') # Fetch data res <- Epidata$covidcast('fb-survey', 'smoothed_cli', 'day', 'county', list(20200401, Epidata$range(20200405, 20200414)), '06001') cat(paste(res$result, res$message, length(res$epidata), "\n")) -```` +``` From 060c0976369ab3f7dc35c31fc72bf9112a33a445 Mon Sep 17 00:00:00 2001 From: Nat DeFries <42820733+nmdefries@users.noreply.github.com> Date: Thu, 30 May 2024 11:37:32 -0400 Subject: [PATCH 28/30] reorder clients by importance --- docs/api/client_libraries.md | 34 +++++++++++++++++----------------- 1 file changed, 17 insertions(+), 17 deletions(-) diff --git a/docs/api/client_libraries.md b/docs/api/client_libraries.md index d7bbc142b..5d4abb956 100644 --- a/docs/api/client_libraries.md +++ b/docs/api/client_libraries.md @@ -17,10 +17,10 @@ for release yet, but you can track our development progress and help us test it [epidatpy](https://github.com/cmu-delphi/epidatpy). In the meantime, minimalist Epidata clients remain available for -[JavaScript](https://github.com/cmu-delphi/delphi-epidata/blob/master/src/client/delphi_epidata.js), [Python](https://github.com/cmu-delphi/delphi-epidata/blob/master/src/client/delphi_epidata.py), +[JavaScript](https://github.com/cmu-delphi/delphi-epidata/blob/master/src/client/delphi_epidata.js), and -[R](https://github.com/cmu-delphi/delphi-epidata/blob/master/src/client/delphi_epidata.R). +[R (legacy)](https://github.com/cmu-delphi/delphi-epidata/blob/master/src/client/delphi_epidata.R). The following samples show how to import the library and fetch Delphi's COVID-19 Surveillance Streams from Facebook Survey CLI for county 06001, and days `20200401` and `20200405-20200414` (11 days total). @@ -39,21 +39,6 @@ res <- pub_covidcast('fb-survey', 'smoothed_cli', 'county', 'day', geo_values = cat(res) ```` -### JavaScript (in a web browser) - -The minimalist JavaScript client does not currently support API keys. If you need API key support in JavaScript, contact delphi-support+privacy@andrew.cmu.edu. - -````html - - - - -```` - ### Python Optionally install the [package from PyPI](https://pypi.org/project/delphi-epidata/) using pip(env): @@ -75,6 +60,21 @@ res = Epidata.covidcast('fb-survey', 'smoothed_cli', 'day', 'county', [20200401, print(res['result'], res['message'], len(res['epidata'])) ```` +### JavaScript (in a web browser) + +The minimalist JavaScript client does not currently support API keys. If you need API key support in JavaScript, contact delphi-support+privacy@andrew.cmu.edu. + +````html + + + + +```` + ### R (legacy) ```R From 3673ac9907c961eed6642d3b988c4343602a5929 Mon Sep 17 00:00:00 2001 From: Dmitry Shemetov Date: Fri, 31 May 2024 06:59:56 -0700 Subject: [PATCH 29/30] fix: Python client logger import (#1460) * fix: Python client logger import * add delphi-utils as dependency to Python client * import logger from delphi-utils instead of locally * unpin delphi-utils in both requirements files * update CHANGELOG --------- Co-authored-by: george haff --- requirements.api.txt | 2 +- requirements.dev.txt | 2 +- src/client/delphi_epidata.py | 2 +- src/client/packaging/pypi/CHANGELOG.md | 9 +++++++++ src/client/packaging/pypi/setup.py | 2 +- 5 files changed, 13 insertions(+), 4 deletions(-) diff --git a/requirements.api.txt b/requirements.api.txt index cb5195367..f9a46b113 100644 --- a/requirements.api.txt +++ b/requirements.api.txt @@ -1,4 +1,4 @@ -delphi_utils==0.3.15 +delphi_utils epiweeks==2.1.2 Flask==2.2.5 Flask-Limiter==3.3.0 diff --git a/requirements.dev.txt b/requirements.dev.txt index 840d885f5..ff7da9923 100644 --- a/requirements.dev.txt +++ b/requirements.dev.txt @@ -2,7 +2,7 @@ aiohttp==3.9.4 black>=20.8b1 bump2version==1.0.1 covidcast==0.1.5 -delphi_utils==0.3.15 +delphi_utils docker==6.0.1 dropbox==11.36.0 freezegun==1.2.2 diff --git a/src/client/delphi_epidata.py b/src/client/delphi_epidata.py index 7756f655c..2c25e07e6 100644 --- a/src/client/delphi_epidata.py +++ b/src/client/delphi_epidata.py @@ -16,7 +16,7 @@ from aiohttp import ClientSession, TCPConnector, BasicAuth -from delphi.epidata.common.logger import get_structured_logger +from delphi_utils.logger import get_structured_logger __version__ = "4.1.22" diff --git a/src/client/packaging/pypi/CHANGELOG.md b/src/client/packaging/pypi/CHANGELOG.md index 7cefbf96c..4d3890175 100644 --- a/src/client/packaging/pypi/CHANGELOG.md +++ b/src/client/packaging/pypi/CHANGELOG.md @@ -3,6 +3,15 @@ All notable future changes to the `delphi_epidata` python client will be documented in this file. The format is based on [Keep a Changelog](http://keepachangelog.com/). +## [4.2.23] - 2024-05-31 + +### Includes +- https://github.com/cmu-delphi/delphi-epidata/pull/1460 + +### Fixed +- Replaced bad internal logger package import with one from `delphi_utils` package instead. + - This bug affected releases 4.1.21 and 4.1.22 + ## [4.1.21] - 2024-05-20 ### Includes diff --git a/src/client/packaging/pypi/setup.py b/src/client/packaging/pypi/setup.py index 1a49acd8d..a7f57556a 100644 --- a/src/client/packaging/pypi/setup.py +++ b/src/client/packaging/pypi/setup.py @@ -16,7 +16,7 @@ "Changelog": "https://github.com/cmu-delphi/delphi-epidata/blob/main/src/client/packaging/pypi/CHANGELOG.md", }, packages=setuptools.find_packages(), - install_requires=["aiohttp", "requests>=2.7.0", "tenacity"], + install_requires=["aiohttp", "delphi-utils", "requests>=2.7.0", "tenacity"], classifiers=[ "Programming Language :: Python", "License :: OSI Approved :: MIT License", From 573fdb54d755178ec618f3776ce5ceedbdf3cf51 Mon Sep 17 00:00:00 2001 From: melange396 Date: Fri, 31 May 2024 14:01:12 +0000 Subject: [PATCH 30/30] chore: release delphi-epidata 4.1.23 --- .bumpversion.cfg | 2 +- dev/local/setup.cfg | 2 +- src/client/delphi_epidata.R | 2 +- src/client/delphi_epidata.js | 2 +- src/client/delphi_epidata.py | 2 +- src/client/packaging/npm/package.json | 2 +- src/client/packaging/pypi/setup.py | 2 +- src/server/_config.py | 2 +- 8 files changed, 8 insertions(+), 8 deletions(-) diff --git a/.bumpversion.cfg b/.bumpversion.cfg index 698741c02..b9f9c3763 100644 --- a/.bumpversion.cfg +++ b/.bumpversion.cfg @@ -1,5 +1,5 @@ [bumpversion] -current_version = 4.1.22 +current_version = 4.1.23 commit = False tag = False diff --git a/dev/local/setup.cfg b/dev/local/setup.cfg index 602c4ff5e..56dadceb4 100644 --- a/dev/local/setup.cfg +++ b/dev/local/setup.cfg @@ -1,6 +1,6 @@ [metadata] name = Delphi Development -version = 4.1.22 +version = 4.1.23 [options] packages = diff --git a/src/client/delphi_epidata.R b/src/client/delphi_epidata.R index 946fceaa8..b35e1213e 100644 --- a/src/client/delphi_epidata.R +++ b/src/client/delphi_epidata.R @@ -15,7 +15,7 @@ Epidata <- (function() { # API base url BASE_URL <- getOption('epidata.url', default = 'https://api.delphi.cmu.edu/epidata/') - client_version <- '4.1.22' + client_version <- '4.1.23' auth <- getOption("epidata.auth", default = NA) diff --git a/src/client/delphi_epidata.js b/src/client/delphi_epidata.js index 5a5c57cae..7c94b4d87 100644 --- a/src/client/delphi_epidata.js +++ b/src/client/delphi_epidata.js @@ -22,7 +22,7 @@ } })(this, function (exports, fetchImpl, jQuery) { const BASE_URL = "https://api.delphi.cmu.edu/epidata/"; - const client_version = "4.1.22"; + const client_version = "4.1.23"; // Helper function to cast values and/or ranges to strings function _listitem(value) { diff --git a/src/client/delphi_epidata.py b/src/client/delphi_epidata.py index 2c25e07e6..6fb7ab1ef 100644 --- a/src/client/delphi_epidata.py +++ b/src/client/delphi_epidata.py @@ -18,7 +18,7 @@ from delphi_utils.logger import get_structured_logger -__version__ = "4.1.22" +__version__ = "4.1.23" _HEADERS = {"user-agent": "delphi_epidata/" + __version__ + " (Python)"} diff --git a/src/client/packaging/npm/package.json b/src/client/packaging/npm/package.json index dcdd981ea..c1b92738c 100644 --- a/src/client/packaging/npm/package.json +++ b/src/client/packaging/npm/package.json @@ -2,7 +2,7 @@ "name": "delphi_epidata", "description": "Delphi Epidata API Client", "authors": "Delphi Group", - "version": "4.1.22", + "version": "4.1.23", "license": "MIT", "homepage": "https://github.com/cmu-delphi/delphi-epidata", "bugs": { diff --git a/src/client/packaging/pypi/setup.py b/src/client/packaging/pypi/setup.py index a7f57556a..d71ce3db9 100644 --- a/src/client/packaging/pypi/setup.py +++ b/src/client/packaging/pypi/setup.py @@ -5,7 +5,7 @@ setuptools.setup( name="delphi_epidata", - version="4.1.22", + version="4.1.23", author="David Farrow", author_email="dfarrow0@gmail.com", description="A programmatic interface to Delphi's Epidata API.", diff --git a/src/server/_config.py b/src/server/_config.py index 57e031b83..73b8f88f5 100644 --- a/src/server/_config.py +++ b/src/server/_config.py @@ -7,7 +7,7 @@ load_dotenv() -VERSION = "4.1.22" +VERSION = "4.1.23" MAX_RESULTS = int(10e6) MAX_COMPATIBILITY_RESULTS = int(3650)