tests/testthat/test-comorbid-maps-icd9.R

context("comorbidity maps")

test_that("try to induce c++ segfault bug", {
  expect_error(icd9_comorbid(ahrq_test_dat,
    map = icd9_map_ahrq,
    short_code = TRUE
  ),
  regexp = NA
  )
})

test_that("icd9 comorbidities correct, logical to binary ok", {
  ptdf <- icd9_comorbid(simple_pts,
    map = icd9_map_ahrq, short_code = TRUE,
    visit_name = "visit_id", return_df = TRUE
  )
  expect_equal(names(ptdf), c("visit_id", names(icd9_map_ahrq)))
  expect_true(all(vapply(names(icd9_map_ahrq),
    FUN = function(x) is.logical(ptdf[, x]),
    FUN.VALUE = logical(1)
  )))
  ptdflogical <- logical_to_binary(ptdf)
  expect_true(all(vapply(names(icd9_map_ahrq),
    function(x) {
      is.integer(ptdflogical[, x])
    },
    FUN.VALUE = logical(1)
  )))
  # do not expect all the rest of patient data to be returned - we
  # aren't responsible for aggregating other fields by visit_id!
  expect_equal(
    dim(ptdf),
    c(
      length(unique(simple_pts[["visit_id"]])),
      1 + length(icd9_map_ahrq)
    )
  )
  expect_true(
    setequal(names(ptdf), c("visit_id", names(icd9_map_ahrq)))
  )
  expect_true(
    setequal(names(ptdflogical), c("visit_id", names(icd9_map_ahrq)))
  )

  expect_equal(
    logical_to_binary(data.frame(
      a = c("jack", "hayley"),
      b = c(TRUE, FALSE),
      f = c(TRUE, TRUE)
    )),
    data.frame(
      a = c("jack", "hayley"),
      b = c(1, 0),
      f = c(1, 1)
    )
  )
})

test_that("condense big lists of comorbidities", {
  skip_slow("Skipping slow condense big lists of comorbidities")
  # this is a useful but slow (8s on my PC) test because the data weren't
  # generated by just expanding base ranges (which is how the condense works in
  # reverse)
  for (defined_codes in c(TRUE, FALSE)) {
    if (defined_codes) {
      expect_warning(ahrq <- lapply(icd9_map_ahrq[c(1, 30)],
        condense.icd9,
        short_code = TRUE,
        defined = defined_codes
      ))
      expect_warning(qd <- lapply(icd9_map_quan_deyo[c(1, 17)],
        condense.icd9,
        short_code = TRUE,
        defined = defined_codes
      ))
      expect_warning(qe <- lapply(icd9_map_quan_elix[c(1, 31)],
        condense.icd9,
        short_code = TRUE,
        defined = defined_codes
      ))
      expect_warning(elix <- lapply(icd9_map_elix[c(1, 31)],
        condense.icd9,
        defined = defined_codes
      ))
    } else {
      expect_warning(ahrq <- lapply(icd9_map_ahrq[c(1, 30)],
        condense.icd9,
        short_code = TRUE,
        defined = defined_codes
      ),
      regexp = NA
      )
      expect_warning(qd <- lapply(icd9_map_quan_deyo[c(1, 17)],
        condense.icd9,
        short_code = TRUE,
        defined = defined_codes
      ),
      regexp = NA
      )
      expect_warning(qe <- lapply(icd9_map_quan_elix[c(1, 30)],
        condense.icd9,
        short_code = TRUE,
        defined = defined_codes
      ),
      regexp = NA
      )
      expect_warning(elix <- lapply(icd9_map_elix[c(1, 30)],
        condense.icd9,
        short_code = TRUE,
        defined = defined_codes
      ),
      regexp = NA
      )
    }
    expect_is(ahrq, class = "list")
    expect_is(elix, class = "list")
    expect_is(qd, class = "list")
    expect_is(qe, class = "list")
    # the comorbidity mappings save in \code{data} should not be condensed.
    expect_false(isTRUE(all.equal(ahrq, icd9_map_ahrq)))
    expect_false(isTRUE(all.equal(qd, icd9_map_quan_deyo)))
    expect_false(isTRUE(all.equal(qe, icd9_map_quan_elix)))
    expect_false(isTRUE(all.equal(elix, icd9_map_elix)))
  }
})

