Skip to content

Commit

Permalink
Fix cid generation
Browse files Browse the repository at this point in the history
  • Loading branch information
burgerga committed Dec 13, 2023
1 parent 6cc6842 commit 5f43d11
Show file tree
Hide file tree
Showing 2 changed files with 24 additions and 5 deletions.
6 changes: 4 additions & 2 deletions R/CPTraceR.R
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,7 @@ groupIndList <- data %>%
mutate(cid = {{obj_var}}, uid = {{obj_var}}, alt_uid= as.character(.data$cid)) %>%
select(-{{par_obj_var}})

max_cid <- max(groupIndList[[1]]$cid)
max_uid <- max(groupIndList[[1]]$uid)

for(i in 2:length(groupIndList)) {
Expand All @@ -50,7 +51,7 @@ groupIndList <- data %>%
# find the new cells (which have par_obj_num == 0) and assign them a new cid
new <- groupIndList[[i]] %>%
filter({{par_obj_var}} == 0) %>%
mutate(cid = row_number() + max(groupIndList[[i-1]]$cid),
mutate(cid = row_number() + max_cid,
uid = row_number() + max_uid,
alt_uid = as.character(.data$cid)) %>%
select(-{{par_obj_var}})
Expand Down Expand Up @@ -84,8 +85,9 @@ groupIndList <- data %>%
# put together and update time frame in list
groupIndList[[i]] <- bind_rows(new, cont_single, cont_multi) %>% arrange(.data$uid)

# update max_uid to the new max
# update max_uid/max_cid to the new max
max_uid <- max(max_uid, groupIndList[[i]]$uid)
max_cid <- max(max_cid, groupIndList[[i]]$cid)

}

Expand Down
23 changes: 20 additions & 3 deletions tests/testthat/test-CPTrackR.R
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ test_that("tracks get unique uid", {
par_obj_var = par_obj_num)$uid) == 4)
})

test_that("new tracks get new uid, even if highest uid so far is not in the previous frame", {
test_that("new tracks get new uid/cid, even if highest uid/cid so far is not in the previous frame", {
# In case new cells appear
data1 <- tribble(
~groupInd, ~par_obj_num, ~obj_num,
Expand All @@ -48,19 +48,36 @@ test_that("new tracks get new uid, even if highest uid so far is not in the prev
obj_var = obj_num,
par_obj_var = par_obj_num)
expect_equal(lut1$uid, c(1,2,1,1,3))
expect_equal(lut1$cid, c(1,2,1,1,3))

# In case a cell splits
data2 <- tribble(
~groupInd, ~par_obj_num, ~obj_num,
1, 0, 1, # cell 1
1, 0, 2, # cell 2
2, 1, 1, # cell 1 in frame 2, cell 2 disappears
3, 1, 1, # cell 1 has now split in frame 3
3, 1, 2, # cell 3 appears as a daughter cell of 1
3, 1, 1, # cell 1 has now split in frame 3, this is the first daughter cell of 1
3, 1, 2, # cell 3 appears as the second daughter cell of 1
)
lut2 <- createLUTGroup(data2,
frame_var = groupInd,
obj_var = obj_num,
par_obj_var = par_obj_num)
expect_equal(lut2$uid, c(1,2,1,3,4))

data3 <- tribble(
~groupInd, ~par_obj_num, ~obj_num,
1, 0, 1, # cell 1
1, 0, 2, # cell 2
2, 1, 1, # cell 1 in frame 2, cell 2 disappears
3, 1, 1, # cell 1 has now split in frame 3, this is the first daughter cell of 1
3, 1, 2, # cell 3 appears as the second daughter cell of 1
4, 0, 1, # cell 4 appears
)
lut3 <- createLUTGroup(data3,
frame_var = groupInd,
obj_var = obj_num,
par_obj_var = par_obj_num)
expect_equal(lut3$cid, c(1,2,1,1,1,3))
expect_equal(lut3$uid, c(1,2,1,3,4,5))
})

0 comments on commit 5f43d11

Please sign in to comment.