Skip to content

Commit

Permalink
fix a bug where external concepts would not be mapped if they already…
Browse files Browse the repository at this point in the history
… appear in the external table. new mappings should also be possible, even if some other mapping had already been made.
  • Loading branch information
EhrmannS committed Dec 14, 2023
1 parent 91a3f7c commit 56e1b9c
Showing 1 changed file with 9 additions and 9 deletions.
18 changes: 9 additions & 9 deletions R/new_mapping.R
Original file line number Diff line number Diff line change
Expand Up @@ -73,8 +73,7 @@

new_mapping <- function(new = NULL, target, source = NULL, lut = NULL,
match = NULL, certainty = NULL, type = "concept",
ontology = NULL, verbose = FALSE,
beep = NULL){
ontology = NULL, verbose = FALSE, beep = NULL){

assertCharacter(x = new, all.missing = FALSE)
assertDataFrame(x = target, nrows = length(new))
Expand Down Expand Up @@ -197,36 +196,37 @@ new_mapping <- function(new = NULL, target, source = NULL, lut = NULL,

# }

# identify concepts that are not yet in the external concepts
extMps <- temp %>%
distinct(new, has_broader, has_source) %>%
filter(new != "") %>%
rename(label = new)

# identify external mappings that are not yet in the external table
if("has_broader" %in% names(theTable$external)){
extMps <- extMps %>%
newExtMps <- extMps %>%
anti_join(theTable$external, by = c("label", "has_source", "has_broader"))
} else {
extMps <- extMps %>%
newExtMps <- extMps %>%
anti_join(theTable$external, by = c("label", "has_source"))
}

if(!is.null(lut) & !dim(extMps)[1] == 0){
extMps <- extMps %>%
# make a new ID for the new external concepts
if(!is.null(lut) & !dim(newExtMps)[1] == 0){
newExtMps <- newExtMps %>%
distinct(label, has_source) %>%
right_join(lut, by = "label") %>%
mutate(newid = paste0(source, "_", row_number() + prevID),
has_broader = NA_character_,
has_source = srcID) %>%
select(id = newid, label, has_broader, has_source, description)
} else {
extMps <- extMps %>%
newExtMps <- newExtMps %>%
mutate(newid = paste0(source, "_", row_number() + prevID)) %>%
select(id = newid, label, has_broader, has_source) %>%
mutate(description = NA_character_)
}

theTable$external <- extMps %>%
theTable$external <- newExtMps %>%
bind_rows(theTable$external, .)

# map external concept to harmonised table
Expand Down

0 comments on commit 56e1b9c

Please sign in to comment.