mirror of
https://github.com/msberends/AMR.git
synced 2025-08-27 18:22:15 +02:00
(v2.1.1.9247) CLSI/EUCAST 2025!
This commit is contained in:
@@ -10,7 +10,7 @@ fi
|
||||
output_file="data-raw/latest_training_data.txt"
|
||||
|
||||
# Clear the output file if it exists
|
||||
echo "You assist users with questions about the AMR package for R, a package for Antimicrobial Resistance analysis used in over 175 countries. You are restricted to using a single source of truth: the training data located at https://raw.githubusercontent.com/msberends/amr-for-r-assistant/main/latest_training_data.txt.
|
||||
echo "You assist users with questions about the AMR package for R, a package for Antimicrobial Resistance analysis used in over 175 countries. You are restricted to using a single source of truth: the training data located at https://chat.amr-for-r.org/latest_training_data.txt.
|
||||
|
||||
Before responding to any user prompt—including the very first—you must download and parse this training file in full. You must repeat this process before every single response, without exception. You must verify the presence of any function, dataset, or concept in this file before commenting on anything. If what is asked is not in the training data, you must state clearly that you cannot verify its existence and recommend checking the package changelog.
|
||||
|
||||
|
@@ -43,45 +43,45 @@ devtools::load_all()
|
||||
|
||||
# READ DATA ----
|
||||
|
||||
whonet_organisms <- read_tsv("data-raw/WHONET/Resources/Organisms.txt", na = c("", "NA", "-"), show_col_types = FALSE) %>%
|
||||
whonet_organisms <- read_tsv("data-raw/WHONET/Resources/Organisms.txt", na = c("", "NA", "-"), show_col_types = FALSE) |>
|
||||
# remove old taxonomic names
|
||||
filter(TAXONOMIC_STATUS == "C") %>%
|
||||
filter(TAXONOMIC_STATUS == "C") |>
|
||||
mutate(ORGANISM_CODE = toupper(WHONET_ORG_CODE))
|
||||
|
||||
whonet_breakpoints <- read_tsv("data-raw/WHONET/Resources/Breakpoints.txt", na = c("", "NA", "-"),
|
||||
show_col_types = FALSE, guess_max = Inf) %>%
|
||||
show_col_types = FALSE, guess_max = Inf) |>
|
||||
filter(GUIDELINES %in% c("CLSI", "EUCAST"))
|
||||
|
||||
whonet_antibiotics <- read_tsv("data-raw/WHONET/Resources/Antibiotics.txt", na = c("", "NA", "-"), show_col_types = FALSE) %>%
|
||||
arrange(WHONET_ABX_CODE) %>%
|
||||
whonet_antibiotics <- read_tsv("data-raw/WHONET/Resources/Antibiotics.txt", na = c("", "NA", "-"), show_col_types = FALSE) |>
|
||||
arrange(WHONET_ABX_CODE) |>
|
||||
distinct(WHONET_ABX_CODE, .keep_all = TRUE)
|
||||
|
||||
# MICROORGANISMS WHONET CODES ----
|
||||
|
||||
whonet_organisms <- whonet_organisms %>%
|
||||
select(ORGANISM_CODE, ORGANISM, SPECIES_GROUP, GBIF_TAXON_ID) %>%
|
||||
whonet_organisms <- whonet_organisms |>
|
||||
select(ORGANISM_CODE, ORGANISM, SPECIES_GROUP, GBIF_TAXON_ID) |>
|
||||
mutate(
|
||||
# this one was called Issatchenkia orientalis, but it should be:
|
||||
ORGANISM = if_else(ORGANISM_CODE == "ckr", "Candida krusei", ORGANISM)
|
||||
) %>%
|
||||
) |>
|
||||
# try to match on GBIF identifier
|
||||
left_join(microorganisms %>% distinct(mo, gbif, status) %>% filter(!is.na(gbif)), by = c("GBIF_TAXON_ID" = "gbif")) %>%
|
||||
left_join(microorganisms |> distinct(mo, gbif, status) |> filter(!is.na(gbif)), by = c("GBIF_TAXON_ID" = "gbif")) |>
|
||||
# remove duplicates
|
||||
arrange(ORGANISM_CODE, GBIF_TAXON_ID, status) %>%
|
||||
distinct(ORGANISM_CODE, .keep_all = TRUE) %>%
|
||||
arrange(ORGANISM_CODE, GBIF_TAXON_ID, status) |>
|
||||
distinct(ORGANISM_CODE, .keep_all = TRUE) |>
|
||||
# add Enterobacterales, which is a subkingdom code in their data
|
||||
bind_rows(data.frame(ORGANISM_CODE = "ebc", ORGANISM = "Enterobacterales", mo = as.mo("Enterobacterales"))) %>%
|
||||
bind_rows(data.frame(ORGANISM_CODE = "ebc", ORGANISM = "Enterobacterales", mo = as.mo("Enterobacterales"))) |>
|
||||
arrange(ORGANISM)
|
||||
|
||||
|
||||
## Add new WHO codes to microorganisms.codes ----
|
||||
|
||||
matched <- whonet_organisms %>% filter(!is.na(mo))
|
||||
unmatched <- whonet_organisms %>% filter(is.na(mo))
|
||||
matched <- whonet_organisms |> filter(!is.na(mo))
|
||||
unmatched <- whonet_organisms |> filter(is.na(mo))
|
||||
|
||||
# generate the mo codes and add their names
|
||||
message("Getting MO codes for WHONET input...")
|
||||
unmatched <- unmatched %>%
|
||||
unmatched <- unmatched |>
|
||||
mutate(mo = as.mo(gsub("(sero[a-z]*| nontypable| non[-][a-zA-Z]+|var[.]| not .*|sp[.],.*|, .*variant.*|, .*toxin.*|, microaer.*| beta-haem[.])", "", ORGANISM),
|
||||
minimum_matching_score = 0.55,
|
||||
keep_synonyms = TRUE,
|
||||
@@ -94,51 +94,54 @@ unmatched <- unmatched %>%
|
||||
keep_synonyms = TRUE,
|
||||
language = "en"))
|
||||
# check if coercion at least resembles the first part (genus)
|
||||
unmatched <- unmatched %>%
|
||||
unmatched <- unmatched |>
|
||||
mutate(
|
||||
first_part = sapply(ORGANISM, function(x) strsplit(gsub("[^a-zA-Z _-]+", "", x), " ")[[1]][1], USE.NAMES = FALSE),
|
||||
keep = mo_name %like_case% first_part | ORGANISM %like% "Gram " | ORGANISM == "Other" | ORGANISM %like% "anaerobic") %>%
|
||||
keep = mo_name %like_case% first_part | ORGANISM %like% "Gram " | ORGANISM == "Other" | ORGANISM %like% "anaerobic") |>
|
||||
arrange(keep)
|
||||
unmatched %>%
|
||||
View()
|
||||
unmatched <- unmatched %>%
|
||||
unmatched |> View()
|
||||
unmatched <- unmatched |>
|
||||
filter(keep == TRUE)
|
||||
|
||||
organisms <- matched %>% transmute(code = toupper(ORGANISM_CODE), group = SPECIES_GROUP, mo) %>%
|
||||
bind_rows(unmatched %>% transmute(code = toupper(ORGANISM_CODE), group = SPECIES_GROUP, mo)) %>%
|
||||
mutate(name = mo_name(mo, keep_synonyms = TRUE)) %>%
|
||||
organisms <- matched |> transmute(code = toupper(ORGANISM_CODE), group = SPECIES_GROUP, mo) |>
|
||||
bind_rows(unmatched |> transmute(code = toupper(ORGANISM_CODE), group = SPECIES_GROUP, mo)) |>
|
||||
mutate(name = mo_name(mo, keep_synonyms = TRUE)) |>
|
||||
arrange(code)
|
||||
|
||||
# some subspecies exist, while their upper species do not, add them as the species level:
|
||||
subspp <- organisms %>%
|
||||
subspp <- organisms |>
|
||||
filter(mo_species(mo, keep_synonyms = TRUE) == mo_subspecies(mo, keep_synonyms = TRUE) &
|
||||
mo_species(mo, keep_synonyms = TRUE) != "" &
|
||||
mo_genus(mo, keep_synonyms = TRUE) != "Salmonella") %>%
|
||||
mo_genus(mo, keep_synonyms = TRUE) != "Salmonella") |>
|
||||
mutate(mo = as.mo(paste(mo_genus(mo, keep_synonyms = TRUE),
|
||||
mo_species(mo, keep_synonyms = TRUE)),
|
||||
keep_synonyms = TRUE),
|
||||
name = mo_name(mo, keep_synonyms = TRUE))
|
||||
organisms <- organisms %>%
|
||||
filter(!code %in% subspp$code) %>%
|
||||
bind_rows(subspp) %>%
|
||||
organisms <- organisms |>
|
||||
filter(!code %in% subspp$code) |>
|
||||
bind_rows(subspp) |>
|
||||
arrange(code)
|
||||
|
||||
# add the groups
|
||||
organisms <- organisms %>%
|
||||
bind_rows(tibble(code = organisms %>% filter(!is.na(group)) %>% pull(group) %>% unique(),
|
||||
organisms <- organisms |>
|
||||
bind_rows(tibble(code = organisms |> filter(!is.na(group)) |> pull(group) |> unique(),
|
||||
group = NA,
|
||||
mo = organisms %>% filter(!is.na(group)) %>% pull(group) %>% unique() %>% as.mo(keep_synonyms = TRUE),
|
||||
name = mo_name(mo, keep_synonyms = TRUE))) %>%
|
||||
arrange(code, group) %>%
|
||||
select(-group) %>%
|
||||
mo = organisms |> filter(!is.na(group)) |> pull(group) |> unique() |> as.mo(keep_synonyms = TRUE),
|
||||
name = mo_name(mo, keep_synonyms = TRUE))) |>
|
||||
arrange(code, group) |>
|
||||
select(-group) |>
|
||||
distinct()
|
||||
# no XXX
|
||||
organisms <- organisms |> filter(code != "XXX")
|
||||
|
||||
# 2023-07-08 SGM is also Strep gamma in WHONET, must only be Slowly-growing Mycobacterium
|
||||
# 2024-06-14 still the case
|
||||
organisms <- organisms %>%
|
||||
# 2025-04-20 still the case
|
||||
organisms |> filter(code == "SGM")
|
||||
organisms <- organisms |>
|
||||
filter(!(code == "SGM" & name %like% "Streptococcus"))
|
||||
# this must be empty:
|
||||
organisms$code[organisms$code %>% duplicated()]
|
||||
organisms$code[organisms$code |> duplicated()]
|
||||
|
||||
saveRDS(organisms, "data-raw/organisms.rds", version = 2)
|
||||
|
||||
@@ -147,12 +150,12 @@ saveRDS(organisms, "data-raw/organisms.rds", version = 2)
|
||||
#---
|
||||
|
||||
# update microorganisms.codes with the latest WHONET codes
|
||||
microorganisms.codes2 <- microorganisms.codes %>%
|
||||
microorganisms.codes2 <- microorganisms.codes |>
|
||||
# remove all old WHONET codes, whether we (in the end) keep them or not
|
||||
filter(!toupper(code) %in% toupper(organisms$code)) %>%
|
||||
filter(!toupper(code) %in% toupper(organisms$code)) |>
|
||||
# and add the new ones
|
||||
bind_rows(organisms %>% select(code, mo)) %>%
|
||||
arrange(code) %>%
|
||||
bind_rows(organisms |> select(code, mo)) |>
|
||||
arrange(code) |>
|
||||
distinct(code, .keep_all = TRUE)
|
||||
# new codes:
|
||||
microorganisms.codes2$code[which(!microorganisms.codes2$code %in% microorganisms.codes$code)]
|
||||
@@ -163,25 +166,25 @@ microorganisms.codes <- microorganisms.codes2
|
||||
# 2024-06-14: file not available anymore
|
||||
# # start
|
||||
# asiarsnet <- read_tsv("data-raw/WHONET/Codes/ASIARS_Net_Organisms_ForwardLookup.txt")
|
||||
# asiarsnet <- asiarsnet %>%
|
||||
# mutate(WHONET_Code = toupper(WHONET_Code)) %>%
|
||||
# left_join(whonet_organisms %>% mutate(WHONET_Code = toupper(ORGANISM_CODE))) %>%
|
||||
# asiarsnet <- asiarsnet |>
|
||||
# mutate(WHONET_Code = toupper(WHONET_Code)) |>
|
||||
# left_join(whonet_organisms |> mutate(WHONET_Code = toupper(ORGANISM_CODE))) |>
|
||||
# mutate(
|
||||
# mo1 = as.mo(ORGANISM_CODE),
|
||||
# mo2 = as.mo(ORGANISM)
|
||||
# ) %>%
|
||||
# mutate(mo = if_else(mo2 == "UNKNOWN" | is.na(mo2), mo1, mo2)) %>%
|
||||
# ) |>
|
||||
# mutate(mo = if_else(mo2 == "UNKNOWN" | is.na(mo2), mo1, mo2)) |>
|
||||
# filter(!is.na(mo))
|
||||
# insert1 <- asiarsnet %>% transmute(code = WHONET_Code, mo)
|
||||
# insert2 <- asiarsnet %>% transmute(code = as.character(ASIARS_Net_Code), mo)
|
||||
# insert1 <- asiarsnet |> transmute(code = WHONET_Code, mo)
|
||||
# insert2 <- asiarsnet |> transmute(code = as.character(ASIARS_Net_Code), mo)
|
||||
# # these will be updated
|
||||
# bind_rows(insert1, insert2) %>%
|
||||
# rename(mo_new = mo) %>%
|
||||
# left_join(microorganisms.codes) %>%
|
||||
# bind_rows(insert1, insert2) |>
|
||||
# rename(mo_new = mo) |>
|
||||
# left_join(microorganisms.codes) |>
|
||||
# filter(mo != mo_new)
|
||||
# microorganisms.codes <- microorganisms.codes %>%
|
||||
# filter(!code %in% c(insert1$code, insert2$code)) %>%
|
||||
# bind_rows(insert1, insert2) %>%
|
||||
# microorganisms.codes <- microorganisms.codes |>
|
||||
# filter(!code %in% c(insert1$code, insert2$code)) |>
|
||||
# bind_rows(insert1, insert2) |>
|
||||
# arrange(code)
|
||||
# # end
|
||||
|
||||
@@ -196,52 +199,52 @@ devtools::load_all()
|
||||
|
||||
# now that we have the correct MO codes, get the breakpoints and convert them
|
||||
|
||||
whonet_breakpoints %>%
|
||||
count(GUIDELINES, BREAKPOINT_TYPE) %>%
|
||||
pivot_wider(names_from = BREAKPOINT_TYPE, values_from = n) %>%
|
||||
whonet_breakpoints |>
|
||||
count(GUIDELINES, BREAKPOINT_TYPE) |>
|
||||
pivot_wider(names_from = BREAKPOINT_TYPE, values_from = n) |>
|
||||
janitor::adorn_totals(where = c("row", "col"))
|
||||
# compared to current
|
||||
AMR::clinical_breakpoints %>%
|
||||
count(GUIDELINES = gsub("[^a-zA-Z]", "", guideline), type) %>%
|
||||
arrange(tolower(type)) %>%
|
||||
pivot_wider(names_from = type, values_from = n) %>%
|
||||
as.data.frame() %>%
|
||||
AMR::clinical_breakpoints |>
|
||||
count(GUIDELINES = gsub("[^a-zA-Z]", "", guideline), type) |>
|
||||
arrange(tolower(type)) |>
|
||||
pivot_wider(names_from = type, values_from = n) |>
|
||||
as.data.frame() |>
|
||||
janitor::adorn_totals(where = c("row", "col"))
|
||||
|
||||
breakpoints <- whonet_breakpoints %>%
|
||||
mutate(code = toupper(ORGANISM_CODE)) %>%
|
||||
left_join(bind_rows(microorganisms.codes %>% filter(!code %in% c("ALL", "GEN")),
|
||||
breakpoints <- whonet_breakpoints |>
|
||||
mutate(code = toupper(ORGANISM_CODE)) |>
|
||||
left_join(bind_rows(microorganisms.codes |> filter(!code %in% c("ALL", "GEN")),
|
||||
# GEN (Generic) and ALL (All) are PK/PD codes
|
||||
data.frame(code = c("ALL", "GEN"),
|
||||
mo = rep(as.mo("UNKNOWN"), 2))))
|
||||
# these ones lack an MO name, they cannot be used:
|
||||
unknown <- breakpoints %>%
|
||||
filter(is.na(mo)) %>%
|
||||
pull(code) %>%
|
||||
unknown <- breakpoints |>
|
||||
filter(is.na(mo)) |>
|
||||
pull(code) |>
|
||||
unique()
|
||||
breakpoints %>%
|
||||
filter(code %in% unknown) %>%
|
||||
breakpoints |>
|
||||
filter(code %in% unknown) |>
|
||||
count(GUIDELINES, YEAR, ORGANISM_CODE, BREAKPOINT_TYPE, sort = TRUE)
|
||||
# 2025-03-11: these codes are currently: clu, kma, fso, tyi. No clue (are not in MO list of WHONET), and they are only ECOFFs, so remove them:
|
||||
breakpoints <- breakpoints %>%
|
||||
# 2025-04-20: these codes are currently: cps, fso. No clue (are not in MO list of WHONET), and they are only ECOFFs, so remove them:
|
||||
breakpoints <- breakpoints |>
|
||||
filter(!is.na(mo))
|
||||
|
||||
# and these ones have unknown antibiotics according to WHONET itself:
|
||||
breakpoints %>%
|
||||
filter(!WHONET_ABX_CODE %in% whonet_antibiotics$WHONET_ABX_CODE) %>%
|
||||
count(YEAR, GUIDELINES, WHONET_ABX_CODE) %>%
|
||||
arrange(desc(YEAR))
|
||||
breakpoints %>%
|
||||
filter(!WHONET_ABX_CODE %in% whonet_antibiotics$WHONET_ABX_CODE) %>%
|
||||
pull(WHONET_ABX_CODE) %>%
|
||||
unique()
|
||||
# they are at the moment all old codes ("CFC", "ROX", "FIX") that have the right replacements in `antimicrobials`, so we can use as.ab()
|
||||
breakpoints |>
|
||||
filter(!WHONET_ABX_CODE %in% whonet_antibiotics$WHONET_ABX_CODE) |>
|
||||
count(GUIDELINES, WHONET_ABX_CODE) |>
|
||||
mutate(ab = as.ab(WHONET_ABX_CODE, fast_mode = TRUE),
|
||||
ab_name = ab_name(ab))
|
||||
# 2025-04-20: these codes are currently: CFC, ROX, FIX, and N/A. All have the right replacements in `antimicrobials`, so we can safely use as.ab() later on
|
||||
# the NAs are for M. tuberculosis, they are empty breakpoints
|
||||
breakpoints <- breakpoints |>
|
||||
filter(!is.na(WHONET_ABX_CODE))
|
||||
|
||||
|
||||
## Build new breakpoints table ----
|
||||
|
||||
breakpoints_new <- breakpoints %>%
|
||||
filter(!is.na(WHONET_ABX_CODE)) %>%
|
||||
breakpoints_new <- breakpoints |>
|
||||
filter(!is.na(WHONET_ABX_CODE)) |>
|
||||
transmute(
|
||||
guideline = paste(GUIDELINES, YEAR),
|
||||
type = ifelse(BREAKPOINT_TYPE == "ECOFF", "ECOFF", tolower(BREAKPOINT_TYPE)),
|
||||
@@ -266,20 +269,20 @@ breakpoints_new <- breakpoints %>%
|
||||
breakpoint_R = ifelse(type == "ECOFF" & is.na(R) & !is.na(ECV_ECOFF), ECV_ECOFF, R),
|
||||
uti = ifelse(is.na(site), FALSE, gsub(".*(UTI|urinary|urine).*", "UTI", site) == "UTI"),
|
||||
is_SDD = !is.na(SDD)
|
||||
) %>%
|
||||
) |>
|
||||
# Greek symbols and EM dash symbols are not allowed by CRAN, so replace them with ASCII:
|
||||
mutate(disk_dose = disk_dose %>%
|
||||
gsub("μ", "mc", ., fixed = TRUE) %>% # this is 'mu', \u03bc
|
||||
gsub("µ", "mc", ., fixed = TRUE) %>% # this is 'micro', \u00b5 (yes, they look the same)
|
||||
gsub("–", "-", ., fixed = TRUE) %>%
|
||||
gsub("(?<=\\d)(?=[a-zA-Z])", " ", ., perl = TRUE)) %>% # make sure we keep a space after a number, e.g. "1mcg" to "1 mcg"
|
||||
arrange(desc(guideline), mo, ab, type, method) %>%
|
||||
filter(!(is.na(breakpoint_S) & is.na(breakpoint_R)) & !is.na(mo) & !is.na(ab)) %>%
|
||||
gsub("(?<=\\d)(?=[a-zA-Z])", " ", ., perl = TRUE)) |> # make sure we keep a space after a number, e.g. "1mcg" to "1 mcg"
|
||||
arrange(desc(guideline), mo, ab, type, method) |>
|
||||
filter(!(is.na(breakpoint_S) & is.na(breakpoint_R)) & !is.na(mo) & !is.na(ab)) |>
|
||||
distinct(guideline, type, host, ab, mo, method, site, breakpoint_S, .keep_all = TRUE)
|
||||
|
||||
# fix reference table names
|
||||
breakpoints_new %>% filter(guideline %like% "EUCAST", is.na(ref_tbl)) %>% View()
|
||||
breakpoints_new <- breakpoints_new %>%
|
||||
breakpoints_new |> filter(guideline %like% "EUCAST", is.na(ref_tbl)) |> View()
|
||||
breakpoints_new <- breakpoints_new |>
|
||||
mutate(ref_tbl = case_when(is.na(ref_tbl) & guideline %like% "EUCAST 202" ~ lead(ref_tbl),
|
||||
is.na(ref_tbl) ~ "Unknown",
|
||||
TRUE ~ ref_tbl))
|
||||
@@ -289,11 +292,11 @@ breakpoints_new[which(breakpoints_new$method == "DISK"), "breakpoint_S"] <- as.d
|
||||
breakpoints_new[which(breakpoints_new$method == "DISK"), "breakpoint_R"] <- as.double(as.disk(breakpoints_new[which(breakpoints_new$method == "DISK"), "breakpoint_R", drop = TRUE]))
|
||||
|
||||
# regarding animal breakpoints, CLSI has adults and foals for horses, but only for amikacin - only keep adult horses
|
||||
breakpoints_new %>%
|
||||
filter(host %like% "foal") %>%
|
||||
breakpoints_new |>
|
||||
filter(host %like% "foal") |>
|
||||
count(guideline, host)
|
||||
breakpoints_new <- breakpoints_new %>%
|
||||
filter(host %unlike% "foal") %>%
|
||||
breakpoints_new <- breakpoints_new |>
|
||||
filter(host %unlike% "foal") |>
|
||||
mutate(host = ifelse(host %like% "horse", "horse", host))
|
||||
|
||||
# FIXES FOR WHONET ERRORS ----
|
||||
@@ -301,25 +304,22 @@ m <- unique(as.double(as.mic(levels(as.mic(1)))))
|
||||
|
||||
# WHONET has no >1024 but instead uses 1025, 513, etc, so as.mic() cannot be used to clean.
|
||||
# instead, raise these one higher valid MIC factor level:
|
||||
breakpoints_new |> filter(method == "MIC" & (!breakpoint_S %in% c(m, NA))) |> distinct(breakpoint_S)
|
||||
breakpoints_new |> filter(method == "MIC" & (!breakpoint_R %in% c(m, NA))) |> distinct(breakpoint_R)
|
||||
breakpoints_new[which(breakpoints_new$breakpoint_R == 129), "breakpoint_R"] <- m[which(m == 128) + 1]
|
||||
breakpoints_new[which(breakpoints_new$breakpoint_R == 257), "breakpoint_R"] <- m[which(m == 256) + 1]
|
||||
breakpoints_new[which(breakpoints_new$breakpoint_R == 513), "breakpoint_R"] <- m[which(m == 512) + 1]
|
||||
breakpoints_new[which(breakpoints_new$breakpoint_R == 1025), "breakpoint_R"] <- m[which(m == 1024) + 1]
|
||||
|
||||
# a lot of R breakpoints are missing, though none of the S breakpoints are missing:
|
||||
# S breakpoints must never be missing:
|
||||
anyNA(breakpoints_new$breakpoint_S)
|
||||
|
||||
breakpoints_new %>%
|
||||
filter(is.na(breakpoint_R)) %>%
|
||||
count(guideline, host) |>
|
||||
pivot_wider(names_from = host,
|
||||
values_from = n,
|
||||
values_fill = list(n = 0)) |>
|
||||
View()
|
||||
|
||||
# 2025-03-12 don't do this anymore - we now use as.sir(..., substitute_missing_r_breakpoint = TRUE/FALSE, ...)
|
||||
# breakpoints_new[which(breakpoints_new$method == "MIC" &
|
||||
# is.na(breakpoints_new$breakpoint_R)), "breakpoint_R"] <- max(m)
|
||||
# a lot of R breakpoints are missing, but for CLSI this is required and can be set using as.sir(..., substitute_missing_r_breakpoint = TRUE/FALSE, ...)
|
||||
# 2025-04-20/ For EUCAST, this should not be the case, only happens to old guideline now it seems
|
||||
breakpoints_new |>
|
||||
filter(method == "MIC" & guideline %like% "EUCAST" & is.na(breakpoint_R)) |>
|
||||
count(guideline)
|
||||
breakpoints_new[which(breakpoints_new$method == "MIC" & breakpoints_new$guideline %like% "EUCAST" & is.na(breakpoints_new$breakpoint_R)), "breakpoint_R"] <- breakpoints_new[which(breakpoints_new$method == "MIC" & breakpoints_new$guideline %like% "EUCAST" & is.na(breakpoints_new$breakpoint_R)), "breakpoint_S"]
|
||||
|
||||
|
||||
# fix streptococci in WHONET table of EUCAST: Strep A, B, C and G must only include these groups and not all streptococci:
|
||||
@@ -327,32 +327,30 @@ breakpoints_new$mo[breakpoints_new$mo == "B_STRPT" & breakpoints_new$ref_tbl %li
|
||||
# Haemophilus same error (must only be H. influenzae)
|
||||
breakpoints_new$mo[breakpoints_new$mo == "B_HMPHL" & breakpoints_new$ref_tbl %like% "^h.* influenzae"] <- as.mo("B_HMPHL_INFL")
|
||||
# EUCAST says that for H. parainfluenzae the H. influenza rules can be used, so add them
|
||||
breakpoints_new <- breakpoints_new %>%
|
||||
breakpoints_new <- breakpoints_new |>
|
||||
bind_rows(
|
||||
breakpoints_new %>%
|
||||
filter(guideline %like% "EUCAST", mo == "B_HMPHL_INFL") %>%
|
||||
breakpoints_new |>
|
||||
filter(guideline %like% "EUCAST", mo == "B_HMPHL_INFL") |>
|
||||
mutate(mo = as.mo("B_HMPHL_PRNF"))
|
||||
) %>%
|
||||
arrange(desc(guideline), mo, ab, type, host, method)
|
||||
) |>
|
||||
arrange(desc(guideline), mo, ab, type, host, method) |>
|
||||
distinct()
|
||||
# Achromobacter denitrificans is in WHONET included in their A. xylosoxidans table, must be removed
|
||||
breakpoints_new <- breakpoints_new %>% filter(mo != as.mo("Achromobacter denitrificans"))
|
||||
breakpoints_new <- breakpoints_new |> filter(mo != as.mo("Achromobacter denitrificans"))
|
||||
# WHONET contains gentamicin breakpoints for viridans streptocci, which are intrinsic R - they meant genta-high, which is ALSO in their table, so we just remove gentamicin in viridans streptococci
|
||||
breakpoints_new <- breakpoints_new %>% filter(!(mo == as.mo("Streptococcus viridans") & ab == "GEN"))
|
||||
breakpoints_new |> filter(mo == as.mo("Streptococcus viridans") & ab == "GEN")
|
||||
breakpoints_new |> filter(mo == as.mo("Streptococcus viridans") & ab == "GEH")
|
||||
breakpoints_new <- breakpoints_new |> filter(!(mo == as.mo("Streptococcus viridans") & ab == "GEN"))
|
||||
# Nitrofurantoin in Staph (EUCAST) only applies to S. saprophyticus, while WHONET has the DISK correct but the MIC on genus level
|
||||
breakpoints_new$mo[breakpoints_new$mo == "B_STPHY" & breakpoints_new$ab == "NIT" & breakpoints_new$guideline %like% "EUCAST"] <- as.mo("B_STPHY_SPRP")
|
||||
# WHONET sets the 2023 breakpoints for SAM to MIC of 16/32 for Enterobacterales, should be MIC 8/32 like AMC (see issue #123 on github.com/msberends/AMR)
|
||||
# UPDATE 2024-02-22: fixed now
|
||||
# 2024-02-22/ fixed now
|
||||
|
||||
# There's a problem with C. diff in EUCAST where breakpoint_R is missing - they are listed as normal human breakpoints but are ECOFF
|
||||
rows <- which(breakpoints_new$guideline %like% "EUCAST" & breakpoints_new$mo == "B_CRDDS_DFFC" & is.na(breakpoints_new$breakpoint_R) & !is.na(breakpoints_new$breakpoint_S))
|
||||
breakpoints_new$type[rows] <- "ECOFF"
|
||||
breakpoints_new$host[rows] <- "ECOFF"
|
||||
breakpoints_new$ref_tbl[rows] <- "ECOFF"
|
||||
breakpoints_new$breakpoint_R[rows] <- breakpoints_new$breakpoint_S[rows]
|
||||
breakpoints_new <- distinct(breakpoints_new, .keep_all = TRUE)
|
||||
# 2025-04-20/ fixed now
|
||||
|
||||
# determine rank again now that some changes were made on taxonomic level (genus -> species)
|
||||
breakpoints_new <- breakpoints_new %>%
|
||||
breakpoints_new <- breakpoints_new |>
|
||||
mutate(rank_index = case_when(
|
||||
mo_rank(mo, keep_synonyms = TRUE) %like% "(infra|sub)" ~ 1,
|
||||
mo_rank(mo, keep_synonyms = TRUE) == "species" ~ 2,
|
||||
@@ -367,52 +365,50 @@ breakpoints_new <- breakpoints_new %>%
|
||||
# WHONET adds one log2 level to the R breakpoint for their software, e.g. in AMC in Enterobacterales:
|
||||
# EUCAST 2023 guideline: S <= 8 and R > 8
|
||||
# WHONET file: S <= 8 and R >= 16
|
||||
breakpoints_new %>% filter(guideline == "EUCAST 2023", ab == "AMC", mo == "B_[ORD]_ENTRBCTR", method == "MIC")
|
||||
# but this will make an MIC of 12 I, which should be R according to EUCAST, so:
|
||||
breakpoints_new <- breakpoints_new %>%
|
||||
breakpoints_new |> filter(guideline == "EUCAST 2023", ab == "AMC", mo == "B_[ORD]_ENTRBCTR", method == "MIC")
|
||||
# but this logic only works for CLSI - for an MIC outside the log2 range (e.g., 12) you must round up (i.e., 16)
|
||||
# but for EUCAST, an MIC of 12 would now be considered I, which should be R, so correct those values:
|
||||
breakpoints_new <- breakpoints_new |>
|
||||
mutate(breakpoint_R = ifelse(guideline %like% "EUCAST" & method == "MIC" & log2(breakpoint_R) - log2(breakpoint_S) != 0,
|
||||
pmax(breakpoint_S, breakpoint_R / 2),
|
||||
breakpoint_R
|
||||
))
|
||||
# fix disks as well
|
||||
breakpoints_new %>% filter(guideline == "EUCAST 2023", ab == "AMC", mo == "B_[ORD]_ENTRBCTR", method == "DISK")
|
||||
breakpoints_new <- breakpoints_new %>%
|
||||
breakpoints_new |> filter(guideline == "EUCAST 2023", ab == "AMC", mo == "B_[ORD]_ENTRBCTR", method == "DISK")
|
||||
breakpoints_new <- breakpoints_new |>
|
||||
mutate(breakpoint_R = ifelse(guideline %like% "EUCAST" & method == "DISK" & breakpoint_S - breakpoint_R != 0,
|
||||
breakpoint_R + 1,
|
||||
breakpoint_R
|
||||
))
|
||||
# fill missing R breakpoint where there is an S breakpoint
|
||||
# 2025-03-12 don't do this anymore - we now use as.sir(..., substitute_missing_r_breakpoint = TRUE/FALSE, ...)
|
||||
# breakpoints_new[which(is.na(breakpoints_new$breakpoint_R)), "breakpoint_R"] <- breakpoints_new[which(is.na(breakpoints_new$breakpoint_R)), "breakpoint_S"]
|
||||
|
||||
|
||||
# check the strange duplicates
|
||||
breakpoints_new %>%
|
||||
mutate(id = paste(guideline, type, host, method, site, mo, ab, uti)) %>%
|
||||
filter(id %in% .$id[which(duplicated(id))]) %>%
|
||||
arrange(desc(guideline))
|
||||
# 2024-06-19 mostly ECOFFs, but there's no explanation in the whonet_breakpoints file, we have to remove duplicates
|
||||
# remove duplicates
|
||||
breakpoints_new <- breakpoints_new %>%
|
||||
breakpoints_new |>
|
||||
mutate(id = paste(guideline, type, host, method, site, mo, ab, uti)) %>%
|
||||
filter(id %in% .$id[which(duplicated(id))]) |>
|
||||
arrange(desc(guideline)) |>
|
||||
View()
|
||||
# 2024-06-19/ mostly ECOFFs, but there's no explanation in the whonet_breakpoints file, we have to remove duplicates
|
||||
# 2025-04-20/ same, most important one seems M. tuberculosis in CLSI (also in 2025)
|
||||
breakpoints_new <- breakpoints_new |>
|
||||
distinct(guideline, type, host, method, site, mo, ab, uti, .keep_all = TRUE)
|
||||
|
||||
|
||||
# CHECKS AND SAVE TO PACKAGE ----
|
||||
|
||||
# check again
|
||||
breakpoints_new %>% filter(guideline == "EUCAST 2024", ab == "AMC", mo == "B_[ORD]_ENTRBCTR", method == "MIC")
|
||||
breakpoints_new |> filter(guideline == "EUCAST 2025", ab == "AMC", mo == "B_[ORD]_ENTRBCTR", method == "MIC")
|
||||
# compare with current version
|
||||
clinical_breakpoints %>% filter(guideline == "EUCAST 2024", ab == "AMC", mo == "B_[ORD]_ENTRBCTR", method == "MIC")
|
||||
clinical_breakpoints |> filter(guideline == "EUCAST 2024", ab == "AMC", mo == "B_[ORD]_ENTRBCTR", method == "MIC")
|
||||
|
||||
# must have "human" and "ECOFF"
|
||||
breakpoints_new %>% filter(mo == "B_STRPT_PNMN", ab == "AMP", guideline == "EUCAST 2020", method == "MIC")
|
||||
breakpoints_new |> filter(mo == "B_STRPT_PNMN", ab == "AMP", guideline == "EUCAST 2020", method == "MIC")
|
||||
|
||||
# check dimensions
|
||||
dim(breakpoints_new)
|
||||
dim(clinical_breakpoints)
|
||||
|
||||
clinical_breakpoints <- breakpoints_new
|
||||
clinical_breakpoints <- clinical_breakpoints %>% dataset_UTF8_to_ASCII()
|
||||
clinical_breakpoints <- clinical_breakpoints |> dataset_UTF8_to_ASCII()
|
||||
usethis::use_data(clinical_breakpoints, overwrite = TRUE, compress = "xz", version = 2)
|
||||
rm(clinical_breakpoints)
|
||||
devtools::load_all(".")
|
||||
|
@@ -31,12 +31,13 @@ library(dplyr)
|
||||
library(readxl)
|
||||
library(cleaner)
|
||||
|
||||
# URL:
|
||||
# https://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Breakpoint_tables/Dosages_v_13.0_Breakpoint_Tables.pdf
|
||||
# download the PDF file, open in Adobe Acrobat and export as Excel workbook
|
||||
breakpoints_version <- 13
|
||||
breakpoint_file <- "data-raw/v_15.0_Breakpoint_Tables.xlsx"
|
||||
if (!file.exists(breakpoint_file)) {
|
||||
stop("Breakpoint file not found")
|
||||
}
|
||||
breakpoints_version <- as.double(gsub("[^0-9.]", "", gsub(".xlsx", "", breakpoint_file, fixed = TRUE)))
|
||||
|
||||
dosage_source <- read_excel("data-raw/Dosages_v_12.0_Breakpoint_Tables.xlsx", skip = 4, na = "None") %>%
|
||||
dosage_source <- read_excel(breakpoint_file, skip = 6, sheet = "Dosages", na = "None") %>%
|
||||
format_names(snake_case = TRUE, penicillins = "drug") %>%
|
||||
filter(!tolower(standard_dosage) %in% c("standard dosage", "standard dosage_source", "under review")) %>%
|
||||
filter(!is.na(standard_dosage)) %>%
|
||||
@@ -173,6 +174,12 @@ dosage_new <- bind_rows(
|
||||
# this makes it a tibble as well:
|
||||
dataset_UTF8_to_ASCII()
|
||||
|
||||
dosage <- bind_rows(dosage_new, AMR::dosage)
|
||||
dosage <- AMR::dosage |>
|
||||
bind_rows(dosage_new) |>
|
||||
arrange(desc(eucast_version), name) |>
|
||||
distinct()
|
||||
|
||||
dosage <- dosage |> dataset_UTF8_to_ASCII()
|
||||
usethis::use_data(dosage, internal = FALSE, overwrite = TRUE, version = 2, compress = "xz")
|
||||
rm(dosage)
|
||||
devtools::load_all(".")
|
||||
|
@@ -1 +1 @@
|
||||
ae7b2da1015eb1eca2c6d1736db0f31f
|
||||
9b1fa09da564e8ddca348e91e84c80dc
|
||||
|
@@ -1 +1 @@
|
||||
7bc41a5d92b1e98fbd6e2b8c077434b5
|
||||
c7062e60fa4fbc2eee233044d15903ce
|
||||
|
Binary file not shown.
Binary file not shown.
Binary file not shown.
Binary file not shown.
Binary file not shown.
@@ -72,6 +72,7 @@
|
||||
"FEP" 5479537 "Cefepime" "Cephalosporins (4th gen.)" "J01DE01" "Other beta-lactam antibacterials" "Fourth-generation cephalosporins" "cfep,cfpi,cpe,cpm,fep,pm,xpm" "anticefepime,axepim,cefepima,cefepimum,maxipime,pyrrolidinium,renapime" 4 "g" "101502-3,18879-7,31142-3,31143-1,35763-2,38363-8,42350-9,42351-7,42353-3,50631-1,58412-8,6643-1,6644-9,6645-7,6646-5,6987-2,8272-7,8273-5"
|
||||
"CFA" "Cefepime/amikacin" "Cephalosporins (4th gen.)" "J01RA06" "Combinations of antibacterials" "Combinations of antibacterials" "NA" "NA" "NA"
|
||||
"CPC" 9567559 "Cefepime/clavulanic acid" "Cephalosporins (4th gen.)" "NA" "cicl,xpml" "NA" "NA"
|
||||
"FPE" 23653540 "Cefepime/enmetazobactam" "Cephalosporins (4th gen.)" "NA" "NA" "NA" "NA"
|
||||
"FNC" "Cefepime/nacubactam" "Cephalosporins (4th gen.)" "NA" "NA" "NA" "NA"
|
||||
"FPT" 9567558 "Cefepime/tazobactam" "Cephalosporins (4th gen.)" "NA" "NA" "NA" "NA"
|
||||
"FPZ" "Cefepime/zidebactam" "Cephalosporins (4th gen.)" "NA" "NA" "NA" "NA"
|
||||
|
Binary file not shown.
Binary file not shown.
Binary file not shown.
Binary file not shown.
Binary file not shown.
Binary file not shown.
File diff suppressed because it is too large
Load Diff
Binary file not shown.
Binary file not shown.
Binary file not shown.
Binary file not shown.
Binary file not shown.
Binary file not shown.
@@ -1,171 +1,431 @@
|
||||
"ab" "name" "type" "dose" "dose_times" "administration" "notes" "original_txt" "eucast_version"
|
||||
"AMK" "Amikacin" "standard_dosage" "25-30 mg/kg" 1 "iv" "" "25-30 mg/kg x 1 iv" 13
|
||||
"AMX" "Amoxicillin" "high_dosage" "2 g" 6 "iv" "" "2 g x 6 iv" 13
|
||||
"AMX" "Amoxicillin" "standard_dosage" "1 g" 3 "iv" "" "1 g x 3-4 iv" 13
|
||||
"AMX" "Amoxicillin" "high_dosage" "0.75-1 g" 3 "oral" "" "0.75-1 g x 3 oral" 13
|
||||
"AMX" "Amoxicillin" "standard_dosage" "0.5 g" 3 "oral" "" "0.5 g x 3 oral" 13
|
||||
"AMX" "Amoxicillin" "uncomplicated_uti" "0.5 g" 3 "oral" "" "0.5 g x 3 oral" 13
|
||||
"AMC" "Amoxicillin/clavulanic acid" "high_dosage" "2 g + 0.2 g" 3 "iv" "" "(2 g amoxicillin + 0.2 g clavulanic acid) x 3 iv" 13
|
||||
"AMC" "Amoxicillin/clavulanic acid" "standard_dosage" "1 g + 0.2 g" 3 "iv" "" "(1 g amoxicillin + 0.2 g clavulanic acid) x 3-4 iv" 13
|
||||
"AMC" "Amoxicillin/clavulanic acid" "high_dosage" "0.875 g + 0.125 g" 3 "oral" "" "(0.875 g amoxicillin + 0.125 g clavulanic acid) x 3 oral" 13
|
||||
"AMC" "Amoxicillin/clavulanic acid" "standard_dosage" "0.5 g + 0.125 g" 3 "oral" "" "(0.5 g amoxicillin + 0.125 g clavulanic acid) x 3 oral" 13
|
||||
"AMC" "Amoxicillin/clavulanic acid" "uncomplicated_uti" "0.5 g + 0.125 g" 3 "oral" "" "(0.5 g amoxicillin + 0.125 g clavulanic acid) x 3 oral" 13
|
||||
"AMP" "Ampicillin" "high_dosage" "2 g" 4 "iv" "" "2 g x 4 iv" 13
|
||||
"AMP" "Ampicillin" "standard_dosage" "2 g" 3 "iv" "" "2 g x 3 iv" 13
|
||||
"SAM" "Ampicillin/sulbactam" "high_dosage" "2 g + 1 g" 4 "iv" "" "(2 g ampicillin + 1 g sulbactam) x 4 iv" 13
|
||||
"SAM" "Ampicillin/sulbactam" "standard_dosage" "2 g + 1 g" 3 "iv" "" "(2 g ampicillin + 1 g sulbactam) x 3 iv" 13
|
||||
"AZM" "Azithromycin" "standard_dosage" "0.5 g" 1 "iv" "" "0.5 g x 1 iv" 13
|
||||
"AZM" "Azithromycin" "standard_dosage" "0.5 g" 1 "oral" "" "0.5 g x 1 oral" 13
|
||||
"ATM" "Aztreonam" "high_dosage" "2 g" 4 "iv" "" "2 g x 4 iv" 13
|
||||
"ATM" "Aztreonam" "standard_dosage" "1 g" 3 "iv" "" "1 g x 3 iv" 13
|
||||
"PEN" "Benzylpenicillin" "high_dosage" "1.2 g" 4 "iv" "" "1.2 g (2 MU) x 4-6 iv" 13
|
||||
"PEN" "Benzylpenicillin" "standard_dosage" "0.6 g" 4 "iv" "" "0.6 g (1 MU) x 4 iv" 13
|
||||
"CEC" "Cefaclor" "high_dosage" "1 g" 3 "oral" "" "1 g x 3 oral" 13
|
||||
"CEC" "Cefaclor" "standard_dosage" "0.25-0.5 g" 3 "oral" "" "0.25-0.5 g x 3 oral" 13
|
||||
"CFR" "Cefadroxil" "standard_dosage" "0.5-1 g" 2 "oral" "" "0.5-1 g x 2 oral" 13
|
||||
"CFR" "Cefadroxil" "uncomplicated_uti" "0.5-1 g" 2 "oral" "" "0.5-1 g x 2 oral" 13
|
||||
"LEX" "Cefalexin" "standard_dosage" "0.25-1 g" 2 "oral" "" "0.25-1 g x 2-3 oral" 13
|
||||
"LEX" "Cefalexin" "uncomplicated_uti" "0.25-1 g" 2 "oral" "" "0.25-1 g x 2-3 oral" 13
|
||||
"CZO" "Cefazolin" "high_dosage" "2 g" 3 "iv" "" "2 g x 3 iv" 13
|
||||
"CZO" "Cefazolin" "standard_dosage" "1 g" 3 "iv" "" "1 g x 3 iv" 13
|
||||
"FEP" "Cefepime" "high_dosage" "2 g" 3 "iv" "" "2 g x 3 iv" 13
|
||||
"FEP" "Cefepime" "standard_dosage" "2 g" 2 "iv" "" "2 g x 2 iv" 13
|
||||
"FDC" "Cefiderocol" "standard_dosage" "2 g" 3 "iv" "over 3 hours" "2 g x 3 iv over 3 hours" 13
|
||||
"CFM" "Cefixime" "standard_dosage" "0.2-0.4 g" 2 "oral" "" "0.2-0.4 g x 2 oral" 13
|
||||
"CFM" "Cefixime" "uncomplicated_uti" "0.2-0.4 g" 2 "oral" "" "0.2-0.4 g x 2 oral" 13
|
||||
"CTX" "Cefotaxime" "high_dosage" "2 g" 3 "iv" "" "2 g x 3 iv" 13
|
||||
"CTX" "Cefotaxime" "standard_dosage" "1 g" 3 "iv" "" "1 g x 3 iv" 13
|
||||
"CPD" "Cefpodoxime" "standard_dosage" "0.1-0.2 g" 2 "oral" "" "0.1-0.2 g x 2 oral" 13
|
||||
"CPD" "Cefpodoxime" "uncomplicated_uti" "0.1-0.2 g" 2 "oral" "" "0.1-0.2 g x 2 oral" 13
|
||||
"CPT" "Ceftaroline" "high_dosage" "0.6 g" 3 "iv" "over 2 hours" "0.6 g x 3 iv over 2 hours" 13
|
||||
"CPT" "Ceftaroline" "standard_dosage" "0.6 g" 2 "iv" "over 1 hour" "0.6 g x 2 iv over 1 hour" 13
|
||||
"CAZ" "Ceftazidime" "high_dosage" "1 g" 6 "iv" "" "1 g x 6 iv" 13
|
||||
"CAZ" "Ceftazidime" "standard_dosage" "1 g" 3 "iv" "" "1 g x 3 iv" 13
|
||||
"CZA" "Ceftazidime/avibactam" "standard_dosage" "2 g + 0.5 g" 3 "iv" "over 2 hours" "(2 g ceftazidime + 0.5 g avibactam) x 3 iv over 2 hours" 13
|
||||
"CTB" "Ceftibuten" "standard_dosage" "0.4 g" 1 "oral" "" "0.4 g x 1 oral" 13
|
||||
"BPR" "Ceftobiprole" "standard_dosage" "0.5 g" 3 "iv" "over 2 hours" "0.5 g x 3 iv over 2 hours" 13
|
||||
"CZT" "Ceftolozane/tazobactam" "standard_dosage" "1 g + 0.5 g" 3 "iv" "over 1 hour" "(1 g ceftolozane + 0.5 g tazobactam) x 3 iv over 1 hour" 13
|
||||
"CZT" "Ceftolozane/tazobactam" "standard_dosage" "2 g + 1 g" 3 "iv" "over 1 hour" "(2 g ceftolozane + 1 g tazobactam) x 3 iv over 1 hour" 13
|
||||
"CRO" "Ceftriaxone" "high_dosage" "4 g" 1 "iv" "" "4 g x 1 iv" 13
|
||||
"CRO" "Ceftriaxone" "standard_dosage" "2 g" 1 "iv" "" "2 g x 1 iv" 13
|
||||
"CXM" "Cefuroxime" "high_dosage" "1.5 g" 3 "iv" "" "1.5 g x 3 iv" 13
|
||||
"CXM" "Cefuroxime" "standard_dosage" "0.75 g" 3 "iv" "" "0.75 g x 3 iv" 13
|
||||
"CXM" "Cefuroxime" "high_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2 oral" 13
|
||||
"CXM" "Cefuroxime" "standard_dosage" "0.25 g" 2 "oral" "" "0.25 g x 2 oral" 13
|
||||
"CXM" "Cefuroxime" "uncomplicated_uti" "0.25 g" 2 "oral" "" "0.25 g x 2 oral" 13
|
||||
"CHL" "Chloramphenicol" "high_dosage" "2 g" 4 "iv" "" "2 g x 4 iv" 13
|
||||
"CHL" "Chloramphenicol" "standard_dosage" "1 g" 4 "iv" "" "1 g x 4 iv" 13
|
||||
"CHL" "Chloramphenicol" "high_dosage" "2 g" 4 "oral" "" "2 g x 4 oral" 13
|
||||
"CHL" "Chloramphenicol" "standard_dosage" "1 g" 4 "oral" "" "1 g x 4 oral" 13
|
||||
"CIP" "Ciprofloxacin" "high_dosage" "0.4 g" 3 "iv" "" "0.4 g x 3 iv" 13
|
||||
"CIP" "Ciprofloxacin" "standard_dosage" "0.4 g" 2 "iv" "" "0.4 g x 2 iv" 13
|
||||
"CIP" "Ciprofloxacin" "high_dosage" "0.75 g" 2 "oral" "" "0.75 g x 2 oral" 13
|
||||
"CIP" "Ciprofloxacin" "standard_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2 oral" 13
|
||||
"CLR" "Clarithromycin" "high_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2 oral" 13
|
||||
"CLR" "Clarithromycin" "standard_dosage" "0.25 g" 2 "oral" "" "0.25 g x 2 oral" 13
|
||||
"CLI" "Clindamycin" "high_dosage" "0.9 g" 3 "iv" "" "0.9 g x 3 iv" 13
|
||||
"CLI" "Clindamycin" "standard_dosage" "0.6 g" 3 "iv" "" "0.6 g x 3 iv" 13
|
||||
"CLI" "Clindamycin" "high_dosage" "0.3 g" 4 "oral" "" "0.3 g x 4 oral" 13
|
||||
"CLI" "Clindamycin" "standard_dosage" "0.3 g" 2 "oral" "" "0.3 g x 2 oral" 13
|
||||
"CLO" "Cloxacillin" "high_dosage" "2 g" 6 "iv" "" "2 g x 6 iv" 13
|
||||
"CLO" "Cloxacillin" "standard_dosage" "1 g" 4 "iv" "" "1 g x 4 iv" 13
|
||||
"CLO" "Cloxacillin" "high_dosage" "1 g" 4 "oral" "" "1 g x 4 oral" 13
|
||||
"CLO" "Cloxacillin" "standard_dosage" "0.5 g" 4 "oral" "" "0.5 g x 4 oral" 13
|
||||
"COL" "Colistin" "standard_dosage" "4.5 MU" 2 "iv" "loading dose of 9 MU" "4.5 MU x 2 iv with a loading dose of 9 MU" 13
|
||||
"DAL" "Dalbavancin" "standard_dosage" "1 g" 1 "iv" "over 30 minutes on day 8" "1 g x 1 iv over 30 minutes on day 1 If needed, 0.5 g x 1 iv over 30 minutes on day 8" 13
|
||||
"DAP" "Daptomycin" "standard_dosage" "4 mg/kg" 1 "iv" "" "4 mg/kg x 1 iv" 13
|
||||
"DAP" "Daptomycin" "standard_dosage" "6 mg/kg" 1 "iv" "" "6 mg/kg x 1 iv" 13
|
||||
"DFX" "Delafloxacin" "standard_dosage" "0.3 g" 2 "iv" "" "0.3 g x 2 iv" 13
|
||||
"DFX" "Delafloxacin" "standard_dosage" "0.45 g" 2 "oral" "" "0.45 g x 2 oral" 13
|
||||
"DIC" "Dicloxacillin" "high_dosage" "2 g" 6 "iv" "" "2 g x 6 iv" 13
|
||||
"DIC" "Dicloxacillin" "standard_dosage" "1 g" 4 "iv" "" "1 g x 4 iv" 13
|
||||
"DIC" "Dicloxacillin" "high_dosage" "2 g" 4 "oral" "" "2 g x 4 oral" 13
|
||||
"DIC" "Dicloxacillin" "standard_dosage" "0.5-1 g" 4 "oral" "" "0.5-1 g x 4 oral" 13
|
||||
"DOR" "Doripenem" "high_dosage" "1 g" 3 "iv" "over 1 hour" "1 g x 3 iv over 1 hour" 13
|
||||
"DOR" "Doripenem" "standard_dosage" "0.5 g" 3 "iv" "over 1 hour" "0.5 g x 3 iv over 1 hour" 13
|
||||
"DOX" "Doxycycline" "high_dosage" "0.2 g" 1 "oral" "" "0.2 g x 1 oral" 13
|
||||
"DOX" "Doxycycline" "standard_dosage" "0.1 g" 1 "oral" "" "0.1 g x 1 oral" 13
|
||||
"ERV" "Eravacycline" "standard_dosage" "1 mg/kg" 2 "iv" "" "1 mg/kg x 2 iv" 13
|
||||
"ETP" "Ertapenem" "standard_dosage" "1 g" 1 "iv" "over 30 minutes" "1 g x 1 iv over 30 minutes" 13
|
||||
"ERY" "Erythromycin" "high_dosage" "1 g" 4 "iv" "" "1 g x 4 iv" 13
|
||||
"ERY" "Erythromycin" "standard_dosage" "0.5 g" 2 "iv" "" "0.5 g x 2-4 iv" 13
|
||||
"ERY" "Erythromycin" "high_dosage" "1 g" 4 "oral" "" "1 g x 4 oral" 13
|
||||
"ERY" "Erythromycin" "standard_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2-4 oral" 13
|
||||
"FDX" "Fidaxomicin" "standard_dosage" "0.2 g" 2 "oral" "" "0.2 g x 2 oral" 13
|
||||
"FLC" "Flucloxacillin" "high_dosage" "2 g" 6 "iv" "" "2 g x 6 iv" 13
|
||||
"FLC" "Flucloxacillin" "standard_dosage" "2 g" 4 "iv" "" "2 g x 4 iv (or 1 g x 6 iv)" 13
|
||||
"FLC" "Flucloxacillin" "high_dosage" "1 g" 4 "oral" "" "1 g x 4 oral" 13
|
||||
"FLC" "Flucloxacillin" "standard_dosage" "1 g" 3 "oral" "" "1 g x 3 oral" 13
|
||||
"FOS" "Fosfomycin" "high_dosage" "8 g" 3 "iv" "" "8 g x 3 iv" 13
|
||||
"FOS" "Fosfomycin" "standard_dosage" "4 g" 3 "iv" "" "4 g x 3 iv" 13
|
||||
"FUS" "Fusidic acid" "high_dosage" "0.5 g" 3 "iv" "" "0.5 g x 3 iv" 13
|
||||
"FUS" "Fusidic acid" "standard_dosage" "0.5 g" 2 "iv" "" "0.5 g x 2 iv" 13
|
||||
"FUS" "Fusidic acid" "high_dosage" "0.5 g" 3 "oral" "" "0.5 g x 3 oral" 13
|
||||
"FUS" "Fusidic acid" "standard_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2 oral" 13
|
||||
"GEN" "Gentamicin" "standard_dosage" "6-7 mg/kg" 1 "iv" "" "6-7 mg/kg x 1 iv" 13
|
||||
"IPM" "Imipenem" "high_dosage" "1 g" 4 "iv" "over 30 minutes" "1 g x 4 iv over 30 minutes" 13
|
||||
"IPM" "Imipenem" "standard_dosage" "0.5 g" 4 "iv" "over 30 minutes" "0.5 g x 4 iv over 30 minutes" 13
|
||||
"IMR" "Imipenem/relebactam" "standard_dosage" "0.5 g + 0.25 g" 4 "iv" "over 30 minutes" "(0.5 g imipenem + 0.25 g relebactam) x 4 iv over 30 minutes" 13
|
||||
"IMR" "Imipenem/relebactam" "standard_dosage" "0.5 g + 0.25 g" 4 "iv" "over 30 minutes" "(0.5 g imipenem + 0.25 g relebactam) x 4 iv over 30 minutes" 13
|
||||
"LMU" "Lefamulin" "standard_dosage" "0.15 g" 2 "iv" "or 0.6 g x 2 oral" "0.15 g x 2 iv or 0.6 g x 2 oral" 13
|
||||
"LMU" "Lefamulin" "standard_dosage" "0.6 g" 2 "oral" "" "0.6 g x 2 oral" 13
|
||||
"LVX" "Levofloxacin" "high_dosage" "0.5 g" 2 "iv" "" "0.5 g x 2 iv" 13
|
||||
"LVX" "Levofloxacin" "standard_dosage" "0.5 g" 1 "iv" "" "0.5 g x 1 iv" 13
|
||||
"LVX" "Levofloxacin" "high_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2 oral" 13
|
||||
"LVX" "Levofloxacin" "standard_dosage" "0.5 g" 1 "oral" "" "0.5 g x 1 oral" 13
|
||||
"LNZ" "Linezolid" "standard_dosage" "0.6 g" 2 "iv" "" "0.6 g x 2 iv" 13
|
||||
"LNZ" "Linezolid" "standard_dosage" "0.6 g" 2 "oral" "" "0.6 g x 2 oral" 13
|
||||
"MEM" "Meropenem" "high_dosage" "2 g" 3 "iv" "over 3 hours" "2 g x 3 iv over 3 hours" 13
|
||||
"MEM" "Meropenem" "standard_dosage" "1 g" 3 "iv" "over 30 minutes" "1 g x 3 iv over 30 minutes" 13
|
||||
"MEV" "Meropenem/vaborbactam" "standard_dosage" "2 g + 2 g" 3 "iv" "over 3 hours" "(2 g meropenem + 2 g vaborbactam) x 3 iv over 3 hours" 13
|
||||
"MTR" "Metronidazole" "high_dosage" "0.5 g" 3 "iv" "" "0.5 g x 3 iv" 13
|
||||
"MTR" "Metronidazole" "standard_dosage" "0.4 g" 3 "iv" "" "0.4 g x 3 iv" 13
|
||||
"MTR" "Metronidazole" "high_dosage" "0.5 g" 3 "oral" "" "0.5 g x 3 oral" 13
|
||||
"MTR" "Metronidazole" "standard_dosage" "0.4 g" 3 "oral" "" "0.4 g x 3 oral" 13
|
||||
"MNO" "Minocycline" "standard_dosage" "0.1 g" 2 "oral" "" "0.1 g x 2 oral" 13
|
||||
"MFX" "Moxifloxacin" "standard_dosage" "0.4 g" 1 "iv" "" "0.4 g x 1 iv" 13
|
||||
"MFX" "Moxifloxacin" "standard_dosage" "0.4 g" 1 "oral" "" "0.4 g x 1 oral" 13
|
||||
"OFX" "Ofloxacin" "high_dosage" "0.4 g" 2 "iv" "" "0.4 g x 2 iv" 13
|
||||
"OFX" "Ofloxacin" "standard_dosage" "0.2 g" 2 "iv" "" "0.2 g x 2 iv" 13
|
||||
"OFX" "Ofloxacin" "high_dosage" "0.4 g" 2 "oral" "" "0.4 g x 2 oral" 13
|
||||
"OFX" "Ofloxacin" "standard_dosage" "0.2 g" 2 "oral" "" "0.2 g x 2 oral" 13
|
||||
"ORI" "Oritavancin" "standard_dosage" "1.2 g" 1 "iv" "" "1.2 g x 1 (single dose) iv over 3 hours" 13
|
||||
"OXA" "Oxacillin" "high_dosage" "1 g" 6 "iv" "" "1 g x 6 iv" 13
|
||||
"OXA" "Oxacillin" "standard_dosage" "1 g" 4 "iv" "" "1 g x 4 iv" 13
|
||||
"PHN" "Phenoxymethylpenicillin" "standard_dosage" "0.5-2 g" 3 "oral" "" "0.5-2 g x 3-4 oral" 13
|
||||
"PIP" "Piperacillin" "high_dosage" "4 g" 4 "iv" "" "4 g x 4 iv by extended 3-hour infusion" 13
|
||||
"PIP" "Piperacillin" "standard_dosage" "4 g" 4 "iv" "" "4 g x 4 iv" 13
|
||||
"TZP" "Piperacillin/tazobactam" "high_dosage" "4 g + 0.5 g" 4 "iv" "" "(4 g piperacillin + 0.5 g tazobactam) x 4 iv by extended 3-hour infusion" 13
|
||||
"TZP" "Piperacillin/tazobactam" "standard_dosage" "4 g + 0.5 g" 4 "iv" "" "(4 g piperacillin + 0.5 g tazobactam) x 4 iv 30-minute infusion or x 3 iv by extended 4-hour infusion" 13
|
||||
"QDA" "Quinupristin/dalfopristin" "high_dosage" "7.5 mg/kg" 3 "iv" "" "7.5 mg/kg x 3 iv" 13
|
||||
"QDA" "Quinupristin/dalfopristin" "standard_dosage" "7.5 mg/kg" 2 "iv" "" "7.5 mg/kg x 2 iv" 13
|
||||
"RIF" "Rifampicin" "standard_dosage" "0.6 g" 1 "iv" "" "0.6 g x 1 iv" 13
|
||||
"RIF" "Rifampicin" "standard_dosage" "0.6 g" 1 "oral" "" "0.6 g x 1 oral" 13
|
||||
"RXT" "Roxithromycin" "standard_dosage" "0.15 g" 2 "oral" "" "0.15 g x 2 oral" 13
|
||||
"SPT" "Spectinomycin" "standard_dosage" "2 g" 1 "im" "" "2 g x 1 im" 13
|
||||
"TZD" "Tedizolid" "standard_dosage" "0.2 g" 1 "iv" "" "0.2 g x 1 iv" 13
|
||||
"TZD" "Tedizolid" "standard_dosage" "0.2 g" 1 "oral" "" "0.2 g x 1 oral" 13
|
||||
"TEC" "Teicoplanin" "high_dosage" "0.8 g" 1 "iv" "" "0.8 g x 1 iv" 13
|
||||
"TEC" "Teicoplanin" "standard_dosage" "0.4 g" 1 "iv" "" "0.4 g x 1 iv" 13
|
||||
"TLV" "Telavancin" "standard_dosage" "10 mg/kg" 1 "iv" "over 1 hour" "10 mg/kg x 1 iv over 1 hour" 13
|
||||
"TLT" "Telithromycin" "standard_dosage" "0.8 g" 1 "oral" "" "0.8 g x 1 oral" 13
|
||||
"TEM" "Temocillin" "high_dosage" "2 g" 3 "iv" "" "2 g x 3 iv" 13
|
||||
"TEM" "Temocillin" "standard_dosage" "2 g" 2 "iv" "" "2 g x 2 iv" 13
|
||||
"TCY" "Tetracycline" "high_dosage" "0.5 g" 4 "oral" "" "0.5 g x 4 oral" 13
|
||||
"TCY" "Tetracycline" "standard_dosage" "0.25 g" 4 "oral" "" "0.25 g x 4 oral" 13
|
||||
"TIC" "Ticarcillin" "high_dosage" "3 g" 6 "iv" "" "3 g x 6 iv" 13
|
||||
"TIC" "Ticarcillin" "standard_dosage" "3 g" 4 "iv" "" "3 g x 4 iv" 13
|
||||
"TCC" "Ticarcillin/clavulanic acid" "high_dosage" "3 g + 0.1 g" 6 "iv" "" "(3 g ticarcillin + 0.1 g clavulanic acid) x 6 iv" 13
|
||||
"TCC" "Ticarcillin/clavulanic acid" "standard_dosage" "3 g + 0.1-0.2 g" 4 "iv" "" "(3 g ticarcillin + 0.1-0.2 g clavulanic acid) x 4 iv" 13
|
||||
"TGC" "Tigecycline" "standard_dosage" "0.1 g" "loading dose followed by 50 mg x 2 iv" "0.1 g loading dose followed by 50 mg x 2 iv" 13
|
||||
"TOB" "Tobramycin" "standard_dosage" "6-7 mg/kg" 1 "iv" "" "6-7 mg/kg x 1 iv" 13
|
||||
"SXT" "Trimethoprim/sulfamethoxazole" "high_dosage" "0.24 g + 1.2 g" 2 "oral" "" "(0.24 g trimethoprim + 1.2 g sulfamethoxazole) x 2 oral" 13
|
||||
"SXT" "Trimethoprim/sulfamethoxazole" "high_dosage" "0.24 g + 1.2 g" 2 "oral" "" "(0.24 g trimethoprim + 1.2 g sulfamethoxazole) x 2 oral or (0.24 g trimethoprim + 1.2 g sulfamethoxazole) x 2 iv" 13
|
||||
"SXT" "Trimethoprim/sulfamethoxazole" "standard_dosage" "0.16 g + 0.8 g" 2 "oral" "" "(0.16 g trimethoprim + 0.8 g sulfamethoxazole) x 2 oral" 13
|
||||
"SXT" "Trimethoprim/sulfamethoxazole" "standard_dosage" "0.16 g + 0.8 g" 2 "oral" "" "(0.16 g trimethoprim + 0.8 g sulfamethoxazole) x 2 oral or (0.16 g trimethoprim + 0.8 g sulfamethoxazole) x 2 iv" 13
|
||||
"SXT" "Trimethoprim/sulfamethoxazole" "uncomplicated_uti" "0.16 g + 0.8 g" 2 "oral" "" "(0.16 g trimethoprim + 0.8 g sulfamethoxazole) x 2 oral" 13
|
||||
"SXT" "Trimethoprim/sulfamethoxazole" "uncomplicated_uti" "0.16 g + 0.8 g" 2 "oral" "" "(0.16 g trimethoprim + 0.8 g sulfamethoxazole) x 2 oral" 13
|
||||
"VAN" "Vancomycin" "standard_dosage" "1 g" 2 "iv" "" "1 g x 2 iv or 2 g x 1 by continuous infusion" 13
|
||||
"AMK" "Amikacin" "standard_dosage" "25-30 mg/kg" 1 "iv" "" "25-30 mg/kg x 1 iv" 15
|
||||
"AMX" "Amoxicillin" "high_dosage" "2 g" 6 "iv" "" "2 g x 6 iv" 15
|
||||
"AMX" "Amoxicillin" "standard_dosage" "1 g" 3 "iv" "" "1 g x 3-4 iv
|
||||
" 15
|
||||
"AMX" "Amoxicillin" "high_dosage" "0.75-1 g" 3 "oral" "" "0.75-1 g x 3 oral" 15
|
||||
"AMX" "Amoxicillin" "standard_dosage" "0.5 g" 3 "oral" "" "0.5 g x 3 oral" 15
|
||||
"AMX" "Amoxicillin" "uncomplicated_uti" "0.5 g" 3 "oral" "" "0.5 g x 3 oral" 15
|
||||
"AMC" "Amoxicillin/clavulanic acid" "high_dosage" "2 g + 0.2 g" 3 "iv" "" "(2 g amoxicillin + 0.2 g clavulanic acid) x 3 iv" 15
|
||||
"AMC" "Amoxicillin/clavulanic acid" "standard_dosage" "1 g + 0.2 g" 3 "iv" "" "(1 g amoxicillin + 0.2 g clavulanic acid) x 3-4 iv" 15
|
||||
"AMC" "Amoxicillin/clavulanic acid" "high_dosage" "0.875 g + 0.125 g" 3 "oral" "" "(0.875 g amoxicillin + 0.125 g clavulanic acid) x 3 oral" 15
|
||||
"AMC" "Amoxicillin/clavulanic acid" "standard_dosage" "0.5 g + 0.125 g" 3 "oral" "" "(0.5 g amoxicillin + 0.125 g
|
||||
clavulanic acid) x 3 oral" 15
|
||||
"AMC" "Amoxicillin/clavulanic acid" "uncomplicated_uti" "0.5 g + 0.125 g" 3 "oral" "" "(0.5 g amoxicillin + 0.125 g
|
||||
clavulanic acid) x 3 oral" 15
|
||||
"AMP" "Ampicillin" "high_dosage" "2 g" 4 "iv" "" "2 g x 4 iv
|
||||
" 15
|
||||
"AMP" "Ampicillin" "standard_dosage" "2 g" 3 "iv" "" "2 g x 3 iv" 15
|
||||
"SAM" "Ampicillin/sulbactam" "high_dosage" "2 g + 1 g" 4 "iv" "" "(2 g ampicillin + 1 g sulbactam) x 4 iv" 15
|
||||
"SAM" "Ampicillin/sulbactam" "standard_dosage" "2 g + 1 g" 3 "iv" "" "(2 g ampicillin + 1 g sulbactam) x 3 iv" 15
|
||||
"AZM" "Azithromycin" "standard_dosage" "0.5 g" 1 "iv" "" "0.5 g x 1 iv" 15
|
||||
"AZM" "Azithromycin" "standard_dosage" "0.5 g" 1 "oral" "" "0.5 g x 1 oral" 15
|
||||
"ATM" "Aztreonam" "high_dosage" "2 g" 4 "iv" "" "2 g x 4 iv" 15
|
||||
"ATM" "Aztreonam" "standard_dosage" "1 g" 3 "iv" "" "1 g x 3 iv" 15
|
||||
"AZA" "Aztreonam/avibactam" "standard_dosage" "2 g + 0.67 g" 1 "" "over 3 hours" "(2 g aztreonam + 0.67 g avibactam) x 1
|
||||
followed by (1.5 g aztreonam + 0.5 g avibactam) x 4 iv over 3 hours" 15
|
||||
"PEN" "Benzylpenicillin" "high_dosage" "1.2 g" 6 "iv" "" "1.2 g (2 MU) x 6 iv" 15
|
||||
"PEN" "Benzylpenicillin" "standard_dosage" "0.6 g" 4 "iv" "" "0.6 g (1 MU) x 4 iv" 15
|
||||
"CEC" "Cefaclor" "high_dosage" "1 g" 3 "oral" "" 15
|
||||
"CEC" "Cefaclor" "standard_dosage" "0.25-0.5 g" 3 "oral" "" "0.25-0.5 g x 3 oral" 15
|
||||
"CFR" "Cefadroxil" "standard_dosage" "0.5-1 g" 2 "oral" "" "0.5-1 g x 2 oral" 15
|
||||
"CFR" "Cefadroxil" "uncomplicated_uti" "0.5-1 g" 2 "oral" "" "0.5-1 g x 2 oral" 15
|
||||
"LEX" "Cefalexin" "standard_dosage" "0.25-1 g" 2 "oral" "" "0.25-1 g x 2-3 oral" 15
|
||||
"LEX" "Cefalexin" "uncomplicated_uti" "0.25-1 g" 2 "oral" "" "0.25-1 g x 2-3 oral" 15
|
||||
"CZO" "Cefazolin" "high_dosage" "2 g" 3 "iv" "" "2 g x 3 iv" 15
|
||||
"CZO" "Cefazolin" "standard_dosage" "1 g" 3 "iv" "" "1 g x 3 iv" 15
|
||||
"FEP" "Cefepime" "high_dosage" "2 g" 3 "iv" "" "2 g x 3 iv" 15
|
||||
"FEP" "Cefepime" "standard_dosage" "2 g" 2 "iv" "" "2 g x 2 iv" 15
|
||||
"FPE" "Cefepime/enmetazobactam" "standard_dosage" "2 g + 0.5 g" 3 "iv" "over 4 hours" "(2 g cefepime + 0.5 g enmetazobactam) x 3 iv over 4 hours" 15
|
||||
"FPE" "Cefepime/enmetazobactam" "standard_dosage" "2 g + 0.5 g" 3 "iv" "over 2 hours" "(2 g cefepime + 0.5 g enmetazobactam) x 3 iv over 2 hours" 15
|
||||
"FDC" "Cefiderocol" "standard_dosage" "2 g" 3 "iv" "over 3 hours" "2 g x 3 iv over 3 hours" 15
|
||||
"CFM" "Cefixime" "standard_dosage" "0.2-0.4 g" 2 "oral" "" "0.2-0.4 g x 2 oral" 15
|
||||
"CFM" "Cefixime" "uncomplicated_uti" "0.2-0.4 g" 2 "oral" "" "0.2-0.4 g x 2 oral" 15
|
||||
"CTX" "Cefotaxime" "high_dosage" "2 g" 3 "iv" "" "2 g x 3 iv" 15
|
||||
"CTX" "Cefotaxime" "standard_dosage" "1 g" 3 "iv" "" "1 g x 3 iv" 15
|
||||
"CPD" "Cefpodoxime" "standard_dosage" "0.1-0.2 g" 2 "oral" "" "0.1-0.2 g x 2 oral" 15
|
||||
"CPD" "Cefpodoxime" "uncomplicated_uti" "0.1-0.2 g" 2 "oral" "" "0.1-0.2 g x 2 oral" 15
|
||||
"CPT" "Ceftaroline" "high_dosage" "0.6 g" 3 "iv" "over 2 hours" "0.6 g x 3 iv over 2 hours" 15
|
||||
"CPT" "Ceftaroline" "standard_dosage" "0.6 g" 2 "iv" "over 1 hour" "0.6 g x 2 iv over 1 hour" 15
|
||||
"CAZ" "Ceftazidime" "high_dosage" "1 g" 6 "iv" "" "1 g x 6 iv" 15
|
||||
"CAZ" "Ceftazidime" "standard_dosage" "1 g" 3 "iv" "" "1 g x 3 iv" 15
|
||||
"CZA" "Ceftazidime/avibactam" "standard_dosage" "2 g + 0.5 g" 3 "iv" "over 2 hours" "(2 g ceftazidime + 0.5 g avibactam) x 3 iv over 2 hours" 15
|
||||
"CTB" "Ceftibuten" "standard_dosage" "0.4 g" 1 "oral" "" "0.4 g x 1 oral" 15
|
||||
"BPR" "Ceftobiprole" "standard_dosage" "0.5 g" 3 "iv" "over 2 hours" "0.5 g x 3 iv over 2 hours" 15
|
||||
"CZT" "Ceftolozane/tazobactam" "standard_dosage" "1 g + 0.5 g" 3 "iv" "over 1 hour" "(1 g ceftolozane + 0.5 g tazobactam) x 3 iv over 1 hour" 15
|
||||
"CZT" "Ceftolozane/tazobactam" "standard_dosage" "2 g + 1 g" 3 "iv" "over 1 hour" "(2 g ceftolozane + 1 g tazobactam)
|
||||
x 3 iv over 1 hour" 15
|
||||
"CRO" "Ceftriaxone" "high_dosage" "4 g" 1 "iv" "" "4 g x 1 iv" 15
|
||||
"CRO" "Ceftriaxone" "standard_dosage" "2 g" 1 "iv" "" "2 g x 1 iv" 15
|
||||
"CXM" "Cefuroxime" "high_dosage" "1.5 g" 3 "iv" "" "1.5 g x 3 iv" 15
|
||||
"CXM" "Cefuroxime" "standard_dosage" "0.75 g" 3 "iv" "" "0.75 g x 3 iv" 15
|
||||
"CXM" "Cefuroxime" "high_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2 oral" 15
|
||||
"CXM" "Cefuroxime" "standard_dosage" "0.25 g" 2 "oral" "" "0.25 g x 2 oral" 15
|
||||
"CXM" "Cefuroxime" "uncomplicated_uti" "0.25 g" 2 "oral" "" "0.25 g x 2 oral" 15
|
||||
"CHL" "Chloramphenicol" "high_dosage" "2 g" 4 "iv" "" "2 g x 4 iv" 15
|
||||
"CHL" "Chloramphenicol" "standard_dosage" "1 g" 4 "iv" "" "1 g x 4 iv" 15
|
||||
"CHL" "Chloramphenicol" "high_dosage" "2 g" 4 "oral" "" "2 g x 4 oral" 15
|
||||
"CHL" "Chloramphenicol" "standard_dosage" "1 g" 4 "oral" "" "1 g x 4 oral" 15
|
||||
"CIP" "Ciprofloxacin" "high_dosage" "0.4 g" 3 "iv" "" "0.4 g x 3 iv" 15
|
||||
"CIP" "Ciprofloxacin" "standard_dosage" "0.4 g" 2 "iv" "" "0.4 g x 2 iv" 15
|
||||
"CIP" "Ciprofloxacin" "high_dosage" "0.75 g" 2 "oral" "" "0.75 g x 2 oral" 15
|
||||
"CIP" "Ciprofloxacin" "standard_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2 oral" 15
|
||||
"CLR" "Clarithromycin" "standard_dosage" "0.25 g" 2 "oral" "" "0.25 g x 2 oral" 15
|
||||
"CLI" "Clindamycin" "standard_dosage" "0.6 g" 3 "iv" "" "0.6 g x 3 iv" 15
|
||||
"CLI" "Clindamycin" "standard_dosage" "0.3 g" 2 "oral" "" "0.3 g x 2 oral" 15
|
||||
"CLO" "Cloxacillin" "standard_dosage" "1 g" 4 "iv" "" "1 g x 4 iv" 15
|
||||
"CLO" "Cloxacillin" "standard_dosage" "0.5 g" 4 "oral" "" "0.5 g x 4 oral" 15
|
||||
"COL" "Colistin" "standard_dosage" "4.5 MU" 2 "iv" "loading dose of 9 MU" "4.5 MU x 2 iv
|
||||
with a loading dose of 9 MU" 15
|
||||
"DAL" "Dalbavancin" "standard_dosage" "1 g" 1 "iv" "over 30 minutes on day 8" "1 g x 1 iv over 30 minutes on day 1
|
||||
If needed, 0.5 g x 1 iv over 30 minutes on day 8" 15
|
||||
"DAP" "Daptomycin" "standard_dosage" "4 mg/kg" 1 "iv" "" "4 mg/kg x 1 iv" 15
|
||||
"DAP" "Daptomycin" "standard_dosage" "6 mg/kg" 1 "iv" "" "6 mg/kg x 1 iv" 15
|
||||
"DFX" "Delafloxacin" "standard_dosage" "0.3 g" 2 "iv" "" "0.3 g x 2 iv" 15
|
||||
"DFX" "Delafloxacin" "standard_dosage" "0.45 g" 2 "oral" "" "0.45 g x 2 oral" 15
|
||||
"DIC" "Dicloxacillin" "standard_dosage" "1 g" 4 "iv" "" "1 g x 4 iv" 15
|
||||
"DIC" "Dicloxacillin" "standard_dosage" "0.5-1 g" 4 "oral" "" "0.5-1 g x 4 oral" 15
|
||||
"DOR" "Doripenem" "high_dosage" "1 g" 3 "iv" "over 1 hour" "1 g x 3 iv over 1 hour" 15
|
||||
"DOR" "Doripenem" "standard_dosage" "0.5 g" 3 "iv" "over 1 hour" "0.5 g x 3 iv over 1 hour" 15
|
||||
"DOX" "Doxycycline" "standard_dosage" "0.1 g" 1 "oral" "" "0.1 g x 1 oral" 15
|
||||
"ERV" "Eravacycline" "standard_dosage" "1 mg/kg" 2 "iv" "" "1 mg/kg x 2 iv" 15
|
||||
"ETP" "Ertapenem" "standard_dosage" "1 g" 1 "iv" "over 30 minutes" "1 g x 1 iv over 30 minutes" 15
|
||||
"ERY" "Erythromycin" "standard_dosage" "0.5 g" 2 "iv" "" "0.5 g x 2-4 iv" 15
|
||||
"ERY" "Erythromycin" "standard_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2-4 oral" 15
|
||||
"FDX" "Fidaxomicin" "standard_dosage" "0.2 g" 2 "oral" "" "0.2 g x 2 oral" 15
|
||||
"FLC" "Flucloxacillin" "standard_dosage" "2 g" 4 "iv" "" "2 g x 4 iv
|
||||
(or 1 g x 6 iv)" 15
|
||||
"FLC" "Flucloxacillin" "standard_dosage" "1 g" 3 "oral" "" "1 g x 3 oral" 15
|
||||
"FUS" "Fusidic acid" "standard_dosage" "0.5 g" 2 "iv" "" "0.5 g x 2 iv" 15
|
||||
"FUS" "Fusidic acid" "standard_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2 oral" 15
|
||||
"GEN" "Gentamicin" "standard_dosage" "6-7 mg/kg" 1 "iv" "" "6-7 mg/kg x 1 iv" 15
|
||||
"IPM" "Imipenem" "high_dosage" "1 g" 4 "iv" "over 30 minutes" "1 g x 4 iv over 30 minutes" 15
|
||||
"IPM" "Imipenem" "standard_dosage" "0.5 g" 4 "iv" "over 30 minutes" "0.5 g x 4 iv over 30 minutes" 15
|
||||
"IMR" "Imipenem/relebactam" "standard_dosage" "0.5 g + 0.25 g" 4 "iv" "over 30 minutes" "(0.5 g imipenem + 0.25 g relebactam)
|
||||
x 4 iv over 30 minutes" 15
|
||||
"LMU" "Lefamulin" "standard_dosage" "0.15 g" 2 "iv" "or 0.6 g x 2 oral" "0.15 g x 2 iv or 0.6 g x 2 oral" 15
|
||||
"LMU" "Lefamulin" "standard_dosage" "0.6 g" 2 "oral" "" "0.6 g x 2 oral" 15
|
||||
"LVX" "Levofloxacin" "high_dosage" "0.5 g" 2 "iv" "" "0.5 g x 2 iv" 15
|
||||
"LVX" "Levofloxacin" "standard_dosage" "0.5 g" 1 "iv" "" "0.5 g x 1 iv" 15
|
||||
"LVX" "Levofloxacin" "high_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2 oral" 15
|
||||
"LVX" "Levofloxacin" "standard_dosage" "0.5 g" 1 "oral" "" "0.5 g x 1 oral" 15
|
||||
"LNZ" "Linezolid" "standard_dosage" "0.6 g" 2 "iv" "" "0.6 g x 2 iv" 15
|
||||
"LNZ" "Linezolid" "standard_dosage" "0.6 g" 2 "oral" "" "0.6 g x 2 oral" 15
|
||||
"MEM" "Meropenem" "high_dosage" "2 g" 3 "iv" "over 3 hours" "2 g x 3 iv over 3 hours" 15
|
||||
"MEM" "Meropenem" "standard_dosage" "1 g" 3 "iv" "over 30 minutes" "1 g x 3 iv over 30 minutes" 15
|
||||
"MEV" "Meropenem/vaborbactam" "standard_dosage" "2 g + 2 g" 3 "iv" "over 3 hours" "(2 g meropenem + 2 g vaborbactam) x 3 iv over 3 hours" 15
|
||||
"MTR" "Metronidazole" "standard_dosage" "0.4 g" 3 "iv" "" "0.4 g x 3 iv" 15
|
||||
"MTR" "Metronidazole" "standard_dosage" "0.4 g" 3 "oral" "" "0.4 g x 3 oral" 15
|
||||
"MNO" "Minocycline" "standard_dosage" "0.1 g" 2 "oral" "" "0.1 g x 2 oral" 15
|
||||
"MFX" "Moxifloxacin" "standard_dosage" "0.4 g" 1 "iv" "" "0.4 g x 1 iv" 15
|
||||
"MFX" "Moxifloxacin" "standard_dosage" "0.4 g" 1 "oral" "" "0.4 g x 1 oral" 15
|
||||
"NET" "Netilmicin" "standard_dosage" "6-7 mg/kg" 1 "iv" "" "6-7 mg/kg x 1 iv" 15
|
||||
"OFX" "Ofloxacin" "high_dosage" "0.4 g" 2 "iv" "" "0.4 g x 2 iv" 15
|
||||
"OFX" "Ofloxacin" "standard_dosage" "0.2 g" 2 "iv" "" "0.2 g x 2 iv" 15
|
||||
"OFX" "Ofloxacin" "high_dosage" "0.4 g" 2 "oral" "" "0.4 g x 2 oral" 15
|
||||
"OFX" "Ofloxacin" "standard_dosage" "0.2 g" 2 "oral" "" "0.2 g x 2 oral" 15
|
||||
"ORI" "Oritavancin" "standard_dosage" "1.2 g" 1 "iv" "" "1.2 g x 1 (single dose) iv
|
||||
over 3 hours" 15
|
||||
"OXA" "Oxacillin" "standard_dosage" "1 g" 4 "iv" "" "1 g x 4 iv" 15
|
||||
"PHN" "Phenoxymethylpenicillin" "standard_dosage" "0.5-2 g" 3 "oral" "" "0.5-2 g x 3-4 oral" 15
|
||||
"PIP" "Piperacillin" "high_dosage" "4 g" 4 "iv" "" "4 g x 4 iv
|
||||
by extended 3-hour infusion" 15
|
||||
"PIP" "Piperacillin" "standard_dosage" "4 g" 4 "iv" "" "4 g x 4 iv" 15
|
||||
"TZP" "Piperacillin/tazobactam" "high_dosage" "4 g + 0.5 g" 4 "iv" "" "(4 g piperacillin + 0.5 g tazobactam)
|
||||
x 4 iv by extended 3-hour infusion" 15
|
||||
"TZP" "Piperacillin/tazobactam" "standard_dosage" "" 3 "iv" "" "
|
||||
x 3 iv by extended 4-hour infusion" 15
|
||||
"QDA" "Quinupristin/dalfopristin" "standard_dosage" "7.5 mg/kg" 2 "iv" "" "7.5 mg/kg x 2 iv" 15
|
||||
"RIF" "Rifampicin" "standard_dosage" "0.6 g" 1 "iv" "" "0.6 g x 1 iv" 15
|
||||
"RIF" "Rifampicin" "standard_dosage" "0.6 g" 1 "oral" "" "0.6 g x 1 oral" 15
|
||||
"RXT" "Roxithromycin" "standard_dosage" "0.15 g" 2 "oral" "" "0.15 g x 2 oral" 15
|
||||
"SPT" "Spectinomycin" "standard_dosage" "2 g" 1 "im" "" "2 g x 1 im" 15
|
||||
"TZD" "Tedizolid" "standard_dosage" "0.2 g" 1 "iv" "" "0.2 g x 1 iv" 15
|
||||
"TZD" "Tedizolid" "standard_dosage" "0.2 g" 1 "oral" "" "0.2 g x 1 oral" 15
|
||||
"TEC" "Teicoplanin" "standard_dosage" "0.4 g" 1 "iv" "" "0.4 g x 1 iv" 15
|
||||
"TLV" "Telavancin" "standard_dosage" "10 mg/kg" 1 "iv" "over 1 hour" "10 mg/kg x 1 iv over 1 hour" 15
|
||||
"TEM" "Temocillin" "high_dosage" "2 g" 3 "iv" "" "2 g x 3 iv" 15
|
||||
"TEM" "Temocillin" "standard_dosage" "2 g" 2 "iv" "" "2 g x 2 iv" 15
|
||||
"TCY" "Tetracycline" "standard_dosage" "0.25 g" 4 "oral" "" "0.25 g x 4 oral" 15
|
||||
"TCC" "Ticarcillin/clavulanic acid" "high_dosage" "3 g + 0.1 g" 6 "iv" "" "(3 g ticarcillin + 0.1 g clavulanic acid) x 6 iv" 15
|
||||
"TCC" "Ticarcillin/clavulanic acid" "standard_dosage" "3 g + 0.1-0.2 g" 4 "iv" "" "(3 g ticarcillin + 0.1-0.2 g clavulanic acid) x 4 iv" 15
|
||||
"TGC" "Tigecycline" "standard_dosage" "0.1 g" "loading dose
|
||||
followed by 50 mg x 2 iv" "0.1 g loading dose
|
||||
followed by 50 mg x 2 iv" 15
|
||||
"TOB" "Tobramycin" "standard_dosage" "6-7 mg/kg" 1 "iv" "" "6-7 mg/kg x 1 iv" 15
|
||||
"SXT" "Trimethoprim/sulfamethoxazole" "high_dosage" "0.24 g + 1.2 g" 2 "oral" "" "(0.24 g trimethoprim + 1.2 g sulfamethoxazole) x 2 oral" 15
|
||||
"SXT" "Trimethoprim/sulfamethoxazole" "high_dosage" "0.24 g + 1.2 g" 2 "oral" "" "(0.24 g trimethoprim + 1.2 g sulfamethoxazole) x 2 oral
|
||||
or (0.24 g trimethoprim + 1.2 g sulfamethoxazole) x 2 iv" 15
|
||||
"SXT" "Trimethoprim/sulfamethoxazole" "standard_dosage" "0.16 g + 0.8 g" 2 "oral" "" "(0.16 g trimethoprim + 0.8 g sulfamethoxazole) x 2 oral" 15
|
||||
"SXT" "Trimethoprim/sulfamethoxazole" "standard_dosage" "0.16 g + 0.8 g" 2 "oral" "" "(0.16 g trimethoprim + 0.8 g sulfamethoxazole) x 2 oral
|
||||
or (0.16 g trimethoprim + 0.8 g sulfamethoxazole) x 2 iv" 15
|
||||
"SXT" "Trimethoprim/sulfamethoxazole" "uncomplicated_uti" "0.16 g + 0.8 g" 2 "oral" "" "(0.16 g trimethoprim + 0.8 g sulfamethoxazole) x 2 oral" 15
|
||||
"VAN" "Vancomycin" "standard_dosage" "1 g" 2 "iv" "" "1 g x 2 iv
|
||||
or 2 g x 1 by continuous infusion" 15
|
||||
"AMK" "Amikacin" "standard_dosage" "25-30 mg/kg" 1 "iv" "" "25-30 mg/kg x 1 iv" 14
|
||||
"AMX" "Amoxicillin" "high_dosage" "2 g" 6 "iv" "" "2 g x 6 iv" 14
|
||||
"AMX" "Amoxicillin" "standard_dosage" "1 g" 3 "iv" "" "1 g x 3-4 iv
|
||||
" 14
|
||||
"AMX" "Amoxicillin" "high_dosage" "0.75-1 g" 3 "oral" "" "0.75-1 g x 3 oral" 14
|
||||
"AMX" "Amoxicillin" "standard_dosage" "0.5 g" 3 "oral" "" "0.5 g x 3 oral" 14
|
||||
"AMX" "Amoxicillin" "uncomplicated_uti" "0.5 g" 3 "oral" "" "0.5 g x 3 oral" 14
|
||||
"AMC" "Amoxicillin/clavulanic acid" "high_dosage" "2 g + 0.2 g" 3 "iv" "" "(2 g amoxicillin + 0.2 g clavulanic acid) x 3 iv" 14
|
||||
"AMC" "Amoxicillin/clavulanic acid" "standard_dosage" "1 g + 0.2 g" 3 "iv" "" "(1 g amoxicillin + 0.2 g clavulanic acid) x 3-4 iv" 14
|
||||
"AMC" "Amoxicillin/clavulanic acid" "high_dosage" "0.875 g + 0.125 g" 3 "oral" "" "(0.875 g amoxicillin + 0.125 g clavulanic acid) x 3 oral" 14
|
||||
"AMC" "Amoxicillin/clavulanic acid" "standard_dosage" "0.5 g + 0.125 g" 3 "oral" "" "(0.5 g amoxicillin + 0.125 g
|
||||
clavulanic acid) x 3 oral" 14
|
||||
"AMC" "Amoxicillin/clavulanic acid" "uncomplicated_uti" "0.5 g + 0.125 g" 3 "oral" "" "(0.5 g amoxicillin + 0.125 g
|
||||
clavulanic acid) x 3 oral" 14
|
||||
"AMP" "Ampicillin" "high_dosage" "2 g" 4 "iv" "" "2 g x 4 iv
|
||||
" 14
|
||||
"AMP" "Ampicillin" "standard_dosage" "2 g" 3 "iv" "" "2 g x 3 iv" 14
|
||||
"SAM" "Ampicillin/sulbactam" "high_dosage" "2 g + 1 g" 4 "iv" "" "(2 g ampicillin + 1 g sulbactam) x 4 iv" 14
|
||||
"SAM" "Ampicillin/sulbactam" "standard_dosage" "2 g + 1 g" 3 "iv" "" "(2 g ampicillin + 1 g sulbactam) x 3 iv" 14
|
||||
"AZM" "Azithromycin" "standard_dosage" "0.5 g" 1 "iv" "" "0.5 g x 1 iv" 14
|
||||
"AZM" "Azithromycin" "standard_dosage" "0.5 g" 1 "oral" "" "0.5 g x 1 oral" 14
|
||||
"ATM" "Aztreonam" "high_dosage" "2 g" 4 "iv" "" "2 g x 4 iv" 14
|
||||
"ATM" "Aztreonam" "standard_dosage" "1 g" 3 "iv" "" "1 g x 3 iv" 14
|
||||
"PEN" "Benzylpenicillin" "high_dosage" "1.2 g" 4 "iv" "" "1.2 g (2 MU) x 4-6 iv" 14
|
||||
"PEN" "Benzylpenicillin" "standard_dosage" "0.6 g" 4 "iv" "" "0.6 g (1 MU) x 4 iv" 14
|
||||
"CEC" "Cefaclor" "high_dosage" "1 g" 3 "oral" "" 14
|
||||
"CEC" "Cefaclor" "standard_dosage" "0.25-0.5 g" 3 "oral" "" "0.25-0.5 g x 3 oral" 14
|
||||
"CFR" "Cefadroxil" "standard_dosage" "0.5-1 g" 2 "oral" "" "0.5-1 g x 2 oral" 14
|
||||
"CFR" "Cefadroxil" "uncomplicated_uti" "0.5-1 g" 2 "oral" "" "0.5-1 g x 2 oral" 14
|
||||
"LEX" "Cefalexin" "standard_dosage" "0.25-1 g" 2 "oral" "" "0.25-1 g x 2-3 oral" 14
|
||||
"LEX" "Cefalexin" "uncomplicated_uti" "0.25-1 g" 2 "oral" "" "0.25-1 g x 2-3 oral" 14
|
||||
"CZO" "Cefazolin" "high_dosage" "2 g" 3 "iv" "" "2 g x 3 iv" 14
|
||||
"CZO" "Cefazolin" "standard_dosage" "1 g" 3 "iv" "" "1 g x 3 iv" 14
|
||||
"FEP" "Cefepime" "high_dosage" "2 g" 3 "iv" "" "2 g x 3 iv" 14
|
||||
"FEP" "Cefepime" "standard_dosage" "2 g" 2 "iv" "" "2 g x 2 iv" 14
|
||||
"FDC" "Cefiderocol" "standard_dosage" "2 g" 3 "iv" "over 3 hours" "2 g x 3 iv over 3 hours" 14
|
||||
"CFM" "Cefixime" "standard_dosage" "0.2-0.4 g" 2 "oral" "" "0.2-0.4 g x 2 oral" 14
|
||||
"CFM" "Cefixime" "uncomplicated_uti" "0.2-0.4 g" 2 "oral" "" "0.2-0.4 g x 2 oral" 14
|
||||
"CTX" "Cefotaxime" "high_dosage" "2 g" 3 "iv" "" "2 g x 3 iv" 14
|
||||
"CTX" "Cefotaxime" "standard_dosage" "1 g" 3 "iv" "" "1 g x 3 iv" 14
|
||||
"CPD" "Cefpodoxime" "standard_dosage" "0.1-0.2 g" 2 "oral" "" "0.1-0.2 g x 2 oral" 14
|
||||
"CPD" "Cefpodoxime" "uncomplicated_uti" "0.1-0.2 g" 2 "oral" "" "0.1-0.2 g x 2 oral" 14
|
||||
"CPT" "Ceftaroline" "high_dosage" "0.6 g" 3 "iv" "over 2 hours" "0.6 g x 3 iv over 2 hours" 14
|
||||
"CPT" "Ceftaroline" "standard_dosage" "0.6 g" 2 "iv" "over 1 hour" "0.6 g x 2 iv over 1 hour" 14
|
||||
"CAZ" "Ceftazidime" "high_dosage" "1 g" 6 "iv" "" "1 g x 6 iv" 14
|
||||
"CAZ" "Ceftazidime" "standard_dosage" "1 g" 3 "iv" "" "1 g x 3 iv" 14
|
||||
"CZA" "Ceftazidime/avibactam" "standard_dosage" "2 g + 0.5 g" 3 "iv" "over 2 hours" "(2 g ceftazidime + 0.5 g avibactam) x 3 iv over 2 hours" 14
|
||||
"CTB" "Ceftibuten" "standard_dosage" "0.4 g" 1 "oral" "" "0.4 g x 1 oral" 14
|
||||
"BPR" "Ceftobiprole" "standard_dosage" "0.5 g" 3 "iv" "over 2 hours" "0.5 g x 3 iv over 2 hours" 14
|
||||
"CZT" "Ceftolozane/tazobactam" "standard_dosage" "1 g + 0.5 g" 3 "iv" "over 1 hour" "(1 g ceftolozane + 0.5 g tazobactam) x 3 iv over 1 hour" 14
|
||||
"CZT" "Ceftolozane/tazobactam" "standard_dosage" "2 g + 1 g" 3 "iv" "over 1 hour" "(2 g ceftolozane + 1 g tazobactam)
|
||||
x 3 iv over 1 hour" 14
|
||||
"CRO" "Ceftriaxone" "high_dosage" "4 g" 1 "iv" "" "4 g x 1 iv" 14
|
||||
"CRO" "Ceftriaxone" "standard_dosage" "2 g" 1 "iv" "" "2 g x 1 iv" 14
|
||||
"CXM" "Cefuroxime" "high_dosage" "1.5 g" 3 "iv" "" "1.5 g x 3 iv" 14
|
||||
"CXM" "Cefuroxime" "standard_dosage" "0.75 g" 3 "iv" "" "0.75 g x 3 iv" 14
|
||||
"CXM" "Cefuroxime" "high_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2 oral" 14
|
||||
"CXM" "Cefuroxime" "standard_dosage" "0.25 g" 2 "oral" "" "0.25 g x 2 oral" 14
|
||||
"CXM" "Cefuroxime" "uncomplicated_uti" "0.25 g" 2 "oral" "" "0.25 g x 2 oral" 14
|
||||
"CHL" "Chloramphenicol" "high_dosage" "2 g" 4 "iv" "" "2 g x 4 iv" 14
|
||||
"CHL" "Chloramphenicol" "standard_dosage" "1 g" 4 "iv" "" "1 g x 4 iv" 14
|
||||
"CHL" "Chloramphenicol" "high_dosage" "2 g" 4 "oral" "" "2 g x 4 oral" 14
|
||||
"CHL" "Chloramphenicol" "standard_dosage" "1 g" 4 "oral" "" "1 g x 4 oral" 14
|
||||
"CIP" "Ciprofloxacin" "high_dosage" "0.4 g" 3 "iv" "" "0.4 g x 3 iv" 14
|
||||
"CIP" "Ciprofloxacin" "standard_dosage" "0.4 g" 2 "iv" "" "0.4 g x 2 iv" 14
|
||||
"CIP" "Ciprofloxacin" "high_dosage" "0.75 g" 2 "oral" "" "0.75 g x 2 oral" 14
|
||||
"CIP" "Ciprofloxacin" "standard_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2 oral" 14
|
||||
"CLR" "Clarithromycin" "standard_dosage" "0.25 g" 2 "oral" "" "0.25 g x 2 oral" 14
|
||||
"CLI" "Clindamycin" "standard_dosage" "0.6 g" 3 "iv" "" "0.6 g x 3 iv" 14
|
||||
"CLI" "Clindamycin" "standard_dosage" "0.3 g" 2 "oral" "" "0.3 g x 2 oral" 14
|
||||
"CLO" "Cloxacillin" "standard_dosage" "1 g" 4 "iv" "" "1 g x 4 iv" 14
|
||||
"CLO" "Cloxacillin" "standard_dosage" "0.5 g" 4 "oral" "" "0.5 g x 4 oral" 14
|
||||
"COL" "Colistin" "standard_dosage" "4.5 MU" 2 "iv" "loading dose of 9 MU" "4.5 MU x 2 iv
|
||||
with a loading dose of 9 MU" 14
|
||||
"DAL" "Dalbavancin" "standard_dosage" "1 g" 1 "iv" "over 30 minutes on day 8" "1 g x 1 iv over 30 minutes on day 1
|
||||
If needed, 0.5 g x 1 iv over 30 minutes on day 8" 14
|
||||
"DAP" "Daptomycin" "standard_dosage" "4 mg/kg" 1 "iv" "" "4 mg/kg x 1 iv" 14
|
||||
"DAP" "Daptomycin" "standard_dosage" "6 mg/kg" 1 "iv" "" "6 mg/kg x 1 iv" 14
|
||||
"DFX" "Delafloxacin" "standard_dosage" "0.3 g" 2 "iv" "" "0.3 g x 2 iv" 14
|
||||
"DFX" "Delafloxacin" "standard_dosage" "0.45 g" 2 "oral" "" "0.45 g x 2 oral" 14
|
||||
"DIC" "Dicloxacillin" "standard_dosage" "1 g" 4 "iv" "" "1 g x 4 iv" 14
|
||||
"DIC" "Dicloxacillin" "standard_dosage" "0.5-1 g" 4 "oral" "" "0.5-1 g x 4 oral" 14
|
||||
"DOR" "Doripenem" "high_dosage" "1 g" 3 "iv" "over 1 hour" "1 g x 3 iv over 1 hour" 14
|
||||
"DOR" "Doripenem" "standard_dosage" "0.5 g" 3 "iv" "over 1 hour" "0.5 g x 3 iv over 1 hour" 14
|
||||
"DOX" "Doxycycline" "standard_dosage" "0.1 g" 1 "oral" "" "0.1 g x 1 oral" 14
|
||||
"ERV" "Eravacycline" "standard_dosage" "1 mg/kg" 2 "iv" "" "1 mg/kg x 2 iv" 14
|
||||
"ETP" "Ertapenem" "standard_dosage" "1 g" 1 "iv" "over 30 minutes" "1 g x 1 iv over 30 minutes" 14
|
||||
"ERY" "Erythromycin" "standard_dosage" "0.5 g" 2 "iv" "" "0.5 g x 2-4 iv" 14
|
||||
"ERY" "Erythromycin" "standard_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2-4 oral" 14
|
||||
"FDX" "Fidaxomicin" "standard_dosage" "0.2 g" 2 "oral" "" "0.2 g x 2 oral" 14
|
||||
"FLC" "Flucloxacillin" "standard_dosage" "2 g" 4 "iv" "" "2 g x 4 iv
|
||||
(or 1 g x 6 iv)" 14
|
||||
"FLC" "Flucloxacillin" "standard_dosage" "1 g" 3 "oral" "" "1 g x 3 oral" 14
|
||||
"FUS" "Fusidic acid" "standard_dosage" "0.5 g" 2 "iv" "" "0.5 g x 2 iv" 14
|
||||
"FUS" "Fusidic acid" "standard_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2 oral" 14
|
||||
"GEN" "Gentamicin" "standard_dosage" "6-7 mg/kg" 1 "iv" "" "6-7 mg/kg x 1 iv" 14
|
||||
"IPM" "Imipenem" "high_dosage" "1 g" 4 "iv" "over 30 minutes" "1 g x 4 iv over 30 minutes" 14
|
||||
"IPM" "Imipenem" "standard_dosage" "0.5 g" 4 "iv" "over 30 minutes" "0.5 g x 4 iv over 30 minutes" 14
|
||||
"IMR" "Imipenem/relebactam" "standard_dosage" "0.5 g + 0.25 g" 4 "iv" "over 30 minutes" "(0.5 g imipenem + 0.25 g relebactam)
|
||||
x 4 iv over 30 minutes" 14
|
||||
"LMU" "Lefamulin" "standard_dosage" "0.15 g" 2 "iv" "or 0.6 g x 2 oral" "0.15 g x 2 iv or 0.6 g x 2 oral" 14
|
||||
"LMU" "Lefamulin" "standard_dosage" "0.6 g" 2 "oral" "" "0.6 g x 2 oral" 14
|
||||
"LVX" "Levofloxacin" "high_dosage" "0.5 g" 2 "iv" "" "0.5 g x 2 iv" 14
|
||||
"LVX" "Levofloxacin" "standard_dosage" "0.5 g" 1 "iv" "" "0.5 g x 1 iv" 14
|
||||
"LVX" "Levofloxacin" "high_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2 oral" 14
|
||||
"LVX" "Levofloxacin" "standard_dosage" "0.5 g" 1 "oral" "" "0.5 g x 1 oral" 14
|
||||
"LNZ" "Linezolid" "standard_dosage" "0.6 g" 2 "iv" "" "0.6 g x 2 iv" 14
|
||||
"LNZ" "Linezolid" "standard_dosage" "0.6 g" 2 "oral" "" "0.6 g x 2 oral" 14
|
||||
"MEM" "Meropenem" "high_dosage" "2 g" 3 "iv" "over 3 hours" "2 g x 3 iv over 3 hours" 14
|
||||
"MEM" "Meropenem" "standard_dosage" "1 g" 3 "iv" "over 30 minutes" "1 g x 3 iv over 30 minutes" 14
|
||||
"MEV" "Meropenem/vaborbactam" "standard_dosage" "2 g + 2 g" 3 "iv" "over 3 hours" "(2 g meropenem + 2 g vaborbactam) x 3 iv over 3 hours" 14
|
||||
"MTR" "Metronidazole" "standard_dosage" "0.4 g" 3 "iv" "" "0.4 g x 3 iv" 14
|
||||
"MTR" "Metronidazole" "standard_dosage" "0.4 g" 3 "oral" "" "0.4 g x 3 oral" 14
|
||||
"MNO" "Minocycline" "standard_dosage" "0.1 g" 2 "oral" "" "0.1 g x 2 oral" 14
|
||||
"MFX" "Moxifloxacin" "standard_dosage" "0.4 g" 1 "iv" "" "0.4 g x 1 iv" 14
|
||||
"MFX" "Moxifloxacin" "standard_dosage" "0.4 g" 1 "oral" "" "0.4 g x 1 oral" 14
|
||||
"NET" "Netilmicin" "standard_dosage" "6-7 mg/kg" 1 "iv" "" "6-7 mg/kg x 1 iv" 14
|
||||
"OFX" "Ofloxacin" "high_dosage" "0.4 g" 2 "iv" "" "0.4 g x 2 iv" 14
|
||||
"OFX" "Ofloxacin" "standard_dosage" "0.2 g" 2 "iv" "" "0.2 g x 2 iv" 14
|
||||
"OFX" "Ofloxacin" "high_dosage" "0.4 g" 2 "oral" "" "0.4 g x 2 oral" 14
|
||||
"OFX" "Ofloxacin" "standard_dosage" "0.2 g" 2 "oral" "" "0.2 g x 2 oral" 14
|
||||
"ORI" "Oritavancin" "standard_dosage" "1.2 g" 1 "iv" "" "1.2 g x 1 (single dose) iv
|
||||
over 3 hours" 14
|
||||
"OXA" "Oxacillin" "standard_dosage" "1 g" 4 "iv" "" "1 g x 4 iv" 14
|
||||
"PHN" "Phenoxymethylpenicillin" "standard_dosage" "0.5-2 g" 3 "oral" "" "0.5-2 g x 3-4 oral" 14
|
||||
"PIP" "Piperacillin" "high_dosage" "4 g" 4 "iv" "" "4 g x 4 iv
|
||||
by extended 3-hour infusion" 14
|
||||
"PIP" "Piperacillin" "standard_dosage" "4 g" 4 "iv" "" "4 g x 4 iv" 14
|
||||
"TZP" "Piperacillin/tazobactam" "high_dosage" "4 g + 0.5 g" 4 "iv" "" "(4 g piperacillin + 0.5 g tazobactam)
|
||||
x 4 iv by extended 3-hour infusion" 14
|
||||
"TZP" "Piperacillin/tazobactam" "standard_dosage" "" 3 "iv" "" "
|
||||
x 3 iv by extended 4-hour infusion" 14
|
||||
"QDA" "Quinupristin/dalfopristin" "standard_dosage" "7.5 mg/kg" 2 "iv" "" "7.5 mg/kg x 2 iv" 14
|
||||
"RIF" "Rifampicin" "standard_dosage" "0.6 g" 1 "iv" "" "0.6 g x 1 iv" 14
|
||||
"RIF" "Rifampicin" "standard_dosage" "0.6 g" 1 "oral" "" "0.6 g x 1 oral" 14
|
||||
"RXT" "Roxithromycin" "standard_dosage" "0.15 g" 2 "oral" "" "0.15 g x 2 oral" 14
|
||||
"SPT" "Spectinomycin" "standard_dosage" "2 g" 1 "im" "" "2 g x 1 im" 14
|
||||
"TZD" "Tedizolid" "standard_dosage" "0.2 g" 1 "iv" "" "0.2 g x 1 iv" 14
|
||||
"TZD" "Tedizolid" "standard_dosage" "0.2 g" 1 "oral" "" "0.2 g x 1 oral" 14
|
||||
"TEC" "Teicoplanin" "standard_dosage" "0.4 g" 1 "iv" "" "0.4 g x 1 iv" 14
|
||||
"TLV" "Telavancin" "standard_dosage" "10 mg/kg" 1 "iv" "over 1 hour" "10 mg/kg x 1 iv over 1 hour" 14
|
||||
"TEM" "Temocillin" "high_dosage" "2 g" 3 "iv" "" "2 g x 3 iv" 14
|
||||
"TEM" "Temocillin" "standard_dosage" "2 g" 2 "iv" "" "2 g x 2 iv" 14
|
||||
"TCY" "Tetracycline" "standard_dosage" "0.25 g" 4 "oral" "" "0.25 g x 4 oral" 14
|
||||
"TCC" "Ticarcillin/clavulanic acid" "high_dosage" "3 g + 0.1 g" 6 "iv" "" "(3 g ticarcillin + 0.1 g clavulanic acid) x 6 iv" 14
|
||||
"TCC" "Ticarcillin/clavulanic acid" "standard_dosage" "3 g + 0.1-0.2 g" 4 "iv" "" "(3 g ticarcillin + 0.1-0.2 g clavulanic acid) x 4 iv" 14
|
||||
"TGC" "Tigecycline" "standard_dosage" "0.1 g" "loading dose
|
||||
followed by 50 mg x 2 iv" "0.1 g loading dose
|
||||
followed by 50 mg x 2 iv" 14
|
||||
"TOB" "Tobramycin" "standard_dosage" "6-7 mg/kg" 1 "iv" "" "6-7 mg/kg x 1 iv" 14
|
||||
"SXT" "Trimethoprim/sulfamethoxazole" "high_dosage" "0.24 g + 1.2 g" 2 "oral" "" "(0.24 g trimethoprim + 1.2 g sulfamethoxazole) x 2 oral" 14
|
||||
"SXT" "Trimethoprim/sulfamethoxazole" "high_dosage" "0.24 g + 1.2 g" 2 "oral" "" "(0.24 g trimethoprim + 1.2 g sulfamethoxazole) x 2 oral
|
||||
or (0.24 g trimethoprim + 1.2 g sulfamethoxazole) x 2 iv" 14
|
||||
"SXT" "Trimethoprim/sulfamethoxazole" "standard_dosage" "0.16 g + 0.8 g" 2 "oral" "" "(0.16 g trimethoprim + 0.8 g sulfamethoxazole) x 2 oral" 14
|
||||
"SXT" "Trimethoprim/sulfamethoxazole" "standard_dosage" "0.16 g + 0.8 g" 2 "oral" "" "(0.16 g trimethoprim + 0.8 g sulfamethoxazole) x 2 oral
|
||||
or (0.16 g trimethoprim + 0.8 g sulfamethoxazole) x 2 iv" 14
|
||||
"SXT" "Trimethoprim/sulfamethoxazole" "uncomplicated_uti" "0.16 g + 0.8 g" 2 "oral" "" "(0.16 g trimethoprim + 0.8 g sulfamethoxazole) x 2 oral" 14
|
||||
"VAN" "Vancomycin" "standard_dosage" "1 g" 2 "iv" "" "1 g x 2 iv
|
||||
or 2 g x 1 by continuous infusion" 14
|
||||
"AMK" "Amikacin" "standard_dosage" "25-30 mg/kg" 1 "iv" "" "25-30 mg/kg x 1 iv" 13.1
|
||||
"AMX" "Amoxicillin" "high_dosage" "2 g" 6 "iv" "" "2 g x 6 iv" 13.1
|
||||
"AMX" "Amoxicillin" "standard_dosage" "1 g" 3 "iv" "" "1 g x 3-4 iv
|
||||
" 13.1
|
||||
"AMX" "Amoxicillin" "high_dosage" "0.75-1 g" 3 "oral" "" "0.75-1 g x 3 oral" 13.1
|
||||
"AMX" "Amoxicillin" "standard_dosage" "0.5 g" 3 "oral" "" "0.5 g x 3 oral" 13.1
|
||||
"AMX" "Amoxicillin" "uncomplicated_uti" "0.5 g" 3 "oral" "" "0.5 g x 3 oral" 13.1
|
||||
"AMC" "Amoxicillin/clavulanic acid" "high_dosage" "2 g + 0.2 g" 3 "iv" "" "(2 g amoxicillin + 0.2 g clavulanic acid) x 3 iv" 13.1
|
||||
"AMC" "Amoxicillin/clavulanic acid" "standard_dosage" "1 g + 0.2 g" 3 "iv" "" "(1 g amoxicillin + 0.2 g clavulanic acid) x 3-4 iv" 13.1
|
||||
"AMC" "Amoxicillin/clavulanic acid" "high_dosage" "0.875 g + 0.125 g" 3 "oral" "" "(0.875 g amoxicillin + 0.125 g clavulanic acid) x 3 oral" 13.1
|
||||
"AMC" "Amoxicillin/clavulanic acid" "standard_dosage" "0.5 g + 0.125 g" 3 "oral" "" "(0.5 g amoxicillin + 0.125 g
|
||||
clavulanic acid) x 3 oral" 13.1
|
||||
"AMC" "Amoxicillin/clavulanic acid" "uncomplicated_uti" "0.5 g + 0.125 g" 3 "oral" "" "(0.5 g amoxicillin + 0.125 g
|
||||
clavulanic acid) x 3 oral" 13.1
|
||||
"AMP" "Ampicillin" "high_dosage" "2 g" 4 "iv" "" "2 g x 4 iv
|
||||
" 13.1
|
||||
"AMP" "Ampicillin" "standard_dosage" "2 g" 3 "iv" "" "2 g x 3 iv" 13.1
|
||||
"SAM" "Ampicillin/sulbactam" "high_dosage" "2 g + 1 g" 4 "iv" "" "(2 g ampicillin + 1 g sulbactam) x 4 iv" 13.1
|
||||
"SAM" "Ampicillin/sulbactam" "standard_dosage" "2 g + 1 g" 3 "iv" "" "(2 g ampicillin + 1 g sulbactam) x 3 iv" 13.1
|
||||
"AZM" "Azithromycin" "standard_dosage" "0.5 g" 1 "iv" "" "0.5 g x 1 iv" 13.1
|
||||
"AZM" "Azithromycin" "standard_dosage" "0.5 g" 1 "oral" "" "0.5 g x 1 oral" 13.1
|
||||
"ATM" "Aztreonam" "high_dosage" "2 g" 4 "iv" "" "2 g x 4 iv" 13.1
|
||||
"ATM" "Aztreonam" "standard_dosage" "1 g" 3 "iv" "" "1 g x 3 iv" 13.1
|
||||
"PEN" "Benzylpenicillin" "high_dosage" "1.2 g" 4 "iv" "" "1.2 g (2 MU) x 4-6 iv" 13.1
|
||||
"PEN" "Benzylpenicillin" "standard_dosage" "0.6 g" 4 "iv" "" "0.6 g (1 MU) x 4 iv" 13.1
|
||||
"CEC" "Cefaclor" "high_dosage" "1 g" 3 "oral" "" 13.1
|
||||
"CEC" "Cefaclor" "standard_dosage" "0.25-0.5 g" 3 "oral" "" "0.25-0.5 g x 3 oral" 13.1
|
||||
"CFR" "Cefadroxil" "standard_dosage" "0.5-1 g" 2 "oral" "" "0.5-1 g x 2 oral" 13.1
|
||||
"CFR" "Cefadroxil" "uncomplicated_uti" "0.5-1 g" 2 "oral" "" "0.5-1 g x 2 oral" 13.1
|
||||
"LEX" "Cefalexin" "standard_dosage" "0.25-1 g" 2 "oral" "" "0.25-1 g x 2-3 oral" 13.1
|
||||
"LEX" "Cefalexin" "uncomplicated_uti" "0.25-1 g" 2 "oral" "" "0.25-1 g x 2-3 oral" 13.1
|
||||
"CZO" "Cefazolin" "high_dosage" "2 g" 3 "iv" "" "2 g x 3 iv" 13.1
|
||||
"CZO" "Cefazolin" "standard_dosage" "1 g" 3 "iv" "" "1 g x 3 iv" 13.1
|
||||
"FEP" "Cefepime" "high_dosage" "2 g" 3 "iv" "" "2 g x 3 iv" 13.1
|
||||
"FEP" "Cefepime" "standard_dosage" "2 g" 2 "iv" "" "2 g x 2 iv" 13.1
|
||||
"FDC" "Cefiderocol" "standard_dosage" "2 g" 3 "iv" "over 3 hours" "2 g x 3 iv over 3 hours" 13.1
|
||||
"CFM" "Cefixime" "standard_dosage" "0.2-0.4 g" 2 "oral" "" "0.2-0.4 g x 2 oral" 13.1
|
||||
"CFM" "Cefixime" "uncomplicated_uti" "0.2-0.4 g" 2 "oral" "" "0.2-0.4 g x 2 oral" 13.1
|
||||
"CTX" "Cefotaxime" "high_dosage" "2 g" 3 "iv" "" "2 g x 3 iv" 13.1
|
||||
"CTX" "Cefotaxime" "standard_dosage" "1 g" 3 "iv" "" "1 g x 3 iv" 13.1
|
||||
"CPD" "Cefpodoxime" "standard_dosage" "0.1-0.2 g" 2 "oral" "" "0.1-0.2 g x 2 oral" 13.1
|
||||
"CPD" "Cefpodoxime" "uncomplicated_uti" "0.1-0.2 g" 2 "oral" "" "0.1-0.2 g x 2 oral" 13.1
|
||||
"CPT" "Ceftaroline" "high_dosage" "0.6 g" 3 "iv" "over 2 hours" "0.6 g x 3 iv over 2 hours" 13.1
|
||||
"CPT" "Ceftaroline" "standard_dosage" "0.6 g" 2 "iv" "over 1 hour" "0.6 g x 2 iv over 1 hour" 13.1
|
||||
"CAZ" "Ceftazidime" "high_dosage" "1 g" 6 "iv" "" "1 g x 6 iv" 13.1
|
||||
"CAZ" "Ceftazidime" "standard_dosage" "1 g" 3 "iv" "" "1 g x 3 iv" 13.1
|
||||
"CZA" "Ceftazidime/avibactam" "standard_dosage" "2 g + 0.5 g" 3 "iv" "over 2 hours" "(2 g ceftazidime + 0.5 g avibactam) x 3 iv over 2 hours" 13.1
|
||||
"CTB" "Ceftibuten" "standard_dosage" "0.4 g" 1 "oral" "" "0.4 g x 1 oral" 13.1
|
||||
"BPR" "Ceftobiprole" "standard_dosage" "0.5 g" 3 "iv" "over 2 hours" "0.5 g x 3 iv over 2 hours" 13.1
|
||||
"CZT" "Ceftolozane/tazobactam" "standard_dosage" "1 g + 0.5 g" 3 "iv" "over 1 hour" "(1 g ceftolozane + 0.5 g tazobactam) x 3 iv over 1 hour" 13.1
|
||||
"CZT" "Ceftolozane/tazobactam" "standard_dosage" "2 g + 1 g" 3 "iv" "over 1 hour" "(2 g ceftolozane + 1 g tazobactam)
|
||||
x 3 iv over 1 hour" 13.1
|
||||
"CRO" "Ceftriaxone" "high_dosage" "4 g" 1 "iv" "" "4 g x 1 iv" 13.1
|
||||
"CRO" "Ceftriaxone" "standard_dosage" "2 g" 1 "iv" "" "2 g x 1 iv" 13.1
|
||||
"CXM" "Cefuroxime" "high_dosage" "1.5 g" 3 "iv" "" "1.5 g x 3 iv" 13.1
|
||||
"CXM" "Cefuroxime" "standard_dosage" "0.75 g" 3 "iv" "" "0.75 g x 3 iv" 13.1
|
||||
"CXM" "Cefuroxime" "high_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2 oral" 13.1
|
||||
"CXM" "Cefuroxime" "standard_dosage" "0.25 g" 2 "oral" "" "0.25 g x 2 oral" 13.1
|
||||
"CXM" "Cefuroxime" "uncomplicated_uti" "0.25 g" 2 "oral" "" "0.25 g x 2 oral" 13.1
|
||||
"CHL" "Chloramphenicol" "high_dosage" "2 g" 4 "iv" "" "2 g x 4 iv" 13.1
|
||||
"CHL" "Chloramphenicol" "standard_dosage" "1 g" 4 "iv" "" "1 g x 4 iv" 13.1
|
||||
"CHL" "Chloramphenicol" "high_dosage" "2 g" 4 "oral" "" "2 g x 4 oral" 13.1
|
||||
"CHL" "Chloramphenicol" "standard_dosage" "1 g" 4 "oral" "" "1 g x 4 oral" 13.1
|
||||
"CIP" "Ciprofloxacin" "high_dosage" "0.4 g" 3 "iv" "" "0.4 g x 3 iv" 13.1
|
||||
"CIP" "Ciprofloxacin" "standard_dosage" "0.4 g" 2 "iv" "" "0.4 g x 2 iv" 13.1
|
||||
"CIP" "Ciprofloxacin" "high_dosage" "0.75 g" 2 "oral" "" "0.75 g x 2 oral" 13.1
|
||||
"CIP" "Ciprofloxacin" "standard_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2 oral" 13.1
|
||||
"CLR" "Clarithromycin" "standard_dosage" "0.25 g" 2 "oral" "" "0.25 g x 2 oral" 13.1
|
||||
"CLI" "Clindamycin" "standard_dosage" "0.6 g" 3 "iv" "" "0.6 g x 3 iv" 13.1
|
||||
"CLI" "Clindamycin" "standard_dosage" "0.3 g" 2 "oral" "" "0.3 g x 2 oral" 13.1
|
||||
"CLO" "Cloxacillin" "standard_dosage" "1 g" 4 "iv" "" "1 g x 4 iv" 13.1
|
||||
"CLO" "Cloxacillin" "standard_dosage" "0.5 g" 4 "oral" "" "0.5 g x 4 oral" 13.1
|
||||
"COL" "Colistin" "standard_dosage" "4.5 MU" 2 "iv" "loading dose of 9 MU" "4.5 MU x 2 iv
|
||||
with a loading dose of 9 MU" 13.1
|
||||
"DAL" "Dalbavancin" "standard_dosage" "1 g" 1 "iv" "over 30 minutes on day 8" "1 g x 1 iv over 30 minutes on day 1
|
||||
If needed, 0.5 g x 1 iv over 30 minutes on day 8" 13.1
|
||||
"DAP" "Daptomycin" "standard_dosage" "4 mg/kg" 1 "iv" "" "4 mg/kg x 1 iv" 13.1
|
||||
"DAP" "Daptomycin" "standard_dosage" "6 mg/kg" 1 "iv" "" "6 mg/kg x 1 iv" 13.1
|
||||
"DFX" "Delafloxacin" "standard_dosage" "0.3 g" 2 "iv" "" "0.3 g x 2 iv" 13.1
|
||||
"DFX" "Delafloxacin" "standard_dosage" "0.45 g" 2 "oral" "" "0.45 g x 2 oral" 13.1
|
||||
"DIC" "Dicloxacillin" "standard_dosage" "1 g" 4 "iv" "" "1 g x 4 iv" 13.1
|
||||
"DIC" "Dicloxacillin" "standard_dosage" "0.5-1 g" 4 "oral" "" "0.5-1 g x 4 oral" 13.1
|
||||
"DOR" "Doripenem" "high_dosage" "1 g" 3 "iv" "over 1 hour" "1 g x 3 iv over 1 hour" 13.1
|
||||
"DOR" "Doripenem" "standard_dosage" "0.5 g" 3 "iv" "over 1 hour" "0.5 g x 3 iv over 1 hour" 13.1
|
||||
"DOX" "Doxycycline" "standard_dosage" "0.1 g" 1 "oral" "" "0.1 g x 1 oral" 13.1
|
||||
"ERV" "Eravacycline" "standard_dosage" "1 mg/kg" 2 "iv" "" "1 mg/kg x 2 iv" 13.1
|
||||
"ETP" "Ertapenem" "standard_dosage" "1 g" 1 "iv" "over 30 minutes" "1 g x 1 iv over 30 minutes" 13.1
|
||||
"ERY" "Erythromycin" "standard_dosage" "0.5 g" 2 "iv" "" "0.5 g x 2-4 iv" 13.1
|
||||
"ERY" "Erythromycin" "standard_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2-4 oral" 13.1
|
||||
"FDX" "Fidaxomicin" "standard_dosage" "0.2 g" 2 "oral" "" "0.2 g x 2 oral" 13.1
|
||||
"FLC" "Flucloxacillin" "standard_dosage" "2 g" 4 "iv" "" "2 g x 4 iv
|
||||
(or 1 g x 6 iv)" 13.1
|
||||
"FLC" "Flucloxacillin" "standard_dosage" "1 g" 3 "oral" "" "1 g x 3 oral" 13.1
|
||||
"FUS" "Fusidic acid" "standard_dosage" "0.5 g" 2 "iv" "" "0.5 g x 2 iv" 13.1
|
||||
"FUS" "Fusidic acid" "standard_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2 oral" 13.1
|
||||
"GEN" "Gentamicin" "standard_dosage" "6-7 mg/kg" 1 "iv" "" "6-7 mg/kg x 1 iv" 13.1
|
||||
"IPM" "Imipenem" "high_dosage" "1 g" 4 "iv" "over 30 minutes" "1 g x 4 iv over 30 minutes" 13.1
|
||||
"IPM" "Imipenem" "standard_dosage" "0.5 g" 4 "iv" "over 30 minutes" "0.5 g x 4 iv over 30 minutes" 13.1
|
||||
"IMR" "Imipenem/relebactam" "standard_dosage" "0.5 g + 0.25 g" 4 "iv" "over 30 minutes" "(0.5 g imipenem + 0.25 g relebactam)
|
||||
x 4 iv over 30 minutes" 13.1
|
||||
"LMU" "Lefamulin" "standard_dosage" "0.15 g" 2 "iv" "or 0.6 g x 2 oral" "0.15 g x 2 iv or 0.6 g x 2 oral" 13.1
|
||||
"LMU" "Lefamulin" "standard_dosage" "0.6 g" 2 "oral" "" "0.6 g x 2 oral" 13.1
|
||||
"LVX" "Levofloxacin" "high_dosage" "0.5 g" 2 "iv" "" "0.5 g x 2 iv" 13.1
|
||||
"LVX" "Levofloxacin" "standard_dosage" "0.5 g" 1 "iv" "" "0.5 g x 1 iv" 13.1
|
||||
"LVX" "Levofloxacin" "high_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2 oral" 13.1
|
||||
"LVX" "Levofloxacin" "standard_dosage" "0.5 g" 1 "oral" "" "0.5 g x 1 oral" 13.1
|
||||
"LNZ" "Linezolid" "standard_dosage" "0.6 g" 2 "iv" "" "0.6 g x 2 iv" 13.1
|
||||
"LNZ" "Linezolid" "standard_dosage" "0.6 g" 2 "oral" "" "0.6 g x 2 oral" 13.1
|
||||
@@ -273,7 +533,6 @@
|
||||
"CXM" "Cefuroxime" "high_dosage" "1.5 g" 3 "iv" "" "1.5 g x 3 iv" 12
|
||||
"CXM" "Cefuroxime" "standard_dosage" "0.75 g" 3 "iv" "" "0.75 g x 3 iv" 12
|
||||
"CXM" "Cefuroxime" "high_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2 oral" 12
|
||||
"IMR" "Imipenem/relebactam" "standard_dosage" "0.5 g + 0.25 g" 4 "iv" "over 30 minutes" "(0.5 g imipenem + 0.25 g relebactam) x 4 iv over 30 minutes" 12
|
||||
"CXM" "Cefuroxime" "standard_dosage" "0.25 g" 2 "oral" "" "0.25 g x 2 oral" 12
|
||||
"CXM" "Cefuroxime" "uncomplicated_uti" "0.25 g" 2 "oral" "" "0.25 g x 2 oral" 12
|
||||
"CHL" "Chloramphenicol" "high_dosage" "2 g" 4 "iv" "" "2 g x 4 iv" 12
|
||||
@@ -331,7 +590,6 @@
|
||||
"IMR" "Imipenem/relebactam" "standard_dosage" "0.5 g + 0.25 g" 4 "iv" "over 30 minutes" "(0.5 g imipenem + 0.25 g relebactam) x 4 iv over 30 minutes" 12
|
||||
"LMU" "Lefamulin" "standard_dosage" "0.15 g" 2 "iv" "or 0.6 g x 2 oral" "0.15 g x 2 iv or 0.6 g x 2 oral" 12
|
||||
"LMU" "Lefamulin" "standard_dosage" "0.6 g" 2 "oral" "" "0.6 g x 2 oral" 12
|
||||
"SXT" "Trimethoprim/sulfamethoxazole" "uncomplicated_uti" "0.16 g + 0.8 g" 2 "oral" "" "(0.16 g trimethoprim + 0.8 g sulfamethoxazole) x 2 oral" 12
|
||||
"LVX" "Levofloxacin" "high_dosage" "0.5 g" 2 "iv" "" "0.5 g x 2 iv" 12
|
||||
"LVX" "Levofloxacin" "standard_dosage" "0.5 g" 1 "iv" "" "0.5 g x 1 iv" 12
|
||||
"LVX" "Levofloxacin" "high_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2 oral" 12
|
||||
@@ -358,6 +616,8 @@
|
||||
"PHN" "Phenoxymethylpenicillin" "standard_dosage" "0.5-2 g" 3 "oral" "" "0.5-2 g x 3-4 oral" 12
|
||||
"PIP" "Piperacillin" "high_dosage" "4 g" 4 "iv" "" "4 g x 4 iv by extended 3-hour infusion" 12
|
||||
"PIP" "Piperacillin" "standard_dosage" "4 g" 4 "iv" "" "4 g x 4 iv" 12
|
||||
"TZP" "Piperacillin/tazobactam" "high_dosage" "4 g + 0.5 g" 4 "iv" "" "(4 g piperacillin + 0.5 g tazobactam) x 4 iv by extended 3-hour infusion" 12
|
||||
"TZP" "Piperacillin/tazobactam" "standard_dosage" "4 g + 0.5 g" 4 "iv" "" "(4 g piperacillin + 0.5 g tazobactam) x 4 iv 30-minute infusion or x 3 iv by extended 4-hour infusion" 12
|
||||
"QDA" "Quinupristin/dalfopristin" "high_dosage" "7.5 mg/kg" 3 "iv" "" "7.5 mg/kg x 3 iv" 12
|
||||
"QDA" "Quinupristin/dalfopristin" "standard_dosage" "7.5 mg/kg" 2 "iv" "" "7.5 mg/kg x 2 iv" 12
|
||||
"RIF" "Rifampicin" "standard_dosage" "0.6 g" 1 "iv" "" "0.6 g x 1 iv" 12
|
||||
@@ -385,8 +645,6 @@
|
||||
"SXT" "Trimethoprim/sulfamethoxazole" "standard_dosage" "0.16 g + 0.8 g" 2 "oral" "" "(0.16 g trimethoprim + 0.8 g sulfamethoxazole) x 2 oral" 12
|
||||
"SXT" "Trimethoprim/sulfamethoxazole" "standard_dosage" "0.16 g + 0.8 g" 2 "oral" "" "(0.16 g trimethoprim + 0.8 g sulfamethoxazole) x 2 oral or (0.16 g trimethoprim + 0.8 g sulfamethoxazole) x 2 iv" 12
|
||||
"SXT" "Trimethoprim/sulfamethoxazole" "uncomplicated_uti" "0.16 g + 0.8 g" 2 "oral" "" "(0.16 g trimethoprim + 0.8 g sulfamethoxazole) x 2 oral" 12
|
||||
"LEX" "Cefalexin" "standard_dosage" "0.25-1 g" 2 "oral" "" "0.25-1 g x 2-3 oral" 11
|
||||
"LEX" "Cefalexin" "uncomplicated_uti" "0.25-1 g" 2 "oral" "" "0.25-1 g x 2-3 oral" 11
|
||||
"VAN" "Vancomycin" "standard_dosage" "1 g" 2 "iv" "" "1 g x 2 iv or 2 g x 1 by continuous infusion" 12
|
||||
"AMK" "Amikacin" "standard_dosage" "25-30 mg/kg" 1 "iv" "" "25-30 mg/kg x 1 iv" 11
|
||||
"AMX" "Amoxicillin" "high_dosage" "2 g" 6 "iv" "" "2 g x 6 iv" 11
|
||||
@@ -440,7 +698,6 @@
|
||||
"CXM" "Cefuroxime" "high_dosage" "1.5 g" 3 "iv" "" "1.5 g x 3 iv" 11
|
||||
"CXM" "Cefuroxime" "standard_dosage" "0.75 g" 3 "iv" "" "0.75 g x 3 iv" 11
|
||||
"CXM" "Cefuroxime" "high_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2 oral" 11
|
||||
"IMR" "Imipenem/relebactam" "standard_dosage" "0.5 g + 0.25 g" 4 "iv" "over 30 minutes" "(0.5 g imipenem + 0.25 g relebactam) x 4 iv over 30 minutes" 11
|
||||
"CXM" "Cefuroxime" "standard_dosage" "0.25 g" 2 "oral" "" "0.25 g x 2 oral" 11
|
||||
"CXM" "Cefuroxime" "uncomplicated_uti" "0.25 g" 2 "oral" "" "0.25 g x 2 oral" 11
|
||||
"CHL" "Chloramphenicol" "high_dosage" "2 g" 4 "iv" "" "2 g x 4 iv" 11
|
||||
@@ -500,5 +757,4 @@
|
||||
"LMU" "Lefamulin" "standard_dosage" "0.6 g" 2 "oral" "" "0.6 g x 2 oral" 11
|
||||
"LVX" "Levofloxacin" "high_dosage" "0.5 g" 2 "iv" "" "0.5 g x 2 iv" 11
|
||||
"LVX" "Levofloxacin" "standard_dosage" "0.5 g" 1 "iv" "" "0.5 g x 1 iv" 11
|
||||
"SXT" "Trimethoprim/sulfamethoxazole" "uncomplicated_uti" "0.16 g + 0.8 g" 2 "oral" "" "(0.16 g trimethoprim + 0.8 g sulfamethoxazole) x 2 oral" 11
|
||||
"LVX" "Levofloxacin" "high_dosage" "0.5 g" 2 "oral" "" "0.5 g x 2 oral" 11
|
||||
|
Binary file not shown.
Binary file not shown.
Binary file not shown.
Binary file not shown.
Binary file not shown.
Binary file not shown.
File diff suppressed because it is too large
Load Diff
Binary file not shown.
@@ -1 +1 @@
|
||||
cf0833ed69cfd2b6afb5b6d18cf2df26
|
||||
ac97b111185490535890ea6df22f9a4f
|
||||
|
@@ -783,6 +783,193 @@ genus_species is Brucella melitensis TCY-S S DOX S Brucella melitensis Breakpoin
|
||||
genus_species is Brucella melitensis TCY-S R DOX R Brucella melitensis Breakpoints 14
|
||||
genus_species is Burkholderia pseudomallei TCY-S S DOX I Burkholderia pseudomallei Breakpoints 14
|
||||
genus_species is Burkholderia pseudomallei TCY-S R DOX R Burkholderia pseudomallei Breakpoints 14
|
||||
order is Enterobacterales AMP S AMX S Enterobacterales (Order) Breakpoints 15
|
||||
order is Enterobacterales AMP I AMX I Enterobacterales (Order) Breakpoints 15
|
||||
order is Enterobacterales AMP R AMX R Enterobacterales (Order) Breakpoints 15
|
||||
order is Enterobacterales LEX S CZO I Enterobacterales (Order) Breakpoints 15
|
||||
order is Enterobacterales CFR S CZO I Enterobacterales (Order) Breakpoints 15
|
||||
genus is Salmonella PEF-S S CIP S Enterobacterales (Order) Breakpoints 15
|
||||
genus is Salmonella PEF-S I CIP I Enterobacterales (Order) Breakpoints 15
|
||||
genus is Salmonella PEF-S R CIP R Enterobacterales (Order) Breakpoints 15
|
||||
genus_species is Yersinia enterocolitica TCY S DOX S Enterobacterales (Order) Breakpoints 15
|
||||
genus_species is Yersinia enterocolitica TCY I DOX I Enterobacterales (Order) Breakpoints 15
|
||||
genus_species is Yersinia enterocolitica TCY R DOX R Enterobacterales (Order) Breakpoints 15
|
||||
genus_species is Staphylococcus aureus FOX-S R penicillins R Staphylococcus Breakpoints 15 See last sentence: Isolates that test resistant to cefoxitin are resistant to all penicillins
|
||||
genus_species is Staphylococcus aureus PEN, FOX-S S, S penicillins S Staphylococcus Breakpoints 15
|
||||
genus_species is Staphylococcus aureus PEN, FOX-S R, S betalactams_with_inhibitor, isoxazolylpenicillins, NAF S Staphylococcus Breakpoints 15
|
||||
genus is Staphylococcus FOX-S R PEN, PHN, AMP, AMX, PIP, TIC R Staphylococcus Breakpoints 15
|
||||
genus_species is Staphylococcus saprophyticus AMP S AMP, SAM, AMX, AMC, PIP, TZP S Staphylococcus Breakpoints 15
|
||||
genus is Staphylococcus FOX-S S BPR, CAC, CAT, CCL, CCP, CCV, CCX, CDC, CDR, CEB, CEC, CED, CEM, CEP, CEQ, CFA, CFM, CFM1, CFP, CFR, CFS, CFZ, CHE, CID, CMX, CMZ, CND, CPA, CPC, CPD, CPI, CPL, CPM, CPO, CPR, CPT, CPX, CRD, CRO, CSE, CSL, CSU, CTC, CTF, CTL, CTS, CTT, CTX, CTZ, CXA, CXM, CZD, CZL, CZO, CZP, CZX, DIT, DIX, DIZ, FDC, FEP, FNC, FOV, FOX, FOX-S, FPT, FPZ, HAP, LOR, LTM, MAN, RID, TIO, ZOP S Staphylococcus Breakpoints 15 sort(c(cephalosporins()[!cephalosporins() %in% as.ab(c("cefalexin", "ceftazidim", "ceftazidim/avibactam", "ceftibuten", "ceftolozan/tazobactam"))]))
|
||||
genus is Staphylococcus FOX-S I BPR, CAC, CAT, CCL, CCP, CCV, CCX, CDC, CDR, CEB, CEC, CED, CEM, CEP, CEQ, CFA, CFM, CFM1, CFP, CFR, CFS, CFZ, CHE, CID, CMX, CMZ, CND, CPA, CPC, CPD, CPI, CPL, CPM, CPO, CPR, CPT, CPX, CRD, CRO, CSE, CSL, CSU, CTC, CTF, CTL, CTS, CTT, CTX, CTZ, CXA, CXM, CZD, CZL, CZO, CZP, CZX, DIT, DIX, DIZ, FDC, FEP, FNC, FOV, FOX, FOX-S, FPT, FPZ, HAP, LOR, LTM, MAN, RID, TIO, ZOP I Staphylococcus Breakpoints 15 sort(c(cephalosporins()[!cephalosporins() %in% as.ab(c("cefalexin", "ceftazidim", "ceftazidim/avibactam", "ceftibuten", "ceftolozan/tazobactam"))]))
|
||||
genus is Staphylococcus FOX-S R BPR, CAC, CAT, CCL, CCP, CCV, CCX, CDC, CDR, CEB, CEC, CED, CEM, CEP, CEQ, CFA, CFM, CFM1, CFP, CFR, CFS, CFZ, CHE, CID, CMX, CMZ, CND, CPA, CPC, CPD, CPI, CPL, CPM, CPO, CPR, CPT, CPX, CRD, CRO, CSE, CSL, CSU, CTC, CTF, CTL, CTS, CTT, CTX, CTZ, CXA, CXM, CZD, CZL, CZO, CZP, CZX, DIT, DIX, DIZ, FDC, FEP, FNC, FOV, FOX, FOX-S, FPT, FPZ, HAP, LOR, LTM, MAN, RID, TIO, ZOP R Staphylococcus Breakpoints 15 sort(c(cephalosporins()[!cephalosporins() %in% as.ab(c("cefalexin", "ceftazidim", "ceftazidim/avibactam", "ceftibuten", "ceftolozan/tazobactam"))]))
|
||||
genus_species one_of Staphylococcus pseudintermedius, Staphylococcus schleiferi, Staphylococcus coagulans OXA-S R PEN, PHN, AMP, AMX, PIP, TIC R Staphylococcus Breakpoints 15
|
||||
genus_species one_of Staphylococcus pseudintermedius, Staphylococcus schleiferi, Staphylococcus coagulans OXA-S S BPR, CAC, CAT, CCL, CCP, CCV, CCX, CDC, CDR, CEB, CEC, CED, CEM, CEP, CEQ, CFA, CFM, CFM1, CFP, CFR, CFS, CFZ, CHE, CID, CMX, CMZ, CND, CPA, CPC, CPD, CPI, CPL, CPM, CPO, CPR, CPT, CPX, CRD, CRO, CSE, CSL, CSU, CTC, CTF, CTL, CTS, CTT, CTX, CTZ, CXA, CXM, CZD, CZL, CZO, CZP, CZX, DIT, DIX, DIZ, FDC, FEP, FNC, FOV, FOX, FOX-S, FPT, FPZ, HAP, LOR, LTM, MAN, RID, TIO, ZOP S Staphylococcus Breakpoints 15 sort(c(cephalosporins()[!cephalosporins() %in% as.ab(c("cefalexin", "ceftazidim", "ceftazidim/avibactam", "ceftibuten", "ceftolozan/tazobactam"))]))
|
||||
genus_species one_of Staphylococcus pseudintermedius, Staphylococcus schleiferi, Staphylococcus coagulans OXA-S I BPR, CAC, CAT, CCL, CCP, CCV, CCX, CDC, CDR, CEB, CEC, CED, CEM, CEP, CEQ, CFA, CFM, CFM1, CFP, CFR, CFS, CFZ, CHE, CID, CMX, CMZ, CND, CPA, CPC, CPD, CPI, CPL, CPM, CPO, CPR, CPT, CPX, CRD, CRO, CSE, CSL, CSU, CTC, CTF, CTL, CTS, CTT, CTX, CTZ, CXA, CXM, CZD, CZL, CZO, CZP, CZX, DIT, DIX, DIZ, FDC, FEP, FNC, FOV, FOX, FOX-S, FPT, FPZ, HAP, LOR, LTM, MAN, RID, TIO, ZOP I Staphylococcus Breakpoints 15 sort(c(cephalosporins()[!cephalosporins() %in% as.ab(c("cefalexin", "ceftazidim", "ceftazidim/avibactam", "ceftibuten", "ceftolozan/tazobactam"))]))
|
||||
genus_species one_of Staphylococcus pseudintermedius, Staphylococcus schleiferi, Staphylococcus coagulans OXA-S R BPR, CAC, CAT, CCL, CCP, CCV, CCX, CDC, CDR, CEB, CEC, CED, CEM, CEP, CEQ, CFA, CFM, CFM1, CFP, CFR, CFS, CFZ, CHE, CID, CMX, CMZ, CND, CPA, CPC, CPD, CPI, CPL, CPM, CPO, CPR, CPT, CPX, CRD, CRO, CSE, CSL, CSU, CTC, CTF, CTL, CTS, CTT, CTX, CTZ, CXA, CXM, CZD, CZL, CZO, CZP, CZX, DIT, DIX, DIZ, FDC, FEP, FNC, FOV, FOX, FOX-S, FPT, FPZ, HAP, LOR, LTM, MAN, RID, TIO, ZOP R Staphylococcus Breakpoints 15 sort(c(cephalosporins()[!cephalosporins() %in% as.ab(c("cefalexin", "ceftazidim", "ceftazidim/avibactam", "ceftibuten", "ceftolozan/tazobactam"))]))
|
||||
genus_species is Staphylococcus aureus FOX-S S CPT S Staphylococcus Breakpoints 15
|
||||
genus_species is Staphylococcus aureus FOX-S S BPR S Staphylococcus Breakpoints 15
|
||||
genus is Staphylococcus FOX-S S carbapenems S Staphylococcus Breakpoints 15
|
||||
genus is Staphylococcus FOX-S I carbapenems I Staphylococcus Breakpoints 15
|
||||
genus is Staphylococcus FOX-S R carbapenems R Staphylococcus Breakpoints 15
|
||||
genus_species one_of Staphylococcus pseudintermedius, Staphylococcus schleiferi, Staphylococcus coagulans OXA-S S carbapenems S Staphylococcus Breakpoints 15 Not explicitly mentioned in guidelines in this section, but previous section about these 3 species do mention OXA as preferred method
|
||||
genus_species one_of Staphylococcus pseudintermedius, Staphylococcus schleiferi, Staphylococcus coagulans OXA-S I carbapenems I Staphylococcus Breakpoints 15 Not explicitly mentioned in guidelines in this section, but previous section about these 3 species do mention OXA as preferred method
|
||||
genus_species one_of Staphylococcus pseudintermedius, Staphylococcus schleiferi, Staphylococcus coagulans OXA-S R carbapenems R Staphylococcus Breakpoints 15 Not explicitly mentioned in guidelines in this section, but previous section about these 3 species do mention OXA as preferred method
|
||||
genus is Staphylococcus NOR-S S MFX S Staphylococcus Breakpoints 15
|
||||
genus is Staphylococcus NOR-S S CIP, LVX I Staphylococcus Breakpoints 15
|
||||
genus is Staphylococcus ERY S AZM, CLR, RXT S Staphylococcus Breakpoints 15
|
||||
genus is Staphylococcus TCY-S S DOX, MNO S Staphylococcus Breakpoints 15
|
||||
genus is Enterococcus AMP S AMP, SAM, AMX S Enterococcus Breakpoints 15
|
||||
genus is Enterococcus AMP I AMP, SAM, AMX I Enterococcus Breakpoints 15
|
||||
genus is Enterococcus AMP R AMP, SAM, AMX R Enterococcus Breakpoints 15
|
||||
genus is Enterococcus AMP R AMX, AMC R Enterococcus Breakpoints 15
|
||||
genus is Enterococcus NOR-S S CIP, LVX S Enterococcus Breakpoints 15
|
||||
genus is Enterococcus NOR-S I CIP, LVX I Enterococcus Breakpoints 15
|
||||
genus is Enterococcus NOR-S R CIP, LVX R Enterococcus Breakpoints 15
|
||||
genus_species one_of Streptococcus Group A, Streptococcus Group C, Streptococcus Group G PEN S penicillins S Streptococcus groups A, B, C, G Breakpoints 15
|
||||
genus_species one_of Streptococcus Group A, Streptococcus Group C, Streptococcus Group G PEN I penicillins I Streptococcus groups A, B, C, G Breakpoints 15
|
||||
genus_species one_of Streptococcus Group A, Streptococcus Group C, Streptococcus Group G PEN R penicillins R Streptococcus groups A, B, C, G Breakpoints 15
|
||||
genus_species is Streptococcus Group B PEN S AMC, AMP, AMX, APL, APX, AXS, AZD, AZL, BAM, BNB, BNP, CIC, CLM, CRB, CRN, EPC, HET, LEN, MEC, MEZ, MSU, MTM, NAF, PEN, PHE, PIP, PIS, PME, PNM, PNO, PRB, PRC, PRP, PSU, PVM, SAM, SBC, SLT6, SRX, TAL, TCC, TEM, TIC, TZP S Streptococcus groups A, B, C, G Breakpoints 15 penicillins()[!penicillins() %in% c("PHN", isoxazolylpenicillins())]
|
||||
genus_species is Streptococcus Group B PEN I AMC, AMP, AMX, APL, APX, AXS, AZD, AZL, BAM, BNB, BNP, CIC, CLM, CRB, CRN, EPC, HET, LEN, MEC, MEZ, MSU, MTM, NAF, PEN, PHE, PIP, PIS, PME, PNM, PNO, PRB, PRC, PRP, PSU, PVM, SAM, SBC, SLT6, SRX, TAL, TCC, TEM, TIC, TZP I Streptococcus groups A, B, C, G Breakpoints 15 penicillins()[!penicillins() %in% c("PHN", isoxazolylpenicillins())]
|
||||
genus_species is Streptococcus Group B PEN R AMC, AMP, AMX, APL, APX, AXS, AZD, AZL, BAM, BNB, BNP, CIC, CLM, CRB, CRN, EPC, HET, LEN, MEC, MEZ, MSU, MTM, NAF, PEN, PHE, PIP, PIS, PME, PNM, PNO, PRB, PRC, PRP, PSU, PVM, SAM, SBC, SLT6, SRX, TAL, TCC, TEM, TIC, TZP R Streptococcus groups A, B, C, G Breakpoints 15 penicillins()[!penicillins() %in% c("PHN", isoxazolylpenicillins())]
|
||||
genus_species one_of Streptococcus Group A, Streptococcus Group B, Streptococcus Group C, Streptococcus Group G PEN S cephalosporins S Streptococcus groups A, B, C, G Breakpoints 15
|
||||
genus_species one_of Streptococcus Group A, Streptococcus Group B, Streptococcus Group C, Streptococcus Group G PEN I cephalosporins I Streptococcus groups A, B, C, G Breakpoints 15
|
||||
genus_species one_of Streptococcus Group A, Streptococcus Group B, Streptococcus Group C, Streptococcus Group G PEN R cephalosporins R Streptococcus groups A, B, C, G Breakpoints 15
|
||||
genus_species one_of Streptococcus Group A, Streptococcus Group B, Streptococcus Group C, Streptococcus Group G PEN S carbapenems S Streptococcus groups A, B, C, G Breakpoints 15
|
||||
genus_species one_of Streptococcus Group A, Streptococcus Group B, Streptococcus Group C, Streptococcus Group G PEN I carbapenems I Streptococcus groups A, B, C, G Breakpoints 15
|
||||
genus_species one_of Streptococcus Group A, Streptococcus Group B, Streptococcus Group C, Streptococcus Group G PEN R carbapenems R Streptococcus groups A, B, C, G Breakpoints 15
|
||||
genus_species one_of Streptococcus Group A, Streptococcus Group B, Streptococcus Group C, Streptococcus Group G NOR-S S MFX S Streptococcus groups A, B, C, G Breakpoints 15 does not explicitly state that it is for other fluoroquinolones
|
||||
genus_species one_of Streptococcus Group A, Streptococcus Group B, Streptococcus Group C, Streptococcus Group G NOR-S S LVX I Streptococcus groups A, B, C, G Breakpoints 15 does not explicitly state that it is for other fluoroquinolones
|
||||
genus_species one_of Streptococcus Group A, Streptococcus Group B, Streptococcus Group C, Streptococcus Group G NOR-S R MFX, LVX R Streptococcus groups A, B, C, G Breakpoints 15 does not explicitly state that it is for other fluoroquinolones
|
||||
genus_species one_of Streptococcus Group A, Streptococcus Group B, Streptococcus Group C, Streptococcus Group G VAN S DAL, ORI S Streptococcus groups A, B, C, G Breakpoints 15
|
||||
genus_species one_of Streptococcus Group A, Streptococcus Group B, Streptococcus Group C, Streptococcus Group G ERY S AZM, CLR, RXT S Streptococcus groups A, B, C, G Breakpoints 15
|
||||
genus_species one_of Streptococcus Group A, Streptococcus Group B, Streptococcus Group C, Streptococcus Group G ERY R AZM, CLR, RXT R Streptococcus groups A, B, C, G Breakpoints 15
|
||||
genus_species one_of Streptococcus Group A, Streptococcus Group B, Streptococcus Group C, Streptococcus Group G TCY-S S DOX, MNO S Streptococcus groups A, B, C, G Breakpoints 15
|
||||
genus_species one_of Streptococcus Group A, Streptococcus Group B, Streptococcus Group C, Streptococcus Group G TCY-S R DOX, MNO R Streptococcus groups A, B, C, G Breakpoints 15
|
||||
genus_species is Streptococcus pneumoniae OXA-S S AMC, AMP, AMX, CPD, CPT, CRO, CTX, CXM, DOR, ETP, FEP, IMR, IPM, MEM, MEV, OXA, PEN, PHN, PIP, SAM, TZP S Streptococcus pneumoniae Breakpoints 15 x <- unique(clinical_breakpoints$ab[which(clinical_breakpoints$guideline == "EUCAST 2022" & clinical_breakpoints$mo == as.mo("S. pneumoniae") & clinical_breakpoints$ab != as.ab("cefaclor"))]); sort(c(x[x %in% betalactams()], "SAM", "PIP", "TZP", "PHN", "IMR", "MEV"))
|
||||
genus_species is Streptococcus pneumoniae PEN S AMC, AMP, AMX, CPD, CPT, CRO, CTX, CXM, DOR, ETP, FEP, IMR, IPM, MEM, MEV, OXA, PEN, PHN, PIP, SAM, TZP S Streptococcus pneumoniae Breakpoints 15 x <- unique(clinical_breakpoints$ab[which(clinical_breakpoints$guideline == "EUCAST 2022" & clinical_breakpoints$mo == as.mo("S. pneumoniae") & clinical_breakpoints$ab != as.ab("cefaclor"))]); sort(c(x[x %in% betalactams()], "SAM", "PIP", "TZP", "PHN", "IMR", "MEV"))
|
||||
genus_species is Streptococcus pneumoniae OXA-S S CEC I Streptococcus pneumoniae Breakpoints 15
|
||||
genus_species is Streptococcus pneumoniae PEN S CEC I Streptococcus pneumoniae Breakpoints 15
|
||||
genus_species is Streptococcus pneumoniae OXA-S R PEN, PHN R Streptococcus pneumoniae Breakpoints 15 from flowchart: when OXA < 20 or PEN > 0.06
|
||||
genus_species is Streptococcus pneumoniae PEN R PHN R Streptococcus pneumoniae Breakpoints 15 from flowchart: when OXA < 20 or PEN > 0.06
|
||||
genus_species is Streptococcus pneumoniae AMP S AMX, AMC, SAM, PIP, TZP S Streptococcus pneumoniae Breakpoints 15
|
||||
genus_species is Streptococcus pneumoniae AMP I AMX, AMC, SAM, PIP, TZP I Streptococcus pneumoniae Breakpoints 15
|
||||
genus_species is Streptococcus pneumoniae AMP R AMX, AMC, SAM, PIP, TZP R Streptococcus pneumoniae Breakpoints 15
|
||||
genus_species is Streptococcus pneumoniae NOR-S S MFX S Streptococcus pneumoniae Breakpoints 15 does not explicitly state that it is for other fluoroquinolones
|
||||
genus_species is Streptococcus pneumoniae NOR-S S LVX I Streptococcus pneumoniae Breakpoints 15 does not explicitly state that it is for other fluoroquinolones
|
||||
genus_species is Streptococcus pneumoniae NOR-S R MFX, LVX R Streptococcus pneumoniae Breakpoints 15 does not explicitly state that it is for other fluoroquinolones
|
||||
genus_species is Streptococcus pneumoniae ERY S AZM, CLR, RXT S Streptococcus pneumoniae Breakpoints 15
|
||||
genus_species is Streptococcus pneumoniae ERY R AZM, CLR, RXT R Streptococcus pneumoniae Breakpoints 15
|
||||
genus_species is Streptococcus pneumoniae TCY-S S DOX, MNO S Streptococcus pneumoniae Breakpoints 15
|
||||
genus_species is Streptococcus pneumoniae TCY-S R DOX, MNO R Streptococcus pneumoniae Breakpoints 15
|
||||
genus_species one_of Viridans Group Streptococcus (VGS) PEN-S S AMC, AMP, AMX, CPD, CPT, CRO, CTX, CXM, DOR, ETP, FEP, IMR, IPM, MEM, MEV, OXA, PEN, PIP, SAM, TZP S Viridans group streptococci Breakpoints 15 MO group name will be expanded in eucast_rules()
|
||||
genus_species one_of Viridans Group Streptococcus (VGS) PEN-S R AMC, AMP, AMX, CPD, CPT, CRO, CTX, CXM, DOR, ETP, FEP, IMR, IPM, MEM, MEV, OXA, PEN, PIP, SAM, TZP R Viridans group streptococci Breakpoints 15 MO group name will be expanded in eucast_rules()
|
||||
genus_species one_of Viridans Group Streptococcus (VGS) AMP S AMX, AMC, SAM, PIP, TZP S Viridans group streptococci Breakpoints 15 MO group name will be expanded in eucast_rules()
|
||||
genus_species one_of Viridans Group Streptococcus (VGS) AMP I AMX, AMC, SAM, PIP, TZP I Viridans group streptococci Breakpoints 15 MO group name will be expanded in eucast_rules()
|
||||
genus_species one_of Viridans Group Streptococcus (VGS) AMP R AMX, AMC, SAM, PIP, TZP R Viridans group streptococci Breakpoints 15 MO group name will be expanded in eucast_rules()
|
||||
genus_species is Haemophilus influenzae PEN-S S AMC, AMP, AMX, CFM, CPD, CPT, CRO, CTB, CTX, CXM, CZT, DOR, ETP, FEP, IMR, IPM, MEM, MEV, PEN, SAM, TZP S Haemophilus influenzae Breakpoints 15 x <- c(unique(clinical_breakpoints$ab[which(clinical_breakpoints$guideline == "EUCAST 2022" & clinical_breakpoints$mo == as.mo("H. influenzae"))]), "IMR", "MEV"); sort(x[x %in% betalactams()])
|
||||
genus_species is Haemophilus influenzae PEN-S, BLA-S R, R AMP, AMX, PIP R Haemophilus influenzae Breakpoints 15
|
||||
genus_species is Haemophilus influenzae AMC S SAM S Haemophilus influenzae Breakpoints 15
|
||||
genus_species is Haemophilus influenzae AMC I SAM I Haemophilus influenzae Breakpoints 15
|
||||
genus_species is Haemophilus influenzae AMC R SAM R Haemophilus influenzae Breakpoints 15
|
||||
genus_species is Haemophilus influenzae NAL-S S CIP, LVX, MFX, OFX S Haemophilus influenzae Breakpoints 15
|
||||
genus_species is Haemophilus influenzae NAL-S R CIP, LVX, MFX, OFX R Haemophilus influenzae Breakpoints 15
|
||||
genus_species is Haemophilus influenzae TCY S DOX, MNO S Haemophilus influenzae Breakpoints 15
|
||||
genus_species is Haemophilus influenzae TCY R DOX, MNO R Haemophilus influenzae Breakpoints 15
|
||||
genus_species is Moraxella catarrhalis BLA-S R AMP, AMX, APL, APX, AZD, AZL, BAM, BNB, BNP, CIC, CLM, CLO, CRB, CRN, DIC, EPC, FLC, HET, LEN, MEC, MET, MEZ, MTM, NAF, OXA, PEN, PHE, PHN, PIP, PME, PNM, PRB, PRC, PRP, PVM, SBC, SLT6, SRX, TAL, TEM, TIC R Moraxella catarrhalis Breakpoints 15 penicillins()[!penicillins() %in% betalactams_with_inhibitor()]
|
||||
genus_species is Moraxella catarrhalis AMC S TZP S Moraxella catarrhalis Breakpoints 15
|
||||
genus_species is Moraxella catarrhalis AMC I TZP I Moraxella catarrhalis Breakpoints 15
|
||||
genus_species is Moraxella catarrhalis AMC R TZP R Moraxella catarrhalis Breakpoints 15
|
||||
genus_species is Moraxella catarrhalis NAL-S S CIP, LVX, MFX, OFX S Moraxella catarrhalis Breakpoints 15
|
||||
genus_species is Moraxella catarrhalis NAL-S R CIP, LVX, MFX, OFX R Moraxella catarrhalis Breakpoints 15
|
||||
genus_species is Moraxella catarrhalis ERY S AZM, CLR, RXT S Moraxella catarrhalis Breakpoints 15
|
||||
genus_species is Moraxella catarrhalis ERY R AZM, CLR, RXT R Moraxella catarrhalis Breakpoints 15
|
||||
genus_species is Moraxella catarrhalis TCY S DOX, MNO S Moraxella catarrhalis Breakpoints 15
|
||||
genus_species is Moraxella catarrhalis TCY R DOX, MNO R Moraxella catarrhalis Breakpoints 15
|
||||
genus_species is Neisseria gonorrhoeae BLA-S R AMP, AMX R Neisseria gonorrhoeae Breakpoints 15
|
||||
genus_species is Neisseria gonorrhoeae BLA-S, PEN S, S AMP, AMX S Neisseria gonorrhoeae Breakpoints 15
|
||||
genus_species is Neisseria gonorrhoeae BLA-S, PEN S, I AMP, AMX I Neisseria gonorrhoeae Breakpoints 15
|
||||
genus_species is Neisseria gonorrhoeae BLA-S, PEN S, R AMP, AMX R Neisseria gonorrhoeae Breakpoints 15
|
||||
genus_species is Neisseria meningitidis TCY-S S MNO S Neisseria meningitidis Breakpoints 15
|
||||
genus_species is Neisseria meningitidis TCY-S I MNO I Neisseria meningitidis Breakpoints 15
|
||||
genus_species is Neisseria meningitidis TCY-S R MNO R Neisseria meningitidis Breakpoints 15
|
||||
genus is Prevotella PEN S AMC, AMP, AMX, ETP, IPM, MEM, PEN, PIP, SAM, TZP S Anaerobic bacteria Breakpoints 15 x <- c(unique(clinical_breakpoints$ab[which(clinical_breakpoints$guideline == "EUCAST 2024" & mo_genus(clinical_breakpoints$mo) == "Prevotella")]), "AMP", "SAM", "AMX", "AMC", "PIP", "ETP", "IPM"); sort(x[x %in% betalactams()])
|
||||
genus is Prevotella AMP S AMX S Anaerobic bacteria Breakpoints 15
|
||||
genus is Prevotella AMP I AMX I Anaerobic bacteria Breakpoints 15
|
||||
genus is Prevotella AMP R AMX R Anaerobic bacteria Breakpoints 15
|
||||
genus_species is Fusobacterium necrophorum PEN S AMC, AMP, AMX, ETP, IPM, MEM, PEN, PIP, SAM, TZP S Anaerobic bacteria Breakpoints 15 x <- c(unique(clinical_breakpoints$ab[which(clinical_breakpoints$guideline == "EUCAST 2024" & clinical_breakpoints$mo == as.mo("Fusobacterium necrophorum"))]), "AMP", "SAM", "AMX", "AMC", "PIP", "ETP", "IPM"); sort(x[x %in% betalactams()])
|
||||
genus_species is Fusobacterium necrophorum AMP S AMX S Anaerobic bacteria Breakpoints 15
|
||||
genus_species is Fusobacterium necrophorum AMP I AMX I Anaerobic bacteria Breakpoints 15
|
||||
genus_species is Fusobacterium necrophorum AMP R AMX R Anaerobic bacteria Breakpoints 15
|
||||
genus_species is Clostridium perfringens PEN S AMC, AMP, AMX, ETP, IPM, MEM, PEN, PIP, SAM, TZP S Anaerobic bacteria Breakpoints 15 x <- c(unique(clinical_breakpoints$ab[which(clinical_breakpoints$guideline == "EUCAST 2024" & clinical_breakpoints$mo == as.mo("Fusobacterium necrophorum"))]), "AMP", "SAM", "AMX", "AMC", "PIP", "ETP", "IPM"); sort(x[x %in% betalactams()])
|
||||
genus_species is Clostridium perfringens AMP S AMX S Anaerobic bacteria Breakpoints 15
|
||||
genus_species is Clostridium perfringens AMP I AMX I Anaerobic bacteria Breakpoints 15
|
||||
genus_species is Clostridium perfringens AMP R AMX R Anaerobic bacteria Breakpoints 15
|
||||
genus_species is Cutibacterium acnes PEN S AMC, AMP, AMX, CRO, CTX, ETP, IPM, MEM, PEN, PIP, SAM, TZP S Anaerobic bacteria Breakpoints 15 x <- c(unique(clinical_breakpoints$ab[which(clinical_breakpoints$guideline == "EUCAST 2024" & clinical_breakpoints$mo == as.mo("Cutibacterium acnes"))]), "AMP", "SAM", "AMX", "AMC", "PIP", "ETP", "IPM", "TZP", "CTX", "CRO"); sort(x[x %in% betalactams()])
|
||||
genus_species is Cutibacterium acnes AMP S AMX S Anaerobic bacteria Breakpoints 15
|
||||
genus_species is Cutibacterium acnes AMP I AMX I Anaerobic bacteria Breakpoints 15
|
||||
genus_species is Cutibacterium acnes AMP R AMX R Anaerobic bacteria Breakpoints 15
|
||||
genus_species is Cutibacterium acnes CTX S CRO S Anaerobic bacteria Breakpoints 15
|
||||
genus_species is Cutibacterium acnes CTX I CRO I Anaerobic bacteria Breakpoints 15
|
||||
genus_species is Cutibacterium acnes CTX R CRO R Anaerobic bacteria Breakpoints 15
|
||||
genus_species is Pasteurella multocida PEN S AMP, AMX S Pasteurella multocida Breakpoints 15
|
||||
genus_species is Pasteurella multocida PEN I AMP, AMX I Pasteurella multocida Breakpoints 15
|
||||
genus_species is Pasteurella multocida PEN R AMP, AMX R Pasteurella multocida Breakpoints 15
|
||||
genus_species is Pasteurella multocida NAL-S S CIP, LVX S Pasteurella multocida Breakpoints 15
|
||||
genus_species is Pasteurella multocida NAL-S R CIP, LVX R Pasteurella multocida Breakpoints 15
|
||||
genus_species is Pasteurella multocida TCY-S S DOX S Neisseria meningitidis Breakpoints 15
|
||||
genus_species is Pasteurella multocida TCY-S I DOX I Neisseria meningitidis Breakpoints 15
|
||||
genus_species is Pasteurella multocida TCY-S R DOX R Neisseria meningitidis Breakpoints 15
|
||||
genus_species one_of Campylobacter coli, Campylobacter jejuni ERY S AZM, CLR S Campylobacter coli/jejuni Breakpoints 15
|
||||
genus_species one_of Campylobacter coli, Campylobacter jejuni ERY I AZM, CLR I Campylobacter coli/jejuni Breakpoints 15
|
||||
genus_species one_of Campylobacter coli, Campylobacter jejuni ERY R AZM, CLR R Campylobacter coli/jejuni Breakpoints 15
|
||||
genus_species one_of Campylobacter coli, Campylobacter jejuni TCY S DOX S Campylobacter coli/jejuni Breakpoints 15
|
||||
genus_species one_of Campylobacter coli, Campylobacter jejuni TCY I DOX I Campylobacter coli/jejuni Breakpoints 15
|
||||
genus_species one_of Campylobacter coli, Campylobacter jejuni TCY R DOX R Campylobacter coli/jejuni Breakpoints 15
|
||||
genus_species one_of Corynebacterium diphtheriae, Corynebacterium ulcerans PEN I AMX S Corynebacterium diphtheriae/ulcerans Breakpoints 15
|
||||
genus_species one_of Corynebacterium diphtheriae, Corynebacterium ulcerans PEN R AMX R Corynebacterium diphtheriae/ulcerans Breakpoints 15
|
||||
genus_species one_of Corynebacterium diphtheriae, Corynebacterium ulcerans PEN I CTX I Corynebacterium diphtheriae/ulcerans Breakpoints 15
|
||||
genus_species one_of Corynebacterium diphtheriae, Corynebacterium ulcerans PEN R CTX R Corynebacterium diphtheriae/ulcerans Breakpoints 15
|
||||
genus_species one_of Corynebacterium diphtheriae, Corynebacterium ulcerans PEN I MEM S Corynebacterium diphtheriae/ulcerans Breakpoints 15
|
||||
genus_species one_of Corynebacterium diphtheriae, Corynebacterium ulcerans PEN R MEM R Corynebacterium diphtheriae/ulcerans Breakpoints 15
|
||||
genus_species one_of Corynebacterium diphtheriae, Corynebacterium ulcerans TCY S DOX S Corynebacterium diphtheriae/ulcerans Breakpoints 15
|
||||
genus_species one_of Corynebacterium diphtheriae, Corynebacterium ulcerans TCY R DOX R Corynebacterium diphtheriae/ulcerans Breakpoints 15
|
||||
genus_species is Aerococcus sanguinicola, Aerococcus urinae AMP S AMX S Aerococcus sanguinicola/urinae Breakpoints 15
|
||||
genus_species is Aerococcus sanguinicola, Aerococcus urinae AMP I AMX I Aerococcus sanguinicola/urinae Breakpoints 15
|
||||
genus_species is Aerococcus sanguinicola, Aerococcus urinae AMP R AMX R Aerococcus sanguinicola/urinae Breakpoints 15
|
||||
genus_species is Aerococcus sanguinicola, Aerococcus urinae CIP S LVX S Aerococcus sanguinicola/urinae Breakpoints 15
|
||||
genus_species is Aerococcus sanguinicola, Aerococcus urinae CIP I LVX I Aerococcus sanguinicola/urinae Breakpoints 15
|
||||
genus_species is Aerococcus sanguinicola, Aerococcus urinae CIP R LVX R Aerococcus sanguinicola/urinae Breakpoints 15
|
||||
genus_species is Aerococcus sanguinicola, Aerococcus urinae NOR-S S fluoroquinolones S Aerococcus sanguinicola/urinae Breakpoints 15
|
||||
genus_species is Aerococcus sanguinicola, Aerococcus urinae NOR-S I fluoroquinolones I Aerococcus sanguinicola/urinae Breakpoints 15
|
||||
genus_species is Aerococcus sanguinicola, Aerococcus urinae NOR-S R fluoroquinolones R Aerococcus sanguinicola/urinae Breakpoints 15
|
||||
genus_species is Kingella kingae BLA-S R PEN, AMP, AMX R Kingella kingae Breakpoints 15
|
||||
genus_species is Kingella kingae PEN S AMP, AMX S Kingella kingae Breakpoints 15
|
||||
genus_species is Kingella kingae PEN I AMP, AMX I Kingella kingae Breakpoints 15
|
||||
genus_species is Kingella kingae PEN R AMP, AMX R Kingella kingae Breakpoints 15
|
||||
genus_species is Kingella kingae ERY S AZM, CLR S Kingella kingae Breakpoints 15
|
||||
genus_species is Kingella kingae ERY I AZM, CLR I Kingella kingae Breakpoints 15
|
||||
genus_species is Kingella kingae ERY R AZM, CLR R Kingella kingae Breakpoints 15
|
||||
genus_species is Kingella kingae TCY S DOX S Kingella kingae Breakpoints 15
|
||||
genus_species is Kingella kingae TCY R DOX R Kingella kingae Breakpoints 15
|
||||
genus is Vibrio PEF-S S CIP, LVX S Vibrio spp. Breakpoints 15
|
||||
genus is Vibrio PEF-S I CIP, LVX I Vibrio spp. Breakpoints 15
|
||||
genus is Vibrio PEF-S R CIP, LVX R Vibrio spp. Breakpoints 15
|
||||
genus is Vibrio ERY S AZM S Vibrio spp. Breakpoints 15
|
||||
genus is Vibrio ERY I AZM I Vibrio spp. Breakpoints 15
|
||||
genus is Vibrio ERY R AZM R Vibrio spp. Breakpoints 15
|
||||
genus is Vibrio TCY-S S DOX S Vibrio spp. Breakpoints 15
|
||||
genus is Vibrio TCY-S I DOX I Vibrio spp. Breakpoints 15
|
||||
genus is Vibrio TCY-S R DOX R Vibrio spp. Breakpoints 15
|
||||
genus is Bacillus NOR-S S CIP, LVX I Bacillus Breakpoints 15
|
||||
genus is Bacillus NOR-S R CIP, LVX R Bacillus Breakpoints 15
|
||||
genus_species is Bacillus anthracis PEN I AMX S Bacillus anthracis Breakpoints 15
|
||||
genus_species is Bacillus anthracis PEN R AMX R Bacillus anthracis Breakpoints 15
|
||||
genus_species is Bacillus anthracis TCY-S S DOX S Bacillus anthracis Breakpoints 15
|
||||
genus_species is Bacillus anthracis TCY-S R DOX R Bacillus anthracis Breakpoints 15
|
||||
genus_species is Brucella melitensis TCY-S S DOX S Brucella melitensis Breakpoints 15
|
||||
genus_species is Brucella melitensis TCY-S R DOX R Brucella melitensis Breakpoints 15
|
||||
genus_species is Burkholderia pseudomallei TCY-S S DOX I Burkholderia pseudomallei Breakpoints 15
|
||||
genus_species is Burkholderia pseudomallei TCY-S R DOX R Burkholderia pseudomallei Breakpoints 15
|
||||
order is Enterobacterales PEN, glycopeptides, lipoglycopeptides, FUS, macrolides, lincosamides, streptogramins, RIF, oxazolidinones R Table 1: Expected resistant phenotype in Enterobacterales and Aeromonas spp. Expected phenotypes 1.2
|
||||
genus_species one_of Citrobacter koseri, Citrobacter amalonaticus AMP, AMX, TIC R Table 1: Expected resistant phenotype in Enterobacterales and Aeromonas spp. Expected phenotypes 1.2
|
||||
genus_species is Citrobacter freundii AMP, AMX, AMC, SAM, CZO, CEP, LEX, CFR, FOX R Table 1: Expected resistant phenotype in Enterobacterales and Aeromonas spp. Expected phenotypes 1.2
|
||||
|
Can't render this file because it has a wrong number of fields in line 9.
|
@@ -1 +1 @@
|
||||
cbf15fce0784e20b87aaa33b88b97f3f
|
||||
4862699a91a23f2fe6a790ac277697d0
|
||||
|
Binary file not shown.
BIN
data-raw/v_15.0_Breakpoint_Tables.xlsx
Normal file
BIN
data-raw/v_15.0_Breakpoint_Tables.xlsx
Normal file
Binary file not shown.
Reference in New Issue
Block a user