test_that("Charlson Deyo doesn't double count disease with two severities", {
  expect_false(any(icd9_map_quan_deyo[["LiverMild"]] %in% icd9_map_quan_deyo[["LiverSevere"]]))
  expect_false(any(icd9_map_quan_deyo$Cancer %in% icd9_map_quan_deyo$Mets))
  expect_false(any(icd9_map_quan_deyo$DM %in% icd9_map_quan_deyo$DMcx))
})

test_that("Elixhauser doesn't double count disease with multiple severities", {
  expect_false(any(icd9_map_quan_elix[["DM"]] %in%
    icd9_map_quan_elix[["DMcx"]]))
  expect_false(any(icd9_map_quan_elix[["Tumor"]] %in%
    icd9_map_quan_elix[["Mets"]]))
  expect_false(any(icd9_map_elix[["DM"]] %in%
    icd9_map_elix[["DMcx"]]))
  expect_false(any(icd9_map_elix[["Tumor"]] %in%
    icd9_map_elix[["Mets"]]))
  expect_false(any(icd9_map_ahrq[["DM"]] %in% icd9_map_ahrq[["DMcx"]]))
  expect_false(any(icd9_map_ahrq[["Tumor"]] %in% icd9_map_ahrq[["Mets"]]))
})

# next couple of tests demonstrate that the interpreted data is correctly
# transcribed in cases where the data is structured differently, and also
# affirms that 'child' codes are included in the RData mappings in the package.
# E.g. if the mapping specifies "044", we do expect 111 total codes to be in the
# mapping 0440 04400 04401 etc. Ahrq
test_that("ICD-9 codes from SAS source AHRQ exist", {
  # specific codes that have had parsing problems in the past:
  expect_true("3970" %in% icd9_map_ahrq$Valvular)
  expect_true("39706" %in% icd9_map_ahrq$Valvular)
  expect_true("3971" %in% icd9_map_ahrq$Valvular)
  expect_true("3979" %in% icd9_map_ahrq$Valvular)
  # SAS source is "7463 "-"7466 "
  expect_true("7463" %in% icd9_map_ahrq$Valvular)
  expect_true("7466" %in% icd9_map_ahrq$Valvular)
  expect_true("74645" %in% icd9_map_ahrq$Valvular)
  # "3420 "-"3449 ",
  # "43820"-"43853",
  # "78072"         = "PARA"      /* Paralysis */
  expect_true("43820" %in% icd9_map_ahrq$Paralysis)
  expect_true("43822" %in% icd9_map_ahrq$Paralysis)
  expect_true("43850" %in% icd9_map_ahrq$Paralysis)
  expect_true("43852" %in% icd9_map_ahrq$Paralysis)
  expect_true("43853" %in% icd9_map_ahrq$Paralysis)
  # although 4385 implies an overly broad range, all its children are in the
  # requested range, so it should appear.
  expect_true("4383" %in% icd9_map_ahrq$Paralysis)
  expect_true("4384" %in% icd9_map_ahrq$Paralysis)
  expect_true("4385" %in% icd9_map_ahrq$Paralysis)
  expect_false("438" %in% icd9_map_ahrq$Paralysis)
  expect_false("4386" %in% icd9_map_ahrq$Paralysis)
  # neuro other problem codes
  #   "3411 "-"3419 ",
  #   "34500"-"34511",
  #   "3452 "-"3453 ",
  #   "34540"-"34591",
  #   "34700"-"34701",
  #   "34710"-"34711",
  expect_true("3337" %in% icd9_map_ahrq[["NeuroOther"]])
  # single value sub-code - zero not defined in 2015
  expect_true("33371" %in% icd9_map_ahrq[["NeuroOther"]])
  expect_true("494" %in% icd9_map_ahrq$Pulmonary) # top-level at start of range
  expect_true("4940" %in% icd9_map_ahrq$Pulmonary) # value within range
  expect_true("49400" %in% icd9_map_ahrq$Pulmonary) # sub-value within range
  expect_true("3450" %in% icd9_map_ahrq[["NeuroOther"]])
  expect_true("34500" %in% icd9_map_ahrq[["NeuroOther"]])
  expect_true("3451" %in% icd9_map_ahrq[["NeuroOther"]])
  expect_true("34511" %in% icd9_map_ahrq[["NeuroOther"]])
  expect_true("34519" %in% icd9_map_ahrq[["NeuroOther"]])
  expect_true("3452" %in% icd9_map_ahrq[["NeuroOther"]])
  expect_true("34529" %in% icd9_map_ahrq[["NeuroOther"]])
  expect_true("3453" %in% icd9_map_ahrq[["NeuroOther"]])
  expect_true("34539" %in% icd9_map_ahrq[["NeuroOther"]])
  expect_true("3459" %in% icd9_map_ahrq[["NeuroOther"]])
  expect_true("34599" %in% icd9_map_ahrq[["NeuroOther"]]) # by implication
  #   "490  "-"4928 ",
  #   "49300"-"49392", # this is all of asthma
  #   "494  "-"4941 ", # bronchiectasis is just 494, 4940 and 4941
  #   "4950 "-"505  ",
  #   "5064 "         = "CHRNLUNG"  /* Chronic pulmonary disease */
  expect_true("492" %in% icd9_map_ahrq$Pulmonary) # implied, and more below
  expect_true("4929" %in% icd9_map_ahrq$Pulmonary)
  expect_true("4920" %in% icd9_map_ahrq$Pulmonary)
  expect_true("4928" %in% icd9_map_ahrq$Pulmonary)
  expect_true("493" %in% icd9_map_ahrq$Pulmonary)
  expect_true("49392" %in% icd9_map_ahrq$Pulmonary)
  expect_true("49300" %in% icd9_map_ahrq$Pulmonary)
  expect_true("49322" %in% icd9_map_ahrq$Pulmonary) # implied intermediate
  expect_true("494" %in% icd9_map_ahrq$Pulmonary)
  expect_true("4940" %in% icd9_map_ahrq$Pulmonary)
  expect_true("4941" %in% icd9_map_ahrq$Pulmonary)
  expect_true("49499" %in% icd9_map_ahrq$Pulmonary) # implied
  #   "25000"-"25033",
  #   "64800"-"64804",
  #   "24900"-"24931" = "DM"        /* Diabetes w/o chronic complications*/
  expect_false("249" %in% icd9_map_ahrq$DM)
  expect_false("2494" %in% icd9_map_ahrq$DM)
  expect_false("24941" %in% icd9_map_ahrq$DM)
  expect_true("24900" %in% icd9_map_ahrq$DM)
  expect_true("24931" %in% icd9_map_ahrq$DM)
  expect_true("24939" %in% icd9_map_ahrq$DM)
  expect_true("2493" %in% icd9_map_ahrq$DM)
  expect_false("2504" %in% icd9_map_ahrq$DM)
  expect_false("25043" %in% icd9_map_ahrq$DM)
  expect_false("250" %in% icd9_map_ahrq$DM)
  expect_true("25000" %in% icd9_map_ahrq$DM)
  expect_true("25029" %in% icd9_map_ahrq$DM) # implied
  expect_true("25033" %in% icd9_map_ahrq$DM)
  expect_true("2503" %in% icd9_map_ahrq$DM) # implied
  expect_true("25039" %in% icd9_map_ahrq$DM) # implied
  #   "25040"-"25093",
  #   "7751 ",
  #   "24940"-"24991" = "DMCX"      /* Diabetes w/ chronic complications */
  expect_false("250" %in% icd9_map_ahrq$DMcx)
  expect_false("2503" %in% icd9_map_ahrq$DMcx)
  expect_true("2509" %in% icd9_map_ahrq$DMcx) # implied
  expect_true("25093" %in% icd9_map_ahrq$DMcx)
  expect_true("25099" %in% icd9_map_ahrq$DMcx) # implied
  expect_false("249" %in% icd9_map_ahrq$DMcx)
  expect_true("2499" %in% icd9_map_ahrq$DMcx)
  expect_true("2498" %in% icd9_map_ahrq$DMcx)
  expect_true("24999" %in% icd9_map_ahrq$DMcx)
  expect_true("24991" %in% icd9_map_ahrq$DMcx)
  #   "243  "-"2442 ",
  #   "2448 ",
  #   "2449 "         = "HYPOTHY"   /* Hypothyroidism */
  expect_false("244" %in% icd9_map_ahrq$Hypothyroid) # some kids not included
  expect_false("2443" %in% icd9_map_ahrq$Hypothyroid) # excluded by Quan
  expect_false("24430" %in% icd9_map_ahrq$Hypothyroid) # implied exclusion
  expect_true("2442" %in% icd9_map_ahrq$Hypothyroid)
  expect_true("243" %in% icd9_map_ahrq$Hypothyroid) # top level billable code
  expect_true("2430" %in% icd9_map_ahrq$Hypothyroid) # implied, doesn't exist
  expect_true("24300" %in% icd9_map_ahrq$Hypothyroid) # implied
  expect_true("2448" %in% icd9_map_ahrq$Hypothyroid)
  expect_true("2449" %in% icd9_map_ahrq$Hypothyroid)
  expect_true("24480" %in% icd9_map_ahrq$Hypothyroid)
  expect_true("24499" %in% icd9_map_ahrq$Hypothyroid)
  #      "V560 "-"V5632",
  expect_true("V560" %in% icd9_map_ahrq$Renal)
  expect_true("V563" %in% icd9_map_ahrq$Renal)
  expect_true("V5632" %in% icd9_map_ahrq$Renal)
  expect_true("V568" %in% icd9_map_ahrq$Renal)
  expect_false("V56" %in% icd9_map_ahrq$Renal)
  #   "20000"-"20238",
  #   "20250"-"20301",
  #   "2386 ",
  #   "2733 ",
  #   "20302"-"20382" = "LYMPH"     /* Lymphoma */
  expect_true("200" %in% icd9_map_ahrq$Lymphoma)
  expect_true("2000" %in% icd9_map_ahrq$Lymphoma)
  expect_true("20000" %in% icd9_map_ahrq$Lymphoma)
  expect_true("201" %in% icd9_map_ahrq$Lymphoma)
  expect_true("20100" %in% icd9_map_ahrq$Lymphoma)
  expect_true("20199" %in% icd9_map_ahrq$Lymphoma)
  expect_false("202" %in% icd9_map_ahrq$Lymphoma)
  expect_false("2024" %in% icd9_map_ahrq$Lymphoma)
  expect_false("20240" %in% icd9_map_ahrq$Lymphoma)
  expect_false("20248" %in% icd9_map_ahrq$Lymphoma)
  expect_false("20249" %in% icd9_map_ahrq$Lymphoma)
  expect_true("2025" %in% icd9_map_ahrq$Lymphoma)
  expect_true("20250" %in% icd9_map_ahrq$Lymphoma)
  expect_true("20258" %in% icd9_map_ahrq$Lymphoma)
  expect_true("20259" %in% icd9_map_ahrq$Lymphoma)
  expect_true("20298" %in% icd9_map_ahrq$Lymphoma)
  expect_true("20299" %in% icd9_map_ahrq$Lymphoma)
  # 2030 and 203 are parents: problem because this range is split
  expect_true("2031" %in% icd9_map_ahrq$Lymphoma)
  expect_true("20310" %in% icd9_map_ahrq$Lymphoma)
  expect_true("20300" %in% icd9_map_ahrq$Lymphoma)
  expect_true("20301" %in% icd9_map_ahrq$Lymphoma)
  # "1960 "-"1991 ",
  expect_true("196" %in% icd9_map_ahrq$Mets)
  expect_true("1960" %in% icd9_map_ahrq$Mets)
  expect_true("19600" %in% icd9_map_ahrq$Mets)
  expect_true("1969" %in% icd9_map_ahrq$Mets)
  expect_true("19699" %in% icd9_map_ahrq$Mets)
  expect_true("197" %in% icd9_map_ahrq$Mets)
  expect_true("1970" %in% icd9_map_ahrq$Mets)
  expect_true("19700" %in% icd9_map_ahrq$Mets)
  expect_true("19799" %in% icd9_map_ahrq$Mets)
  expect_true("198" %in% icd9_map_ahrq$Mets)
  expect_true("1980" %in% icd9_map_ahrq$Mets)
  expect_true("19800" %in% icd9_map_ahrq$Mets)
  expect_true("19899" %in% icd9_map_ahrq$Mets)
  expect_true("1990" %in% icd9_map_ahrq$Mets)
  expect_true("19900" %in% icd9_map_ahrq$Mets)
  expect_true("19909" %in% icd9_map_ahrq$Mets)
  expect_true("1991" %in% icd9_map_ahrq$Mets)
  expect_true("19910" %in% icd9_map_ahrq$Mets)
  expect_true("19919" %in% icd9_map_ahrq$Mets)
  expect_false("199" %in% icd9_map_ahrq$Mets)
  expect_false("1992" %in% icd9_map_ahrq$Mets)
  expect_false("19920" %in% icd9_map_ahrq$Mets)
  expect_false("19929" %in% icd9_map_ahrq$Mets)
  expect_false("1993" %in% icd9_map_ahrq$Mets) # implied
  expect_false("19930" %in% icd9_map_ahrq$Mets) # implied
  expect_false("19999" %in% icd9_map_ahrq$Mets) # implied
  #   "179  "-"1958 ",
  #   "20900"-"20924",
  #   "20925"-"2093 ",
  #   "20930"-"20936",
  expect_true("195" %in% icd9_map_ahrq$Tumor) # all children, so implied
  expect_true("1950" %in% icd9_map_ahrq$Tumor)
  expect_true("1958" %in% icd9_map_ahrq$Tumor)
  expect_true("19589" %in% icd9_map_ahrq$Tumor)
  expect_true("1959" %in% icd9_map_ahrq$Tumor)
  expect_true("19599" %in% icd9_map_ahrq$Tumor)
  expect_false("209" %in% icd9_map_ahrq$Tumor)
  expect_false("2094" %in% icd9_map_ahrq$Tumor)
  expect_false("20940" %in% icd9_map_ahrq$Tumor)
  expect_false("2099" %in% icd9_map_ahrq$Tumor)
  expect_false("20999" %in% icd9_map_ahrq$Tumor)
  expect_false("2097" %in% icd9_map_ahrq$Tumor)
  expect_false("20979" %in% icd9_map_ahrq$Tumor)
  expect_true("20936" %in% icd9_map_ahrq$Tumor)
  expect_true("2093" %in% icd9_map_ahrq$Tumor)
  expect_true("20930" %in% icd9_map_ahrq$Tumor)
  expect_true("20939" %in% icd9_map_ahrq$Tumor)
  expect_true("2090" %in% icd9_map_ahrq$Tumor)
  expect_true("2091" %in% icd9_map_ahrq$Tumor)
  # is range split between definitions? ideally this would be included, but it
  # is a corner case e.g. 2092
  expect_true("20900" %in% icd9_map_ahrq$Tumor)
  expect_true("20910" %in% icd9_map_ahrq$Tumor)
  expect_true("20920" %in% icd9_map_ahrq$Tumor)
  expect_true("20907" %in% icd9_map_ahrq$Tumor)
  expect_true("20917" %in% icd9_map_ahrq$Tumor)
  expect_true("20927" %in% icd9_map_ahrq$Tumor)
  expect_true("20909" %in% icd9_map_ahrq$Tumor)
  expect_true("20919" %in% icd9_map_ahrq$Tumor)
  expect_true("20929" %in% icd9_map_ahrq$Tumor)
  #   "2871 ",
  #   "2873 "-"2875 ", # coag
  expect_true("2871" %in% icd9_map_ahrq$Coagulopathy)
  # doesn't exist but really should work simply
  expect_true("28710" %in% icd9_map_ahrq$Coagulopathy)
  # doesn't exist but really should work simply
  expect_true("28719" %in% icd9_map_ahrq$Coagulopathy)
  expect_false("287" %in% icd9_map_ahrq$Coagulopathy)
  expect_false("2872" %in% icd9_map_ahrq$Coagulopathy)
  expect_false("28720" %in% icd9_map_ahrq$Coagulopathy)
  expect_false("28729" %in% icd9_map_ahrq$Coagulopathy)
  expect_true("2873" %in% icd9_map_ahrq$Coagulopathy)
  expect_true("28730" %in% icd9_map_ahrq$Coagulopathy)
  expect_true("28739" %in% icd9_map_ahrq$Coagulopathy)
  expect_true("2874" %in% icd9_map_ahrq$Coagulopathy)
  expect_true("28741" %in% icd9_map_ahrq$Coagulopathy)
  expect_true("28749" %in% icd9_map_ahrq$Coagulopathy)
  expect_true("2875" %in% icd9_map_ahrq$Coagulopathy)
  expect_true("28759" %in% icd9_map_ahrq$Coagulopathy)
  expect_false("2876" %in% icd9_map_ahrq$Coagulopathy)
  expect_false("28760" %in% icd9_map_ahrq$Coagulopathy)
  expect_false("28769" %in% icd9_map_ahrq$Coagulopathy)
  expect_false("2878" %in% icd9_map_ahrq$Coagulopathy)
  expect_false("2879" %in% icd9_map_ahrq$Coagulopathy)
  expect_false("28799" %in% icd9_map_ahrq$Coagulopathy)
  #   "2910 "-"2913 ",
  #   "2915 ",
  #   "2918 ",
  #   "29181",
  #   "29182",
  #   "29189",
  #   "2919 ",
  #   "30300"-"30393",
  #   "30500"-"30503" = "ALCOHOL"   /* Alcohol abuse */
  expect_true("2910" %in% icd9_map_ahrq$Alcohol)
  expect_true("2913" %in% icd9_map_ahrq$Alcohol)
  expect_true("2915" %in% icd9_map_ahrq$Alcohol)
  expect_true("2918" %in% icd9_map_ahrq$Alcohol)
  expect_true("29181" %in% icd9_map_ahrq$Alcohol)
  expect_true("29182" %in% icd9_map_ahrq$Alcohol)
  expect_true("29189" %in% icd9_map_ahrq$Alcohol)
  expect_true("2919" %in% icd9_map_ahrq$Alcohol)
  expect_false("291" %in% icd9_map_ahrq$Alcohol)
  expect_false("2914" %in% icd9_map_ahrq$Alcohol)
  expect_false("29140" %in% icd9_map_ahrq$Alcohol)
  expect_false("29149" %in% icd9_map_ahrq$Alcohol)
  #   "2920 ",
  #   "29282"-"29289",
  #   "2929 ",
  #   "30400"-"30493",
  #   "30520"-"30593",
  #   "64830"-"64834" = "DRUG"      /* Drug abuse */
  expect_true("304" %in% icd9_map_ahrq$Drugs)
  expect_true("3040" %in% icd9_map_ahrq$Drugs)
  expect_true("30400" %in% icd9_map_ahrq$Drugs)
  expect_true("3049" %in% icd9_map_ahrq$Drugs)
  expect_true("30493" %in% icd9_map_ahrq$Drugs)
  expect_false("305" %in% icd9_map_ahrq$Drugs)
  expect_false("3050" %in% icd9_map_ahrq$Drugs)
  expect_false("30500" %in% icd9_map_ahrq$Drugs)
  expect_false("3051" %in% icd9_map_ahrq$Drugs)
  expect_false("30510" %in% icd9_map_ahrq$Drugs)
  expect_true("3052" %in% icd9_map_ahrq$Drugs)
  expect_true("30520" %in% icd9_map_ahrq$Drugs)
  expect_true("30523" %in% icd9_map_ahrq$Drugs)
  expect_true("3059" %in% icd9_map_ahrq$Drugs)
  expect_true("30593" %in% icd9_map_ahrq$Drugs)
})

test_that("ICD-9 codes from SAS source for Quan Deyo Charlson exist", {
  # Quan Deyo Charlson
  # top level single value
  expect_true("410" %in% icd9_map_quan_deyo$MI)
  # this is not included (410 and 412 defined)
  expect_false("411" %in% icd9_map_quan_deyo$MI)
  # this is not included (410 and 412 defined)
  expect_false("41199" %in% icd9_map_quan_deyo$MI)
  # midlevel value, not from range
  expect_true("4100" %in% icd9_map_quan_deyo$MI)
  # lower-level value, not from range
  expect_true("41001" %in% icd9_map_quan_deyo$MI)
  # midlevel definition
  expect_true("2504" %in% icd9_map_quan_deyo$DMcx)
  # midlevel definition lower-level code
  expect_true("25041" %in% icd9_map_quan_deyo$DMcx)
})

# the following two tests cover the mappings in which there was no source SAS
# data, but the numbers were transcribed manually. This is therefore testing a
# little of the transcription, and also the elobration of codes definied in
# ranges
test_that("ICD-9 codes from manually specified Quan Elix mapping exist", {
  expect_true("2500" %in% icd9_map_quan_elix$DM)
  expect_true("2501" %in% icd9_map_quan_elix$DM)
  expect_true("25011" %in% icd9_map_quan_elix$DM)
  expect_true("276" %in% icd9_map_quan_elix[["FluidsLytes"]])
  expect_true("2761" %in% icd9_map_quan_elix[["FluidsLytes"]])
  expect_true("27612" %in% icd9_map_quan_elix[["FluidsLytes"]])
  # top level should not be included automatically
  expect_false("710" %in% icd9_map_quan_elix[["FluidsLytes"]])
})

test_that("ICD-9 codes from manually specified Elixhauser mapping exist", {
  expect_true("09320" %in% icd9_map_elix$Valvular)
  expect_true("3971" %in% icd9_map_elix$Valvular)
  expect_true("V560" %in% icd9_map_elix$Renal)
  expect_true("V1090" %in% icd9_map_elix$Tumor) # child at end of a V range
})

test_that("github #34 - short and long custom map give different results", {
  mydf <- data.frame(
    visit_id = c("a", "b", "b", "c"),
    icd9 = c("001", "010", "010", "020")
  )
  mymaps <- list(jack = c("1", "2", "3"), alf = c("010", "20"))
  mymapd <- lapply(mymaps, icd:::short_to_decimal.icd9)
  expect_identical(
    icd9_comorbid(mydf, map = mymaps, short_code = TRUE, short_map = FALSE),
    icd9_comorbid(mydf, map = mymapd, short_code = FALSE, short_map = FALSE)
  )
})

test_that("no NA values in the co-morbidity lists", {
  expect_false(anyNA(unlist(unname(icd9_map_ahrq))))
  expect_false(anyNA(unlist(unname(icd9_map_quan_deyo))))
  expect_false(anyNA(unlist(unname(icd9_map_quan_elix))))
  expect_false(anyNA(unlist(unname(icd9_map_elix))))
})

