Commit 3570d2a0 authored by pxp9's avatar pxp9

scripts de harmonizacion de David

parents
empty_cell_fixer.r + add_missing_values.r
Cambia las casillas vacías, puntos, "NA", y "Unknowns" por missing, y en el "_numeric" acorde lo cambia por un 999
dora_test.r
Ejecuta la función personalizada que calcula el score derivado de las variables
full_quality_report.r
Genera un documento word con los hospitales y las variables especificadas dónde se ordenan de mayor a menor varianza entre los hosptiales
survival_curve.r
Genera una curva de supervivencia
table1_script.r + necessary_functions_table1_v2_subset.r
Muestra una tabla que muestra la información sobre los hospitales y las variables indicadas.
valid_variables_script.r
Comprueba que los valores de las variables del hospital indicado estén dentro de los rangos
(Se puede cambiar para que refleje lo que se desea obtener)
treatment_heatmap.r
Devuelve un mapa de calor que indica el porcentaje de pacientes que han recibido cada tratamiento spearados por olas.
ressourceCleaner.r
Deja los datos con Yes/No Male/Female etc
ressourceHarmonizer.r
Deriva las variables "_numeric"
\ No newline at end of file
setwd("C:/Users/victor/Documents/TFG/r-analytics-master")
codebook <- read.csv("new_harmon.csv", sep = ",")
binary <- unlist(codebook[codebook["Variable.type"] == "Binary",]["Harmonised.variable.name"])
categorical <- unlist(codebook[codebook["Variable.type"] == "Categorical",]["Harmonised.variable.name"])
continuous <- unlist(codebook[codebook["Variable.type"] == "Continuous",]["Harmonised.variable.name"])
categoric_vars <- c(binary, categorical)
replace_with_Missing_categoric <- function(column){
for (i in 1:length(column)){
x <- column[i]
if (is.na(x)){
x <- "Missing"
}else{
if(x == "" | x == "NA" | x == "Unknown")
x <- "Missing"
}
column[i] <- x
}
return (column)
}
replace_with_Missing_num_categoric <- function(column){
for (i in 1:length(column)){
x <- column[i]
if (is.na(x)){
x <- 9999
}else{
if(x == "" | x == "NA" | x == "Unknown")
x <- 9999
}
column[i] <- x
}
return (column)
}
replace_with_Missing_continuous <- function(column){
for (i in 1:length(column)){
x <- column[i]
if (is.na(x)){
x <- ""
}else{
if(x == "NA" | x == "Unknown")
x <- ""
}
column[i] <- x
}
return (column)
}
add_missing_values <- function(path_to_file){
setwd("C:/Users/victor/Documents/TFG/r-analytics-master/ressources/current_db")
data <- read.csv(path_to_file, sep = ",")
data_colnames <- colnames(data)
num_categoric <- data_colnames[grepl("_numeric", data_colnames)]
aux <- length(data_colnames)
for (i in 1:aux){
colname <- data_colnames[i]
progress <- round((100*i/aux),digits = 0)
print(paste(progress,"%", sep = ""))
if(colname %in% categoric_vars){
column <- unlist(data[colname])
data[colname] <- replace_with_Missing_categoric(column)
}
if(colname %in% num_categoric){
column <- unlist(data[colname])
data[colname] <- replace_with_Missing_num_categoric(column)
}
if(colname %in% continuous){
column <- unlist(data[colname])
data[colname] <- replace_with_Missing_continuous(column)
}
}
return(data)
}
rm(list=ls())
setwd("C:/Users/victor/Documents/TFG/r-analytics-master")
source("dependency_installer.R")
source("connection_parameters.R")
source("necessary_functions_graph.R")
dep_list = c( "stringr","DSI","DSOpal","DSLite", "fields", "metafor", "ggplot2", "gridExtra", "data.table", "dsBaseClient")
install_dependencies(dep_list)
dir.create("./admissions_analysis", showWarnings = FALSE)
setwd("./admissions_analysis")
aux <- connect()
connections <- aux[[1]]
inp <- aux[[2]]
obtain_admissions_graph(connections,inp)
hospital_names <- c( #Añadir Los de Baskent y sacrocuore
"Princesa",
"CIPH",
"UMF_Iasis",
"SMUC",
"HM",
"Porto",
"FJD",
"Coimbra",
"UNAV",
"TU",
"Ankara Impatient",
"Konya Impatient",
"Istambul Impatient",
"Izmir Impatient",
"Alanya Impatient",
"Adana Impatient",
"Ankara Outpatient",
"Konya Outpatient",
"Istambul Outpatient",
"Izmir Outpatient",
"Alanya Outpatient",
"Sacrocuore Emergency",
"Sacrocuore Employees",
"Sacrocuore Verona",
"Sacrocuore Isaric",
"TUDublin",
"UMF_Cluj",
"UdeA",
"Inantro",
"UNSA",
"UZA"
)
project_names <- c(
"FIBHULP",
"CIPH_unCoVer",
"umfiasi",
"SMUC",
"FiHM",
"uncover-up",
"IISFJD",
"IPC",
"unCOVer-UNAV",
"TU_Uncover",
"BU",
"BU",
"BU",
"BU",
"BU",
"BU",
"BU",
"BU",
"BU",
"BU",
"BU",
"S_uncover",
"S_uncover",
"S_uncover",
"S_uncover",
"TUDublin",
"UMF_Cluj",
"INS_Data",
"INANTRO",
"UnCoVer-BiH-Final",
"UZA"
)
resource_names <- c(
"Harmonized_variables_2",
"CIPH_numeric_derivated",
"20220719_HarmonisedUMFIasi",
"SMUC_resource",
"20220720_HarmonisedHM",
"Resource_derived",
"IISFJD_Harmonized_1",
"IPC_Harmonized",
"UNAV_rsc",
"TU_Harmonized",
"inpatient_ankara",
"inpatient_konya",
"inpatient_istanbul",
"inpatient_izmir",
"inpatient_alanya",
"inpatient_adana",
"outpatient_ankara",
"outpatient_konya",
"outpatient_istanbul",
"outpatient_izmir",
"outpatient_alanya",
"emergency",
"employees",
"verona",
"isaric",
"TUDublin_harmonised",
"Romania",
"colombia_all",
"Inantro",
"20220722_HarmonizedUNSA",
"UZA_prelim"
)
urls <- c(
"https://192.168.1.200:8001",
"https://192.168.1.200:8002",
"https://192.168.1.200:8003",
"https://192.168.1.200:8006",
"https://192.168.1.50:9002",
"https://192.168.1.102",
"https://uncover.itg.be",
"https://uncover.itg.be",
"https://192.168.1.50:9001",
"https://192.168.1.200:8004",
"https://192.168.1.101:8443",
"https://192.168.1.101:8443",
"https://192.168.1.101:8443",
"https://192.168.1.101:8443",
"https://192.168.1.101:8443",
"https://192.168.1.101:8443",
"https://192.168.1.101:8443",
"https://192.168.1.101:8443",
"https://192.168.1.101:8443",
"https://192.168.1.101:8443",
"https://192.168.1.101:8443",
"https://192.168.1.50:8890",
"https://192.168.1.50:8890",
"https://192.168.1.50:8890",
"https://192.168.1.50:8890",
"https://uncover.itg.be",
"https://192.168.1.200:8005",
"https://fenfisdi.udea.edu.co/opal",
"https://192.168.1.200:8007",
"https://192.168.1.200:8008",
"https://uncover.itg.be"
)
users <- c(
"user_analisis",
"user_analisis",
"user_analisis",
"user_analisis",
"user_analisis",
"user_analisis",
"emertens",
"emertens",
"user_analisis",
"user_analisis",
"user_analisis",
"user_analisis",
"user_analisis",
"user_analisis",
"user_analisis",
"user_analisis",
"user_analisis",
"user_analisis",
"user_analisis",
"user_analisis",
"user_analisis",
"user_analisis",
"user_analisis",
"user_analisis",
"user_analisis",
"emertens",
"user_analisis",
"user_analisis",
"user_analisis",
"user_analisis",
"emertens"
)
pass <- c(
"Ekfl07UUgz",
"Ekfl07UUgz",
"Ekfl07UUgz",
"Ekfl07UUgz",
"Ekfl07UUgz",
"Ekfl07UUgz",
"3^z4AV.)hG5~PT/]",
"3^z4AV.)hG5~PT/]",
"Ekfl07UUgz",
"Ekfl07UUgz",
"Ekfl07UUgz",
"Ekfl07UUgz",
"Ekfl07UUgz",
"Ekfl07UUgz",
"Ekfl07UUgz",
"Ekfl07UUgz",
"Ekfl07UUgz",
"Ekfl07UUgz",
"Ekfl07UUgz",
"Ekfl07UUgz",
"Ekfl07UUgz",
"Ekfl07UUgz",
"Ekfl07UUgz",
"Ekfl07UUgz",
"Ekfl07UUgz",
"3^z4AV.)hG5~PT/]",
"Ekfl07UUgz",
"Ekfl07UUgz",
"Ekfl07UUgz",
"Ekfl07UUgz",
"3^z4AV.)hG5~PT/]"
)
# This function receives a list of packages to be installed before the execution of a script.
# For each package provided, it verifies that it is not installed already. If so, it proceeds to
# install it.
# ToDo: exception control for unexistent/misspelled packages.
install_dependencies <- function(dep_list) {
# Deprecated since executing server is Ubuntu.
#if(Sys.info()["sysname"] == "Windows"){
# dep_list[length(dep_list)+1] = "Rtools"
#}
for(p in dep_list){
if(require(p, character.only = T) == FALSE){
if(p == "dsBaseClient"){
library(remotes)
install_github("datashield/dsBaseClient", dependencies = TRUE)
}else{
if(p == "DSI"){
library(remotes)
install_github('datashield/DSI', ref = '1.3.3', dependencies = TRUE)
}else{
install.packages(p, dependencies = TRUE, repos = "https://cran.us.r-project.org")
}
}
}
if(p != "Rtools"){
library(p, character.only = T)
}
}
}
rm(list=ls())
setwd("C:/Users/victor/Documents/TFG/r-analytics-master")
source("dependency_installer.R")
dep_list = c("magrittr","officer","dplyr","stringr","DSI","DSOpal","DSLite","dsBaseClient")
install_dependencies(dep_list)
#,"DSI","DSOpal","DSLite"
source("connection_parameters.R")
source("necessary_functions_connection.R")
auxConnections <- connect()
connections <- auxConnections[[1]]
inp <- auxConnections[[2]]
calltext <- call("DORA_scoresDS", "data")
newobj <- "DORA_table"
datashield.assign(connections, newobj, calltext)
ds.colnames("DORA_table")
ds.table("DORA_table$DORA_class")
datashield.logout(connections)
setwd("C:/Users/victor/Documents/TFG/r-analytics-master")
source("add_missing_values.R")
list_of_files <- list.files("C:/Users/victor/Documents/TFG/r-analytics-master/ressources/current_db")[-6]
#ist_of_files <- "Harmonized_LIH.csv"
for (i in 1:length(list_of_files)) {
file_name <- list_of_files[i]
print(paste ("Fixing file:", file_name))
setwd("C:/Users/victor/Documents/TFG/r-analytics-master/ressources/current_db")
ready_file <- add_missing_values(file_name)
setwd("C:/Users/victor/Documents/TFG/r-analytics-master/ressources/current_db/ready")
write.csv(x=ready_file, file = file_name, row.names = FALSE)
}
rm(list=ls())
setwd("/home/david/Documentos/Uncover/ScriptsVictor")
source("dependency_installer.R")
dep_list = c("magrittr","officer","dplyr","stringr","DSI","DSOpal","DSLite","dsBaseClient")
install_dependencies(dep_list)
#,"DSI","DSOpal","DSLite"
source("connection_parameters.R")
source("necessary_functions_connection.R")
codebook <- data.frame(read.csv("new_harmon.csv", sep = ","))
codebook_variable_names <- codebook[,2]
namesDescMes <- codebook[,c(2,4,6)]
categoric_vars = c(
#Si&Sympt
"CSXCTR","SMXASAH","SMXCOA","SMXSTA","SMXSBA","SMXRNA","SMXSEA","SMXMYA","SMXARA","SMXCPA","SMXAPA","SMXINA","SMXNAA","SMXDIA","SMXFAA","SMXHEA","SMXCNA","SMXACA","SMXSLA","SMXTLA","SMXSYA","SMXWHA","SMXLYA","SMXANA","SMXIWA","SMXSRA","SMXBLA","CSXCOT",
#Com&RF
"CMXPRG","CMXCVD","CMXCMP","CMXHT","CMXDI","CMXCKD","CMXCLD","CMXCPD","CMXASM","CMXCND","CMXRHE","CMXCCI","CMXCBD","CMXDE","CMXPU","CMXST","CMXLY","CMXAP","RFXSM","RFXFSM","RFXOB","RFXTB","RFXIMD","RFXHIV","RFXAIDS","RFXUI","RFXHC","RFXONC","RFXMN","CMXCHF","CMXVDP","CMXVDC","CMXCA","CMXVD","CMXABL","CMXAD","CMXNDP","CMXNDD","CMXCOPD","CMXPCD","CMXRI","CMXMLD","CMXNPM","CMXCLH","CMXMET","CMXTU","CMXMY","CMXNP","RFXMD","CMXANX","CMXBDO","CMXEPI","CMXOAR","CMXSPI","CMXSOT","CMXOKD","CMXUTI","CMXINC","CMXHPP","CMXHGL","RFXLC","RFXPM","RFXAP","CMXIHD","CMXATH",
#Treatment
"TRXAV","TRXRIB","TRXLR","TRXRM","TRXIA","TRXIB","TRXCH","TRXAB","TRXCS","TRXHEP","TRXAF","TRXCP","TRXOT","TRXECM","TRXIV","TRXNIV","TRXNO","TRXOX","TRXRR","TRXTR","TRXVA","TRXPE","TRXPV","TRXIT","TRXNMB","TRXAC","TRXINA","TRXIS","TRXIM","TRXVC","TRXVD","TRXZN",
#Dates
"DSXHO","DSXIC","DSXOS",
#Home med
"HMRACI","HMRARB","HMRAHO","HMRNS","HMROS","HMRCS","HMRIS","HMRAV","HMRAB","HMRCOV","HMRANC","HMRAT","HMRINS",
#Demographics
"DMRGENDR","DMRRETH1","DMROCCU","DMRHREDU",
#Imaging Data
"IMDXCT","IMDXCTCR","IMDXCTTE","IMDXCTAB","IMDXXR","IMDXXRI","IMDXPN",
#Complications
"COXRD","COXAR","COXPM","COXMOD","COXPT","COXEC","COXSH","COXIO","COXPE","COXST","COXDIC","COXRIO","COXKF","COXHF","COXBC","COXRF","COXLF","COXADE","COXSTN","COXNOC"
)
date_vars <- c("DATCOT","DATSO","DATAD","DATADI","DATDSI","DATDS","DATPR","DATOS")
#Check which hospitals contain a given value
hospitals_contains_variable <- function(variable){
res <- c()
for(i in seq_along(full_variable_list)){
if (variable %in% unlist(full_variable_list[i]))
res <- c(res, hospital_names[i])
}
return(res)
}
get_working_hospitals <- function(errors){
working <- c()
for(i in seq_along(hosp_to_analyze)){
hosp_in_err <- grepl(hosp_to_analyze[i], errors, fixed = TRUE)
if(!(TRUE %in% hosp_in_err))
working <- c(working, hosp_to_analyze[i])
}
return(working)
}
auxConnections <- connect()
connections <- auxConnections[[1]]
inp <- auxConnections[[2]]
#--------------------------------------------------------
#Extract the column names from the hospital datasets
full_variable_list <- ds.colnames("data")
data_dimentions <- head(ds.dim("data"),-1)
data_dimentions <- lapply(data_dimentions, `[[`, 1)
names(data_dimentions) <- names(full_variable_list)
hospital_names <- names(full_variable_list)
#Intersect the elements from the variables present in the hospitals and the ones in the codebook
# COMPARAR LAS VARIABLES QUE TIENEN CADA HOSPITAL CON LAS DEL CODEBOOK Y ASI ELIMINAR LAS QUE NO ESTEN
for(i in seq_along(full_variable_list)){
hospital_variable_list <- unlist(full_variable_list[i])
full_variable_list[[i]] <- Reduce(intersect, list(hospital_variable_list,codebook_variable_names))
}
#Make a list containing all the variables to analyze
# HACES LA UNION DE LAS VARIABLES DE TODOS LOS HOSPITALES
variables_to_analyze <- Reduce(union, full_variable_list)
#aux_vars <- list("DMRAGEYR","LBXSBUA","LBXCRPA","LBXPLTSIA","CSXCHRA","CSXOSTA","LBXFIOA","SMXBLA","SMXSBA","SMXACA","RFXONC","LBXNENOA","LBXLYMNOA","LBXSBLA","LBXSCBA","DMRGENDR", "CSXRRA","CSXOSTA","SMXACA","LBXSBUA","LBXCRPA")
# CON ESTOS SELECCIONAS LAS VARIABLES QUE QUIERES ANALIZAR
aux_vars <- list("DMRGENDR", "SMXACA", "DMRAGEYR","CSXBTPA","CSXDIA","CSXOSTA","CSXRRA","LBXSBUA")
vars_list <- as.list(variables_to_analyze)
variables_to_analyze <- unlist(Reduce(intersect, list(aux_vars,vars_list)))
df_list <- list()
variances_list <- list()
df_categoric_list <- list()
variances_list_categoric <- list()
for(i in seq_along(variables_to_analyze)){
#Select the variable to analyse
variable <- variables_to_analyze[i]
dataset_variable <- paste0("data$", variable)
is_categoric <- variable %in% categoric_vars
is_date <- variable %in% date_vars
print(variable)
hosp_to_analyze <- hospitals_contains_variable(variable)
#If the variable is categoric
if(is_categoric){
print("categoric")
OK <- FALSE
try({
categoric_table <- ds.table(dataset_variable, datasources = connections[hosp_to_analyze])
OK <- TRUE
})
if(OK){
result <- TRUE
list_bool <- !grepl("failed", categoric_table[[1]])
list_bool <- c(TRUE, TRUE, TRUE)
for (i in seq_along(list_bool)){
result <- result & list_bool[i]
}
if(result){
categoric_table <- as.data.frame(categoric_table[[1]][[2]])
categoric_table[,"column variance"] <- NA
for( j in seq_len(nrow(categoric_table))){
row_values <- as.numeric(as.vector(categoric_table[j,]))
row_variance <- var(row_values[!is.na(row_values)])
categoric_table[j,"column variance"] <- row_variance
}
categoric_table <- categoric_table %>% mutate_if(is.numeric, round, 3)
categoric_table <- as.data.frame(t(categoric_table))
#aux_df <- #INCLUIR UNA COLUMNA QUE TENGA LOS NOMBRES DE LOS HOSPITALES
categoric_table["Hospitals"] <- row.names(categoric_table)
aux_table <- categoric_table[c(ncol(categoric_table), 1:(ncol(categoric_table)-1))]
aux_list <- list(aux_table)
names(aux_list) <- variable
df_categoric_list <- append(df_categoric_list, aux_list)
vector_aux <- as.numeric(aux_table["column variance",][,-1])
mean_aux <- list(mean(vector_aux[!is.na(vector_aux)]))
names(mean_aux) <- variable
variances_list_categoric <- append(variances_list_categoric,mean_aux)
}else{
print("This variable cannot be analyzed")
print(paste("Error in the hospitals:", aux_table["Hospitals"]))
}
}
# If the variable is nuemric
}else
if (!is_categoric & !is_date){
print("numeric")
#Obtain the means and the missing values for each hospital
res <- tryCatch({
# OBTIENE LAS MEDIAS DE LOS HOSPITALES
means <- as.data.frame(ds.mean(dataset_variable, datasources = connections[hosp_to_analyze])[[1]])[c(1,2)]
working_hospitals <- hosp_to_analyze
follow <- TRUE
res<- list(follow, means, working_hospitals)
return(res)
},error = function(e){
errors <- datashield.errors()
#If all the hospitals that contain the variable give errors, the variable is skipped
if(length(errors) != length(hosp_to_analyze)){
working_hospitals <- get_working_hospitals(errors)
means <- as.data.frame(ds.mean(dataset_variable, datasources = connections[working_hospitals])[[1]])[c(1,2)]
follow <- TRUE
print("Hospitals that contain the variable:")
print(hosp_to_analyze)
print("Hospitals that do not give errors:")
print(working_hospitals)
}else{
err_mes <- paste("Unable to analyze data for the variable:", variable)
print(err_mes)
follow <- FALSE
}
res<- list(follow, means, working_hospitals)
return(res)
})
follow <- unlist(res[1])
means <- as.data.frame(res[2])
working_hospitals <- unlist(res[3])
if(follow == TRUE){
# PONES BONITO LOS VALORES MISSING
means["Hospital"] <- rownames(means)
df_aux <- means[,c(3,1,2)]
colnames(df_aux) <- c("Hospital", "Mean", "Missing")
df_aux$Mean<-format(round(df_aux$Mean,2),nsmall=2)
missing <- as.list(df_aux$Missing)
percentages <- lapply(mapply(FUN = `/`, missing, data_dimentions[working_hospitals], SIMPLIFY = FALSE), round, 4)
percentages <- lapply(percentages,"*", 100)
for(j in 1:length(percentages)){
value <- paste(paste(paste(missing[j], "("),percentages[j],sep=""),"%)",sep="")
percentages[j] <- value
}
df_aux$Missing <- unlist(percentages)
}
means_var <- var(means[,1])
#Store the obtained values
aux_list <- list(means_var)
names(aux_list) <- variable
variances_list<- append(variances_list,aux_list)
aux_list <- list(df_aux)
names(aux_list) <- variable
df_list<- append(df_list,aux_list)
}else if (!is_categoric & is_date){
print("date")
}
}
datashield.logout(connections)
doc_1 <- read_docx() %>%
body_add_par("Data quality report", style = "heading 1")%>%
body_add_par("", style = "Normal")%>%
body_add_par(value = "This document contains information on every variable present in the hospital's datasets.", style = "Normal") %>%
body_add_par("The variables will be displayed following a decreasing order of the means variance. If a variable is missing a hospital, it means that there has been an error analyzing that variable in that specific hospital.", style = "Normal")%>%
body_add_par("", style = "Normal")%>%
body_add_par("", style = "Normal")%>%
body_add_par("Numeric variables", style = "heading 1")%>%
body_add_par("", style = "Normal")%>%
body_add_par("", style = "Normal")%>%
print(doc_1, target = "data_quality_report.docx")
ordered_variance_list <- variances_list[order(unlist(variances_list), decreasing = TRUE)]
ordered_variance_list_Not_NA <- ordered_variance_list[!is.na(ordered_variance_list)]
ordered_variance_list_NA <- ordered_variance_list[is.na(ordered_variance_list)]
ordered_names_Not_NA <- names(ordered_variance_list_Not_NA)
ordered_names_NA <- names(ordered_variance_list_NA)
# SOLO RECORRE LAS VARIABLES NUMERICAS QUE TIENE VARIANZA NO NULA
for (i in 1:length(ordered_variance_list_Not_NA)) {
element <- ordered_names_Not_NA[i]
tab1 <- df_list[[element]]
variance <- variances_list[[element]]
if(!is.na(variance))
variance <- format(round(variance, 2), nsmall = 2)
print(element)
codebook_entry <- subset(codebook, codebook$Harmonised.variable.name == element)
description <- unlist(codebook_entry[4])
unit <- str_split(unlist(codebook_entry[6]), " ")[[1]][1]
range <- codebook_entry[[7]]
mes_range <- paste("The range of possible values is:", range)
mes_var <- paste("The means variance obtained for this variable is", variance)
mes_desc_unit <- paste(paste(paste("This variable represents", paste("'",paste(description,"'",sep=""), sep = "")), "and is measured in"),unit)
doc_table <- read_docx(path = "data_quality_report.docx") %>%
body_add_par(element, style = "heading 2")%>%
body_add_par(mes_var)%>%
body_add_par(mes_desc_unit)%>%
body_add_par(mes_range)%>%
body_add_par("", style = "Normal")%>%
body_add_table(tab1, style = "Table Professional")%>%
print(doc_table, target = "data_quality_report.docx")
}
doc_table <- read_docx(path = "data_quality_report.docx") %>%
body_add_par("", style = "Normal")%>%
body_add_par("", style = "Normal")%>%
body_add_par("The following variables only appear in one hospital, the variance between the means will not be displayed.", style = "Normal")%>%
body_add_par("", style = "Normal")%>%
body_add_par("", style = "Normal")%>%
print(doc_table, target = "data_quality_report.docx")
for (i in 1:length(ordered_variance_list_NA)) {
element <- ordered_names_NA[i]
tab1 <- df_list[[element]]
print(element)
codebook_entry <- subset(codebook, codebook$Harmonised.variable.name == element)
description <- unlist(codebook_entry[4])
unit <- str_split(unlist(codebook_entry[6]), " ")[[1]][1]
range <- codebook_entry[[7]]
mes_range <- paste("The range of possible values is:", range)
mes_desc_unit <- paste(paste(paste("This variable represents", paste("'",paste(description,"'",sep=""), sep = "")), "and is measured in"),unit)
doc_table <- read_docx(path = "data_quality_report.docx") %>%
body_add_par(element, style = "heading 2")%>%
body_add_par(mes_desc_unit)%>%
body_add_par(mes_range)%>%
body_add_par("", style = "Normal")%>%
body_add_table(tab1, style = "Table Professional")%>%
print(doc_table, target = "data_quality_report.docx")
}
if (length(df_categoric_list) != 0){
doc_table <- read_docx(path = "data_quality_report.docx") %>%
body_add_par("", style = "Normal")%>%
body_add_par("", style = "Normal")%>%
body_add_par("Categoric variables", style = "heading 1")%>%
body_add_par("", style = "Normal")%>%
body_add_par("", style = "Normal")%>%
print(doc_table, target = "data_quality_report.docx")
categoric_names <- names(df_categoric_list)
ordered_variance_list_categoric <- variances_list_categoric[order(unlist(variances_list_categoric), decreasing = TRUE)]
ordered_variance_list_Not_NA_categoric <- ordered_variance_list_categoric[!is.na(ordered_variance_list_categoric)]
ordered_variance_list_NA_categoric <- ordered_variance_list_categoric[is.na(ordered_variance_list_categoric)]
ordered_names_Not_NA_categoric <- names(ordered_variance_list_Not_NA_categoric)
ordered_names_NA_categoric <- names(ordered_variance_list_NA_categoric)
for (i in 1:length(ordered_names_Not_NA_categoric)) {
element <- ordered_names_Not_NA_categoric[i]
tab1 <- as.data.frame(df_categoric_list[[element]])
var <- unlist(ordered_variance_list_Not_NA_categoric[element])
print(element)
codebook_entry <- subset(codebook, codebook$Harmonised.variable.name == element)
description <- unlist(codebook_entry[4])
unit <- str_split(unlist(codebook_entry[6]), " ")[[1]][1]
mes_desc_unit <- paste(paste(paste("This variable represents", paste("'",paste(description,"'",sep=""), sep = "")), "and the possible values are"),unit)
mes_var <- paste("The variance between rows is:", var)
doc_table <- read_docx(path = "data_quality_report.docx") %>%
body_add_par(element, style = "heading 2")%>%
body_add_par(mes_desc_unit)%>%
body_add_par(mes_var)%>%
body_add_par("", style = "Normal")%>%
body_add_table(tab1, style = "Table Professional")%>%
print(doc_table, target = "data_quality_report.docx")
}
doc_table <- read_docx(path = "data_quality_report.docx") %>%
body_add_par("", style = "Normal")%>%
body_add_par("", style = "Normal")%>%
body_add_par("The following variables only appear in one hospital, the variance between the means will not be displayed.", style = "Normal")%>%
body_add_par("", style = "Normal")%>%
body_add_par("", style = "Normal")%>%
print(doc_table, target = "data_quality_report.docx")
if(length(ordered_names_NA_categoric)>0){
for (i in 1:length(ordered_names_NA_categoric)) {
element <- ordered_names_NA_categoric[i]
tab1 <- as.data.frame(df_categoric_list[[element]])
print(element)
codebook_entry <- subset(codebook, codebook$Harmonised.variable.name == element)
description <- unlist(codebook_entry[4])
unit <- str_split(unlist(codebook_entry[6]), " ")[[1]][1]
mes_desc_unit <- paste(paste(paste("This variable represents", paste("'",paste(description,"'",sep=""), sep = "")), "and the possible values are"),unit)
doc_table <- read_docx(path = "data_quality_report.docx") %>%
body_add_par(element, style = "heading 2")%>%
body_add_par(mes_desc_unit)%>%
body_add_par("", style = "Normal")%>%
body_add_table(tab1, style = "Table Professional")%>%
print(doc_table, target = "data_quality_report.docx")
}
}
}
rm(list=ls())
setwd("C:/Users/victor/Desktop/TFG/r-analytics-master")
source("required_folder_checker.R")
source("argument_hasher.R")
source("dependency_installer.R")
source("connection_parameters.R")
source("necessary_function_table1s.R")
dep_list = c("jsonlite", "stringr","DSI","DSOpal","DSLite", "fields", "metafor", "ggplot2", "gridExtra", "data.table", "dsBaseClient")
install_dependencies(dep_list)
dir.create("./demographic_analisis", showWarnings = FALSE)
setwd("./demographic_analisis")
aux <- connect()
connections <- aux[[1]]
inp <- aux[[2]]
hasOutput <- checkHasOutput(inp)
name <- getHname(inp)
png(paste(name,".png",sep=""),width=800, height=400)
res <- obtainData(connections, hasOutput, inp)
print(res)
dev.off()
datashield.logout(connections)
res
Harmonised variable name;Name Origin;Harmonised variable description;Harmonised data format/unit;,,,,,,,,,,,,,,,,
DATSSA;SELF;Date of assessment during hospitalisation;dd/mm/yyyy;,,,,,,,,,,,,,,,,
DATSSDHn;SELF;Time between admission and assessment;days;,,,,,,,,,,,,,,,,
CSXBTPA;SELF;Body temperature at admission;°C;,,,,,,,,,,,,,,,,
CSXBTPHn;SELF;Body temperature in hospital;°C;,,,,,,,,,,,,,,,,
CSXOSTA;SELF;Oxygen Saturation at admission;%;,,,,,,,,,,,,,,,,
CSXOSTHn;SELF;Oxygen Saturation in hospital;%;,,,,,,,,,,,,,,,,
CSXCHRA;SELF;Heart Rate at admission;bpm;,,,,,,,,,,,,,,,,
CSXCHRHn;SELF;Heart Rate in hospital;bpm;,,,,,,,,,,,,,,,,
CSXRRA;SELF;Respiratory Rate at admission;breaths/min;,,,,,,,,,,,,,,,,
CSXRRHn;SELF;Respiratory Rate in hospital;breaths/min;,,,,,,,,,,,,,,,,
CSXRRI;SELF;Respiratory rate in ICU;breaths/min;,,,,,,,,,,,,,,,,
CSXSYA;SELF;Systolic bp at admission;mmHg;,,,,,,,,,,,,,,,,
CSXSYHn;SELF;Systolic bp in hospital;mmHg;,,,,,,,,,,,,,,,,
CSXDIA;SELF;Diastolic bp at admission;mmHg;,,,,,,,,,,,,,,,,
CSXDIHn;SELF;Diastolic bp in hospital;mmHg;,,,,,,,,,,,,,,,,
SMXASAH;SELF;Asymptomatic during hospitalisation;Yes/No;,,,,,,,,,,,,,,,,
SMXFEA;SELF;Fever at admission;Yes/No;,,,,,,,,,,,,,,,,
SMTFE;SELF;Fever duration;Days;,,,,,,,,,,,,,,,,
SMXCOA;SELF;Cough at admission;Yes/No;,,,,,,,,,,,,,,,,
SMTCO;SELF;Cough duration;Days;,,,,,,,,,,,,,,,,
SMXSTA;SELF;Sore throat at admission;Yes/No;,,,,,,,,,,,,,,,,
SMTST;SELF;Sore throat duration;Days;,,,,,,,,,,,,,,,,
SMXSBA;SELF;Shortness of breath at admission;Yes/No;,,,,,,,,,,,,,,,,
SMTSB;SELF;Shortness of breath duration;Days;,,,,,,,,,,,,,,,,
SMXRNA;SELF;Runny nose at admission;Yes/No;,,,,,,,,,,,,,,,,
SMXSEA;SELF;Convulsions / Seizures;Days;,,,,,,,,,,,,,,,,
SMXMYA;SELF;Myalgia at admission;Yes/No;,,,,,,,,,,,,,,,,
SMXARA;SELF;Arthralgia at admission;Yes/No;,,,,,,,,,,,,,,,,
SMXCPA;SELF;Chest pain at admission;Yes/No;,,,,,,,,,,,,,,,,
SMXAPA;SELF;Abdominal pain at admission;Yes/No;,,,,,,,,,,,,,,,,
SMXINA;SELF;Lower chest wall indrawing at admission;Yes/No;,,,,,,,,,,,,,,,,
SMXNAA;SELF;Nausea / Vomiting at admission;Yes/No;,,,,,,,,,,,,,,,,
SMXDIA;SELF;Diarrhoea at admission;Yes/No;,,,,,,,,,,,,,,,,
SMXFAA;SELF;Fatigue at admission;Yes/No;,,,,,,,,,,,,,,,,
SMXHEA;SELF;Headache at admission;Yes/No;,,,,,,,,,,,,,,,,
SMXCNA;SELF;Conjunctivitis at admission;Yes/No;,,,,,,,,,,,,,,,,
SMXACA;SELF;Confusion / Altered consciousness at admission;Yes/No;,,,,,,,,,,,,,,,,
SMXSLA;SELF;Loss of smell at admission;Yes/No;,,,,,,,,,,,,,,,,
SMXTLA;SELF;Loss of taste at admission;Yes/No;,,,,,,,,,,,,,,,,
SMXSYA;SELF;Syncope / Fall at admission;Yes/No;,,,,,,,,,,,,,,,,
SMXWHA;SELF;Wheezing at admission;Yes/No;,,,,,,,,,,,,,,,,
SMXLYA;SELF;Lymphadenopathy at admission;Yes/No;,,,,,,,,,,,,,,,,
SMXANA;SELF;Anorexia at admission;Yes/No;,,,,,,,,,,,,,,,,
SMXIWA;SELF;Inability to walk at admission;Yes/No;,,,,,,,,,,,,,,,,
SMXSRA;SELF;Skin rash at admission;Yes/No;,,,,,,,,,,,,,,,,
SMXBLA;SELF;Bleeding / Haemorrhage at admission;Yes/No;,,,,,,,,,,,,,,,,
CMXPRG;SELF;Pregnancy;Yes/No;,,,,,,,,,,,,,,,,
CMXCVD;SELF;CVD;Yes/No;,,,,,,,,,,,,,,,,
CMXHT;SELF;Hypertension;Yes/No;,,,,,,,,,,,,,,,,
CMXDI;SELF;Diabetes;Yes/No;,,,,,,,,,,,,,,,,
CMXCKD;SELF;Chronic kidney disease;Yes/No;,,,,,,,,,,,,,,,,
CMXCLD;SELF;Chronic liver disease;Yes/No;,,,,,,,,,,,,,,,,
CMXCPD;SELF;Chronic pulmonary disease;Yes/No;,,,,,,,,,,,,,,,,
CMXASM;SELF;Asthma;Yes/No;,,,,,,,,,,,,,,,,
CMXCND;SELF;Chronic neurological or neuromuscular disorder;Yes/No;,,,,,,,,,,,,,,,,
CMXRHE;SELF;Rheumatism;Yes/No;,,,,,,,,,,,,,,,,
CMXCCI;SELF;Chronic cognitive impairment;Yes/No;,,,,,,,,,,,,,,,,
CMXDE;SELF;Dementia;Yes/No;,,,,,,,,,,,,,,,,
CMXPU;SELF;Peptic Ulcer / Bleeding;Yes/No;,,,,,,,,,,,,,,,,
CMXST;SELF;Solid tumour;Yes/No;,,,,,,,,,,,,,,,,
CMXLY;SELF;Lymphoma;Yes/No;,,,,,,,,,,,,,,,,
CMXAP;SELF;Asplenia;Yes/No;,,,,,,,,,,,,,,,,
RFXSM;SELF;Smoking;Yes/No;,,,,,,,,,,,,,,,,
RFXFSM;SELF;Former smoker;Yes/No;,,,,,,,,,,,,,,,,
RFXOB;SELF;Obesity;Yes/No;,,,,,,,,,,,,,,,,
RFXTB;SELF;TB;Yes/No;,,,,,,,,,,,,,,,,
RFXIMD;SELF;Immunodeficiency;Yes/No;,,,,,,,,,,,,,,,,
RFXOV;SELF;Overall;Yes/No;,,,,,,,,,,,,,,,,
RFXHIV;SELF;HIV;Yes/No;,,,,,,,,,,,,,,,,
RFXAIDS;SELF;AIDS;Yes/No;,,,,,,,,,,,,,,,,
RFXHC;SELF;Haematological cancer;Yes/No;,,,,,,,,,,,,,,,,
RFXONC;SELF;Oncology;Yes/No;,,,,,,,,,,,,,,,,
RFXMN;SELF;Malnutrition;Yes/No;,,,,,,,,,,,,,,,,
TRXAV;SELF;Antiviral or COVID-19 targeted;Yes/No;,,,,,,,,,,,,,,,,
TRXRIB;SELF;Ribavirin;Yes/No;,,,,,,,,,,,,,,,,
TRXLR;SELF;Lopinar / Ritonavir;Yes/No;,,,,,,,,,,,,,,,,
TRXRM;SELF;Remdesivir;Yes/No;,,,,,,,,,,,,,,,,
TRXIA;SELF;Interferon Alpha;Yes/No;,,,,,,,,,,,,,,,,
TRXIB;SELF;Interferon Beta;Yes/No;,,,,,,,,,,,,,,,,
TRXCH;SELF;Chloroquine / Hydroxychloroquine;Yes/No;,,,,,,,,,,,,,,,,
TRXAB;SELF;Antibiotics;Yes/No;,,,,,,,,,,,,,,,,
TRXCS;SELF;Corticosteroids;Yes/No;,,,,,,,,,,,,,,,,
TRXHEP;SELF;Heparin;Yes/No;,,,,,,,,,,,,,,,,
TRXAF;SELF;Antifungal;Yes/No;,,,,,,,,,,,,,,,,
TRXCP;SELF;Convalescent plasma;Yes/No;,,,,,,,,,,,,,,,,
TRXOT;SELF;High-flow nasal cannula oxygen therapy;Yes/No;,,,,,,,,,,,,,,,,
TRXECM;SELF;ECMO;Yes/No;,,,,,,,,,,,,,,,,
TRXIV;SELF;Invasive ventilation;Yes/No;,,,,,,,,,,,,,,,,
TRXNIV;SELF;Non IV;Yes/No;,,,,,,,,,,,,,,,,
TRXNO;SELF;Inhaled NO­2;Yes/No;,,,,,,,,,,,,,,,,
TRXOX;SELF;Oxygen need;Yes/No;,,,,,,,,,,,,,,,,
TRXRR;SELF;Renal replacement therapy;Yes/No;,,,,,,,,,,,,,,,,
TRXTR;SELF;Tracheostomy;Yes/No;,,,,,,,,,,,,,,,,
TRXVA;SELF;Vasopressor;Yes/No;,,,,,,,,,,,,,,,,
TRXPE;SELF;PEEP;Yes/No;,,,,,,,,,,,,,,,,
TRXPV;SELF;Prone ventilation;Yes/No;,,,,,,,,,,,,,,,,
TRXIT;SELF;Intubation;Yes/No;,,,,,,,,,,,,,,,,
TRXNMB;SELF;Neuromuscular blocking agent;Yes/No;,,,,,,,,,,,,,,,,
TRXAC;SELF;Anticoagulant ;Yes/No;,,,,,,,,,,,,,,,,
TRXINA;SELF;Inatropic;Yes/No;,,,,,,,,,,,,,,,,
TRXIS;SELF;Immunosuppressor;Yes/No;,,,,,,,,,,,,,,,,
TRXIM;SELF;Immunomodulator;Yes/No;,,,,,,,,,,,,,,,,
TRXVC;SELF;Vitamin C;Yes/No;,,,,,,,,,,,,,,,,
TRXVD;SELF;Vitamin D;Yes/No;,,,,,,,,,,,,,,,,
TRXZN;SELF;Zinc;Yes/No;,,,,,,,,,,,,,,,,
DATSO;SELF;Date of symptom onset;dd/mm/yyyy;,,,,,,,,,,,,,,,,
DATAD;SELF;Date of admission;dd/mm/yyyy;,,,,,,,,,,,,,,,,
DATADI;SELF;Date of admission to ICU;dd/mm/yyyy;,,,,,,,,,,,,,,,,
DATDSI;SELF;Date of discharge from ICU;dd/mm/yyyy;,,,,,,,,,,,,,,,,
DATDS;SELF;Date of discharge;dd/mm/yyyy;,,,,,,,,,,,,,,,,
DATLGT;SELF;Length of stay in hospital;Days;,,,,,,,,,,,,,,,,
DATLGTI;SELF;Length of stay in ICU;Days;,,,,,,,,,,,,,,,,
DSXIC;SELF;Patient admitted to ICU;Yes/No;,,,,,,,,,,,,,,,,
DSXOS;SELF;Outcome status;Recovered/Deceased/Transferred;,,,,,,,,,,,,,,,,
HMRACI;SELF;ACE Inhibitors;Yes/No;,,,,,,,,,,,,,,,,
HMRARB;SELF;ARBs;Yes/No;,,,,,,,,,,,,,,,,
HMRAHO;SELF;Anti-hypertensive (other);Yes/No;,,,,,,,,,,,,,,,,
HMRNS;SELF;NSAIDs;Yes/No;,,,,,,,,,,,,,,,,
HMROS;SELF;Oral Steroids;Yes/No;,,,,,,,,,,,,,,,,
HMRCS;SELF;Corticosteroids;Yes/No;,,,,,,,,,,,,,,,,
HMRIS;SELF;Immunospressant;Yes/No;,,,,,,,,,,,,,,,,
HMRAV;SELF;Antiviral;Yes/No;,,,,,,,,,,,,,,,,
HMRAB;SELF;Antibiotic;Yes/No;,,,,,,,,,,,,,,,,
HMRCOV;SELF;Other targeted COVID-19 medication ;Yes/No;,,,,,,,,,,,,,,,,
DMRBORN;NHANES;Country of birth;;,,,,,,,,,,,,,,,,
DMRAGEYR;SELF;Age;Years;,,,,,,,,,,,,,,,,
DMRGENDR;SELF;Sex;Male/Female;,,,,,,,,,,,,,,,,
DMXHT;NHANES;Height;;,,,,,,,,,,,,,,,,
DMXWT;NHANES;Weight;;,,,,,,,,,,,,,,,,
DMXBMI;NHANES;BMI;;,,,,,,,,,,,,,,,,
DMRRETH1;NHANES;Ethnicity;;,,,,,,,,,,,,,,,,
DMROCCU;SELF;Occupation;;,,,,,,,,,,,,,,,,
DMRHREDU;NHANES;Education;;,,,,,,,,,,,,,,,,
DATIM;SELF;Date tests performed;dd/mm/yyyy;,,,,,,,,,,,,,,,,
DATIMD;SELF;Time between admission and assessment;days;,,,,,,,,,,,,,,,,
IMDXCT;SELF;CT scan results;;,,,,,,,,,,,,,,,,
IMDXCTCR;SELF;CT CO-RADS;;,,,,,,,,,,,,,,,,
IMDXCTTE;SELF;CT thromboembolism;;,,,,,,,,,,,,,,,,
IMDXCTLD;SELF;CT % lung damage;%;,,,,,,,,,,,,,,,,
IMDXCTAB;SELF;CT abnormal at follow-up;;,,,,,,,,,,,,,,,,
IMDXXR;SELF;X-ray result;;,,,,,,,,,,,,,,,,
IMDXXRI;SELF;X-ray infiltrates;;,,,,,,,,,,,,,,,,
IMDXPN;SELF;Pneumonia on x-ray or CT scan;;,,,,,,,,,,,,,,,,
IMDXEQ;SELF;ECG QTc value;;,,,,,,,,,,,,,,,,
COXRD;SELF;Acute Respiratory Distress Syndrom;Yes/No;,,,,,,,,,,,,,,,,
COXAR;SELF;Arrhythmia;Yes/No;,,,,,,,,,,,,,,,,
COXPM;SELF;Pneumonia;Yes/No;,,,,,,,,,,,,,,,,
COXMOD;SELF;Multiple Organ Dysfunction;Yes/No;,,,,,,,,,,,,,,,,
COXPT;SELF;Pneumothorax;Yes/No;,,,,,,,,,,,,,,,,
COXEC;SELF;Endocarditis;Yes/No;,,,,,,,,,,,,,,,,
COXSH;SELF;Shock;Yes/No;,,,,,,,,,,,,,,,,
COXIO;SELF;Other infections;Yes/No;,,,,,,,,,,,,,,,,
COXPE;SELF;Pulmonary embolism;Yes/No;,,,,,,,,,,,,,,,,
COXST;SELF;Stroke (AVC);Yes/No;,,,,,,,,,,,,,,,,
COXDIC;SELF;Disseminated intravascular coagulation;Yes/No;,,,,,,,,,,,,,,,,
COXRIO;SELF;Other respiratory infections;Yes/No;,,,,,,,,,,,,,,,,
COXKF;SELF;Kidney failure;Yes/No;,,,,,,,,,,,,,,,,
COXHF;SELF;Heart failure;Yes/No;,,,,,,,,,,,,,,,,
COXBC;SELF;Blood complications;Yes/No;,,,,,,,,,,,,,,,,
DATLBHn;SELF;Date of assessment during hospitalisation;dd/mm/yyyy;For the nth assessment,,,,,,,,,,,,,,,,
DATLBDHn;SELF;Time between admission and assessment during hospitalisation;days;,,,,,,,,,,,,,,,,
LBXHGBA;NHANES;Haemoglobin at admission;g/dL;,,,,,,,,,,,,,,,,
LBXHGBHn;NHANES;Haemoglobin during hospitalisation;g/dL;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXESRA;SELF;Erythrocyte Sedimentation Rate (ESR) at admission;mm/hr;,,,,,,,,,,,,,,,,
LBXESRHn;SELF;Erythrocyte Sedimentation Rate (ESR) during hospitalisation;mm/hr;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXWBCSIA;NHANES;WBC count at admission;1000 cells/µL;,,,,,,,,,,,,,,,,
LBXWBCSIHn;NHANES;WBC count during hospitalisation;1000 cells/µL;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXLYMNOA;NHANES;Lymphocyte count at admission;1000 cells/µL;,,,,,,,,,,,,,,,,
LBXLYMNOHn;NHANES;Lymphocyte count during hospitalisation;1000 cells/µL;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXNENOA;NHANES;Neutrophil count at admission;1000 cells/µL;,,,,,,,,,,,,,,,,
LBXNENOHn;NHANES;Neutrophil count during hospitalisation;1000 cells/µL;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXHCTA;NHANES;Haematocrit at admission;%;,,,,,,,,,,,,,,,,
LBXHCTHn;NHANES;Haematocrit during admission;%;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXPLTSIA;NHANES;Platetelets at admission;100 cells/µl;,,,,,,,,,,,,,,,,
LBXPLTSIHn;NHANES;Platetelets during hospitalisation;100 cells/µl;For the nth reading of the variable,,,,,,,,,,,,,,,,
"LBXGHA;NHANES;HbA1c at admission;""nmol/mol; %"";",,,,,,,,,,,,,,,,
"LBXGHHn;NHANES;HbA1c during hospitalisation;""nmol/mol; %"";For the nth reading of the variable",,,,,,,,,,,,,,,,
LBXAPTTA;SELF;Partial Thromboplastin Time (APTT) at admission;;,,,,,,,,,,,,,,,,
LBXAPTTHn;SELF;Partial Thromboplastin Time (APTT) during hospitalisation;;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXAPTRA;SELF;Activated Partial Thromboplastin Time Ratio (APTR) at admission;;,,,,,,,,,,,,,,,,
LBXAPTRHn;SELF;Activated Partial Thromboplastin Time Ratio (APTR) during hospitalisation;;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXINRA;SELF;Prothrombin time (PT) / International Normalised Ratio (INR) at admission;;,,,,,,,,,,,,,,,,
LBXINRHn;SELF;Prothrombin time (PT) / International Normalised Ratio (INR) during hospitalisation;;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXSATSIA;NHANES;Alanine Aminotransferase Test (ALT/SGPT) at admission;U/L;,,,,,,,,,,,,,,,,
LBXSATSIHn;NHANES;Alanine Aminotransferase Test (ALT/SGPT) during hospitalisation;U/L;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXSTBA;NHANES;Total bilirubin at admission;mg/dL;,,,,,,,,,,,,,,,,
LBXSTBHn;NHANES;Total bilirubin during hospitalisation;mg/dL;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXSCBA;SELF;Conjugated bilirubin at admission;;,,,,,,,,,,,,,,,,
LBXSCBHn;SELF;Conjugated bilirubin during hospitalisation;;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXSUBA;SELF;Unconjugated bilirubin at admission;;,,,,,,,,,,,,,,,,
LBXSUBHn;SELF;Unconjugated bilirubin during hospitalisation;;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXSASSIA;NHANES;Aspartate Aminotransferase (AST/SGOT) at admission;U/L;,,,,,,,,,,,,,,,,
LBXSASSIHn;NHANES;Aspartate Aminotransferase (AST/SGOT) during hospitalisation;U/L;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXSGLA;NHANES;Glucose at admission;mg/dL;,,,,,,,,,,,,,,,,
LBXSGLHn;NHANES;Glucose during hospitalisation;mg/dL;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXSBUA;NHANES;Urea at admission;mg/dL;,,,,,,,,,,,,,,,,
LBXSBUHn;NHANES;Urea during hospitalisation;mg/dL;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXSBLA;SELF;Lactate at admission;mmol/L;,,,,,,,,,,,,,,,,
LBXSBLHn;SELF;Lactate during hospitalisation;mmol/L;For the nth reading of the variable,,,,,,,,,,,,,,,,
URXUCRA;NHANES;Creatinine at admission;mg/dL;,,,,,,,,,,,,,,,,
URXUCRHn;NHANES;Creatinine during hospitalisation;mg/dL;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXSCKA;NHANES;Creatinine phosphokinase (CPK) at admission;IU/L;,,,,,,,,,,,,,,,,
LBXSCKHn;NHANES;Creatinine phosphokinase (CPK) during hospitalisation;IU/L;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXSNASIA;NHANES;Sodium at admission;mmol/L;,,,,,,,,,,,,,,,,
LBXSNASIHn;NHANES;Sodium during hospitalisation;mmol/L;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXSCLSIA;NHANES;Chlorine at admission;mmol/L;,,,,,,,,,,,,,,,,
LBXSCLSIHn;NHANES;Chlorine during hospitalisation;mmol/L;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXSKSIA;NHANES;Potassium at admission;mmol/L;,,,,,,,,,,,,,,,,
LBXSKSIHn;NHANES;Potassium during hospitalisation;mmol/L;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXSPCA;SELF;Procalcitonin at admission;ng/ml;,,,,,,,,,,,,,,,,
LBXSPCHn;SELF;Procalcitonin during hospitalisation;ng/ml;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXCRPA;NHANES;C-Reactive Protein (CRP) at admission;mg/dL;,,,,,,,,,,,,,,,,
LBXCRPHn;NHANES;C-Reactive Protein (CRP) during hospitalisation;mg/dL;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXSLDSIA;NHANES;Lactae dehydrogenase (LDH) at admission;U/L;,,,,,,,,,,,,,,,,
LBXSLDSIHn;NHANES;Lactae dehydrogenase (LDH) during hospitalisation;U/L;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXSCKA;NHANES;Creatinine Kinase / Creatinine phosphokinase at admission;IU/L;,,,,,,,,,,,,,,,,
LBXSCKHn;NHANES;Creatinine Kinase / Creatinine phosphokinase during hospitalisation;IU/L;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXCTRA;SELF;Troponin at admission;ng/ml;,,,,,,,,,,,,,,,,
LBXCTRHn;SELF;Troponin during hospitalisation;ng/ml;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXCDDA;SELF;D-dimer at admission;mg/L;,,,,,,,,,,,,,,,,
LBXCDDHn;SELF;D-dimer during hospitalisation;mg/L;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXFERSIA;NHANES;Ferritin at admission;µg/L;,,,,,,,,,,,,,,,,
LBXFERSIHn;NHANES;Ferritin during hospitalisation;µg/L;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXIL6A;SELF;IL-6 at admission;pg/dL;,,,,,,,,,,,,,,,,
LBXIL6Hn;SELF;IL-6 during hospitalisation;pg/dL;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBDFBSIA;NHANES;Fibrinogen at admission;g/L;,,,,,,,,,,,,,,,,
LBDFBSIHn;NHANES;Fibrinogen during hospitalisation;g/L;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBDSALSIA;NHANES;Albumin at admission;g/L;,,,,,,,,,,,,,,,,
LBDSALSIHn;NHANES;Albumin during hospitalisation;g/L;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXSAPSIA;NHANES;Alkaline phosphatase at admission;U/L;,,,,,,,,,,,,,,,,
LBXSAPSIHn;NHANES;Alkaline phosphatase during hospitalisation;U/L;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXSGTSIA;NHANES;GGT at admission;U/L;,,,,,,,,,,,,,,,,
LBXSGTSIHn;NHANES;GGT during hospitalisation;U/L;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXCFDA;SELF;Calcifediol / 25-OH-vitamin D at admission;;,,,,,,,,,,,,,,,,
LBXCFDHn;SELF;Calcifediol / 25-OH-vitamin D dutring hospitalisation;;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXFIOA;SELF;FiO2 at admission;mmHg;,,,,,,,,,,,,,,,,
LBXFIOHn;SELF;FiO2 during hospitalisation;mmHg;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXPOA;SELF;PaO2 at admission;mmHg;,,,,,,,,,,,,,,,,
LBXPOHn;SELF;PaO2 during hospitalisation;mmHg;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXPCOA;SELF;PaCO2 at admission;mmHg;,,,,,,,,,,,,,,,,
LBXPCOHn;SELF;PaCO2 during hospitalisation;mmHg;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXSC3SIA;NHANES;HCO3 at admission;;,,,,,,,,,,,,,,,,
LBXSC3SIHn;NHANES;HCO3 during hospitalisation;;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXPHA;SELF;pH at admission;pH;,,,,,,,,,,,,,,,,
LBXPHHn;SELF;pH during hospitalisation;pH;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXBEH;SELF;Base excess at admission;;,,,,,,,,,,,,,,,,
LBXBEHn;SELF;Base excess during hospitalisation;;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXA4A;SELF;APACHE IV at admission;;,,,,,,,,,,,,,,,,
LBXA4Hn;SELF;APACHE IV during hospitalisation;;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXTCA;NHANES;Cholesterol at admission;mg/dL;,,,,,,,,,,,,,,,,
LBXTCHn;NHANES;Cholesterol during hospitalisation;mg/dL;For the nth reading of the variable,,,,,,,,,,,,,,,,
LBXTRA;NHANES;Triglyceride at admission;mg/dL;,,,,,,,,,,,,,,,,
LBXTRHn;NHANES;Triglyceride during hospitalisation;mg/dL;For the nth reading of the variable,,,,,,,,,,,,,,,,
connect <- function (){
cat("\n\n\n----------------------------------------------------------------------------------------------------------")
cat("\nPlease select the number corresponding to the hospital you want to analyse, if you want to do a combined analysis select multiple hospitals")
cat("\n
Princesa -> 1
CIPH -> 2
UMF_Iasis -> 3
SMUC -> 4
HM -> 5
Porto -> 6
FJD -> 7
Coimbra -> 8
UNAV -> 9
TU -> 10
Baskent:
Ankara Impatient -> 11
Konya Impatient -> 12
Istambul Impatient -> 13
Izmir Impatient -> 14
Alanya Impatient -> 15
Adana Impatient -> 16
Ankara Outpatient -> 17
Konya Outpatient -> 18
Istambul Outpatient -> 19
Izmir Outpatient -> 20
Alanya Outpatient -> 21
Sacrocuore:
Emergency database -> 22
Employees database -> 23
Verona database -> 24
Isaric -> 25
TU Dublin -> 26
UMF Cluj -> 27
UdeA -> 28
Inantro -> 29
UNSA -> 30
UZA -> 31
")
inp <- scan()
builder <- DSI::newDSLoginBuilder()
hospital_names <- hospital_names[inp]
project_names <- project_names[inp]
resource_names <- resource_names[inp]
urls <- urls[inp]
users <- users[inp]
pass <- pass[inp]
print(hospital_names)
print(project_names)
print(resource_names)
print(urls)
print(users)
print(pass)
url_ctr <- 0
for(i in 1:length(urls)){
print(paste("Connecting to Server with URL:", urls[i], sep=" "))
builder$append(server = hospital_names[i], url = urls[i],
user = users[i], password = pass[i],
resource = paste(project_names[i], resource_names[i], sep="."),
driver = "OpalDriver", options="list(ssl_verifyhost=0,ssl_verifypeer=0)")
url_ctr <- url_ctr+1
}
logindata <- builder$build()
connections <- DSI::datashield.login(logins = logindata, assign = TRUE, symbol = "D", failSafe = TRUE)
datashield.assign.expr(connections, symbol = 'data', expr = quote(as.resource.data.frame(D)))
#datashield.assign.expr(connections, symbol = 'auxDf', expr = quote(as.resource.data.frame(D)))
print("Successful connection to servers.")
return(list(connections,inp))
}
connect <- function (){
cat("\n\n\n----------------------------------------------------------------------------------------------------------")
cat("\nPlease select the number corresponding to the hospital you want to analyse, if you want to do a combined analysis select multiple hospitals")
cat("\n
Princesa -> 1
CIPH -> 2
UMF_Iasis -> 3
SMUC -> 4
HM -> 5
Porto -> 6
FJD -> 7
Coimbra -> 8
UNAV -> 9
TU -> 10
Baskent:
Ankara Impatient -> 11
Konya Impatient -> 12
Istambul Impatient -> 13
Izmir Impatient -> 14
Alanya Impatient -> 15
Adana Impatient -> 16
Ankara Outpatient -> 17
Konya Outpatient -> 18
Istambul Outpatient -> 19
Izmir Outpatient -> 20
Alanya Outpatient -> 21
Sacrocuore:
Emergency database -> 22
Employees database -> 23
Verona database -> 24
Isaric -> 25
TU Dublin -> 26
UMF Cluj -> 27
UdeA -> 28
Inantro -> 29
UNSA -> 30
UZA -> 31
")
inp <- scan()
builder <- DSI::newDSLoginBuilder()
hospital_names <- hospital_names[inp]
project_names <- project_names[inp]
resource_names <- resource_names[inp]
urls <- urls[inp]
users <- users[inp]
pass <- pass[inp]
print(hospital_names)
print(project_names)
print(resource_names)
print(urls)
print(users)
print(pass)
url_ctr <- 0
for(i in 1:length(urls)){
print(paste("Connecting to Server with URL:", urls[i], sep=" "))
builder$append(server = hospital_names[i], url = urls[i],
user = users[i], password = pass[i],
resource = paste(project_names[i], resource_names[i], sep="."),
driver = "OpalDriver", options="list(ssl_verifyhost=0,ssl_verifypeer=0)")
url_ctr <- url_ctr+1
}
logindata <- builder$build()
connections <- DSI::datashield.login(logins = logindata, assign = TRUE, symbol = "D", failSafe = TRUE)
datashield.assign.expr(connections, symbol = 'data', expr = quote(as.resource.data.frame(D)))
print("Successful connection to servers.")
return(list(connections,inp))
}
getCountryHosp <- function(hospitals){
Spain <- c("HM", "Princesa", "FJD", "UNAV")
Turkey <- c("Ankara Impatient", "Konya Impatient", "Adana Impatient", "Izmir Impatient", "Istambul Impatient", "Alanya Impatient", "Ankara Outpatient", "Konya Outpatient", "Izmir Outpatient", "Istambul Outpatient", "Alanya Outpatient")
Italy <- c("Sacrocuore Emergency", "Sacrocuore Employees", "Sacrocuore Verona", "Sacrocuore Isaric")
Portugal <- c("Porto", "Coimbra")
UK <- c("SMUC")
Ireland <- c("TUDublin")
Slovakia <- c("TU")
Romania <- c("UMF_Iasis", "UMF_Cluj")
Croatia <- c("CIPH","Inantro")
Colombia <- c("UdeA")
Bosnia_Herzegovina <- c("UNSA")
Belgium <- c("UZA")
Spain_Index <- c()
Turkey_Index <- c()
Italy_Index <- c()
Portugal_Index <- c()
UK_Index <- c()
Ireland_Index <- c()
Slovakia_Index <- c()
Romania_Index <- c()
Croatia_Index <- c()
Colombia_Index <- c()
Bosnia_Herzegovina_Index <- c()
Belgium_Index <- c()
country_index <- list()
for(i in 1:length(hospitals)){
if(hospitals[i] %in% Spain){
Spain_Index <- c(Spain_Index, i)
}else if(hospitals[i] %in% Turkey){
Turkey_Index <- c(Turkey_Index, i)
}else if(hospitals[i] %in% Italy){
Italy_Index <- c(Italy_Index, i)
}else if(hospitals[i] %in% Portugal){
Portugal_Index <- c(Portugal_Index, i)
}else if(hospitals[i] %in% UK){
UK_Index <- c(UK_Index, i)
}else if(hospitals[i] %in% Ireland){
Ireland_Index <- c(Ireland_Index, i)
}else if(hospitals[i] %in% Slovakia){
Slovakia_Index <- c(Slovakia_Index, i)
}else if(hospitals[i] %in% Romania){
Romania_Index <- c(Romania_Index, i)
}else if(hospitals[i] %in% Croatia){
Croatia_Index <- c(Croatia_Index, i)
}else if(hospitals[i] %in% Colombia){
Colombia_Index <- c(Colombia_Index, i)
}else if(hospitals[i] %in% Bosnia_Herzegovina){
Bosnia_Herzegovina_Index <- c(Bosnia_Herzegovina_Index, i)
}else if(hospitals[i] %in% Belgium){
Belgium_Index <- c(Belgium_Index, i)
}
}
if(length(Spain_Index) != 0 ){
aux <- length(country_index)+1
country_index[aux] <- list(Spain_Index)
names(country_index)[aux] <- "Spain"
}
if(length(Turkey_Index) != 0 ){
aux <- length(country_index)+1
country_index[aux] <- list(Turkey_Index)
names(country_index)[aux] <- "Turkey"
}
if(length(Italy_Index) != 0 ){
aux <- length(country_index)+1
country_index[aux] <- list(Italy_Index)
names(country_index)[aux] <- "Italy"
}
if(length(Portugal_Index) != 0 ){
aux <- length(country_index)+1
country_index[aux] <- list(Portugal_Index)
names(country_index)[aux] <- "Portugal"
}
if(length(UK_Index) != 0 ){
aux <- length(country_index)+1
country_index[aux] <- list(UK_Index)
names(country_index)[aux] <- "UK"
}
if(length(Ireland_Index) != 0 ){
aux <- length(country_index)+1
country_index[aux] <- list(Ireland_Index)
names(country_index)[aux] <- "Ireland"
}
if(length(Slovakia_Index) != 0 ){
aux <- length(country_index)+1
country_index[aux] <- list(Slovakia_Index)
names(country_index)[aux] <- "Slovakia"
}
if(length(Romania_Index) != 0 ){
aux <- length(country_index)+1
country_index[aux] <- list(Romania_Index)
names(country_index)[aux] <- "Romania"
}
if(length(Croatia_Index) != 0 ){
aux <- length(country_index)+1
country_index[aux] <- list(Croatia_Index)
names(country_index)[aux] <- "Croatia"
}
if(length(Colombia_Index) != 0 ){
aux <- length(country_index)+1
country_index[aux] <- list(Colombia_Index)
names(country_index)[aux] <- "Colombia"
}
if(length(Bosnia_Herzegovina_Index) != 0 ){
aux <- length(country_index)+1
country_index[aux] <- list(Bosnia_Herzegovina_Index)
names(country_index)[aux] <- "Bosnia & Herzegovina"
}
if(length(Belgium_Index) != 0 ){
aux <- length(country_index)+1
country_index[aux] <- list(Belgium_Index)
names(country_index)[aux] <- "Belgium"
}
return(country_index)
}
#Distinguish variable Types
numeric <- c("DMRAGEYR","DMXHT","DMXWT","DMXBMI","DATLGT","DATLGTI","DATSSDHn","CSXBTPA","CSXBTPHn","CSXOSTA","CSXOSTHn","CSXCHRA","CSXCHRHn","CSXRRA","CSXRRHn","CSXRRI","CSXSYA","CSXSYHn","CSXDIA","CSXDIHn","SMTFE","SMTCO","SMTST","SMTSB","SMXSEA","DATIMD","IMDXCTLD","IMDXEQ","DATLBDHn","LBXHGBA","LBXHGBHn","LBXESRA","LBXESRHn","LBXWBCSIA","LBXWBCSIHn","LBXLYMNOA","LBXLYMNOHn","LBXNENOA","LBXNENOHn","LBXHCTA","LBXHCTHn","LBXPLTSIA","LBXPLTSIHn","LBXGHA","LBXGHHn","LBXAPTTA","LBXAPTTHn","LBXAPTRA","LBXAPTRHn","LBXPTA","LBXPRHn","LBXINRA","LBXINRHn","LBXSATSIA","LBXSATSIHn","LBXSTBA","LBXSTBHn","LBXSCBA","LBXSCBHn","LBXSUBA","LBXSUBHn","LBXSASSIA","LBXSASSIHn","LBXSGLA","LBXSGLHn","LBXSBUA","LBXSBUHn","LBXSBLA","LBXSBLHn","LBXSCRA","LBXSCRHn","LBXSNASIA","LBXSNASIHn","LBXSCLSIA","LBXSCLSIHn","LBXSKSIA","LBXSKSIHn","LBXSPCA","LBXSPCHn","LBXCRPA","LBXCRPHn","LBXSLDSIA","LBXSLDSIHn","LBXCTRA","LBXCTRHn","LBXCDDA","LBXCDDHn","LBXFERSIA","LBXFERSIHn","LBXIL6A","LBXIL6Hn","LBDFBSIA","LBDFBSIHn","LBDSALSIA","LBDSALSIHn","LBXSAPSIA","LBXSAPSIHn","LBXSGTSIA","LBXSGTSIHn","LBXCFDA","LBXCFDHn","LBXFIOA","LBXFIOHn","LBXPOA","LBXPOHn","LBXPCOA","LBXPCOHn","LBXSC3SIA","LBXSC3SIHn","LBXPHA","LBXPHHn","LBXBEH","LBXBEHn","LBXA4A","LBXA4Hn","LBXTCA","LBXTCHn","LBXTRA","LBXTRHn","LBXSCKA","LBXSCKHn","LBXPSCKA","LBXPSCKHn")
categoric <- c("DMRGENDR", "DMRBORN", "DMRRETH1", "DMROCCU", "DMRHREDU", "DSXOS", "DSXHO", "DSXIC", "TRXAV","TRXRIB","TRXLR","TRXRM","TRXIA","TRXIB","TRXCH","TRXAB","TRXCS","TRXHEP","TRXAF","TRXCP","TRXOT","TRXECM","TRXIV","TRXNIV","TRXNO","TRXOX","TRXRR","TRXTR","TRXVA","TRXPE","TRXPV","TRXIT","TRXNMB","TRXAC","TRXINA","TRXIS","TRXIM","TRXVC","TRXVD","TRXZN", "CSXCOT","CSXCTR","SMXASAH","SMXFEA","SMXCOA","SMXSTA","SMXSBA","SMXRNA","SMXMYA","SMXARA","SMXCPA","SMXAPA","SMXINA","SMXNAA","SMXDIA","SMXFAA","SMXHEA","SMXCNA","SMXACA","SMXSLA","SMXTLA","SMXSYA","SMXWHA","SMXLYA","SMXANA","SMXIWA","SMXSRA","SMXBLA","CMXPRG","CMXCVD","CMXCMP","CMXHT","CMXDI","CMXCKD","CMXCLD","CMXCPD","CMXASM","CMXCND","CMXRHE","CMXCCI","CMXCBD","CMXDE","CMXPU","CMXST","CMXLY","CMXAP","RFXSM","RFXFSM","RFXOB","RFXTB","RFXIMD","RFXHIV","RFXAIDS","RFXUI","RFXHC","RFXONC","RFXMN", "HMRACI","HMRARB","HMRAHO","HMRNS","HMROS","HMRCS","HMRIS","HMRAV","HMRAB","HMRCOV","IMDXCT","IMDXCTCR","IMDXCTTE","IMDXCTAB","IMDXXR","IMDXPN", "COXRD","COXAR","COXPM","COXMOD","COXPT","COXEC","COXSH","COXIO","COXPE","COXST","COXDIC","COXRIO","COXKF","COXHF","COXBC")
hospitals_contain_var <- function(hospitals_cols, variable, index){
res <- c()
for(i in 1: length(hospitals_cols)){
if(variable %in% unlist(hospitals_cols[i]))
res <- c(res, i)
}
if(is.null(res)){
return(NULL)
}else if(is.null(index)){
return (res)
}else{
return(index[res])
}
}
get_working_hosp <- function(index, connections, to_analyse){
new_index <- c()
for(i in 1:length(index)){
analysisRes <- NULL
try(analysisRes <- ds.table(to_analyse,datasources = connections[index[i]]))
if(!is.null(analysisRes)){
if(!grepl("Error", analysisRes[1]) & !grepl("failed", analysisRes[1]))
new_index <- c(new_index,index[i])
}
}
return(new_index)
}
obtain_table1 <- function(connections, inp, varToAnalize){
#Obtain the name of the hospitals and the corresoponding indexes according to country
hospitals_cols <- ds.colnames("data")
hospitals <- names(hospitals_cols)
country_Index_Total <- getCountryHosp(hospitals)
#Create empty result
result_df <- data.frame(matrix(ncol = 3, nrow = 1))
colnames(result_df) <- c('Codebook Variable', 'Description', 'Category/Units')
name_df <- result_df
#Add the necessary headers
for(i in 1:length(country_Index_Total)){
country <- names(country_Index_Total)[i]
country_Index <- unname(unlist(country_Index_Total[i]))
country_hospitals <- hospitals[country_Index]
nPatients <- ds.dim("data",datasources = connections[country_hospitals])
for(j in 1:length(country_Index)){
n_Patients_Hosp <- nPatients[[j]][1]
new_col_name <- paste(paste(paste(country_hospitals[j],"(N ="),n_Patients_Hosp),")",sep="")
result_df[new_col_name] <- NA
name_df[country_hospitals[j]] <- NA
}
new_col_name <- paste(paste(paste(paste("Total", country), "(N ="),nPatients[[j+1]][1]),")",sep="")
result_df[new_col_name] <- NA
name_df[country] <- NA
}
for(i in 1:length(varToAnalize)){
variable <- varToAnalize[i]
description <- subset(codebook$description,codebook$variable == variable)
if(length(description)== 0)
description <- ""
category <- subset(codebook$unit,codebook$variable == variable)
to_analyse <- paste("data$",variable,sep="")
if(variable %in% categoric){
print("Categoric")
possible_vars <- c()
contain_var <- hospitals_contain_var(hospitals_cols, variable, NULL)
analysis <- NULL
analysis <- try(ds.table(to_analyse,datasources = connections[contain_var]))
if(is.null(analysis)){
new_index <- get_working_hosp(contain_var, connections, to_analyse)
if(length(new_index) > 0)
analysis <- try(ds.table(to_analyse,datasources = connections[new_index]))
if(is.null(new_index))
next
}else if(grepl("Error", analysis[1]) | grepl("failed", analysis[1])){
new_index <- get_working_hosp(contain_var, connections, to_analyse)
if(length(new_index) > 0)
analysis <- try(ds.table(to_analyse,datasources = connections[new_index]))
if(is.null(new_index))
next
}
if(!is.null(analysis) & !grepl("Error", analysis[1])){
auxAnalisis <- analysis[[1]]
auxAnalisis <- unlist(unname(auxAnalisis[length(auxAnalisis)]))
for(j in 1:length(auxAnalisis)){
possible_vars <- c(possible_vars, names(auxAnalisis[j]))
}
auxdf <- data.frame (matrix(ncol = length(colnames(name_df)), nrow = length(possible_vars)))
colnames(auxdf) <- colnames(name_df)
auxdf[1,"Codebook Variable"] <- variable
auxdf[1,"Description"] <- description
for(k in 1:length(country_Index_Total)){
countries_index <- unlist(country_Index_Total[k])
country <- names(country_Index_Total)[k]
print("Analysis for the country:")
print(country)
if(length(countries_index)>1)
contain_var <- hospitals_contain_var(hospitals_cols[countries_index], variable, countries_index)
else{
if(variable %in% unlist(hospitals_cols[countries_index]))
contain_var <- countries_index
else
next
}
if(is.null(contain_var)){
print("No selected hospitals contain this variable in this country")
next
}
for(j in 1:length(contain_var)){
new_index <- contain_var[j]
hospital <- hospitals[new_index]
print(hospital)
analysis <- NULL
try(analysis <- ds.table(to_analyse,datasources = connections[new_index]))
if(!is.null(analysis)){
if(!(grepl("Error", analysis[1]) | grepl("failed", analysis[1]))){
auxAnalisis <- analysis[[1]]
auxAnalisis <- unlist(unname(auxAnalisis[length(auxAnalisis)]))
num_result_per_hosp <- as.data.frame(analysis[[1]][[3]])
prop_result_per_hosp <- as.data.frame(analysis[[1]][[2]])
for(h in 1:length(possible_vars)){
auxdf[h,"Category/Units"] <- possible_vars[h]
}
for(l in 1:dim(num_result_per_hosp)[[1]]){
num_res <- num_result_per_hosp[hospital][[1]][l]
position <- get_posVal_index(row.names(num_result_per_hosp)[l], possible_vars)
if(is.na(num_res))
auxdf[position,hospital] <- ""
else{
prop_res <- format(round(prop_result_per_hosp[hospital][[1]][l], 4), nsmall = 2)
prop_res <- as.double(prop_res)*100
res <- paste(paste(paste(num_res, "("),prop_res,sep=""),"%)",sep="")
auxdf[position,hospital] <- res
}
}
}
}
}
try(analysis <- ds.table(to_analyse,datasources = connections[contain_var]))
if(is.null(analysis)){
new_index <- get_working_hosp(contain_var, connections, to_analyse)
if(length(new_index) > 0)
analysis <- try(ds.table(to_analyse,datasources = connections[new_index]))
if(is.null(new_index))
next
}else if(grepl("Error", analysis[1]) | grepl("failed", analysis[1])){
new_index <- get_working_hosp(contain_var, connections, to_analyse)
if(length(new_index) > 0)
analysis <- try(ds.table(to_analyse,datasources = connections[new_index]))
if(is.null(new_index))
next
}
for(l in 1:length(possible_vars)){
num_result_tot <- as.data.frame(analysis[[1]][[5]])
prop_result_tot <- as.data.frame(analysis[[1]][[4]])
num_res <- num_result_tot[[1]][l]
position <- get_posVal_index(row.names(num_result_tot)[l], possible_vars)
if(is.na(num_res))
auxdf[position,country] <- ""
else{
prop_res <- format(round(prop_result_tot[[1]][l], 4), nsmall = 2)
prop_res <- as.double(prop_res)*100
res <- paste(paste(paste(num_res, "("),prop_res,sep=""),"%)",sep="")
auxdf[position,country] <- res
}
}
}
colnames(auxdf) <- colnames(result_df)
result_df <- rbind(result_df,auxdf)
# auxdf <- name_df
# colnames(auxdf) <- colnames(result_df)
# result_df <- rbind(result_df,auxdf)
}else{
print("Unable to abtain data form the field:")
print(variable)
}
}else if (variable %in% numeric){
print("Numeric")
auxdf <- data.frame (matrix(ncol = length(colnames(name_df)), nrow = 1))
colnames(auxdf) <- colnames(name_df)
auxdf[1,"Codebook Variable"] <- variable
auxdf[1,"Description"] <- description
auxdf[1,"Category/Units"] <- category
for(k in 1:length(country_Index_Total)){
countries_index <- unlist(country_Index_Total[k])
country <- names(country_Index_Total)[k]
print("Analysis for the country:")
print(country)
analyzedHosp <- hospitals[countries_index]
if(length(countries_index)>1)
contain_var <- hospitals_contain_var(hospitals_cols[countries_index], variable, countries_index)
else
contain_var <- countries_index
if(is.null(contain_var)){
print("No selected hospitals contain this variable in this country")
next
}
analysisMean <- NULL
try(analysisMean <- ds.mean(to_analyse,datasources = connections[contain_var]))
try(analysisVar <- ds.var(to_analyse,datasources = connections[contain_var]))
#If the variable exists
if(!is.null(analysisMean)){
if(!(grepl("Error", analysisMean[1]) | grepl("FAILED", analysisMean[3]))){
means <- c()
for(j in 1:length(contain_var)){
index_hosp <- contain_var[j]
hospital <- hospitals[index_hosp]
mean_res <- analysisMean[[1]][j]
var_res <- analysisVar[[1]][j]
if(!is.na(mean_res) & mean_res !=0){
means <- c(means,mean_res)
mean_res <- format(round(mean_res, 2), nsmall = 2)
sd_res <- format(round(sqrt(var_res), 2), nsmall = 2)
res <- paste(paste(paste(mean_res, "(+-"),sd_res,sep=""),")",sep="")
auxdf[hospital] <- res
}else{
auxdf[hospital] <- NA
}
}
if(length(means)!= 0){
res <- format(round(mean(means), 2), nsmall = 2)
auxdf[country] <- res
}else {
auxdf[country] <- NA
}
}
}
}
colnames(auxdf) <- colnames(result_df)
result_df <- rbind(result_df,auxdf)
}
}
for(i in 1:nrow(result_df)){
for (j in 1:ncol(result_df)){
if(is.na(result_df[i,j]))
result_df[i,j] <- ""
}
}
result_df <- result_df[-1,]
write.csv(x=result_df, file = "table1.csv", row.names = FALSE)
datashield.logout(connections)
saveRDS(result_df,file="table1_save.Rda")
return(result_df)
}
apply_filters <- function(){
cols <- ds.colnames("data")
posVarsCols <- Reduce(intersect, cols)
filters <- TRUE
while(filters){
okvar <- FALSE
okval <- FALSE
okcountry <- FALSE
while(!okvar | !okcountry){
variableN <- readline("Please enter the variable you want to subset from > ")
if(variableN %in% categoric)
okvar <- TRUE
else{
okvar <- FALSE
print("Please enter a categoric variable")
}
if(variableN %in% posVarsCols)
okcountry <- TRUE
else{
print("Please use a variable that is present in all datasets")
print("The variables that are present in all the datasets are the following")
print(posVarsCols)
}
}
posvals <- strsplit(subset(codebook, codebook$variable == variableN)[1,3], split = "/")
variableN <- paste(variableN,"_numeric", sep="")
while(!okval){
value<- readline("Please enter the desired value > ")
if(value %in% unlist(posvals)){
okval <- TRUE
}else
print("Please enter a valid value")
}
if(value == "Yes")
value <- "1"
if(value == "No")
value <- "0"
if(value == "Male")
value <- "0"
if(value == "Female")
value <- "1"
if(value == "Recovered")
value <- "0"
if(value == "Deceased")
value <- "1"
if(value == "Transferred")
value <- "2"
#Only if you want to divide the subset
try(ds.dataFrameSubset(df.name = 'data', V1.name = paste("data$",variableN,sep=""), V2.name = value, Boolean.operator = "==", newobj = "data", datasources = connections))
input <- readline("Do you wish to apply another filter? Yes=1 / No=0 > " )
if(input == "0")
filters <- FALSE
}
}
get_posVal_index <- function(var, possible_vars){
for(i in 1:length(possible_vars)){
if(is.na(var)){
if(is.na(possible_vars[i]))
return (i)
else if(possible_vars[i] == "NA"){
return (i)
}
}else if(var == possible_vars[i])
return (i)
}
}
Name Origin,Harmonised variable name,Variables in REDCap,Variable description,Variable type,Possible values,Possible values format
NHANES,DMRBORN,,Country of birth,ISO country code,ISO 3166-1-alpha-2 English country name / missing,https://pkgstore.datahub.io/core/country-list/data_csv/data/d7c9d7cfb42cb69f4422dec222dbbaa8/data_csv.csv
SELF,DMRDOB,,Date of birth,Calendar date,Date / Missing,yyyy-mm-dd / .
SELF,DMRAGEYR,age_estimateyears,Age,Continuous,Years / Missing,0-150 / .
SELF,DMRGENDR,sex,Sex,Binary,Male/Female / Missing,0 / 1 / .
NHANES,DMXHT,taille,Height,Continuous,cm / Missing,40-250 / .
NHANES,DMXWT,poids,Weight,Continuous,kg / Missing,0-440 / .
NHANES,DMXBMI,bmi,BMI,Continuous,kg/m2 / Missing,11-130 / .
NHANES,DMRRETH1,ethnic/other_ethnic,Ethnicity,Categorical,Asian/Black/Hispanic/White/Multiracial/Other / Missing,1 /2 / 3 / 4/ 5 / 6 / .
SELF,DMROCCU,,Occupation,Categorical,Unemployed/Student/Employed/Self-employed/Retired / Missing,1 /2 / 3 / 4/ 5 / .
NHANES,DMRHREDU,,Education,Categorical,High school/Bachelors/Postgraduate/Other / Missing,1 /2 / 3 / 4/ .
SELF,CMXPRG,pregyn_rptestcd ,Pregnancy,Binary,No /Yes / Missing,0 / 1 / .
SELF,CMXCVD,chroniccard_mhyn,CVD,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXCMP,,Cardiomyopathy,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXHT,hypertention_mhyn,Hypertension,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXDI,antec_two,Diabetes,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXCKD,renal_mhyn,Chronic kidney disease,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXCLD,,Chronic liver disease,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXCPD,chronicpul_mhyn,Chronic pulmonary disease,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXASM,asthma_mhyn,Asthma,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXCND,chronicneu_mhyn,Chronic neurological or neuromuscular disorder,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXRHE,rheumatology_mhyr,Rheumatism,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXCCI,,Chronic cognitive impairment,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXCBD,,Cerebrovascular disease,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXDE,dementia_mhyn,Dementia,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXPU,,Peptic Ulcer / Bleeding,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXST,,Solid tumour,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXLY,,Lymphoma,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXAP,,Asplenia,Binary,No/Yes / Missing,0 / 1 / .
SELF,RFXSM,smoking_mhyn,Smoking,Binary,No/Yes / Missing,0 / 1 / .
SELF,RFXFSM,,Former smoker,Binary,No/Yes / Missing,0 / 1 / .
SELF,RFXOB,obesity_mhyn,Obesity,Binary,No/Yes / Missing,0 / 1 / .
SELF,RFXTB,,TB,Binary,No/Yes / Missing,0 / 1 / .
SELF,RFXIMD,,Immunodeficiency,Binary,No/Yes / Missing,0 / 1 / .
SELF,RFXHIV,aidshiv_mhyn,HIV,Binary,No/Yes / Missing,0 / 1 / .
SELF,RFXAIDS,aidshiv_mhyn,AIDS,Binary,No/Yes / Missing,0 / 1 / .
SELF,RFXUI,,Immunodeficiency - unknown cause,Binary,No/Yes / Missing,0 / 1 / .
SELF,RFXHC,,Haematological cancer,Binary,No/Yes / Missing,0 / 1 / .
SELF,RFXONC,,Oncology,Binary,No/Yes / Missing,0 / 1 / .
SELF,RFXMN,malnutrition_mhyn,Malnutrition,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXCHF,,Congestive heart failure,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXVDP,,Peripheral vascular disease,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXVDC,,Collapsed vascular disease,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXCA,,Cardiac arrhythmia,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXVD,,Valvular disease,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXABL,,Blood loss anaemia,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXAD,,Deficiency anaemia,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXNDP,,Psychosis,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXNDD,,Depression,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXCOPD,copd_mhyn,Chronic Obstructive Pulmonary Disease,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXPCD,,Pulmonary circulation disorder,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXRI,,Acute renal insufficiency,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXMLD,mildliv_mhyn,Mild liver disease,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXNPM,malignantneo_mhyn,Malignant neoplasia,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXCLH,,Lymphatic or haematopoietic cancer,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXMET,,Metastases,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXTU,,Tumour without metastasis,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXMY,,Myeloma,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXNP,,Neutropenia,Binary,No/Yes / Missing,0 / 1 / .
SELF,RFXMD,,Metabolic disorders,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXANX,,Anxiety disorder,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXBDO,,Obstruction of the bile duct,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXEPI,,Exocrine pancreatic insufficiency,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXOAR,,Osteoarthritis,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXSPI,,Spinal condition,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXSOT,,Soft tissue disorder,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXOKD,,Other disorder of the kidneys or ureter,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXUTI,,Urinary tract infection,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXINC,,Incontinence,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXHPP,,Hyperplasia,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXHGL,,Hyperglycaemia,Binary,No/Yes / Missing,0 / 1 / .
SELF,RFXLC,,Problems relating to living conditions,Binary,No/Yes / Missing,0 / 1 / .
SELF,RFXPM,,Pacemaker,Binary,No/Yes / Missing,0 / 1 / .
SELF,RFXAP,,Angioplasty,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXIHD,,Ischaemic heart disease,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXATH,,Atherothrombotic disease,Binary,No/Yes / Missing,0 / 1 / .
SELF,CMXLK,,Leukaemia,Binary,No/Yes / Missing,0 / 1 / .
SELF,HMRACI,,ACE Inhibitors,Binary,No/Yes / Missing,0 / 1 / .
SELF,HMRARB,,ARBs,Binary,No/Yes / Missing,0 / 1 / .
SELF,HMRAHO,,Anti-hypertensive (other),Binary,No/Yes / Missing,0 / 1 / .
SELF,HMRNS,,NSAIDs,Binary,No/Yes / Missing,0 / 1 / .
SELF,HMROS,,Oral Steroids,Binary,No/Yes / Missing,0 / 1 / .
SELF,HMRCS,,Corticosteroids,Binary,No/Yes / Missing,0 / 1 / .
SELF,HMRIS,,Immunospressant,Binary,No/Yes / Missing,0 / 1 / .
SELF,HMRAV,,Antiviral,Binary,No/Yes / Missing,0 / 1 / .
SELF,HMRAB,,Antibiotic,Binary,No/Yes / Missing,0 / 1 / .
SELF,HMRCOV,,Other targeted COVID-19 medication ,Binary,No/Yes / Missing,0 / 1 / .
SELF,HMRANC,,Anticoagulant,Binary,No/Yes / Missing,0 / 1 / .
SELF,HMRAT,,Antithrombotic,Binary,No/Yes / Missing,0 / 1 / .
SELF,HMRINS,,Insulin,Binary,No/Yes / Missing,0 / 1 / .
SELF,DATSSA,hostdat,Date of assessment during hospitalisation,Calendar date,Date / Missing, yyy-mm-dd / .
SELF,DATSSDHn,,Time between admission and assessment,Continuous,Days / Missing,0-180 / .
SELF,CSXBTPA,temp_vsorres,Body temperature at admission,Continuous,C / Missing,25-43 / .
SELF,CSXBTPHn,,Body temperature in hospital,Continuous,C / Missing,25-43 / .
SELF,CSXOSTA,oxy_vsorresu,Oxygen Saturation at admission,Continuous,% / Missing,0-100 / .
SELF,CSXOSTHn,,Oxygen Saturation in hospital,Continuous,% / Missing,0-100 / .
SELF,CSXCHRA,,Heart Rate at admission,Continuous,bpm / Missing,0-288 / .
SELF,CSXCHRHn,,Heart Rate in hospital,Continuous,bpm / Missing,0-288 / .
SELF,CSXRRA,,Respiratory Rate at admission,Continuous,breaths/min / Missing,0-200 / .
SELF,CSXRRHn,,Respiratory Rate in hospital,Continuous,breaths/min / Missing,0-200 / .
SELF,CSXRRI,,Respiratory rate in ICU,Continuous,breaths/min / Missing,0-200 / .
SELF,CSXSYA,sysbp_vsorres,Systolic bp at admission,Continuous,mmHg / Missing,74-270 / .
SELF,CSXSYHn,,Systolic bp in hospital,Continuous,mmHg / Missing,74-270 / .
SELF,CSXDIA,admission_diabp_vsorres,Diastolic bp at admission,Continuous,mmHg / Missing,0-124 / .
SELF,CSXDIHn,,Diastolic bp in hospital,Continuous,mmHg / Missing,0-124 / .
SELF,CSXMAPA,,Mean arterial pressure at admission,Continuous,mmHg / Missing,30-150 / .
SELF,CSXMAPHn,,Mean arterial pressure during hospitalisation,Continuous,mmHg / Missing,30-150 / .
SELF,CSXCOT,test_type,Received covid test,Categorical,PCR/antigen/other/unspecified / Missing,1 / 2 / 3 / 4 / .
SELF,DATCOT,covidpos_dat1,Date of covid test,Calendar date,Date / Missing, yyy-mm-dd / .
SELF,CSXCTR,,Covid test results,Binary,Negative / Positive / Missing,0 / 1 / .
SELF,SMXASAH,,Asymptomatic during hospitalisation,Binary,No / Yes / Missing,0 / 1 / .
SELF,SMXFEA,fever_ceoccur_two,Fever at admission,Binary,No / Yes / Missing,0 / 1 / .
SELF,SMTFE,,Fever duration,Continuous,Days / Missing,0-180 / .
SELF,SMXCOA,cough_ceoccur_two,Cough at admission,Binary,No / Yes / Missing,0 / 1 / .
SELF,SMTCO,,Cough duration,Continuous,Days / Missing,0-180 / .
SELF,SMXSTA,sorethroat_ceoccur_two,Sore throat at admission,Binary,No / Yes / Missing,0 / 1 / .
SELF,SMTST,,Sore throat duration,Continuous,Days / Missing,0-180 / .
SELF,SMXSBA,,Shortness of breath at admission,Binary,No / Yes / Missing,0 / 1 / .
SELF,SMTSB,,Shortness of breath duration,Continuous,Days / Missing,0-180 / .
SELF,SMXRNA,runnynose_ceoccur_two,Runny nose at admission,Binary,No / Yes / Missing,0 / 1 / .
SELF,SMTRN,,Runny nose duration,Continuous,Days / Missing,0-180 / .
SELF,SMXSEA,seizures_cecoccur_two,Convulsions / Seizures,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXMYA,myalgia_ceoccur_two,Myalgia at admission,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXARA,jointpain_ceoccur_two,Arthralgia at admission,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXCPA,chestpain_ceoccur_two,Chest pain at admission,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXAPA,abdopain_ceoccur_two,Abdominal pain at admission,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXINA,,Lower chest wall indrawing at admission,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXNAA,vomit_ceoccur_two,Nausea / Vomiting at admission,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXDIA,diarrhoea_ceoccur_two,Diarrhoea at admission,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXFAA,fatigue_ceoccur_two,Fatigue at admission,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXHEA,headache_ceoccur_two,Headache at admission,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXCNA,conjunct_ceoccur_two,Conjunctivitis at admission,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXACA,confusion_ceoccur_two,Confusion / Altered consciousness at admission,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXSLA,,Loss of smell at admission,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXTLA,,Loss of taste at admission,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXSYA,,Syncope / Fall at admission,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXWHA,wheeze_ceoccur_two,Wheezing at admission,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXLYA,lymp_ceoccur_two,Lymphadenopathy at admission,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXANA,,Anorexia at admission,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXIWA,,Inability to walk at admission,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXSRA,rash_ceoccur_two,Skin rash at admission,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXBLA,bleed_ceterm_two,Bleeding / Haemorrhage at admission,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXURT,,Upper respiratory tract complaint,Binary,No/Yes / Missing,0 / 1 / .
SELF,SMXGCS,daily_gcs_vsorres?,Glasgow Coma Scale,Continuous,Score / Missing,3-15/ .
SELF,SMXAVPU,avpu_vsorres,AVPU,Categorical,Alert/Voice/Pain/Unresponsive / Missing,1 / 2 / 3 / 4 / .
SELF,SMXSOFA,,qSOFA Score,Continuous,0 / 1 / 2 / 3 / Missing,1 / 2 / 3 / .
SELF,SMXRASS,rass_vsorres,Richmond Agitation Sedation Scale,Continuous,Score / Missing,-5 to +4 / .
SELF,TRXOT,oxygen_cmoccur,High-flow nasal cannula oxygen therapy,Binary,No/Yes / Missing,0 / 1 / .
SELF,TRXECM,extracorp_prtrt,ECMO,Binary,No/Yes / Missing,0 / 1 / .
SELF,TRXIV,,Invasive ventilation,Binary,No/Yes / Missing,0 / 1 / .
SELF,TRXNIV,noninvasive_proccur,Non IV,Binary,No/Yes / Missing,0 / 1 / .
SELF,TRXNO,,Inhaled NO�2,Binary,No/Yes / Missing,0 / 1 / .
SELF,TRXOX,oxygen_proccur,Oxygen need,Binary,No/Yes / Missing,0 / 1 / .
SELF,TRXRR,rrt_prtrt,Renal replacement therapy,Binary,No/Yes / Missing,0 / 1 / .
SELF,TRXTR,tracheo_prtrt,Tracheostomy,Binary,No/Yes / Missing,0 / 1 / .
SELF,TRXVA,inotrop_cmtrt,Vasopressor,Binary,No/Yes / Missing,0 / 1 / .
SELF,TRXPE,,PEEP,Binary,No/Yes / Missing,0 / 1 / .
SELF,TRXPV,pronevent_prtrt,Prone ventilation,Binary,No/Yes / Missing,0 / 1 / .
SELF,TRXIT,,Intubation,Binary,No/Yes / Missing,0 / 1 / .
SELF,TRXNMB,,Neuromuscular blocking agent,Binary,No/Yes / Missing,0 / 1 / .
SELF,TRXAC,,Anticoagulant ,Binary,No/Yes / Missing,0 / 1 / .
SELF,TRXINA,,Inatropic,Binary,No/Yes / Missing,0 / 1 / .
SELF,TRXIS,,Immunosuppressor,Binary,No/Yes / Missing,0 / 1 / .
SELF,TRXIM,,Immunomodulator,Binary,No/Yes / Missing,0 / 1 / .
SELF,TRXVC,,Vitamin C,Binary,No/Yes / Missing,0 / 1 / .
SELF,TRXVD,,Vitamin D,Binary,No/Yes / Missing,0 / 1 / .
SELF,TRXZN,,Zinc,Binary,No/Yes / Missing,0 / 1 / .
SELF,DATLBHn,daily_lbdat?,Date of assessment during hospitalisation,Calendar date,Date / Missing,yyyy-mm-dd / .
SELF,DATLBDHn,,Time between admission and assessment during hospitalisation,Continuous,Days / Missing,0-180 / .
NHANES,LBXHGBA,daily_hb_lborres,Haemoglobin at admission,Continuous,g/dL / Missing,"7,5-19,7 / ."
NHANES,LBXHGBHn,,Haemoglobin during hospitalisation,Continuous,g/dL / Missing,"7,5-19,7 / ."
NHANES,LBXHGBM,,Mean haemoglobin during hospitalisation,Continuous,g/dL / Missing,"7,5-19,7 / ."
SELF,LBXESRA,,Erythrocyte Sedimentation Rate (ESR) at admission,Continuous,mm/hr / Missing,0-120 / .
SELF,LBXESRHn,,Erythrocyte Sedimentation Rate (ESR) during hospitalisation,Continuous,mm/hr / Missing,0-120 / .
SELF,LBXESRM,,Mean Erythrocyte Sedimentation Rate (ESR) during hospitalisation,Continuous,mm/hr / Missing,0-120 / .
NHANES,LBXWBCSIA,daily_wbc_lborres,WBC count at admission,Continuous,1000 cells/uL / Missing,1-84 / .
NHANES,LBXWBCSIHn,,WBC count during hospitalisation,Continuous,1000 cells/uL / Missing,1-84 / .
NHANES,LBXWBCSIM,,Mean WBC count during hospitalisation,Continuous,1000 cells/uL / Missing,1-84 / .
NHANES,LBXMONOA,,Monocyte count at admission,Continuous,1000 cells/uL / Missing,
NHANES,LBXMONOHn,,Monocyte count during hospitalisation,Continuous,1000 cells/uL / Missing,
NHANES,LBXEONOA,,Eosinophil count at admission,Continuous,1000 cells/uL / Missing,
NHANES,LBXEONOHn,,Eosinophil count during admission,Continuous,1000 cells/uL / Missing,
NHANES,LBXBANOA,,Basophil count at admission,Continuous,1000 cells/uL / Missing,
NHANES,LBXBANOHn,,Basophil count during admission,Continuous,1000 cells/uL / Missing,
NHANES,LBXLYMNOA,,Lymphocyte count at admission,Continuous,1000 cells/uL / Missing,0-72 / .
NHANES,LBXLYMNOHn,,Lymphocyte count during hospitalisation,Continuous,1000 cells/uL / Missing,0-72 / .
NHANES,LBXLYMNOM,,Mean lymphocyte count during hospitalisation,Continuous,1000 cells/uL / Missing,0-72 / .
NHANES,LBXNENOA,daily_neutro_lborres,Neutrophil count at admission,Continuous,1000 cells/uL / Missing,0-21 / .
NHANES,LBXNENOHn,,Neutrophil count during hospitalisation,Continuous,1000 cells/uL / Missing,0-21 / .
NHANES,LBXNENOM,,Mean neutrophil count during hospitalisation,Continuous,1000 cells/uL / Missing,0-21 / .
NHANES,LBXHCTA,daily_haematocrit_lborres,Haematocrit at admission,Continuous,% / Missing,22-57 / .
NHANES,LBXHCTHn,,Haematocrit during hospitalisation,Continuous,% / Missing,22-57 / .
NHANES,LBXHCTM,,Mean haematocrit during hospitalisation,Continuous,% / Missing,22-57 / .
NHANES,LBXPLTSIA,daily_plt_lborres,Platelets at admission,Continuous,1000 cells/uL / Missing,28-1000 / .
NHANES,LBXPLTSIHn,,Platelets during hospitalisation,Continuous,1000 cells/uL / Missing,28-1000 / .
NHANES,LBXPLTSIM,,Mean platetelets during hospitalisation,Continuous,1000 cells/uL / Missing,28-1000 / .
NHANES,LBXGHA,,HbA1c at admission,Continuous,nmol/mol; % / Missing,2-16 / .
NHANES,LBXGHHn,,HbA1c during hospitalisation,Continuous,nmol/mol; % / Missing,2-16 / .
NHANES,LBXGHM,,Mean HbA1c during hospitalisation,Continuous,nmol/mol; % / Missing,2-16 / .
SELF,LBXAPTTA,,Partial Thromboplastin Time (APTT) at admission,Continuous,s / Missing,20-120 / .
SELF,LBXAPTTHn,,Partial Thromboplastin Time (APTT) during hospitalisation,Continuous,s / Missing,20-120 / .
SELF,LBXAPTTM,,Mean partial Thromboplastin Time (APTT) during hospitalisation,Continuous,s / Missing,20-120 / .
SELF,LBXAPTRA,,Activated Partial Thromboplastin Time Ratio (APTR) at admission,Continuous,Ratio / Missing,"0,5-3 / ."
SELF,LBXAPTRHn,,Activated Partial Thromboplastin Time Ratio (APTR) during hospitalisation,Continuous,Ratio / Missing,"0,5-3 / ."
SELF,LBXAPTRM,,Mean activated Partial Thromboplastin Time Ratio (APTR) during hospitalisation,Continuous,Ratio / Missing,"0,5-3 / ."
SELF,LBXPRA,,Prothrombin time (PT),Continuous,s / Missing,1-100 / .
SELF,LBXPRHn,,Prothrombin time (PT),Continuous,s / Missing,1-100 / .
SELF,LBXPRM,,Mean Prothrombin time (PT),Continuous,s / Missing,1-100 / .
SELF,LBXINRA,daily_inr_lborres,International Normalised Ratio (INR) at admission,Continuous,Ratio / Missing,0-10 / .
SELF,LBXINRHn,,International Normalised Ratio (INR) at admission,Continuous,Ratio / Missing,0-10 / .
SELF,LBXINRM,,Mean International Normalised Ratio (INR) at admission,Continuous,Ratio / Missing,0-10 / .
NHANES,LBXSATSIA,daily_alt_lborres,Alanine Aminotransferase Test (ALT/SGPT) at admission,Continuous,U/L / Missing,4-890 / .
NHANES,LBXSATSIHn,,Alanine Aminotransferase Test (ALT/SGPT) during hospitalisation,Continuous,U/L / Missing,4-890 / .
NHANES,LBXSATSIM,,Mean Alanine Aminotransferase Test (ALT/SGPT) during hospitalisation,Continuous,U/L / Missing,4-890 / .
NHANES,LBXSTBA,daily_bil_lborres,Total bilirubin at admission,Continuous,mg/dL / Missing,"0,1-4 / ."
NHANES,LBXSTBHn,,Total bilirubin during hospitalisation,Continuous,mg/dL / Missing,"0,1-4 / ."
NHANES,LBXSTBM,,Mean total bilirubin during hospitalisation,Continuous,mg/dL / Missing,"0,1-4 / ."
SELF,LBXSCBA,,Conjugated bilirubin at admission,Continuous,mg/dL / Missing,0-1 / .
SELF,LBXSCBHn,,Conjugated bilirubin during hospitalisation,Continuous,mg/dL / Missing,0-1 / .
SELF,LBXSCBM,,Mean conjugated bilirubin during hospitalisation,Continuous,mg/dL / Missing,0-1 / .
SELF,LBXSUBA,,Unconjugated bilirubin at admission,Continuous,mg/dL / Missing,0-3 / .
SELF,LBXSUBHn,,Unconjugated bilirubin during hospitalisation,Continuous,mg/dL / Missing,0-3 / .
SELF,LBXSUBM,,Mean unconjugated bilirubin during hospitalisation,Continuous,mg/dL / Missing,0-3 / .
NHANES,LBXSASSIA,daily_ast_lborres,Aspartate Aminotransferase (AST/SGOT) at admission,Continuous,U/L / Missing,8-1034 / .
NHANES,LBXSASSIHn,,Aspartate Aminotransferase (AST/SGOT) during hospitalisation,Continuous,U/L / Missing,8-1034 / .
NHANES,LBXSASSIM,,Mean Aspartate Aminotransferase (AST/SGOT) during hospitalisation,Continuous,U/L / Missing,8-1034 / .
NHANES,LBXSGLA,daily_glucose_lborres,Glucose at admission,Continuous,mg/dL / Missing,33-559 / .
NHANES,LBXSGLHn,,Glucose during hospitalisation,Continuous,mg/dL / Missing,33-559 / .
NHANES,LBXSGLM,,Mean glucose during hospitalisation,Continuous,mg/dL / Missing,33-559 / .
NHANES,LBXSBUA,daily_bun_lborres,Urea at admission,Continuous,mg/dL / Missing,2-72 / .
NHANES,LBXSBUHn,,Urea during hospitalisation,Continuous,mg/dL / Missing,2-72 / .
NHANES,LBXSBUM,,Mean urea during hospitalisation,Continuous,mg/dL / Missing,2-72 / .
SELF,LBXSBLA,,Lactate at admission,Continuous,mmol/L / Missing,0-3 / .
SELF,LBXSBLHn,,Lactate during hospitalisation,Continuous,mmol/L / Missing,0-3 / .
SELF,LBXSBLM,,Mean lactate during hospitalisation,Continuous,mmol/L / Missing,0-3 / .
NHANES,LBXSCRA,daily_creat_lborres,Creatinine at admission,Continuous,mg/dL / Missing,"0,3-8,5 / ."
NHANES,LBXSCRHn,,Creatinine during hospitalisation,Continuous,mg/dL / Missing,"0,3-8,5 / ."
NHANES,LBXSCRM,,Mean creatinine during hospitalisation,Continuous,mg/dL / Missing,"0,3-8,5 / ."
NHANES,LBXPSCKA,,Creatinine phosphokinase (CPK) at admission,Continuous,IU/L / Missing,15-3892 / .
NHANES,LBXPSCKHn,,Creatinine phosphokinase (CPK) during hospitalisation,Continuous,IU/L / Missing,15-3892 / .
NHANES,LBXPSCKM,,Mean creatinine phosphokinase (CPK) during hospitalisation,Continuous,IU/L / Missing,15-3892 / .
NHANES,LBXSNASIA,daily_sodium_lborres,Sodium at admission,Continuous,mmol/L / Missing,114-160 / .
NHANES,LBXSNASIHn,,Sodium during hospitalisation,Continuous,mmol/L / Missing,114-160 / .
NHANES,LBXSNASIM,,Mean sodium during hospitalisation,Continuous,mmol/L / Missing,114-160 / .
NHANES,LBXSCLSIA,,Chlorine at admission,Continuous,mmol/L / Missing,82-120 / .
NHANES,LBXSCLSIHn,,Chlorine during hospitalisation,Continuous,mmol/L / Missing,82-120 / .
NHANES,LBXSCLSIM,,Mean chlorine during hospitalisation,Continuous,mmol/L / Missing,82-120 / .
NHANES,LBXSKSIA,daily_potassium_lborres,Potassium at admission,Continuous,mmol/L / Missing,"2,5-6 / ."
NHANES,LBXSKSIHn,,Potassium during hospitalisation,Continuous,mmol/L / Missing,"2,5-6 / ."
NHANES,LBXSKSIM,,Mean potassium during hospitalisation,Continuous,mmol/L / Missing,"2,5-6 / ."
SELF,LBXSPCA,daily_procal_lborres,Procalcitonin at admission,Continuous,ng/ml / Missing,0-1 / .
SELF,LBXSPCHn,,Procalcitonin during hospitalisation,Continuous,ng/ml / Missing,0-1 / .
SELF,LBXSPCM,,Mean procalcitonin during hospitalisation,Continuous,ng/ml / Missing,0-1 / .
NHANES,LBXCRPA,daily_crp_lborres,C-Reactive Protein (CRP) at admission,Continuous,mg/dL / Missing,"0,01-20 / ."
NHANES,LBXCRPHn,,C-Reactive Protein (CRP) during hospitalisation,Continuous,mg/dL / Missing,"0,01-20 / ."
NHANES,LBXCRPM,,Mean C-Reactive Protein (CRP) during hospitalisation,Continuous,mg/dL / Missing,"0,01-20 / ."
NHANES,LBXSLDSIA,,Lactate dehydrogenase (LDH) at admission,Continuous,U/L / Missing,50-661 / .
NHANES,LBXSLDSIHn,,Lactate dehydrogenase (LDH) during hospitalisation,Continuous,U/L / Missing,50-661 / .
NHANES,LBXSLDSIM,,Mean lactate dehydrogenase (LDH) during hospitalisation,Continuous,U/L / Missing,50-661 / .
NHANES,LBXSCKA,,Creatinine Kinase / Creatinine phosphokinase at admission,Continuous,IU/L / Missing,6-3966 / .
NHANES,LBXSCKHn,,Creatinine Kinase / Creatinine phosphokinase during hospitalisation,Continuous,IU/L / Missing,6-3966 / .
NHANES,LBXSCKM,,Mean Creatinine Kinase / Creatinine phosphokinase during hospitalisation,Continuous,IU/L / Missing,6-3966 / .
SELF,LBXCTRA,,Troponin at admission,Continuous,ng/ml / Missing,0-100 / .
SELF,LBXCTRHn,,Troponin during hospitalisation,Continuous,ng/ml / Missing,0-100 / .
SELF,LBXCTRM,,Mean troponin during hospitalisation,Continuous,ng/ml / Missing,0-100 / .
SELF,LBXCDDA,,D-dimer at admission,Continuous,ng/ml / Missing,0-1000 / .
SELF,LBXCDDHn,,D-dimer during hospitalisation,Continuous,ng/ml / Missing,0-1000 / .
SELF,LBXCDDM,,Mean D-dimer during hospitalisation,Continuous,ng/ml / Missing,0-1000 / .
NHANES,LBXFERSIA,,Ferritin at admission,Continuous,�g/L / Missing,2-420 / .
NHANES,LBXFERSIHn,,Ferritin during hospitalisation,Continuous,�g/L / Missing,2-420 / .
NHANES,LBXFERSIM,,Mean ferritin during hospitalisation,Continuous,�g/L / Missing,2-420 / .
SELF,LBXIL6A,,IL-6 at admission,Continuous,pg/ml / Missing,0-10000 / .
SELF,LBXIL6Hn,,IL-6 during hospitalisation,Continuous,pg/ml / Missing,0-10000 / .
SELF,LBXIL6M,,Mean IL-6 during hospitalisation,Continuous,pg/ml / Missing,0-10000 / .
NHANES,LBDFBSIA,,Fibrinogen at admission,Continuous,g/L / Missing,1-10 / .
NHANES,LBDFBSIHn,,Fibrinogen during hospitalisation,Continuous,g/L / Missing,1-10 / .
NHANES,LBDFBSIM,,Mean fibrinogen during hospitalisation,Continuous,g/L / Missing,1-10 / .
NHANES,LBDSALSIA,,Albumin at admission,Continuous,g/L / Missing,12-55 / .
NHANES,LBDSALSIHn,,Albumin during hospitalisation,Continuous,g/L / Missing,12-55 / .
NHANES,LBDSALSIM,,Mean albumin during hospitalisation,Continuous,g/L / Missing,12-55 / .
NHANES,LBXSAPSIA,,Alkaline phosphatase at admission,Continuous,U/L / Missing,14-679 / .
NHANES,LBXSAPSIHn,,Alkaline phosphatase during hospitalisation,Continuous,U/L / Missing,14-679 / .
NHANES,LBXSAPSIM,,Mean alkaline phosphatase during hospitalisation,Continuous,U/L / Missing,14-679 / .
NHANES,LBXSGTSIA,,Gamma Glutamyl Transferase (GGT) at admission,Continuous,U/L / Missing,4-892 / .
NHANES,LBXSGTSIHn,,Gamma Glutamyl Transferase (GGT) during hospitalisation,Continuous,U/L / Missing,4-892 / .
NHANES,LBXSGTSIM,,Mean Gamma Glutamyl Transferase (GGT) during hospitalisation,Continuous,U/L / Missing,4-892 / .
SELF,LBXCFDA,,Calcifediol / 25-OH-vitamin D at admission,Continuous,ng/ml / Missing,0-200 / .
SELF,LBXCFDHn,,Calcifediol / 25-OH-vitamin D dutring hospitalisation,Continuous,ng/ml / Missing,0-200 / .
SELF,LBXCFDM,,Mean calcifediol / 25-OH-vitamin D dutring hospitalisation,Continuous,ng/ml / Missing,0-200 / .
SELF,LBXFIOA,,FiO2 at admission,Continuous,Fraction / Missing,0-1 / .
SELF,LBXFIOHn,,FiO2 during hospitalisation,Continuous,Fraction / Missing,0-1 / .
SELF,LBXFIOM,,Mean FiO2 during hospitalisation,Continuous,Fraction / Missing,0-1 / .
SELF,LBXPOA,,PaO2 at admission,Continuous,mmHg / Missing,0-250 / .
SELF,LBXPOHn,,PaO2 during hospitalisation,Continuous,mmHg / Missing,0-250 / .
SELF,LBXPOM,,Mean PaO2 during hospitalisation,Continuous,mmHg / Missing,0-250 / .
SELF,LBXPCOA,,PaCO2 at admission,Continuous,mmHg / Missing,0-150 / .
SELF,LBXPCOHn,,PaCO2 during hospitalisation,Continuous,mmHg / Missing,0-150 / .
SELF,LBXPCOM,,Mean PaCO2 during hospitalisation,Continuous,mmHg / Missing,0-150 / .
NHANES,LBXSC3SIA,,HCO3 at admission,Continuous,mmol/l / Missing,10-40 / .
NHANES,LBXSC3SIHn,,HCO3 during hospitalisation,Continuous,mmol/l / Missing,10-40 / .
NHANES,LBXSC3SIM,,Mean HCO3 during hospitalisation,Continuous,mmol/l / Missing,10-40 / .
SELF,LBXPHA,,pH at admission,Continuous,pH / Missing,7-8 / .
SELF,LBXPHHn,,pH during hospitalisation,Continuous,pH / Missing,7-8 / .
SELF,LBXPHM,,Mean pH during hospitalisation,Continuous,pH / Missing,7-8 / .
SELF,LBXBEA,,Base excess at admission,Continuous,mEq/l / Missing,-20 - +20 / .
SELF,LBXBEHn,,Base excess during hospitalisation,Continuous,mEq/l / Missing,-20 - +20 / .
SELF,LBXBEM,,Mean Base excess during hospitalisation,Continuous,mEq/l / Missing,-20 - +20 / .
SELF,LBXA4A,,APACHE IV at admission,Continuous,Score / Missing,0-286 / .
SELF,LBXA4Hn,,APACHE IV during hospitalisation,Continuous,Score / Missing,0-286 / .
SELF,LBXA4M,,Mean APACHE IV during hospitalisation,Continuous,Score / Missing,0-286 / .
NHANES,LBXTCA,,Cholesterol at admission,Continuous,mg/dL / Missing,74-453 / .
NHANES,LBXTCHn,,Cholesterol during hospitalisation,Continuous,mg/dL / Missing,74-453 / .
NHANES,LBXTCM,,Mean cholesterol during hospitalisation,Continuous,mg/dL / Missing,74-453 / .
NHANES,LBXTRA,,Triglyceride at admission,Continuous,mg/dL / Missing,16-3281 / .
NHANES,LBXTRHn,,Triglyceride during hospitalisation,Continuous,mg/dL / Missing,16-3281 / .
NHANES,LBXTRM,,Mean triglyceride during hospitalisation,Continuous,mg/dL / Missing,16-3281 / .
SELF,LBXUFRA,,Urine flow rate at admission,Continuous,mL/s / Missing,0-30 / .
SELF,LBXUFRHn,,Urine flow rate during hospitalisation,Continuous,mL/s / Missing,0-30 / .
SELF,COXRD,ards_ceterm,Acute Respiratory Distress Syndrom,Binary,No/Yes / Missing,0 / 1 / .
SELF,COXAR,arrhythmia_ceterm,Arrhythmia,Binary,No/Yes / Missing,0 / 1 / .
SELF,COXPM,"viralpneu_ceterm, bactpneu_ceterm",Pneumonia,Binary,No/Yes / Missing,0 / 1 / .
SELF,COXMOD,,Multiple Organ Dysfunction,Binary,No/Yes / Missing,0 / 1 / .
SELF,COXPT,pneumothorax_ceterm,Pneumothorax,Binary,No/Yes / Missing,0 / 1 / .
SELF,COXEC,endocarditis_aeterm,Endocarditis,Binary,No/Yes / Missing,0 / 1 / .
SELF,COXSH,,Shock,Binary,No/Yes / Missing,0 / 1 / .
SELF,COXIO,,Other infections,Binary,No/Yes / Missing,0 / 1 / .
SELF,COXPE,,Pulmonary embolism,Binary,No/Yes / Missing,0 / 1 / .
SELF,COXST,stroke_ceterm,Stroke (AVC),Binary,No/Yes / Missing,0 / 1 / .
SELF,COXDIC,coagulo_ceterm,Disseminated intravascular coagulation,Binary,No/Yes / Missing,0 / 1 / .
SELF,COXRIO,respiratory_infect_yn_two/other_mbyn,Other respiratory infections,Binary,No/Yes / Missing,0 / 1 / .
SELF,COXKF,renalinjury_ceterm,Kidney failure,Binary,No/Yes / Missing,0 / 1 / .
SELF,COXHF,heartfailure_ceterm,Heart failure,Binary,No/Yes / Missing,0 / 1 / .
SELF,COXBC,,Blood complications,Binary,No/Yes / Missing,0 / 1 / .
SELF,COXRF,,Respiratory failure,Binary,No/Yes / Missing,0 / 1 / .
SELF,COXLF,liverdysfunction_ceterm,Hepatic failure,Binary,No/Yes / Missing,0 / 1 / .
SELF,COXADE,,Adverse drug effect,Binary,No/Yes / Missing,0 / 1 / .
SELF,COXSTN,,Stenosis,Binary,No/Yes / Missing,0 / 1 / .
SELF,COXNOC,,Nosocomial condition,Binary,No/Yes / Missing,0 / 1 / .
SELF,DATIM,,Date tests performed,Calendar date,Date / Missing, yyyy-mm-dd / .
SELF,DATIMD,,Time between admission and assessment,Continuous,Days / Missing,0-180 / .
SELF,IMDIT,xray_prperf?,Imaging test performed ,Binary,No/Yes / Missing,0 / 1 / .
SELF,IMDXCT,,CT scan results,Categorical, 1. Normal / 2. Groundglass / 3. Crazy paving / 4. Bronchiectasis / 5. Reticulations / 6. Micronodules / 7. Consolidation / 8. Pleural effusion / 9. Other / Missing,1 / 2 / 3 /4 / 5/ 6 / 7/ 8 / 9 /.
SELF,IMDXCTCR,,CT CO-RADS,Categorical,1. CO-RADS1No / 2. CO-RADS2Low / 3. CO-RADS3Intermediate / 4. CO-RADS4High / 5. CO-RADS5Very high / 6. CO-RADS 6PCR+ / Missing,1 / 2 / 3 /4 / 5/ 6 / .
SELF,IMDXCTTE,,CT thromboembolism,Binary,No/Yes / Missing,0 / 1 / .
SELF,IMDXCTLD,,CT % lung damage,Continuous,% / Missing,0-100 / .
SELF,IMDXCTAB,,CT abnormal at follow-up,Binary,No/Yes / Missing,0 / 1 / .
SELF,IMDXXR,,X-ray result,Categorical,1. Normal 2. Intersitial Syndrome 3. Pleural Effusion 4. Alveolar Consolidation 5. Cardiomegaly 6. Other / Missing,1-6 / .
SELF,IMDXXRI,infiltrates_faorres,X-ray infiltrates,Binary,No/Yes / Missing,0 / 1 / .
SELF,IMDXPN,,Pneumonia on x-ray or CT scan,Binary,No/Yes / Missing,0 / 1 / .
SELF,IMDXEQ,,ECG QTc value,,,
SELF,DRXIDT,ISO_hdiet,How important is it to you to maintain a healthy diet in social isolation/quarantine? ,Categorical,0. No / 1. Yes / Missing,1-5 / .
SELF,DRXIFDT,ISO_FAMSUP_hdiet,How important is it for you that your family/partner(s) support you in maintaining a healthy diet in social isolation/quarantine? ,Categorical,Number,1-5 / .
SELF,DRXFPR,ISO_FAMSUP_hdiet2,How often do your family members/partner(s) in social isolation/quarantine [praise your attempt to follow a healthy diet? ,Categorical,0. No / 1. Yes / Missing,0 / 1 / 2 / 3 / .
SELF,DRXFGLT,ISO_FAMSUP_glt,How often do your family members/partner(s) in social isolation/quarantine [make you feel guilty when you don't eat healthy?] ,Categorical,Number,0 / 1 / 2 / 3 / .
SELF,DRXFVG,ISO_FAMSUP_veg,How often do your family members/partner(s) in social isolation/quarantine [encourage you to consume vegetables?] ,Categorical,0. Never / 1. 1 time per week / 2. 2-4 times per week / 3. 5-6 times per week / 4. 7+ times per week / missing,0 / 1 / 2 / 3 / .
SELF,DRXFFR,ISO_FAMSUP_fr,How often do your family members/partner(s) in social isolation/quarantine [encourage you to consume fruit?] ,Categorical,0. Never / 1. 1 time per week / 2. 2-4 times per week / 3. 5-6 times per week / 4. 7+ times per week / missing,0 / 1 / 2 / 3 / .
SELF,DRXFFN,ISO_FAMSUP_nut,How often do your family members/partner(s) in social isolation/quarantine [talk to you about food and nutrition?] ,Categorical,0. Never / 1. 1 time per week / 2. 2-4 times per week / 3. 5-6 times per week / 4. 7+ times per week / missing,0 / 1 / 2 / 3 / .
SELF,DRXFHF,ISO_FAMSUP_homehf,How often do your family members/partner(s) in social isolation/quarantine [bring healthy food home?] ,Categorical,0. Never / 1. 1 time per week / 2. 2-4 times per week / 3. 5-6 times per week / 4. 7+ times per week / missing,0 / 1 / 2 / 3 / .
SELF,DRXFHFR,ISO_FAMSUP_homefr,How often do your family members/partner(s) in social isolation/quarantine [bring fruit home?] ,Categorical,0. Never / 1. 1 time per week / 2. 2-4 times per week / 3. 5-6 times per week / 4. 7+ times per week / missing,0 / 1 / 2 / 3 / .
SELF,DRXFHVG,ISO_FAMSUP_homeveg,How often do your family members/partner(s) in social isolation/quarantine [bring vegetables home?] ,,0. Never / 1. 1 time per week / 2. 2-4 times per week / 3. 5-6 times per week / 4. 7+ times per week / missing,0 / 1 / 2 / 3 / .
SELF,DRXWK,ISO_regime,What regime do you have in a period of social isolation/quarantine? ,,0. Never / 1. 1 time per week / 2. 2-4 times per week / 3. 5-6 times per week / 4. 7+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXHCG,,Did you look after someone isolating from covid?,,0. Never / 1. 1 time per week / 2. 2-4 times per week / 3. 5-6 times per week / 4. 7+ times per week / missing,0 / 1 / .
SELF,DRXQUI,ISO_alone,Are you in social isolation/quarantine alone? ,Binary,0. Never / 1. 1 time per week / 2. 2-4 times per week / 3. 5-6 times per week / 4. 7+ times per week / missing,0 / 1 / .
SELF,DRXQUA,ISO_countadult,"Not counting yourself, how many adults (aged 18 and over) are with you in social isolation/quarantine? ",Continuous,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0-100 / .
SELF,DRXFSP,DMXspouse,Do you live with a spouse? ,Binary,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / .
SELF,DRXQUC,ISO_countchild,How many children under the age of 18 are with you in social isolation/quarantine? ,Continuous,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0-100 / .
SELF,DRXMS,ISO_DIET_milk_skim,Milk and dairy products - in a period of social isolation/quarantine [Skim milk (250ml / lunch cup)] ,Continuous,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXMSS,ISO_DIET_milk_semi,Milk and dairy products - in a period of social isolation/quarantine [Semi-skimmed milk (250ml / lunch cup)] ,Continuous,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXMW,ISO_DIET_milk_whole,Milk and dairy products - in a period of social isolation/quarantine [Whole milk (250ml / lunch cup)] ,Continuous,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXMY,ISO_DIET_milk_yog,Milk and dairy products - in a period of social isolation/quarantine [Yogurt (200 grams)] ,Continuous,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXMIC,ISO_DIET_milk_ice,Milk and dairy products - in a period of social isolation/quarantine [Milk Ice Cream (125 grams)] ,Continuous,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXMC,ISO_DIET_milk_cheese,Milk and dairy products - in a period of social isolation/quarantine [Cheese (40gr or 2 slices)] ,Continuous,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXMFC,ISO_DIET_milk_frche,Milk and dairy products - in a period of social isolation/quarantine [Fresh cheese (50 grams)] ,Continuous,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXMCC,ISO_DIET_milk_crcheese,Milk and dairy products - in a period of social isolation/quarantine [cream cheese (100 grams)] ,Continuous,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXMB,ISO_DIET_milk_butter,Milk and dairy products - in a period of social isolation/quarantine [Butter excluding that used in food production (15 grams/1 dessert spoon)] ,Continuous,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXFRA,ISO_DIET_fr_apples,Fruit - in a period of social isolation/quarantine [Apples and/or pears] ,Continuous,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXFRO,ISO_DIET_fr_orange,Fruit - in a period of social isolation/quarantine [Oranges] ,Continuous,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXFRJ,ISO_DIET_fr_juice,Fruit - in a period of social isolation/quarantine [Natural fruit juice (small glass)] ,Continuous,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXFRB,ISO_DIET_fr_banana,Fruit - in a period of social isolation/quarantine [Bananas] ,Continuous,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXFROF,ISO_DIET_fr_other,Fruit - in a period of social isolation/quarantine [Others fresh fruit] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXFRCF,ISO_DIET_fr_canned,Fruit - in a period of social isolation/quarantine [Canned fruit] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXVR,ISO_DIET_veg_raw,Vegetables - in a period of social isolation/quarantine [Raw vegetables (180 grams)] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXVC,ISO_DIET_veg_cooked,Vegetables - in a period of social isolation/quarantine [Cooked vegetables (140 grams)] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXVS,ISO_DIET_veg_soup,Vegetables - in a period of social isolation/quarantine [Vegetable soup (250 ml)] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXVD,ISO_DIET_leg_dried,"Vegetables - in period of social isolation/quarantine [Dried cooked vegetables eg beans, beans, lentils (80 grams)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXVF,ISO_DIET_leg_fresh,"Legumes - in period of social isolation/quarantine [Fresh cooked legumes eg peas, broad beans (80 grams)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXPE,ISO_DIET_mfe_egg,"Meat, fish and eggs - in a period of social isolation/quarantine [1 egg (medium size)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXPCS,ISO_DIET_mfe_chickenskinn,"Meat, fish and eggs - in a period of social isolation/quarantine [Chicken or turkey with skin (100 grams)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXPC,ISO_DIET_mfe_chicken,"Meat, fish and eggs - in a period of social isolation/quarantine [Skinless chicken or turkey (100 grams)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXPB,ISO_DIET_mfe_bacon,"Meat, fish and eggs - in a period of social isolation/quarantine [Bacon (2 slices)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXPTM,ISO_DIET_mfe_pmeat,"Meat, fish and eggs - in a period of social isolation/quarantine [Transformed meat (sausages, salami, etc.)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXPL,ISO_DIET_mfe_liver,"Meat, fish and eggs - in a period of social isolation/quarantine [Liver (85 grams)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXPBU,ISO_DIET_mfe_burger,"Meat, fish and eggs - in a period of social isolation/quarantine [Burger (1 unit)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXPRM,ISO_DIET_mfe_rmeat,"Meat, fish and eggs - in a period of social isolation/quarantine [Beef, pork or lamb (main dish)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXPF,ISO_DIET_mfe_fish,"Meat, fish and eggs - in a period of social isolation/quarantine [Fish (110 grams)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXSCH,ISO_DIET_swe_choco,"Sweets, cakes and snacks - in a period of social isolation/quarantine [Chocolate (30grams)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXSNCH,ISO_DIET_swe_sweets,"Sweets, cakes and snacks - in a period of social isolation/quarantine [Sweets without chocolate (30 grams)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXSSP,ISO_DIET_swe_pie,"Sweets, cakes and snacks - in a period of social isolation/quarantine [Sweet pie (1 slice)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXSCA,ISO_DIET_swe_cake,"Sweets, cakes and snacks - in a period of social isolation/quarantine [Cake (1 slice)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXSCO,ISO_DIET_swe_cookie,"Sweets, cakes and snacks - in a period of social isolation/quarantine [Cookies] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXSSC,ISO_DIET_swe_cereal,"Sweets, cakes and snacks - in a period of social isolation/quarantine [Sweet cereals] ",,Frequency,0 / 1 / 2 / 3 / 4 / .
SELF,DRXSCP,ISO_DIET_swe_chips,"Sweets, cakes and snacks - in a period of social isolation/quarantine [chips] ",,Frequency,0 / 1 / 2 / 3 / 4 / .
SELF,DRXSO,ISO_DIET_swe_others,"Sweets, cakes and snacks - in a period of social isolation/quarantine [Others] ",,Frequency,0 / 1 / 2 / 3 / 4 / .
SELF,DRXDC,ISO_DIET_drink_coffee,Drinks - in a period of social isolation/quarantine [Coffee (1 cup)] ,,0. Don't know or don't cook / 1. Olive oil / 2. Vegetable oil / 3. Butter / 4. Margarine / 5. Lard / Missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXDT,ISO_DIET_drink_tea,Drinks - in a period of social isolation/quarantine [Tea (1 mug)] ,,0. Don't know or don't cook / 1. Olive oil / 2. Vegetable oil / 3. Butter / 4. Margarine / 5. Lard / Missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXDB,ISO_DIET_drink_beer,Drinks - in a period of social isolation/quarantine [Beer (20cl)] ,,0. 0-1 time per week / 1. 2-3 times per week / 2. 4-6 times per week / 3. daily / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXDWI,ISO_DIET_drink_wine,Drinks - in a period of social isolation/quarantine [Wine (10cl)] ,,0. 0-1 time per week / 1. 2-3 times per week / 2. 4-6 times per week / 3. daily / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXDL,ISO_DIET_drink_liquor,"Drinks - in a period of social isolation/quarantine [Liquor, whiskey, gin, etc. (5cl)] ",,0. 0-1 time per week / 1. 2-3 times per week / 2. 4-6 times per week / 3. daily / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXDDS,ISO_DIET_drink_dietsoft,Drinks - in a period of social isolation/quarantine [Calorie-reduced carbonated drinks] ,,0. 0-1 time per week / 1. 2-3 times per week / 2. 4-6 times per week / 3. daily / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXDSS,ISO_DIET_drink_soft,Drinks - in a period of social isolation/quarantine [Sparkling drinks with sugar] ,,0. 0-1 time per week / 1. 2-3 times per week / 2. 4-6 times per week / 3. daily / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXDF,ISO_DIET_drink_juice,Drinks - in a period of social isolation/quarantine [Fruit juices (no fresh)] ,,0. 0-1 time per week / 1. 2-3 times per week / 2. 4-6 times per week / 3. daily / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXDWA,ISO_DIET_drink_water,Drinks - in a period of social isolation/quarantine [Water] ,,0. 0-1 time per week / 1. 2-3 times per week / 2. 4-6 times per week / 3. daily / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXDTS,ISO_DIET_drink_sugar,How many teaspoons of sugar do you add to your drinks daily? (in a period of social isolation/quarantine) ,,0. Little or none / 1. Shared equally (50%) / 2. Most or always / missing,
SELF,DRXVT,ISO_DIET_vit,Do you take any vitamin supplements? (in a period of social isolation/quarantine) ,,0. Little or none / 1. Shared equally (50%) / 2. Most or always / missing,
SELF,DRXRMF,ISO_DIET_rmeatfat,"When you eat red meat (beef, pork, lamb, etc.) does it remove visible fat on the plate? (in a period of social isolation/quarantine) ",,0. Little or none / 1. Shared equally (50%) / 2. Most or always / missing,
SELF,DRXFASF,ISO_DIET_fat_stirfry,What kind of fat do you use to stir-fry food at home? (in a period of social isolation/quarantine) ,,0. 0-1 days per week / 1. 2-3 days per week / 2. 4-5 days per week / 3. 6-7 days per week / missing,0 / 1 / 2 / 3 / 4 / 5 / .
SELF,DRXFAC,ISO_DIET_fat_cook,What kind of fat do you use to cook food at home? (in a period of social isolation/quarantine) ,,0. 0-1 days per week / 1. 2-3 days per week / 2. 4-5 days per week / 3. 6-7 days per week / missing,0 / 1 / 2 / 3 / 4 / 5 / .
SELF,DRXFF,ISO_DIET_fried,How often do you eat fried foods? (in a period of social isolation/quarantine) ,,0. 0-1 days per week / 1. 2-3 days per week / 2. 4-5 days per week / 3. 6-7 days per week / missing,0 / 1 / 2 / 3 / .
SELF,DRXCSF,ISO_FOODPREP_stuf,Methods of confection used (in a period of social isolation/quarantine) [Stuffed] ,,0.Never / 1.Rarely / 2. Occasionally / 3.Often,0 / 1 / 2 / 3 / .
SELF,DRXCSW,ISO_FOODPREP_stew,Methods of confection used (in a period of social isolation/quarantine) [Stew] ,,0.Never / 1.Rarely / 2. Occasionally / 3.Often,0 / 1 / 2 / 3 / .
SELF,DRXCR,ISO_FOODPREP_roast,Methods of confection used (in a period of social isolation/quarantine) [Roasting] ,,0.Never / 1.Rarely / 2. Occasionally / 3.Often,0 / 1 / 2 / 3 / .
SELF,DRXCMC,ISO_FOODPREP_cook,Cooking methods used (in a period of social isolation/quarantine) [Cooked] ,,0.Never / 1.Rarely / 2. Occasionally / 3.Often,0 / 1 / 2 / 3 / .
SELF,DRXMG,ISO_FOODPREP_grill,Preparation methods used (in a period of social isolation/quarantine) [Grilled] ,,0.Never / 1.Rarely / 2. Occasionally / 3.Often,0 / 1 / 2 / 3 / .
SELF,DRXMSF,ISO_FOODPREP_stirfry,Methods of confection used (in a period of social isolation/quarantine) [Stir-fry] ,,0.Never / 1.Rarely / 2. Occasionally / 3.Often,0 / 1 / 2 / 3 / .
SELF,DRXRSM,ISO_RESP_supermarket,What is your responsibility for (in a period of social isolation/quarantine) [Going to the supermarket to buy food?] ,,0.Never / 1.Rarely / 2. Occasionally / 3.Often,0 / 1 / 2 / .
SELF,DRXRMPL,ISO_RESP_mplan,What is your responsibility for (in a period of social isolation/quarantine) [Planning meals] ,,0.Never / 1.Rarely / 2. Occasionally / 3.Often,0 / 1 / 2 / .
SELF,DRXRMPR,ISO_RESP_mprep,What is your responsibility for (in a period of social isolation/quarantine) [Preparing meals] ,,0. Never / 1. 1 time per week / 2. 2-4 times per week / 3. 5-6 times per week / 4. 7+ times per week / missing,0 / 1 / 2 / .
SELF,DRXBSB,BEF_SHARE_breakfast,"Before the quarantine period, in a typical week, how often would you share the meals below with people who are with you in social isolation/quarantine? [Breakfast] ",,0. Never / 1. 1 time per week / 2. 2-4 times per week / 3. 5-6 times per week / 4. 7+ times per week / missing,0 / 1 / 2 / 3 / .
SELF,DRXBSL,BEF_SHARE_lunch,"Before the quarantine period, in a typical week, how often would you share the meals below with people who are with you in social isolation/quarantine? [Lunch] ",,0. Never / 1. 1 time per week / 2. 2-4 times per week / 3. 5-6 times per week / 4. 7+ times per week / missing,0 / 1 / 2 / 3 / .
SELF,DRXBSD,BEF_SHARE_dinner,"Before the quarantine period, in a typical week, how often would you share the meals below with people who are with you in social isolation/quarantine? [Dinner] ",,0. Never / 1. 1 time per week / 2. 2-4 times per week / 3. 5-6 times per week / 4. 7+ times per week / missing,0 / 1 / 2 / 3 / .
SELF,DRXBFPR,BEF_FAMSUP_hdiet2,"Prior to the period of social isolation/quarantine, how often did your family members/partners [praise your attempt to follow a healthy diet?] ",,0. Never / 1. 1 time per week / 2. 2-4 times per week / 3. 5-6 times per week / 4. 7+ times per week / missing,0 / 1 / 2 / 3 / .
SELF,DRXBFGLT,BEF_FAMSUP_glt,"Prior to the period of social isolation/quarantine, how often did your relatives/partners [make you feel guilty when you ate healthy] ",,0. Never / 1. 1 time per week / 2. 2-4 times per week / 3. 5-6 times per week / 4. 7+ times per week / missing,0 / 1 / 2 / 3 / .
SELF,DRXBFVG,BEF_FAMSUP_veg,"Before the period of social isolation/quarantine, how often did your family members/partners [encourage you to consume vegetables?] ",,0. Never / 1. 1 time per week / 2. 2-4 times per week / 3. 5-6 times per week / 4. 7+ times per week / missing,0 / 1 / 2 / 3 / .
SELF,DRXBFFR,BEF_FAMSUP_fr,"Before the period of social isolation/quarantine, how often did your family members/partners [encourage you to consume fruit?] ",,0. Never / 1. 1 time per week / 2. 2-4 times per week / 3. 5-6 times per week / 4. 7+ times per week / missing,0 / 1 / 2 / 3 / .
SELF,DRXBFFN,BEF_FAMSUP_nut,"Before the period of social isolation/quarantine, how often did your family members/partners [talk to you about food and nutrition?] ",,0. Never / 1. 1 time per week / 2. 2-4 times per week / 3. 5-6 times per week / 4. 7+ times per week / missing,0 / 1 / 2 / 3 / .
SELF,DRXBFHF,BEF_FAMSUP_homehf,"Prior to the period of social isolation/quarantine, how often did your family members/partners [bring healthy food home?] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / .
SELF,DRXBFHFR,BEF_FAMSUP_homefr,"Before the period of social isolation/quarantine, how often did your family members/partners [bring fruit home?] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / .
SELF,DRXBFHVG,BEF_FAMSUP_homeveg,"Before the period of social isolation/quarantine, how often did your family members/partners [bring vegetables home?] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / .
SELF,DRXBMS,BEF_DIET_milk_skim,Milk and dairy products (before the period of social isolation/quarantine) [skimmed milk (250ml / lunch cup)] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBMSS,BEF_DIET_milk_semi,Milk and dairy products (before the period of social isolation/quarantine) [Semi-skimmed milk (250ml / lunch cup)] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBMW,BEF_DIET_milk_whole,Milk and dairy products (before the period of social isolation/quarantine) [Whole milk (250ml / lunch cup)] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBMY,BEF_DIET_milk_yog,Milk and dairy products (before the period of social isolation/quarantine) [Yogurt (200 grams)] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBMIC,BEF_DIET_milk_ice,Milk and dairy products (before the period of social isolation/quarantine) [Ice Cream (125 grams)] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBMC,BEF_DIET_milk_cheese,Milk and dairy products (before the period of social isolation/quarantine) [Cheese (40gr or 2 slices)] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBMFC,BEF_DIET_milk_frche,Milk and dairy products (before the period of social isolation/quarantine) [Fresh cheese (50 grams)] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBMCC,BEF_DIET_milk_crcheese,Milk and dairy products (before the period of social isolation/quarantine) [Cream cheese (100 grams)] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBMB,BEF_DIET_milk_butter,Milk and dairy products (before the period of social isolation/quarantine) [Butter excluding that used in food production (15 grams/1 dessert spoon)] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBFRA,BEF_DIET_fr_apples,Fruit (before the social isolation/quarantine period) [Apples and/or pears] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBFRO,BEF_DIET_fr_orange,Fruit (before the social isolation/quarantine period) [Oranges] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBFRJ,BEF_DIET_fr_juice,Fruit (before the social isolation/quarantine period) [Natural fruit juice (small glass)] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBFRB,BEF_DIET_fr_banana,Fruit (before the social isolation/quarantine period) [Bananas] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBFROF,BEF_DIET_fr_other,Fruit (before the social isolation/quarantine period) [Others fresh fruit] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBFRCF,BEF_DIET_fr_canned,Fruit (before the social isolation/quarantine period) [Canned fruit] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBVR,BEF_DIET_veg_raw,Vegetables (before the period of social isolation/quarantine) [Raw vegetables (180 grams)] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBVC,BEF_DIET_veg_cooked,Vegetables (before the period of social isolation/quarantine) [Cooked vegetables (140 grams)] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBVS,BEF_DIET_veg_soup,Vegetables (before the period of social isolation/quarantine) [Vegetable soup (250 ml)] ,,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBVD,BEF_DIET_leg_dried,"Legumes (before the period of social isolation/quarantine) [Dried cooked legumes eg beans, beans, lentils (80 grams)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBVF,BEF_DIET_leg_fresh,"Legumes (before the period of social isolation/quarantine) [Fresh cooked legumes eg peas, broad beans (80 grams)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBPE,BEF_DIET_mfe_egg,"Meat, fish and eggs (before the period of social isolation/quarantine) [1 egg (medium size)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBPCS,BEF_DIET_mfe_chickenskinn,"Meat, fish and eggs (before the period of social isolation/quarantine) [Chicken or turkey with skin (100 grams)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBPC,BEF_DIET_mfe_chicken,"Meat, fish and eggs (before the period of social isolation/quarantine) [Skinless chicken or turkey (100 grams)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBPB,BEF_DIET_mfe_bacon,"Meat, fish and eggs (before the period of social isolation/quarantine) [Bacon (2 slices)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBPTM,BEF_DIET_mfe_pmeat,"Meat, fish and eggs (before the period of social isolation/quarantine) [Processed meat (sausages, salami, etc.)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBPL,BEF_DIET_mfe_liver,"Meat, fish and eggs (before the period of social isolation/quarantine) [Liver (85 grams)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBPB,BEF_DIET_mfe_burger,"Meat, fish and eggs (before the period of social isolation/quarantine) [Burger (1 unit)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBPRM,BEF_DIET_mfe_rmeat,"Meat, fish and eggs (before the period of social isolation/quarantine) [Beef, pork or lamb (main dish)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBPF,BEF_DIET_mfe_fish,"Meat, fish and eggs (before the period of social isolation/quarantine) [Fish (110 grams)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBSCH,BEF_DIET_swe_choco,"Sweets, cakes and snacks (before the period of social isolation/quarantine) [Chocolate (30 grams)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBSNCH,BEF_DIET_swe_sweets,"Sweets, cakes and snacks (before the period of social isolation/quarantine) [Sweets without chocolate (30 grams)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBSSP,BEF_DIET_swe_pie,"Sweets, cakes and snacks (before the period of social isolation/quarantine) [Sweet tart (1 slice)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBSCA,BEF_DIET_swe_cake,"Sweets, cakes and snacks (before the period of social isolation/quarantine) [Cake (1 slice)] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBSCO,BEF_DIET_swe_cookie,"Sweets, cakes and snacks (before the period of social isolation/quarantine) [Cookies] ",,0. Never / 1. 1 time per week / 2. 2-3 times per week / 3. 4-5 times per week / 4. 6+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBSSC,BEF_DIET_swe_cereal,"Sweets, cakes and snacks (before the period of social isolation/quarantine) [Sweet cereals] ",,Frequency,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBSCP,BEF_DIET_swe_chips,"Sweets, cakes and snacks (before the period of social isolation/quarantine) [chips] ",,Frequency,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBSO,BEF_DIET_swe_others,"Sweets, cakes and snacks (before the period of social isolation/quarantine) [Others] ",,Frequency,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBDC,BEF_DIET_drink_coffee,Drinks (before the social isolation/quarantine period) [Coffee (1 cup)] ,,0. Don't know or don't cook / 1. Olive oil / 2. Vegetable oil / 3. Butter / 4. Margarine / 5. Lard / 6. Don't eat at home / Missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBDT,BEF_DIET_drink_tea,Drinks (before the social isolation/quarantine period) [Tea (1 mug)] ,,0. Don't know or don't cook / 1. Olive oil / 2. Vegetable oil / 3. Butter / 4. Margarine / 5. Lard / 6. Don't eat at home Missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBDB,BEF_DIET_drink_beer,Drinks (before the social isolation/quarantine period) [Beer (20cl)] ,,0. 0-1 time per week / 1. 2-3 times per week / 2. 4-6 times per week / 3. 7+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBDWI,BEF_DIET_drink_wine,Drinks (before the social isolation/quarantine period) [Wine (10cl)] ,,0. 0-1 time per week / 1. 2-3 times per week / 2. 4-6 times per week / 3. 7+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBDL,BEF_DIET_drink_liquor,"Drinks (before the social isolation/quarantine period) [Liquor, whiskey, gin, etc. (5cl)] ",,0. 0-1 time per week / 1. 2-3 times per week / 2. 4-6 times per week / 3. 7+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBDDS,BEF_DIET_drink_dietsoft,Drinks (before the social isolation/quarantine period) [Calorie-reduced carbonated drinks] ,,0. 0-1 time per week / 1. 2-3 times per week / 2. 4-6 times per week / 3. 7+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBDSS,BEF_DIET_drink_soft,Drinks (before the social isolation/quarantine period) [Sparkling drinks with sugar] ,,0. 0-1 time per week / 1. 2-3 times per week / 2. 4-6 times per week / 3. 7+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBDF,BEF_DIET_drink_juice,Drinks (before the social isolation/quarantine period) [Fruit juices (No fresh)] ,,0. 0-1 time per week / 1. 2-3 times per week / 2. 4-6 times per week / 3. 7+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBDWA,BEF_DIET_drink_water,Drinks (before the social isolation/quarantine period) [Water] ,,0. 0-1 time per week / 1. 2-3 times per week / 2. 4-6 times per week / 3. 7+ times per week / missing,0 / 1 / 2 / 3 / 4 / .
SELF,DRXBDTS,BEF_DIET_drink_sugar,How many teaspoons of sugar did you add to your Daily drinks? (before the period of social isolation/quarantine) ,,Frequency,
SELF,DRXBVT,BEF_DIET_vit,Did you take any vitamin supplements? (before the period of social isolation/quarantine) ,,Frequency,
,DRXBRMF,BEF_DIET_rmeatfat,"When you ate red meat (beef, pork, lamb, etc.) did you remove the visible fat on the plate? (before the period of social isolation/quarantine) ",,Frequency,
,DRXBFASF,BEF_DIET_fat_stirfry,What kind of fat did you use to stir-fry food at home? (before the period of social isolation/quarantine) ,,0. no como / 1. At home / 2. Outside of home / missing,0 / 1 / 2 / 3 / 4 / 5 / 6 / .
,DRXBFAC,BEF_DIET_fat_cook,What kind of fat did you use to make food? (before the period of social isolation/quarantine) ,,0. no como / 1. At home / 2. Outside of home / missing,0 / 1 / 2 / 3 / 4 / 5 / 6 / .
,DRXBFF,BEF_DIET_fried,How often did you eat fried foods? (before the period of social isolation/quarantine) ,,0. no como / 1. At home / 2. Outside of home / missing,0 / 1 / 2 / 3 / .
,DRXBCSF,BEF_FOODPREP_stuf,Methods of confection used (before the period of social isolation/quarantine) [Stuffed] ,,0. No change / 1. Increase / 2. Decrease / missing,0 / 1 / 2 / 3 / .
,DRXBCSW,BEF_FOODPREP_stew,Methods of confection used (before the period of social isolation/quarantine) [Stew] ,,0. No change / 1. Increase / 2. Decrease / missing,0 / 1 / 2 / 3 / .
,DRXBCR,BEF_FOODPREP_roast,Methods of confection used (before the period of social isolation/quarantine) [Roasting] ,,0. No change / 1. Increase / 2. Decrease / missing,0 / 1 / 2 / 3 / .
,DRXBCMC,BEF_FOODPREP_cook,Cooking methods used (before the period of social isolation/quarantine) [Cooked] ,,0. No change / 1. Increase / 2. Decrease / missing,0 / 1 / 2 / 3 / .
,DRXBMG,BEF_FOODPREP_grill,Preparation methods used (before the period of social isolation/quarantine) [Grilled] ,,0. No change / 1. Increase / 2. Decrease / missing,0 / 1 / 2 / 3 / .
,DRXBMSF,BEF_FOODPREP_stirfry,Methods of confection used (before the period of social isolation/quarantine) [Stir-fry] ,,0. No change / 1. Increase / 2. Decrease / missing,0 / 1 / 2 / 3 / .
,DRXBRSM,BEF_RESP_supermarket,What is your responsibility for (before the period of social isolation/quarantine) [Going to the supermarket to buy food?] ,,0. No change / 1. Increase / 2. Decrease / missing,
,DRXBRMPL,BEF_RESP_mplan,What is your responsibility for (before the period of social isolation/quarantine) [Planning meals] ,,0. No change / 1. Increase / 2. Decrease / missing,
,DRXBRMPR,BEF_RESP_mprep,What is your responsibility for (before the social isolation/quarantine period) [Preparing meals] ,,0. No change / 1. Increase / 2. Decrease / missing,
,DRXBBSB,BEF_breakfast,"In a typical week, where you mostly have the following meals (before the social isolation/quarantine period) [Breakfast] ",,0. No change / 1. Increase / 2. Decrease / missing,0 / 1 / 2 / .
,DRXBBSL,BEF_lunch,"In a typical week, where you mostly have the following meals (before the social isolation/quarantine period) [Lunch] ",,0. No change / 1. Increase / 2. Decrease / missing,0 / 1 / 2 / .
,DRXBBSD,BEF_dinner,"In a typical week, where you mostly have the following meals (before the social isolation/quarantine period) [Dinner] ",,0. No change / 1. Increase / 2. Decrease / missing,0 / 1 / 2 / .
,DRQTFT,FCM_taste,Select the 3 factors that have the greatest influence on the choice of foods you consume in the context of social isolation/quarantine. [The taste of food] ,,0. No change / 1. Increase / 2. Decrease / missing,0 / 1 / 2 / .
,DRQTFH,FCM_heal,Select the 3 factors that have the greatest influence on the choice of foods you consume in the context of social isolation/quarantine. [Trying to eat healthy] ,,0. No change / 1. Increase / 2. Decrease / missing,0 / 1 / 2 / .
,DRQTFP,FCM_pric,Select the 3 factors that have the greatest influence on the choice of foods you consume in the context of social isolation/quarantine. [Food price] ,,,0 / 1 / 2 / .
,DRQTFR,FCM_habit,Select the 3 factors that have the greatest influence on the choice of foods you consume in the context of social isolation/quarantine. [Habit or routine] ,,,0 / 1 / 2 / .
,DRQTFA,FCM_avail,Select the 3 factors that have the greatest influence on the choice of foods you consume in the context of social isolation/quarantine. [Availability of food] ,,,0 / 1 / 2 / .
,DRQTFQ,FCM_qual,Select the 3 factors that have the greatest influence on the choice of foods you consume in the context of social isolation/quarantine. [Quality or freshness of food] ,,,0 / 1 / 2 / .
,DRQTFO,FCM_otherperson,Select the 3 factors that have the greatest influence on the choice of foods you consume in the context of social isolation/quarantine. [Other person decides most of the food que eu como],,,0 / 1 / 2 / .
,DRQTFE,FCM_conv,Select the 3 factors that have the greatest influence on the choice of foods you consume in the context of social isolation/quarantine. [Ease or convenience of preparation] ,,,0 / 1 / 2 / .
,DRQTFW,FCM_weco,Select the 3 factors that have the greatest influence on the choice of foods you consume in the context of social isolation/quarantine. [Control weight] ,,,0 / 1 / 2 / .
,DRQTFD,FCM_dietphy,Select the 3 factors that have the greatest influence on the choice of foods you consume in the context of social isolation/quarantine. [Diet advised by the physician] ,,,0 / 1 / 2 / .
,DRQTFPR,FCM_pack,Select the 3 factors that have the greatest influence on the choice of foods you consume in the context of social isolation/quarantine. [Presentation or packaging] ,,,0 / 1 / 2 / .
,DRQTFAD,FCM_natu,"Select the 3 factors that have the greatest influence on the choice of foods you consume in the context of social isolation/quarantine. [Content in additives, dyes or preservatives] ",,,0 / 1 / 2 / .
,DRQTFCR,FCM_cult,"Select the 3 factors that have the greatest influence on the choice of foods you consume in the context of social isolation/quarantine. [My cultural, religious or ethnic roots] ",,,0 / 1 / 2 / .
,DRQTFV,FCM_vegediet,Select the 3 factors that have the greatest influence on the choice of foods you consume in the context of social isolation/quarantine. [Vegetarian food or eating habits espec�ficos],,,0 / 1 / 2 / .
SELF,DATSO,cestdat,Date of symptom onset,Calendar date,yyyy-mm-dd / Missing, / .
SELF,DATAD,,Date of admission,Calendar date,yyyy-mm-dd / Missing, / .
SELF,DATADI,icu_hostdat??,Date of admission to ICU,Calendar date,yyyy-mm-dd / Missing, / .
SELF,DATDSI,,Date of discharge from ICU,Calendar date,yyyy-mm-dd / Missing, / .
SELF,DATDS,hoendat,Date of discharge,Calendar date,yyyy-mm-dd / Missing, / .
SELF,DATPR,,Date of drug prescription,Calendar date,yyyy-mm-dd / Missing, / .
SELF,DATLGT,,Length of stay in hospital,Continuous,Days / Missing,0-180 / .
SELF,DATLGTI,hodur,Length of stay in ICU,Continuous,Days / Missing,0-180 / .
SELF,DSXHO,,Patient admitted to hospital,Binary,No/Yes / Missing,0/1/ .
SELF,DSXIC,icu_hoterm,Patient admitted to ICU,Binary,No/Yes / Missing,0/1 / .
SELF,DSXOS,dsterm,Outcome status,Categorical,Recovered/Deceased/Transferred / Missing,0/1/2 / .
SELF,DATOS,dsstdtcyn,Date of outcome status,Calendar date,yyyy-mm-dd / Missing, / .
rm(list=ls())
setwd("C:/Users/Victor/Documents/TFG/r-analytics-master/ressources")
setwd(("C:/Users/Victor/Documents/TFG/r-analytics-master/ressources/new_res_baskent/outpatient"))
#Cambiarlo por el nombre del ressource que se desea limpiar
hospital <- data.frame(read.csv("konya_outpatient.csv", sep=","))
hospital <- hospital %>% select(-contains("numeric"))
# hospital["NOT.HARMONISED"] <- NULL
#
# names <- colnames(hospital)
# for (i in 1:length(names)){
#
# if(grepl("NOT.HARMONISED", names[i])){
# hospital[names[i]] <- NULL
# print(paste("quito ", names[i]))
# }
#
# }
# hospital <- hospital[-1,]
setwd("C:/Users/Victor/Documents/TFG/r-analytics-master/harmonised_data")
ComAndRF <- data.frame(read.csv("Com&RF.csv", sep=","))[1:64,1:5]
Complications <- data.frame(read.csv("Complications.csv", sep=";"))[1:20,1:5]
Dates <- data.frame(read.csv("Dates.csv", sep=";"))[1:12,1:5]
Demographics <- data.frame(read.csv("Demographics.csv", sep=";"))[1:9,1:5]
Home_med <- data.frame(read.csv("Home_med.csv", sep=";"))[1:13,1:5]
Imaging_data <- data.frame(read.csv("Imaging_data.csv", sep=";"))[1:11,1:5]
Labo <- data.frame(read.csv("Labo.csv", sep=";"))[1:143,1:5]
SiAndSympt <- data.frame(read.csv("Si&Sympt.csv", sep=";"))[1:50,1:5]
Treatment <- data.frame(read.csv("Treatment.csv", sep=";"))[1:32,1:5]
LifestyleAndDiet <- data.frame(read.csv("Lifestyle&Diet.csv", sep=";"))[1:165,1:5]
harmonised_data <- rbind(SiAndSympt,ComAndRF)
harmonised_data <- rbind(harmonised_data,Treatment)
harmonised_data <- rbind(harmonised_data,Dates)
harmonised_data <- rbind(harmonised_data,Demographics)
harmonised_data <- rbind(harmonised_data,Home_med)
harmonised_data <- rbind(harmonised_data,Imaging_data)
harmonised_data <- rbind(harmonised_data,Complications)
harmonised_data <- rbind(harmonised_data,Labo)
harmonised_data <- rbind(harmonised_data,LifestyleAndDiet)
rm(list=c("SiAndSympt",
"Complications",
"ComAndRF",
"Dates",
"Demographics",
"Home_med",
"Imaging_data",
"Complications",
"Labo",
"LifestyleAndDiet"))
noYesValues <- subset(harmonised_data, harmonised_data$Harmonised.data.format.unit == "No/Yes / missing" | harmonised_data$Harmonised.data.format.unit == "No/Yes / Missing")
noYesValues <- noYesValues$Harmonised.variable.name
noYesValues <- c(noYesValues,"CSXCOTAB","CSXCOTAG","IMDIT","RFXHIV_RFXAIDS", "SMXASAH", "CMXATH", "CMXNO")
categoric_vars = c("CMXATH", "CMXNO", "SMXASAH","CSXCOTAB","CSXCOTAG","IMDIT","RFXHIV_RFXAIDS","DMRGENDR", "DMRBORN", "DMRRETH1", "DMROCCU", "DMRHREDU", "DSXOS", "DSXHO", "DSXIC", "TRXAV","TRXRIB","TRXLR","TRXRM","TRXIA","TRXIB","TRXCH","TRXAB","TRXCS","TRXHEP","TRXAF","TRXCP","TRXOT","TRXECM","TRXIV","TRXNIV","TRXNO","TRXOX","TRXRR","TRXTR","TRXVA","TRXPE","TRXPV","TRXIT","TRXNMB","TRXAC","TRXINA","TRXIS","TRXIM","TRXVC","TRXVD","TRXZN", "CSXCOT","CSXCTR","SMXASAH","SMXFEA","SMXCOA","SMXSTA","SMXSBA","SMXRNA","SMXMYA","SMXARA","SMXCPA","SMXAPA","SMXINA","SMXNAA","SMXDIA","SMXFAA","SMXHEA","SMXCNA","SMXACA","SMXSLA","SMXTLA","SMXSYA","SMXWHA","SMXLYA","SMXANA","SMXIWA","SMXSRA","SMXBLA","CMXPRG","CMXCVD","CMXCMP","CMXHT","CMXDI","CMXCKD","CMXCLD","CMXCPD","CMXASM","CMXCND","CMXRHE","CMXCCI","CMXCBD","CMXDE","CMXPU","CMXST","CMXLY","CMXAP","RFXSM","RFXFSM","RFXOB","RFXTB","RFXIMD","RFXHIV","RFXAIDS","RFXUI","RFXHC","RFXONC","RFXMN", "HMRACI","HMRARB","HMRAHO","HMRNS","HMROS","HMRCS","HMRIS","HMRAV","HMRAB","HMRCOV","IMDXCT","IMDXCTCR","IMDXCTTE","IMDXCTAB","IMDXXR","IMDXPN", "COXRD","COXAR","COXPM","COXMOD","COXPT","COXEC","COXSH","COXIO","COXPE","COXST","COXDIC","COXRIO","COXKF","COXHF","COXBC")
personalized <- c("DMRGENDR", "DSXOS", "CSXCTR", "SMXFEA", "CSXCOT")
is_number <- function(x){
res <- FALSE
if(length(x)!=0){
x <- str_replace(x,",",".")
aux <- as.numeric(x)
if(!is.na(aux))
res <- TRUE
}
return(res)
}
replaceNoYesValues <- function(x){
#Replace the value with Yes or No
if(is.na(x))
x <- ""
else if (x==0 | x =="No" | x ==" No" | x =="NO")
x <- "No"
else if (x==1 | x == "Yes" | x == " Yes" | x=="SI")
x <- "Yes"
else
x <- ""
return (x)
}
fixNonCategoric <- function(x){
if(!is_number(x)){
x <- ""
}else{
x <- str_replace(x,",",".")
}
return(x)
}
personalizedFun <- function(x, colname){
if(colname == "DMRGENDR"){
if(is.na(x))
x <- ""
else if(x == 1 | x == "F"| x == "f" | x== "Female")
x <- "Female"
else if (x == 0 | x =="M" | x == "m" | x== "Male")
x <- "Male"
}
if(colname == "CSXCTR"){
if(is.na(x))
x <- ""
else if(x == 1 | x == "positive" | x=="PositivM" | x=="POSITIVM" | x =="POS?T?VM" | x =="NMGAT?VM")
x <- "Positive"
else if (x == 0 | x == "negative" | x=="negativM" | x=="NMGATIVM" | x=="NAGATIVM" | x =="NMGATIV" | x =="negativeM" | x == "NAGAT?VM" | x =="NMGAT?V")
x <- "Negative"
}
if(colname == "SMXFEA"){
if(is.na(x))
x <- ""
else if(x == 1)
x <- "Yes"
else if (x == 0)
x <- "No"
else if (x == ".")
x <- ""
}
if(colname == "DMRRETH1"){
if(is.na(x))
x <- ""
else if(x ==1)
x <- "Asian"
else if (x == 2)
x <- "Black"
else if (x == 3)
x <- "Hispanic"
else if (x == 4)
x <- "White"
else if (x == 5)
x <- "Multiracial"
else if (x == 6)
x <- "Other"
}
if(colname == "DMROCCU"){
if(is.na(x))
x <- ""
else if(x ==1)
x <- "Unemployed"
else if (x == 2)
x <- "Student"
else if (x == 3)
x <- "Employed"
else if (x == 4)
x <- "Self-employed"
else if (x == 5)
x <- "Retired"
else if (x == 6)
x <- ""
}
if(colname == "DMRHREDU"){
if(is.na(x))
x <- ""
else if(x ==1)
x <- "High School"
else if (x == 2)
x <- "Bachelors"
else if (x == 3)
x <- "Postgraduate"
else if (x == 4)
x <- "Other"
}
if(colname =="DSXOS"){
if(is.na(x))
x <- ""
else if (x==0 | x == "Recovered")
x <- "Recovered"
else if (x==1 | x == "Deceased")
x <- "Deceased"
else if (x==2 | x == "Transferred")
x <- "Transferred"
else
x <- ""
}
if(colname =="CSXCOT"){
if(is.na(x))
x <- ""
else if (x==1 )
x <- "PCR"
else if (x==2 )
x <- "antigen"
else if (x==3 )
x <- "other"
else
x <- ""
}
return(x)
}
dotToBar <- function (x){
if (grepl(".", x, fixed = TRUE))
res <- format(as.Date(x, format = "%d.%m.%Y"), "%d/%m/%Y")
else res <- x
return(res)
}
rm(newDf)
newDf <- hospital
names <- colnames(hospital)
for (j in 1:ncol(hospital)){
percentage <- trunc(j/ncol(hospital)*100)
mes <- paste(toString(percentage),"% completed", sep="")
print(mes)
print(names[j])
for(i in 1:nrow(hospital)){
if(names[j] %in% noYesValues){
newDf[i,j] <- replaceNoYesValues(hospital[i,j])
}else if(!(names[j] %in% categoric_vars) & names[j] != "DMRBORN" & !grepl("DAT",names[j], fixed=TRUE)){
newDf[i,j] <- fixNonCategoric(hospital[i,j])
}
if(names[j] %in% personalized){
newDf[i,j] <- personalizedFun(hospital[i,j],names[j])
}
if (is.na(hospital[i,j]))
newDf[i,j] <- ""
else if (hospital[i,j] == ".")
newDf[i,j] <- ""
}
}
setwd("C:/Users/Victor/Documents/TFG/r-analytics-master/ressources/newRessources")
setwd(("C:/Users/Victor/Documents/TFG/r-analytics-master/ressources/new_res_baskent/outpatient/clean"))
write.csv(x=newDf, file = "konya_outpatient.csv", row.names = FALSE)
rm(list=ls())
setwd("C:/Users/Victor/Documents/TFG/r-analytics-master/ressources/newRessources")
setwd(("C:/Users/Victor/Documents/TFG/r-analytics-master/ressources/new_res_baskent/outpatient/clean"))
hospital <- data.frame(read.csv("konya_outpatient.csv", sep=","))
setwd("C:/Users/Victor/Documents/TFG/r-analytics-master/harmonised_data")
ComAndRF <- data.frame(read.csv("Com&RF.csv", sep=","))
Complications <- data.frame(read.csv("Complications.csv", sep=";"))[1:20,1:5]
Dates <- data.frame(read.csv("Dates.csv", sep=";"))[1:12,1:5]
Demographics <- data.frame(read.csv("Demographics.csv", sep=";"))[1:9,1:5]
Home_med <- data.frame(read.csv("Home_med.csv", sep=";"))[1:13,1:5]
Imaging_data <- data.frame(read.csv("Imaging_data.csv", sep=";"))[1:11,1:5]
Labo <- data.frame(read.csv("Labo.csv", sep=";"))[1:143,1:5]
SiAndSympt <- data.frame(read.csv("Si&Sympt.csv", sep=";"))[1:50,1:5]
Treatment <- data.frame(read.csv("Treatment.csv", sep=";"))[1:32,1:5]
LifestyleAndDiet <- data.frame(read.csv("Lifestyle&Diet.csv", sep=";"))[1:165,1:5]
harmonised_data <- rbind(SiAndSympt,ComAndRF)
harmonised_data <- rbind(harmonised_data,Treatment)
harmonised_data <- rbind(harmonised_data,Dates)
harmonised_data <- rbind(harmonised_data,Demographics)
harmonised_data <- rbind(harmonised_data,Home_med)
harmonised_data <- rbind(harmonised_data,Imaging_data)
harmonised_data <- rbind(harmonised_data,Complications)
harmonised_data <- rbind(harmonised_data,Labo)
harmonised_data <- rbind(harmonised_data,LifestyleAndDiet)
rm(list=c("SiAndSympt",
"Complications",
"ComAndRF",
"Dates",
"Demographics",
"Home_med",
"Imaging_data",
"Complications",
"Labo",
"LifestyleAndDiet"))
noYesValues <- subset(harmonised_data, harmonised_data$Harmonised.data.format.unit == "No/Yes / missing" | harmonised_data$Harmonised.data.format.unit == "No/Yes / Missing")
noYesValues <- noYesValues$Harmonised.variable.name
noYesValues <- c(noYesValues,"CSXCOTAB","CSXCOTAG","IMDIT","RFXHIV_RFXAIDS", "SMXASAH", "CMXATH", "CMXNO","SMXFEA")
categoric_vars = c("CMXATH", "CMXNO", "SMXASAH","CSXCOTAB","CSXCOTAG","IMDIT","RFXHIV_RFXAIDS","DMRGENDR", "DMRBORN", "DMRRETH1", "DMROCCU", "DMRHREDU", "DSXOS", "DSXHO", "DSXIC", "TRXAV","TRXRIB","TRXLR","TRXRM","TRXIA","TRXIB","TRXCH","TRXAB","TRXCS","TRXHEP","TRXAF","TRXCP","TRXOT","TRXECM","TRXIV","TRXNIV","TRXNO","TRXOX","TRXRR","TRXTR","TRXVA","TRXPE","TRXPV","TRXIT","TRXNMB","TRXAC","TRXINA","TRXIS","TRXIM","TRXVC","TRXVD","TRXZN", "CSXCOT","CSXCTR","SMXASAH","SMXFEA","SMXCOA","SMXSTA","SMXSBA","SMXRNA","SMXMYA","SMXARA","SMXCPA","SMXAPA","SMXINA","SMXNAA","SMXDIA","SMXFAA","SMXHEA","SMXCNA","SMXACA","SMXSLA","SMXTLA","SMXSYA","SMXWHA","SMXLYA","SMXANA","SMXIWA","SMXSRA","SMXBLA","CMXPRG","CMXCVD","CMXCMP","CMXHT","CMXDI","CMXCKD","CMXCLD","CMXCPD","CMXASM","CMXCND","CMXRHE","CMXCCI","CMXCBD","CMXDE","CMXPU","CMXST","CMXLY","CMXAP","RFXSM","RFXFSM","RFXOB","RFXTB","RFXIMD","RFXHIV","RFXAIDS","RFXUI","RFXHC","RFXONC","RFXMN", "HMRACI","HMRARB","HMRAHO","HMRNS","HMROS","HMRCS","HMRIS","HMRAV","HMRAB","HMRCOV","IMDXCT","IMDXCTCR","IMDXCTTE","IMDXCTAB","IMDXXR","IMDXPN", "COXRD","COXAR","COXPM","COXMOD","COXPT","COXEC","COXSH","COXIO","COXPE","COXST","COXDIC","COXRIO","COXKF","COXHF","COXBC")
personalized <- c("DMRGENDR", "DMRRETH1", "DMROCCU", "DMRHREDU", "DSXOS")
is_number <- function(x){
res <- FALSE
if(length(x)!=0){
x <- str_replace(x,",",".")
aux <- as.numeric(x)
if(!is.na(aux))
res <- TRUE
}
return(res)
}
fixNonCategoric <- function(x){
if(!is_number(x)){
x <- ""
}
return(x)
}
getNumericValue <- function (x,colname) {
if(colname %in% noYesValues){
if(is.na(x))
x <- ""
else if (x == "No")
x <- 0
else if (x == "Yes")
x <- 1
}
if(colname == "DMRGENDR"){
if(x == "Female")
x <- 1
else if (x == "Male")
x <- 0
}
if(colname == "DSXOS"){
if(is.na(x))
x<- ""
else if (x == "Missing")
x <- ""
else if (x == "Recovered")
x <- 0
else if (x == "Deceased")
x <- 1
else if (x == "Transferred")
x <- 2
}
if(colname == "DMRRETH1"){
if(is.na(x))
x <- ""
else if(x =="Asian")
x <- 1
else if (x == "Black")
x <- 2
else if (x == "Hispanic")
x <- 3
else if (x == "White")
x <- 4
else if (x == "Multiracial")
x <- 5
else if (x == "Other")
x <- 6
}
if(colname == "DMROCCU"){
if(is.na(x))
x <- ""
else if(x == "Unemployed")
x <- 1
else if (x == "Student")
x <- 2
else if (x == "Employed")
x <- 3
else if (x == "Self-employed")
x <- 4
else if (x == "Retired")
x <- 5
}
if(colname == "DMRHREDU"){
if(is.na(x))
x <- ""
else if(x =="High School")
x <- 1
else if (x == "Bachelors")
x <- 2
else if (x == "Postgraduate")
x <- 3
else if (x == "Other")
x <- 4
}
if(colname =="CSXCOT"){
if(is.na(x))
x <- ""
else if (x=="PCR" )
x <- 1
else if (x=="antigen" )
x <- 2
else if (x=="other" )
x <- 3
else
x <- ""
}
return(x)
}
noNa <- function(x){
if(is.na(x))
x <- ""
return(x)
}
rm(newDf)
newDf <- hospital
names <- colnames(hospital)
list_numeric <- c()
for(k in 1:length(names)){
mes <- paste(names[k], "_numeric",sep ="")
if(names[k] %in% noYesValues){
list_numeric <- c(list_numeric,mes)
}else if(names[k] %in% personalized){
list_numeric <- c(list_numeric,mes)
}
}
numericDf <- data.frame(matrix(NA, nrow = nrow(hospital), ncol = length(list_numeric)))
colnames(numericDf) <- list_numeric
newDf<-bind_cols(newDf,numericDf)
#newDf[,"DMRGENDR_numeric"] <- NA
for (j in 1:ncol(hospital)){
percentage <- trunc(j/ncol(hospital)*100)
mes <- paste(toString(percentage),"% completed", sep="")
print(mes)
numeric_col <- paste(names[j], "_numeric", sep="")
print(names[j])
for(i in 1:nrow(hospital)){
if(i %% 10000 == 0)
print(i)
if(numeric_col %in% list_numeric){
newDf[i,numeric_col] <- getNumericValue(hospital[i,j],names[j])
}
if(is.na(hospital[i,j]))
newDf[i,j] <- ""
}
}
setwd("C:/Users/Victor/Documents/TFG/r-analytics-master/ressources/newRessources/Numeric_derived")
setwd(("C:/Users/Victor/Documents/TFG/r-analytics-master/ressources/new_res_baskent/outpatient/clean/harmonized"))
write.csv(x=newDf, file = "konya_outpatient.csv", row.names = FALSE)
source("dependency_installer.R")
source("required_folder_checker.R")
source("argument_hasher.R")
dep_list = c("survival", "lubridate", "survminer", "stringr", "DSI", "DSOpal", "DSLite", "fields", "hrbrthemes", "metafor", "ggplot2", "gridExtra", "data.table", "dsBaseClient")
install_dependencies(dep_list)
image_format <- ".png"
args <- commandArgs(trailingOnly = TRUE)
hospital_names <- c("HM","Princesa")
project_names <- c("RESOURCE_GUIDE","RESOURCE_GUIDE")
resource_names <- c("HM_rs", "Princesa_rs")
urls <- c("https://192.168.1.50:8844","https://192.168.1.50:8844")
users <- c("opal_admin","opal_admin")
pass <- c("5f%R!&wfbUF*7gZ14mg","5f%R!&wfbUF*7gZ14mg")
hospital_names <- hospital_names[2]
project_names <- project_names[2]
resource_names <- resource_names[2]
urls <- urls[2]
users <- users[2]
pass <- pass[2]
# project_names_o <- args[1]
# project_names <- str_split(project_names_o, ";")[[1]]
#
# resource_names_o <- args[2]
# resource_names <- str_split(resource_names_o, ";")[[1]]
#
# urls_o <- args[3]
# urls <- str_split(urls_o, ";")[[1]]
#
# users_o <- args[4]
# users <- str_split(users_o, ";")[[1]]
#
# pass_o <- args[5]
# pass <- str_split(pass_o, ";")[[1]]
#
# hospital_name <- args[6]
# extra_filter <- args[7]
json_output <- c()
builder <- DSI::newDSLoginBuilder()
url_ctr <- 0
for(i in 1:length(urls)){
print(paste("Connecting to Server with URL:", urls[i], sep=" "))
builder$append(server = paste("study", url_ctr, sep=""), url = urls[i],
user = users[i], password = pass[i],
resource = paste(project_names[i], resource_names[i], sep="."),
driver = "OpalDriver", options="list(ssl_verifyhost=0,ssl_verifypeer=0)")
url_ctr <- url_ctr+1
}
logindata <- builder$build()
connections <- DSI::datashield.login(logins = logindata, assign = TRUE, symbol = "D")
datashield.assign.expr(connections, symbol = 'data', expr = quote(as.resource.data.frame(D)))
datastructure_name <- "data"
ds.colnames(x=datastructure_name, datasources= connections)
data_dim <- ds.dim(x=datastructure_name, datasources= connections)
data_dim_rows <- data_dim$`dimensions of data in combined studies`[1]
data_dim_cols <- data_dim$`dimensions of data in combined studies`[2]
get_reconstructed_population <- function(df, var, size){
data_dim <- ds.dim(x=df, datasources= connections)
data_dim_rows <- data_dim[[length(data_dim)]][1]
data_dim_cols <- data_dim[[length(data_dim)]][2]
quantile_data <- ds.quantileMean(x=paste(df, var, sep="$"), datasources = connections)
est_min <- round(quantile_data[[1]])
est_q1 <- round(quantile_data[[3]])
est_median <- round(quantile_data[[4]])
est_q3 <- round(quantile_data[[5]])
est_max <- round(quantile_data[[7]])
combined_mean <- quantile_data[[8]]
nn <- size
quantiles <- c(est_min, est_q1, est_median, est_q3, est_max)
set.seed(1)
reconstructed_population <- c(
runif(nn/4,quantiles[1],quantiles[2]),
runif(nn/4,quantiles[2],quantiles[3]),
runif(nn/4,quantiles[3],quantiles[4]),
runif(nn/4,quantiles[4],quantiles[5]))
return(reconstructed_population)
}
ds.dataFrameSubset(df.name = datastructure_name, V1.name = "data$DSXOS_numeric", V2.name = "1", Boolean.operator = "==", newobj = "OutFilteredDEATH")
ds.dataFrameSubset(df.name = datastructure_name, V1.name = "data$DSXOS_numeric", V2.name = "0", Boolean.operator = "==", newobj = "OutFilteredALIVE")
data_dim_DEATH <- ds.dim(x="OutFilteredDEATH", datasources= connections)
data_dim_DEATH <- data_dim_DEATH[[length(data_dim_DEATH)]][1]
data_dim_ALIVE <- ds.dim(x="OutFilteredALIVE", datasources= connections)
data_dim_ALIVE <- data_dim_ALIVE[[length(data_dim_ALIVE)]][1]
reconstr_pop_time_outcome_death <- get_reconstructed_population("OutFilteredDEATH", "DATLGT", data_dim_DEATH)
df_death <- data.frame(reconstr_pop_time_outcome_death)
df_death["status"] = "death"
colnames(df_death) = c("out_time", "status")
reconstr_pop_time_outcome_alive <- get_reconstructed_population("OutFilteredALIVE", "DATLGT", data_dim_ALIVE)
df_alive <- data.frame(reconstr_pop_time_outcome_alive)
df_alive["status"] = "alive"
colnames(df_alive) = c("out_time", "status")
full_status_df <- rbind(df_alive, df_death)
filtercol <- c()
samplenum <- sample(0:100000, nrow(full_status_df), replace = T)
for( i in 1:length(samplenum) ) {
if(samplenum[i] %% 2 == 0){
filtercol[length(filtercol)+1] <- "MALE"
}else{
filtercol[length(filtercol)+1] <- "FEMALE"
}
}
full_status_df[extra_filter] = filtercol
full_status_df["status_surv"] = 1
full_status_df[full_status_df$status == "alive" ,"status_surv"] = 0
#filename <- paste0(hospital_name, "survival_curve", sep="")
#filename <- paste(filename, "outcome", sep="_")
#filename <- paste(filename, image_format, sep="")
dir.create("./survAlberto", showWarnings = FALSE)
setwd("./survAlberto")
print("survival_curve.png")
png("survival_curve.png", width = 750, height = 500)
survplot <- ggsurvplot(
fit = survfit(Surv(out_time, status_surv) ~ 1, data = full_status_df),
xlab = "Days",
ylab = "Overall survival probability")
survplot
dev.off()
datashield.logout(connections)
rm(list=ls())
setwd("C:/Users/victor/Documents/TFG/r-analytics-master")
#Obtain the data from the codebook
codebook <- read.csv("harmon.csv", sep = ";")
codebook <- codebook[,c(1,3,4)]
colnames(codebook) <- c("variable", "description", "unit")
source("dependency_installer.R")
source("connection_parameters_aux.R")
source("necessary_functions_table1_v2_subset.R")
dep_list = c("DSI","DSOpal","DSLite", "dsBaseClient")
install_dependencies(dep_list)
dir.create("./table_1", showWarnings = FALSE)
setwd("./table_1")
#Create the connection
auxConnections <- connect()
connections <- auxConnections[[1]]
inp <- auxConnections[[2]]
#Only do this if you want to subset the data for a specific value of a categoric variable
apply_filters()
#Select the variables to be analized (Add the ones you consider relevant and remove the ones that you do not)
varToAnalize <- c("DMRGENDR","DMRAGEYR","DSXOS", "RFXSM", "TRXAV", "CMXCVD", "RFXOB")
varToAnalize <- c("DMRGENDR","DMRAGEYR")
table1 <- obtain_table1(connections, inp, varToAnalize)
#datashield.logout(connections)
library(gridExtra)
png("table1TFGFiltro.png", height = 30*nrow(table1), width = 150*ncol(table1))
grid.table(table1)
dev.off()
rm(list=ls())
library("ggplot2")
setwd("C:/Users/Victor/Documents/TFG/r-analytics-master/harmonised_data")
Treatments <- data.frame(read.csv("Treatment.csv", sep=";"))[1:32,1:5]
descriptions <- Treatments[, c(1,3)]
rownames(descriptions) <- descriptions$Harmonised.variable.name
Treatments <- Treatments$Harmonised.variable.name
setwd("C:/Users/victor/Documents/TFG/r-analytics-master")
source("dependency_installer.R")
source("connection_parameters.R")
source("necessary_functions_treatments_heatmap.R")
dep_list = c("DSI","DSOpal","DSLite", "ggplot2", "dsBaseClient")
install_dependencies(dep_list)
#Create the connection
auxConnections <- connect()
connections <- auxConnections[[1]]
inp <- auxConnections[[2]]
get_treatments_map(connections, inp)
ds.colnames("data")
rm(list=ls())
setwd("C:/Users/Victor/Documents/TFG/r-analytics-master")
source("required_folder_checker.R")
source("argument_hasher.R")
source("dependency_installer.R")
# install.packages("https://cran.r-project.org/src/contrib/Archive/DSI/DSI_1.2.0.tar.gz", repos=NULL, type="source")
# install.packages("https://cran.r-project.org/src/contrib/Archive/DSOpal/DSOpal_1.2.0.tar.gz", repos=NULL, type="source")
# install.packages("https://cran.r-project.org/src/contrib/Archive/DSLite/DSLite_1.2.0.tar.gz", repos=NULL, type="source")
# install.packages("https://cran.r-project.org/src/contrib/Archive/opalr/opalr_2.1.0.tar.gz", repos=NULL, type="source")
dep_list = c("jsonlite", "stringr","DSI","DSOpal","DSLite", "fields", "metafor", "ggplot2", "gridExtra", "data.table", "dsBaseClient")
install_dependencies(dep_list)
#,"DSI","DSOpal","DSLite"
setwd("C:/Users/victor/Documents/TFG/r-analytics-master")
source("connection_parameters.R")
source("necessary_functions_connection.R")
setwd("C:/Users/Victor/Documents/TFG/r-analytics-master/harmonised_data")
ComAndRF <- data.frame(read.csv("Com&RF.csv", sep=","))[1:64,1:5]
Complications <- data.frame(read.csv("Complications.csv", sep=";"))[1:20,1:5]
Dates <- data.frame(read.csv("Dates.csv", sep=";"))[1:12,1:5]
Demographics <- data.frame(read.csv("Demographics.csv", sep=";"))[1:9,1:5]
Home_med <- data.frame(read.csv("Home_med.csv", sep=";"))[1:13,1:5]
Imaging_data <- data.frame(read.csv("Imaging_data.csv", sep=";"))[1:11,1:5]
Labo <- data.frame(read.csv("Labo.csv", sep=";"))[1:143,1:5]
SiAndSympt <- data.frame(read.csv("Si&Sympt.csv", sep=";"))[1:50,1:5]
Treatment <- data.frame(read.csv("Treatment.csv", sep=";"))[1:32,1:5]
LifestyleAndDiet <- data.frame(read.csv("Lifestyle&Diet.csv", sep=";"))[1:165,1:5]
harmonised_data <- rbind(SiAndSympt,ComAndRF)
harmonised_data <- rbind(harmonised_data,Treatment)
harmonised_data <- rbind(harmonised_data,Dates)
harmonised_data <- rbind(harmonised_data,Demographics)
harmonised_data <- rbind(harmonised_data,Home_med)
harmonised_data <- rbind(harmonised_data,Imaging_data)
harmonised_data <- rbind(harmonised_data,Complications)
harmonised_data <- rbind(harmonised_data,Labo)
harmonised_data <- rbind(harmonised_data,LifestyleAndDiet)
rm(list=c("SiAndSympt",
"Complications",
"ComAndRF",
"Dates",
"Demographics",
"Home_med",
"Imaging_data",
"Complications",
"Labo",
"LifestyleAndDiet"))
categoric_vars = c("DMRGENDR", "DMRBORN", "DMRRETH1", "DMROCCU", "DMRHREDU", "DSXOS", "DSXHO", "DSXIC", "TRXAV","TRXRIB","TRXLR","TRXRM","TRXIA","TRXIB","TRXCH","TRXAB","TRXCS","TRXHEP","TRXAF","TRXCP","TRXOT","TRXECM","TRXIV","TRXNIV","TRXNO","TRXOX","TRXRR","TRXTR","TRXVA","TRXPE","TRXPV","TRXIT","TRXNMB","TRXAC","TRXINA","TRXIS","TRXIM","TRXVC","TRXVD","TRXZN", "CSXCOT","CSXCTR","SMXASAH","SMXFEA","SMXCOA","SMXSTA","SMXSBA","SMXRNA","SMXMYA","SMXARA","SMXCPA","SMXAPA","SMXINA","SMXNAA","SMXDIA","SMXFAA","SMXHEA","SMXCNA","SMXACA","SMXSLA","SMXTLA","SMXSYA","SMXWHA","SMXLYA","SMXANA","SMXIWA","SMXSRA","SMXBLA","CMXPRG","CMXCVD","CMXCMP","CMXHT","CMXDI","CMXCKD","CMXCLD","CMXCPD","CMXASM","CMXCND","CMXRHE","CMXCCI","CMXCBD","CMXDE","CMXPU","CMXST","CMXLY","CMXAP","RFXSM","RFXFSM","RFXOB","RFXTB","RFXIMD","RFXHIV","RFXAIDS","RFXUI","RFXHC","RFXONC","RFXMN", "HMRACI","HMRARB","HMRAHO","HMRNS","HMROS","HMRCS","HMRIS","HMRAV","HMRAB","HMRCOV","IMDXCT","IMDXCTCR","IMDXCTTE","IMDXCTAB","IMDXXR","IMDXPN", "COXRD","COXAR","COXPM","COXMOD","COXPT","COXEC","COXSH","COXIO","COXPE","COXST","COXDIC","COXRIO","COXKF","COXHF","COXBC")
#----------------------------------------------------------------------------
#Test if column names are valid
check_column_names <- function(x){
str_res <- "The column names:"
for(i in 1:(nrow(data_colnames))){
if(!check_valid_name(data_colnames[i,1])){
str_res<- paste(str_res, data_colnames[i,1], sep=" ")
}
}
str_res<- paste(str_res,"are not registered in the harmonized data codebook \n", sep=" ")
return (str_res)
}
#Test if a single variable name is valid
check_valid_name <- function(x){
valid <- FALSE
aux <- as.data.frame(strsplit(x , split = "_"))
if(aux[1,1] %in% harmonised_data$Harmonised.variable.name)
valid <- TRUE
return (valid)
}
valid_data_colnames <- function(x){
valid_colnames = c()
for(i in 1:(nrow(data_colnames))){
if(check_valid_name(data_colnames[i,1])){
valid_colnames = c(valid_colnames,data_colnames[i,1])
}
}
return(valid_colnames)
}
remove_space <- function(x){
searchString <- ' '
replacementString <- ''
res = sub(searchString,replacementString,x)
return(res)
}
remove_spaces_from_ds <- function(ds){
res<- lapply(ds,remove_space )
return(as.data.frame(res))
}
is_number <- function(x){
res <- FALSE
if(length(x)!=0){
x <- str_replace(x,",",".")
aux <- as.numeric(x)
if(!is.na(aux))
res <- TRUE
}
return(res)
}
check_values_not_categoric <- function(values, colname){
valid_vals <- values
possible_vals <- possible_values(colname)
for(i in 1:length(values)){
res<- FALSE
value <- values[[i]]
if(is_number(value)){
value <- str_replace(value,",",".")
value <- as.numeric(value)
}
if(is.null(value)){
res <- TRUE
}
else if( value == "NA" | value == "nan" | value == ".")
res <- TRUE
else{
if(nrow(possible_vals) == 2 & (!grepl("DAT",colname, fixed=TRUE)) & colname !="CSXCTR"){
if(colname=="LBXBEH" | colname=="LBXBEHn" | colname=="LBXBEM"){
lower = possible_vals[1,1][[1]]
higher = possible_vals[2,1][[1]]
}else{
bounds <- as.data.frame(strsplit(possible_vals[1,1], '-'))
lowerAux <- str_replace(bounds [1,1],",",".")
higherAux <- str_replace(bounds [2,1],",",".")
lower <- as.numeric(remove_space(lowerAux))
higher <- as.numeric(remove_space(higherAux))
}
if ((value >= lower & value <= higher))
res <- TRUE
}
if(nrow(possible_vals) == 3 | colname=="CSXCTR"){
if(value == 0 | value == 1)
res <- TRUE
}
if(nrow(possible_vals) > 3){
lower <- strtoi(remove_space(possible_vals[1,1]))
higher_b <- nrow(possible_vals)-1
higher <- strtoi(remove_space(possible_vals[higher_b,1]))
if ((value >= lower & value <= higher))
res <- TRUE
}
}
if(res == FALSE)
valid_vals[i] <- res
}
return(valid_vals)
}
possible_values <- function(x){
if(x=="LBXBEH" | x=="LBXBEHn" | x=="LBXBEM")
res <- t(as.data.frame(list(-20,20)))
else{
possible_value <- subset(harmonised_data,harmonised_data$Harmonised.variable.name==x)[1,5]
res <- strsplit(x=possible_value,split="/")
}
return(as.data.frame(res))
}
possible_values_categoric <- function(x){
possible_value <- subset(harmonised_data,harmonised_data$Harmonised.variable.name==x)[1,4]
res <- strsplit(x=possible_value,split="/")
return(as.data.frame(res))
}
check_values_categoric <- function(values, colname){
possible_vals <- possible_values_categoric(colname)
res <- TRUE
for(i in 1:length(values)){
if(!(values[[i]] %in% as.matrix(remove_spaces_from_ds(possible_vals)))){
res <- FALSE
}
}
return(res)
}
get_values_from_quantiles <- function(x){
data_summary <- ds.summary(x)
low_quantile <- data_summary[[1]][3][[1]][[1]]
high_quantile <- data_summary[[1]][3][[1]][[7]]
return(list(low_quantile,high_quantile))
}
notify_error <- function(invalid_name_list,invalid_value_list,wrong_categoric, wrong_categoric_values, missing_numeric){
res <- ""
if(length(invalid_name_list) !=0){
res <- "There are invalid values in the numeric fields:"
for(i in 1:length(invalid_name_list)){
res <- paste(res, invalid_name_list[i], sep=" ")
}
res <- paste(res, "\n", sep="")
for(i in 1:length(invalid_name_list)){
res <- paste(res, error_message(invalid_name_list[i], invalid_value_list[[i]]), sep=" ")
}
}
if(length(wrong_categoric)!=0){
res <- paste(res, "\n############################################################################ \n", sep="")
res <- paste(res,"\nThe following categoric values are invalid:", sep=" ")
for(i in 1:length(wrong_categoric)){
res <- paste(res, wrong_categoric[i], sep=" ")
}
res <- paste(res, "\n", sep="")
for(i in 1:length(wrong_categoric)){
res <- paste(res, error_message_categoric(wrong_categoric[i], wrong_categoric_values[[i]]), sep=" ")
}
}
if(length(missing_numeric)!=0){
res <- paste(res, "\n############################################################################ \n", sep="")
res<- paste(res, "\nThe following fields are missing a numeric field:")
for(i in 1:length(wrong_categoric)){
res <- paste(res, missing_numeric[i], sep=" ")
}
}
res <- paste(res, "\n", sep="")
return(res)
}
error_message_categoric <- function(colname, invalid_values){
res<- "\nValues in the field"
res<- paste(res, colname, sep=" ")
res<- paste(res, "should be", sep=" ")
range <- possible_values_categoric(colname)
for(i in 1:nrow(range)){
res <- paste(res, remove_space(range[i,1]), sep=" ")
}
res<- paste(res, "\nBut values were:", sep=" ")
for(j in 1:length(invalid_values)){
res<- paste(res, invalid_values[[j]], sep=" ")
}
res<- paste(res, "\n\n", sep="")
return(res)
}
error_message <- function(colname, invalid_values){
res<- "\nValues in the field"
res<- paste(res, colname, sep=" ")
res<- paste(res, "should be", sep=" ")
if(grepl("numeric", colname,fixed=TRUE))
new_colname <- strsplit(x=colname,split="_")[[1]][1]
else
new_colname <- colname
range <- subset(harmonised_data, harmonised_data$Harmonised.variable.name == new_colname)
range <- range[5]
range <- as.data.frame(strsplit(range[1,1], '/'))
#Range of values or null
if(nrow(range) == 2 & !grepl("DAT",colname, fixed=TRUE)){
bounds <- as.data.frame(strsplit(range[1,1], '-'))
lower <- remove_space(bounds [1,1])
higher <- remove_space(bounds [2,1])
res<- paste(res, "numbers between", sep=" ")
res<- paste(res, lower, sep=" ")
res<- paste(res, "and", sep=" ")
res<- paste(res, higher, sep=" ")
res<- paste(res, "(both included)", sep=" ")
}
if(nrow(range) == 3){
res<- paste(res, "0 or 1", sep=" ")
}
if(nrow(range) > 3){
lower <- strtoi(remove_space(range[1,1]))
higher_b <- nrow(range)-1
higher <- strtoi(remove_space(range[higher_b,1]))
res<- paste(res, "numbers between", sep=" ")
res<- paste(res, lower, sep=" ")
res<- paste(res, "and", sep=" ")
res<- paste(res, higher, sep=" ")
res<- paste(res, "(both included)", sep=" ")
}
if(grepl("DAT",colname, fixed=TRUE)){
res<- paste(res, "dates with the following format: dd/mm/yyyy", sep=" ")
}
res<- paste(res, "\nBut values were:", sep=" ")
for(j in 1:length(invalid_values)){
res<- paste(res, invalid_values[[j]], sep=" ")
}
res<- paste(res, "\n", sep="")
if(!is_number(invalid_values[[1]]))
res<- paste(res, "(It's missing a \"numeric\" field)", sep="")
res<- paste(res, "\n", sep="")
return(res)
}
check_valid_values <- function(){
invalid_name_list <- c()
cannot_analyse_list <- c()
invalid_values_list <- list()
wrong_categoric_values <- list()
wrong_categoric <- c()
missing_numeric <- c()
j<- 1
k <- 1
for(i in 1:(nrow(valid_colnames))){
data_table ="empty"
if(!grepl("DMRBORN",valid_colnames[i,1], fixed=TRUE) & (!grepl("DAT",valid_colnames[i,1], fixed=TRUE)) & (!grepl("ISO",valid_colnames[i,1], fixed=TRUE))& (!grepl("BEF",valid_colnames[i,1], fixed=TRUE))){
column <- "data$"
column <- paste(column, valid_colnames[i,1], sep="")
tryCatch(
error = function(cnd) {
print("Unable to analyse data")
res <- FALSE
},
data_table <- as.data.frame(ds.table(column))
)
if(data_table == "empty"){
cannot_analyse_list <- c(cannot_analyse_list,valid_colnames[i,1])
}else{
if (data_table[[1]] == "All studies failed for reasons identified below")
values <- get_values_from_quantiles(column)
else
values <- row.names(data_table)
numeric_col<- paste(valid_colnames[i,1],"_numeric", sep="")
if( valid_colnames[i,1] %in% categoric_vars ){
#is_numeric <- grepl("numeric",valid_colnames[i,1], fixed=TRUE)
has_numeric <- numeric_col %in% valid_colnames$`valid_data_colnames(data_colnames)`
if(!has_numeric)
missing_numeric <- c(missing_numeric, valid_colnames[i,1])
if (data_table[[1]] == "All studies failed for reasons identified below"){
cannot_analyse_list <- c(cannot_analyse_list,valid_colnames[i,1])
}else if(!check_values_categoric(values,valid_colnames[i,1])){
print("Wrong categoric value:")
print(valid_colnames[i,1])
wrong_categoric <- c(wrong_categoric, valid_colnames[i,1])
wrong_categoric_values[[k]] <- values
k <- k+1
}
# if((!is_numeric & !has_numeric) | is_numeric)
}else{
if(grepl("numeric", valid_colnames[i,1],fixed=TRUE))
new_colname <- strsplit(x=valid_colnames[i,1],split="_")[[1]][1]
else
new_colname <- valid_colnames[i,1]
valid <- check_values_not_categoric(values, new_colname)
if (FALSE %in% valid){
invalid_name_list <- c(invalid_name_list,valid_colnames[i,1])
invalid_values_list[[j]] <- values
j <- j+1
}
#print(valid_colnames[i,1])
#print(values)
}#else
# print("This variable has a numeric version")
}
}
}
missing_numeric
if(length(invalid_name_list)>0 | length(wrong_categoric)>0 | length(missing_numeric)>0){
res <- notify_error(invalid_name_list, invalid_values_list, wrong_categoric, wrong_categoric_values, missing_numeric)
}else{
res <- "All values are valid \n"
}
if(length(cannot_analyse_list)>0){
res <- paste(res, "\n############################################################################ \n", sep="")
res <- paste(res, notify_unable_analyse(cannot_analyse_list), sep="\n" )
}
return(res)
}
notify_unable_analyse <- function(x){
res <- "\nCould not obtain data from the fields:"
for(i in 1:length(x)){
res <- paste(res, x[i], sep=" ")
}
return (res)
}
auxConnections <- connect()
connections <- auxConnections[[1]]
inp <- auxConnections[[2]]
#Conexión a la base de datos
ds.dim("data", datasources = connections)
ds.colnames("data")
#----------------------------------------------------------------------------
#Check valid column names
datastructure_name <- "data"
data_colnames <- ds.colnames(x=datastructure_name, datasources= connections)
data_colnames <- as.data.frame(data_colnames)
check_valid_columns <- check_column_names(data_colnames)
valid_colnames <- as.data.frame(valid_data_colnames(data_colnames))
#possible_values("CSXCTR")
result <- ""
result<-check_valid_values()
print(check_valid_columns)
datashield.logout(connections)
cat(result)
# ds.dataFrameSubset(df.name = "data", V1.name = "data$DMXWT", "400" , Boolean.operator = '>', newobj = "columna")
# #
# ds.summary("columna$DMXWT")
# ds.dim("columna$DMXWT")
# ds.table("columna$DMXWT")
file_name<- paste(hospital_name,"_invalid_values.txt", sep="")
#ds.heatmapPlot("data$LBDSALSIA", "data$RFXHC_numeric",type="combine", datasources = connections)
#setwd("C:/Users/victor/Desktop/TFG/r-analytics-master/invalid_values")
dir.create("../invalid_values", showWarnings = FALSE)
setwd("../invalid_values")
cat(check_valid_columns,file=file_name,sep="\n")
cat(result,file=file_name,append=TRUE)
datashield.logout(connections)
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment