Skip to content

Commit

Permalink
Merge pull request #2 from ratschlab/merge-fork
Browse files Browse the repository at this point in the history
Merge fork
  • Loading branch information
manuelburger authored Apr 8, 2024
2 parents d7cc29f + 057ff9a commit 8768729
Show file tree
Hide file tree
Showing 10 changed files with 219 additions and 80 deletions.
27 changes: 27 additions & 0 deletions R/callback-icu-mortality.R
Original file line number Diff line number Diff line change
Expand Up @@ -61,3 +61,30 @@ miiv_death_icu <- function(x, env, ...){
mi_death_icu(x, transfers, icu_wards, ...)
}

picdb_death_icu <- function(x, env, ...){
#' Extract in-ICU mortality from PICdb
#'
#' We rely on a concept-dict config, which passes rows for each `icustay_id`
#' separately (e.g. the `icustays` table). As this table does not contain mortality
#' information we rely on a auxiliary column defined for all patients in PICdb in
#' the chosen table (e.g. `los`).
#' We extract the last ICU stay for each `hadm_id`. We reset the `los` column to be
#' FALSE for each `icustay_id` and set it to TRUE for the `icustay_id` of the last
#' ICU stay of each `hadm_id`, which is marked as deceased.

icu_stays <- load_ts(env[["icustays"]], id_var = "hadm_id", index_var = "intime", interval = mins(1L))
admissions <- load_id(env[["admissions"]], id_var = "hadm_id", cols = c("hospital_expire_flag"))

# For each "hadm_id" we find the "icustay_id" of the last ICU stay based on the "intime"
last_icu_stay <- icu_stays[, .(icustay_id = icustay_id[.N]), by = hadm_id]
deceased_hadm_id <- admissions[ricu:::is_true(hospital_expire_flag), .(hadm_id)]$hadm_id
deceased_icustay_id <- icu_stays[hadm_id %in% deceased_hadm_id, .(icustay_id)]$icustay_id

# For all `icustay_id` not in last_icu_stay, we set the value of the `hospital_expire_flag` variable to FALSE
# Patients only die in the last ICU stay
# `los` should be configured to be the target extraction column as a dummy column
# to put the value of the `hospital_expire_flag` variable
x[, los := FALSE]
x[icustay_id %in% deceased_icustay_id, los := TRUE]
x[!icustay_id %in% last_icu_stay$icustay_id, los := FALSE]
}
37 changes: 33 additions & 4 deletions R/data-load.R
Original file line number Diff line number Diff line change
Expand Up @@ -131,7 +131,7 @@ load_difftime.eicu_tbl <- function(x, rows, cols = colnames(x),

warn_dots(...)

load_eiau(x, {{ rows }}, cols, id_hint, time_vars, min_as_mins)
load_eisi(x, {{ rows }}, cols, id_hint, time_vars, min_as_mins)
}

#' @rdname load_src
Expand All @@ -153,7 +153,7 @@ load_difftime.aumc_tbl <- function(x, rows, cols = colnames(x),

warn_dots(...)

load_eiau(x, {{ rows }}, cols, id_hint, time_vars, ms_as_mins)
load_au(x, {{ rows }}, cols, id_hint, time_vars)
}

#' @rdname load_src
Expand All @@ -175,7 +175,7 @@ load_difftime.sic_tbl <- function(x, rows, cols = colnames(x),

sec_as_mins <- function(x) min_as_mins(as.integer(x / 60))
warn_dots(...)
load_eiau(x, {{ rows }}, cols, id_hint, time_vars, sec_as_mins)
load_eisi(x, {{ rows }}, cols, id_hint, time_vars, sec_as_mins)
}

#' @rdname load_src
Expand Down Expand Up @@ -248,7 +248,7 @@ load_mihi <- function(x, rows, cols, id_hint, time_vars) {
as_id_tbl(dat, id_vars = id_col, by_ref = TRUE)
}

load_eiau <- function(x, rows, cols, id_hint, time_vars, mins_fun) {
load_eisi <- function(x, rows, cols, id_hint, time_vars, mins_fun) {

id_col <- resolve_id_hint(x, id_hint)

Expand All @@ -270,6 +270,35 @@ load_eiau <- function(x, rows, cols, id_hint, time_vars, mins_fun) {
as_id_tbl(dat, id_vars = id_col, by_ref = TRUE)
}

load_au <- function(x, rows, cols, id_hint, time_vars) {
dt_round_min <- function(x, y) round_to(ms_as_mins(x - y))

id_col <- resolve_id_hint(x, id_hint)

assert_that(is.string(id_col), id_col %in% colnames(x))

if (!id_col %in% cols) {
cols <- c(cols, id_col)
}

time_vars <- intersect(time_vars, cols)

dat <- load_src(x, {{ rows }}, cols)

if (length(time_vars)) {

dat <- merge(dat, id_origin(x, id_col, origin_name = "origin"),
by = id_col)
dat <- dat[,
c(time_vars) := lapply(.SD, dt_round_min, get("origin")),
.SDcols = time_vars
]
dat <- dat[, c("origin") := NULL]
}

as_id_tbl(dat, id_vars = id_col, by_ref = TRUE)
}

#' Load data as `id_tbl` or `ts_tbl` objects
#'
#' Building on functionality provided by [load_src()] and [load_difftime()],
Expand Down
4 changes: 2 additions & 2 deletions R/utils-ts.R
Original file line number Diff line number Diff line change
Expand Up @@ -643,11 +643,11 @@ padded_capped_diff <- function(x, final, max) {
trunc_time <- function(x, min, max) {

if (not_null(min)) {
replace(x, x < min, min)
x <- replace(x, x < min, min)
}

if (not_null(max)) {
replace(x, x > max, max)
x <- replace(x, x > max, max)
}

x
Expand Down
109 changes: 57 additions & 52 deletions inst/extdata/config/concept-dict/hematology.json
Original file line number Diff line number Diff line change
Expand Up @@ -73,10 +73,14 @@
"picdb": [
{
"table": "labevents",
"ids": [
5492
],
"ids": 5492,
"sub_var": "itemid"
},
{
"table": "labevents",
"ids": 5493,
"sub_var": "itemid",
"callback": "blood_cell_ratio"
}
]
}
Expand Down Expand Up @@ -139,8 +143,7 @@
"table": "labevents",
"sub_var": "itemid"
}
],
"picdb": []
]
}
},
"eos": {
Expand Down Expand Up @@ -217,9 +220,7 @@
"picdb": [
{
"table": "labevents",
"ids": [
5002
],
"ids": 5002,
"sub_var": "itemid"
}
]
Expand Down Expand Up @@ -274,8 +275,7 @@
"table": "labevents",
"sub_var": "itemid"
}
],
"picdb": []
]
}
},
"fgn": {
Expand Down Expand Up @@ -350,7 +350,14 @@
"class": "sic_itm"
}
],
"picdb": []
"picdb": [
{
"table": "labevents",
"ids": 5164,
"sub_var": "itemid",
"callback": "convert_unit(binary_op(`*`, 100), 'mg/dL', 'g/L')"
}
]
}
},
"hba1c": {
Expand Down Expand Up @@ -398,7 +405,13 @@
"class": "sic_itm"
}
],
"picdb": []
"picdb": [
{
"table": "labevents",
"ids": [5628, 6070],
"sub_var": "itemid"
}
]
}
},
"hct": {
Expand Down Expand Up @@ -567,7 +580,8 @@
5099,
5257
],
"sub_var": "itemid"
"sub_var": "itemid",
"callback": "convert_unit(binary_op(`*`, 0.1), 'g/dL', 'g/L')"
}
]
}
Expand Down Expand Up @@ -626,8 +640,7 @@
"table": "labevents",
"sub_var": "itemid"
}
],
"picdb": []
]
}
},
"lymph": {
Expand Down Expand Up @@ -710,7 +723,19 @@
"class": "sic_itm"
}
],
"picdb": []
"picdb": [
{
"table": "labevents",
"ids": [5006, 5503, 5111, 5503],
"sub_var": "itemid"
},
{
"table": "labevents",
"ids": 5110,
"sub_var": "itemid",
"callback": "blood_cell_ratio"
}
]
}
},
"mch": {
Expand Down Expand Up @@ -782,9 +807,7 @@
"picdb": [
{
"table": "labevents",
"ids": [
5113
],
"ids": 5113,
"sub_var": "itemid"
}
]
Expand Down Expand Up @@ -862,10 +885,9 @@
"picdb": [
{
"table": "labevents",
"ids": [
5114
],
"sub_var": "itemid"
"ids": 5114,
"sub_var": "itemid",
"callback": "convert_unit(binary_op(`*`, 0.1), '%')"
}
]
}
Expand Down Expand Up @@ -939,9 +961,7 @@
"picdb": [
{
"table": "labevents",
"ids": [
5115
],
"ids": 5115,
"sub_var": "itemid"
}
]
Expand Down Expand Up @@ -1033,9 +1053,7 @@
"picdb": [
{
"table": "labevents",
"ids": [
5094
],
"ids": [5005, 5094, 5095, 5511],
"sub_var": "itemid"
}
]
Expand Down Expand Up @@ -1118,9 +1136,7 @@
"picdb": [
{
"table": "labevents",
"ids": [
5129
],
"ids": 5129,
"sub_var": "itemid"
}
]
Expand Down Expand Up @@ -1186,11 +1202,9 @@
"picdb": [
{
"table": "labevents",
"ids": [
5186,
6890
],
"sub_var": "itemid"
"ids": [5186, 6890],
"sub_var": "itemid",
"callback": "convert_unit(identity_callback, 'sec')"
}
]
}
Expand Down Expand Up @@ -1263,10 +1277,9 @@
"picdb": [
{
"table": "labevents",
"ids": [
5161
],
"sub_var": "itemid"
"ids": 5161,
"sub_var": "itemid",
"callback": "convert_unit(identity_callback, 'sec')"
}
]
}
Expand Down Expand Up @@ -1336,11 +1349,7 @@
"picdb": [
{
"table": "labevents",
"ids": [
5379,
5381,
6515
],
"ids": 5132,
"sub_var": "itemid"
}
]
Expand Down Expand Up @@ -1399,9 +1408,7 @@
"picdb": [
{
"table": "labevents",
"ids": [
5136
],
"ids": 5136,
"sub_var": "itemid"
}
]
Expand Down Expand Up @@ -1481,9 +1488,7 @@
"picdb": [
{
"table": "labevents",
"ids": [
6516
],
"ids": 5141,
"sub_var": "itemid"
}
]
Expand Down
Loading

0 comments on commit 8768729

Please sign in to comment.