test_that("no duplicate values in the co-morbidity lists", {
  expect_false(any(as.logical(lapply(icd9_map_ahrq, anyDuplicated))))
  expect_false(any(as.logical(lapply(icd9_map_quan_deyo, anyDuplicated))))
  expect_false(any(as.logical(lapply(icd9_map_quan_elix, anyDuplicated))))
  expect_false(any(as.logical(lapply(icd9_map_elix, anyDuplicated))))
})

test_that("built-in icd9 to comorbidity mappings are all valid", {
  expect_true(is_valid.comorbidity_map(icd9_map_ahrq, short_code = TRUE))
  expect_true(is_valid.comorbidity_map(icd9_map_quan_elix, short_code = TRUE))
  expect_true(is_valid.comorbidity_map(icd9_map_quan_elix, short_code = TRUE))
  expect_true(is_valid.comorbidity_map(icd9_map_elix, short_code = TRUE))
})

test_that("disordered visit ids", {
  pts <- data.frame(
    visit_id = c("2", "1", "2", "3", "3"),
    icd9 = c("39891", "40110", "09322", "41514", "39891")
  )
  res <- icd9_comorbid_ahrq(pts, restore_id_order = TRUE)
  expect_equal(rownames(res), c("2", "1", "3"))
})

test_that("diff comorbid works", {
  skip_slow("diff comorbidity maps is relatively slow to test")
  expect_warning(
    utils::capture.output(
      res <- diff_comorbid(icd9_map_ahrq, icd9_map_elix, show = FALSE)
    ),
    regexp = NA
  )
  expect_true(all(names(res) %in% c(
    "CHF", "Valvular", "PHTN", "PVD", "HTN", "HTNcx", "Paralysis",
    "NeuroOther", "Pulmonary", "DM", "DMcx", "Hypothyroid", "Renal",
    "Liver", "PUD", "HIV", "Lymphoma", "Mets", "Tumor", "Rheumatic",
    "Coagulopathy", "Obesity", "WeightLoss", "FluidsLytes", "BloodLoss",
    "Anemia", "Alcohol", "Drugs", "Psychoses", "Depression"
  )))
  # one side diff
  expect_identical(res$Drugs[["only.y"]], character(0))
  # match
  expect_identical(res$Depression[[2]], character(0))
  expect_identical(res$Depression[[3]], character(0))
  # both, also with elements in either side set diff
  expect_equal(res$PUD$both, c("53170", "53270", "53370", "53470"))
  expect_warning(
    expect_output(
      resq <- diff_comorbid(icd9_map_quan_elix, icd9_map_elix, show = TRUE),
      regexp = "Comorbidity Psychoses"
    ),
    regexp = NA
  )
})

pts <- generate_random_pts(101, 13)
ac <- lapply(icd9_map_ahrq, function(x) {
  f <- factor(x, levels(pts[["code"]]))
  f[!is.na(f)]
})

test_that("comorbidities created from source data frame coded as factors", {
  v2 <- wide_to_long(vermont_dx)
  v2$visit_id <- as.factor(v2$visit_id)
  v2$icd_code <- as.factor(v2$icd_code)
  res <- icd9_comorbid_ahrq(v2)
  res_nofactor <- icd9_comorbid_ahrq(wide_to_long(vermont_dx))
  expect_identical(res, res_nofactor)
})

test_that("AHRQ ICD-9 comorbidities are in the ICD-10 maps, in same order", {
  expect_equal_no_icd(names(icd9_map_ahrq), names(icd10_map_ahrq))
  expect_equal_no_icd(names(icd9_map_elix), names(icd10_map_elix))
  expect_equal_no_icd(names(icd9_map_quan_elix), names(icd10_map_quan_elix))
  expect_equal_no_icd(names(icd9_map_quan_deyo), names(icd10_map_quan_deyo))
})

test_that("Charlson synonyms are present", {
  expect_identical(icd9_map_charlson, icd9_map_quan_deyo)
  expect_identical(icd10_map_charlson, icd10_map_quan_deyo)
})

test_that("Quan Elix should only have children of 588.0, not 588", {
  expect_true(all(c("5880", "58809") %in% icd9_map_quan_elix$Renal))
  expect_false(
    any(c("5890", "5881", "58819", "58899") %in% icd9_map_quan_elix$Renal)
  )
})
jackwasey/icd documentation built on Nov. 23, 2021, 9:56 a.m.