Browse code

Bug fixed

DavideMaspero authored on 27/11/2020 11:36:55
Showing 6 changed files

... ...
@@ -1,6 +1,6 @@
1 1
 Package: LACE
2
-Version: 1.3.0
3
-Date: 2020-10-20
2
+Version: 1.3.1
3
+Date: 2020-11-27
4 4
 Title: Longitudinal Analysis of Cancer Evolution (LACE)
5 5
 Authors@R: c(person("Daniele", "Ramazzotti", role=c("aut"),email="daniele.ramazzotti@yahoo.com",
6 6
                 comment = c(ORCID = "0000-0002-6087-2666")),
... ...
@@ -260,8 +260,8 @@ LACE <- function( D, lik_w = NULL, alpha = NULL, beta = NULL, initialization = N
260 260
 
261 261
     # Include Root in clones_prevalence
262 262
     clones_prevalence <- rbind(rep(NA,ncol(clones_prevalence)),clones_prevalence)
263
-    rownames(clones_prevalence)[1] <- "Root_0"
264
-    clones_prevalence["Root_0",] <- (1-colSums(clones_prevalence,na.rm=TRUE))
263
+    rownames(clones_prevalence)[1] <- "Root"
264
+    clones_prevalence["Root",] <- (1-colSums(clones_prevalence,na.rm=TRUE))
265 265
 
266 266
     # Compute clones' summary
267 267
     clones_summary <- list()
... ...
@@ -92,7 +92,7 @@ as.adj.matrix.unsorted <- function( B, root = FALSE ) {
92 92
     }
93 93
     
94 94
     return(adj_matrix)
95
-
95
+    
96 96
 }
97 97
 
98 98
 # Build B from an adjacency matrix where we assume clones and mutations to be both ordered
... ...
@@ -130,14 +130,17 @@ as.B <- function( adj_matrix ) {
130 130
 
131 131
 # check that point Q is not on segments A-B
132 132
 checkQonAB <- function( Ax, Ay, Bx, By, Qx, Qy ) {
133
+
133 134
     if((Qx <= max(Ax,Bx)) && (Qx >= min(Ax, Bx)) && (Qy <= max(Ay, By)) && (Qy >= min(Ay, By))) {
134 135
         return(TRUE)
135 136
     }
136 137
     return(FALSE)
138
+
137 139
 }
138 140
 
139 141
 # check segments orientation
140
-orientation <- function( Ax, Ay, Bx, By, Qx, Qy ) {    
142
+orientation <- function( Ax, Ay, Bx, By, Qx, Qy ) {
143
+
141 144
     res <- ((Qy - Ay) * (Bx - Qx)) - ((Qx - Ax)*(By - Qy))
142 145
     if(res > 0) {
143 146
         return(1)
... ...
@@ -148,6 +151,7 @@ orientation <- function( Ax, Ay, Bx, By, Qx, Qy ) {
148 151
     else {
149 152
         return(0)
150 153
     }
154
+
151 155
 }
152 156
 
153 157
 # check if two segments interserct
... ...
@@ -175,7 +179,7 @@ checkSegmentIntersect <- function( ax1, ay1, ax2, ay2, bx1, by1, bx2, by2 ) {
175 179
     }
176 180
     
177 181
     return(FALSE)
178
-
182
+    
179 183
 }
180 184
 
181 185
 #' Compute mutation distance among variants from LACE corrected genotype and use it to perform hierarchical clustering.
... ...
@@ -195,7 +199,7 @@ compute.mutation.distance <- function( inference ) {
195 199
     mutation_distance <- dist(t(inference$corrected_genotype),method="euclidean")
196 200
     mutation_distance <- list(distance_matrix=as.matrix(mutation_distance),hierarchical_clustering=hclust(mutation_distance,method="complete"))
197 201
     return(mutation_distance)
198
-
202
+    
199 203
 }
200 204
 
201 205
 #' Compute error rates for the considered variants comparing observed data to LACE corrected genotype.
... ...
@@ -222,23 +226,23 @@ compute.variants.error.rates <- function( D, inference ) {
222 226
     for(i in 1:length(D)) {
223 227
         observed_genotype <- rbind(observed_genotype,D[[i]])
224 228
     }
225
-
229
+    
226 230
     for(i in rownames(variants_error_rates)) {
227 231
         fn <- length(which(observed_genotype[,i]==0&corrected_genotype[,i]==1))
228 232
         fp <- length(which(observed_genotype[,i]==1&corrected_genotype[,i]==0))
229 233
         variants_error_rates[i,"Percentage_False_Positives"] <- fp/nrow(observed_genotype)
230 234
         variants_error_rates[i,"Percentage_False_Negatives"] <- fn/nrow(observed_genotype)
231 235
     }
232
-
236
+    
233 237
     return(variants_error_rates)
234
-
238
+    
235 239
 }
236 240
 
237 241
 recursiveDescend <- function( descend ) {
238 242
     
239
-    # Check next node, 
240
-    next_v <- which(descend$adjM[descend$row_v,] == 1)
241
-    #if not than return
243
+    # Check next node,
244
+    next_v <- which(descend$adjM[descend$row_v,] > 0)
245
+    # If not than return
242 246
     if(length(next_v)==0) {
243 247
         descend$max_deep <- max(descend$l_path)
244 248
         return(descend)
... ...
@@ -249,18 +253,22 @@ recursiveDescend <- function( descend ) {
249 253
             descend$row_v = v
250 254
             descend$ind_lPath = descend$ind_lPath + 1
251 255
             descend$l_path[descend$ind_lPath] = curr_level + 1
256
+            descend$mut_list <- c(descend$mut_list, as.numeric(v))
252 257
             descend <- recursiveDescend(descend = descend)
253 258
         }
254 259
     } else  {
255 260
         descend$l_path[descend$ind_lPath] = descend$l_path[descend$ind_lPath] + 1
256 261
         descend$row_v = next_v
262
+        descend$mut_list <- c(descend$mut_list, as.numeric(next_v))
257 263
         descend <- recursiveDescend(descend = descend)
258 264
     }
259 265
     descend$max_deep <- max(descend$l_path)
260 266
     return(descend)
267
+
261 268
 }
262 269
 
263
-recursiveLongitudinalLayout <- function( idx_Vc, Xc, Yc, cl_df, adjMatrix_base, adjMatrix_overall, mut_TP, labels_show ) {
270
+
271
+recursiveLongitudinalLayout <- function( idx_Vc, Xc, Yc, cl_df, adjMatrix_base, adjMatrix_overall, mut_TP, labels_show, label_offset) {
264 272
     
265 273
     
266 274
     cl_vertex_idx_Vc <- which(cl_df$cl_vertex$names == colnames(adjMatrix_overall)[idx_Vc])
... ...
@@ -268,59 +276,62 @@ recursiveLongitudinalLayout <- function( idx_Vc, Xc, Yc, cl_df, adjMatrix_base,
268 276
     cl_df$cl_vertex$coord.x[cl_vertex_idx_Vc] <- Xc
269 277
     cl_df$cl_vertex$coord.y[cl_vertex_idx_Vc] <- Yc
270 278
     
271
-    idx_next_v <- which(adjMatrix_overall[idx_Vc,] != "")
272
-    
279
+    idx_next_v <- which(adjMatrix_overall[idx_Vc,] != 0)
273 280
     if(length(idx_next_v) == 0) {
274 281
         return(cl_df)
275 282
     } else if(length(idx_next_v) > 1){
276 283
         
277
-        # BRANCH
278 284
         deep <- c()
279
-        
280
-        for(v in idx_next_v){
281
-            if(adjMatrix_overall[idx_Vc,v] == "persistence") {
282
-                deep <- c(deep, 0)
283
-            } else {
284
-                descend = list(
285
-                    adjM = adjMatrix_base,
286
-                    l_path = c(1),
287
-                    ind_lPath = 1,
288
-                    row_v = which(colnames(adjMatrix_base) == cl_df$cl_vertex$last_mutation[cl_df$cl_vertex$names == colnames(adjMatrix_overall)[v]])
289
-                )
290
-                deep_tmp <- recursiveDescend(descend)
291
-                deep <- c(deep, deep_tmp$max_deep)
292
-                
293
-            }
285
+        for(v in idx_next_v) {
286
+            descend = list(
287
+                adjM = adjMatrix_overall,
288
+                l_path = c(1),
289
+                ind_lPath = 1,
290
+                mut_list = c(v),
291
+                row_v = v
292
+            )
293
+            deep_tmp <- recursiveDescend(descend)
294
+            dif_clones <- unique(cl_df$cl_vertex$clone[cl_df$cl_vertex$names %in% colnames(adjMatrix_overall)[deep_tmp$mut_list]])
295
+            deep <- c(deep, length(dif_clones))
294 296
         }
297
+        ord <- order(-cl_df$cl_vertex$TP[match(names(idx_next_v),cl_df$cl_vertex$names)], deep, decreasing = F)
295 298
         
296
-        idx_next_v <- idx_next_v[order(deep, decreasing = F)]
297
-        deep <- deep[order(deep, decreasing = F)]
298
-        #deep <- cumsum(deep)
299
-        
299
+        idx_next_v <- idx_next_v[ord]
300
+        deep <- deep[ord]
301
+
300 302
         offset_X = 0
301
-        offset_label = -3
302 303
         for(i in 1:length(idx_next_v)){
303
-            if(adjMatrix_overall[idx_Vc,idx_next_v[i]] == "persistence") {
304
+            
305
+            Vn_name <- colnames(adjMatrix_overall)[idx_next_v[i]]
306
+            
307
+            if(adjMatrix_overall[idx_Vc,idx_next_v[i]] == 2) {
304 308
                 X = Xc
305
-                Y = mut_TP[as.character(cl_df$cl_vertex$TP[cl_vertex_idx_Vc])] + 1
309
+                Y = mut_TP[as.character((cl_df$cl_vertex$TP[cl_df$cl_vertex$names == Vn_name]-1))] + 1
310
+                offset_X = offset_X + deep[i] - 1
306 311
             } else {
307
-                Y = Yc + 1
312
+                
313
+                
314
+                
315
+                if(cl_df$cl_vertex$TP[cl_vertex_idx_Vc] < cl_df$cl_vertex$TP[cl_df$cl_vertex$names == Vn_name]) {
316
+                    Y = mut_TP[as.character((cl_df$cl_vertex$TP[cl_df$cl_vertex$names == Vn_name]-1))] + 1
317
+                } else {
318
+                    Y = Yc + 1
319
+                }
308 320
                 
309 321
                 X = (Xc + offset_X + 1)
322
+
310 323
                 offset_X = offset_X + deep[i]
311
-                
312
-                #offset_label = -2*offset_label 
313
-                Vn_name <- colnames(adjMatrix_overall)[idx_next_v[i]]
324
+
314 325
                 idx_row_edges = which(cl_df$cl_edges$from == cl_df$cl_vertex$names[cl_vertex_idx_Vc] & cl_df$cl_edges$to == Vn_name)
315 326
                 mutation_name <- cl_df$cl_vertex$last_mutation[cl_df$cl_vertex$names == Vn_name]
316 327
                 
317 328
                 clone_fake_edge <- data.frame(from = cl_df$cl_edges$from[idx_row_edges],
318
-                                                  to = paste0('H_',mutation_name),
319
-                                                  type = "Parental",
320
-                                                  extincion = FALSE,
321
-                                                  label = "", 
322
-                                                  name = "",
323
-                                                  lty = 1)
329
+                                              to = paste0('H_',mutation_name),
330
+                                              type = "Parental",
331
+                                              extincion = FALSE,
332
+                                              label = "", 
333
+                                              name = "",
334
+                                              lty = 1)
324 335
                 
325 336
                 fake_mutation_edge <- data.frame(from = paste0('H_',mutation_name),
326 337
                                                  to = mutation_name,
... ...
@@ -339,39 +350,39 @@ recursiveLongitudinalLayout <- function( idx_Vc, Xc, Yc, cl_df, adjMatrix_base,
339 350
                                                   lty = 1)
340 351
                 
341 352
                 fake_vertex <- data.frame(names = paste0('H_',mutation_name), 
342
-                                              branch_level = NA,
343
-                                              branch = NA,
344
-                                              label = "",
345
-                                              last_mutation = "",
346
-                                              TP = cl_df$cl_vertex$TP[cl_df$cl_vertex$names == Vn_name],
347
-                                              clone = cl_df$cl_vertex$clone[cl_df$cl_vertex$names == Vn_name],
348
-                                              prevalance = NA,
349
-                                              size = 0,
350
-                                              size2 = 0,
351
-                                              shape = "none",
352
-                                              label.dist = 0,
353
+                                          branch_level = NA,
354
+                                          branch = NA,
355
+                                          label = "",
356
+                                          last_mutation = "",
357
+                                          TP = NA, 
358
+                                          clone = cl_df$cl_vertex$clone[cl_vertex_idx_Vc],
359
+                                          prevalance = NA,
360
+                                          size = 0,
361
+                                          size2 = 0,
362
+                                          shape = "none",
363
+                                          label.dist = 0,
353 364
                                           label.degree = 0,
354
-                                              extincion = 0,
355
-                                              coord.x = X,
356
-                                              coord.y = Yc,
357
-                                              color = NA)
365
+                                          extincion = 0,
366
+                                          coord.x = X,
367
+                                          coord.y = Yc,
368
+                                          color = NA)
358 369
                 
359 370
                 mutation_vertex <- data.frame(names = mutation_name, 
360 371
                                               branch_level = NA,
361 372
                                               branch = NA,
362 373
                                               label = ifelse(test = labels_show %in% c("both", "mutations"), yes = mutation_name, no = ""),
363 374
                                               last_mutation = "",
364
-                                              TP = cl_df$cl_vertex$TP[cl_df$cl_vertex$names == Vn_name],
365
-                                              clone = cl_df$cl_vertex$clone[cl_df$cl_vertex$names == Vn_name],
375
+                                              TP = NA, 
376
+                                              clone = cl_df$cl_vertex$clone[cl_vertex_idx_Vc],
366 377
                                               prevalance = NA,
367 378
                                               size = 6,
368 379
                                               size2 = 6,
369 380
                                               shape = "square",
370
-                                              label.dist = 4,
381
+                                              label.dist = label_offset,
371 382
                                               label.degree = 0,
372 383
                                               extincion = 0,
373 384
                                               coord.x = X,
374
-                                              coord.y = (Yc + 0.33),
385
+                                              coord.y = (Yc + Y)*0.5,
375 386
                                               color = cl_df$cl_vertex$color[cl_df$cl_vertex$names == Vn_name])
376 387
                 
377 388
                 cl_df$cl_edges <- cl_df$cl_edges[-idx_row_edges,]
... ...
@@ -380,20 +391,25 @@ recursiveLongitudinalLayout <- function( idx_Vc, Xc, Yc, cl_df, adjMatrix_base,
380 391
                 cl_df$cl_vertex <- rbind(cl_df$cl_vertex, fake_vertex, mutation_vertex)
381 392
                 
382 393
             }
383
-            cl_df <- recursiveLongitudinalLayout(idx_next_v[i], X, Y, cl_df, adjMatrix_base, adjMatrix_overall, mut_TP, labels_show)
394
+            cl_df <- recursiveLongitudinalLayout(idx_next_v[i], X, Y, cl_df, adjMatrix_base, adjMatrix_overall, mut_TP, labels_show, label_offset)
384 395
         }
385 396
     } else {
386 397
         # NO BRANCH
387
-        if(adjMatrix_overall[idx_Vc,idx_next_v] == "persistence") {
398
+        Vn_name <- colnames(adjMatrix_overall)[idx_next_v]
399
+        
400
+        if(adjMatrix_overall[idx_Vc,idx_next_v] == 2) {
388 401
             X = Xc
389
-            Y = mut_TP[as.character(cl_df$cl_vertex$TP[cl_vertex_idx_Vc])] + 1
402
+            Y = mut_TP[as.character((cl_df$cl_vertex$TP[cl_df$cl_vertex$names == Vn_name]-1))] + 1
390 403
         } else {
391 404
             
392
-            Y = Yc + 1
405
+            if(cl_df$cl_vertex$TP[cl_vertex_idx_Vc] < cl_df$cl_vertex$TP[cl_df$cl_vertex$names == Vn_name]) {
406
+                Y = mut_TP[as.character((cl_df$cl_vertex$TP[cl_df$cl_vertex$names == Vn_name]-1))] + 1
407
+            } else {
408
+                Y = Yc + 1
409
+            }
393 410
             
394 411
             X = Xc + 1
395 412
             
396
-            Vn_name <- colnames(adjMatrix_overall)[idx_next_v]
397 413
             idx_row_edges = which(cl_df$cl_edges$from == cl_df$cl_vertex$names[cl_vertex_idx_Vc] & cl_df$cl_edges$to == Vn_name)
398 414
             mutation_name <- cl_df$cl_vertex$last_mutation[cl_df$cl_vertex$names == Vn_name]
399 415
             clone_fake_edge <- data.frame(from = cl_df$cl_edges$from[idx_row_edges],
... ...
@@ -425,8 +441,8 @@ recursiveLongitudinalLayout <- function( idx_Vc, Xc, Yc, cl_df, adjMatrix_base,
425 441
                                       branch = NA,
426 442
                                       label = "",
427 443
                                       last_mutation = "",
428
-                                      TP = cl_df$cl_vertex$TP[cl_df$cl_vertex$names == Vn_name],
429
-                                      clone = cl_df$cl_vertex$clone[cl_df$cl_vertex$names == Vn_name],
444
+                                      TP = NA,#cl_df$cl_vertex$TP[cl_vertex_idx_Vc],
445
+                                      clone = cl_df$cl_vertex$clone[cl_vertex_idx_Vc],
430 446
                                       prevalance = NA,
431 447
                                       size = 0,
432 448
                                       size2 = 0,
... ...
@@ -443,29 +459,28 @@ recursiveLongitudinalLayout <- function( idx_Vc, Xc, Yc, cl_df, adjMatrix_base,
443 459
                                           branch = NA,
444 460
                                           label = ifelse(test = labels_show %in% c("both", "mutations"), yes = mutation_name, no = ""),
445 461
                                           last_mutation = "",
446
-                                          TP = cl_df$cl_vertex$TP[cl_df$cl_vertex$names == Vn_name],
447
-                                          clone = cl_df$cl_vertex$clone[cl_df$cl_vertex$names == Vn_name],
462
+                                          TP = NA,#cl_df$cl_vertex$TP[cl_vertex_idx_Vc],
463
+                                          clone = cl_df$cl_vertex$clone[cl_vertex_idx_Vc],
448 464
                                           prevalance = NA,
449 465
                                           size = 6,
450 466
                                           size2 = 6,
451 467
                                           shape = "square",
452
-                                          label.dist = 4,
468
+                                          label.dist = label_offset,
453 469
                                           label.degree = 0,
454 470
                                           extincion = 0,
455 471
                                           coord.x = X,
456
-                                          coord.y = (Yc + 0.33),
472
+                                          coord.y = (Yc + Y)*0.5,
457 473
                                           color = cl_df$cl_vertex$color[cl_df$cl_vertex$names == Vn_name])
458 474
             
459 475
             cl_df$cl_edges <- cl_df$cl_edges[-idx_row_edges,]
460 476
             cl_df$cl_edges <- rbind(cl_df$cl_edges, clone_fake_edge, fake_mutation_edge, mutation_clone_edge)
461 477
             
462 478
             cl_df$cl_vertex <- rbind(cl_df$cl_vertex, fake_vertex, mutation_vertex)
463
-
464
-
479
+            
465 480
         }
466
-        cl_df <- recursiveLongitudinalLayout(idx_next_v, X, Y, cl_df, adjMatrix_base, adjMatrix_overall, mut_TP, labels_show)
481
+        cl_df <- recursiveLongitudinalLayout(idx_next_v, X, Y, cl_df, adjMatrix_base, adjMatrix_overall, mut_TP, labels_show, label_offset)
467 482
     }
468 483
     
469 484
     return(cl_df)
470
-
485
+    
471 486
 }
... ...
@@ -10,6 +10,7 @@
10 10
 #'                        legend_position = "topleft")
11 11
 #'
12 12
 #' @param inference Results of the inference by LACE.
13
+#' @param rem_unseen_leafs If TRUE (default) remove all the leafs that have never been observed (prevalence = 0 in each time point)
13 14
 #' @param show_plot If TRUE (default) output the longitudinal tree to the current graphical device.
14 15
 #' @param filename Specify the name of the file where to save the longitudinal tree. Dot or graphml formats are supported and are chosen based on the extenction of the filename (.dot or .xml).
15 16
 #' @param labels_show Specify which type of label should be placed on the tree; options are, 
... ...
@@ -20,7 +21,6 @@
20 21
 #' @param clone_labels Character vector that specifies the name of the nodes (genotypes). If it is NULL (default), nodes will be labeled as specified by "label" parameter.
21 22
 #' @param show_prev If TRUE (default) add to clones label the correspongind prevalance.
22 23
 #' @param label.cex Specify the size of the labels.
23
-#' @param iter_max Maximum number of iteration to be used to remove intersecting edges.
24 24
 #' @param size Specify size of the nodes. The final area is proportional with the node prevalence.
25 25
 #' @param size2 Specify the size of the second dimension of the nodes. If NULL (default), it is set equal to "size".
26 26
 #' @param tk_plot If TRUE, uses tkplot function from igraph library to plot an interactive tree. Default is FALSE.
... ...
@@ -29,6 +29,7 @@
29 29
 #' @param tp_mark_alpha Specify the alpha value of the area drawed when tp_mark = TRUE.
30 30
 #' @param legend If TRUE (default) a legend will be displayed on the plot.
31 31
 #' @param legend_position Specify the legend position.
32
+#' @param label_offset Move the mutation labels horizontally (default = 4)
32 33
 #' @param legend_cex Specify size of the legend text.
33 34
 #' @return An igraph object g with the longitudinal tree inferred by LACE. 
34 35
 #' @export longitudinal.tree.plot
... ...
@@ -39,13 +40,13 @@
39 40
 #' @import utils
40 41
 #'
41 42
 longitudinal.tree.plot <- function( inference, 
43
+                                    rem_unseen_leafs = TRUE,
42 44
                                     show_plot = TRUE, 
43 45
                                     filename = "lg_output.xml", 
44 46
                                     labels_show = "mutations", 
45 47
                                     clone_labels = NULL, 
46 48
                                     show_prev = TRUE, 
47 49
                                     label.cex = 1, 
48
-                                    iter_max = 100, 
49 50
                                     size = 500, 
50 51
                                     size2 = NULL, 
51 52
                                     tk_plot = FALSE, 
... ...
@@ -54,33 +55,48 @@ longitudinal.tree.plot <- function( inference,
54 55
                                     tp_mark_alpha = 0.5, 
55 56
                                     legend = TRUE, 
56 57
                                     legend_position = "topright", 
58
+                                    label_offset = 4, 
57 59
                                     legend_cex = 0.8 ) {
58 60
     
59 61
     if(is.null(size2)) {
60 62
         size2 <- size
61 63
     }
62
-    # 
63
-    # root <- list()
64
-    # root$prev <- sum(unlist(lapply(inference$C, function(x){sum(x == 0)}))) /
65
-    #     sum(unlist(lapply(inference$C, function(x){length(x)})))
66
-    # 
67
-    # root$prev <- round(root$prev, digits = 2)
68
-    # 
69
-    # root$size <- 2*sqrt(size*root$prev/pi)
70
-    # root$size2 <- 2*sqrt(size2*root$prev/pi)
71
-    # 
72
-    # root$label <- "Root"
73
-    # 
74
-    # if(show_prev) {
75
-    #     num_str <- sub("^(-?)0.", "\\1.", sprintf("%.2f", root$prev))
76
-    #     root$label <- paste0(root$label, " (", num_str , ")")
77
-    # }
64
+
65
+    adjMatrix_base <- as.adj.matrix.unsorted(inference$B, root = TRUE)
66
+    
67
+    M_leafs <- which(apply(X = adjMatrix_base, MARGIN = 1, FUN = sum)==0)
68
+    Clone_Mut <- sapply(inference$clones_summary, function(x){tail(x,1)}, USE.NAMES = T)
69
+    C_leafs <- Clone_Mut[match(names(M_leafs), Clone_Mut)]
70
+    
71
+    
72
+    if(rem_unseen_leafs == TRUE) {
73
+
74
+        uns_cl_mut <- C_leafs[which(inference$clones_prevalence[match(names(C_leafs),rownames(inference$clones_prevalence)), "Total"] == 0)]
75
+
76
+            while(length(uns_cl_mut) > 0) {
77
+                
78
+                # Delete each clone and corresponding mutation from B, clone_prevalence and clone_summary
79
+                del_mut <- as.character(uns_cl_mut)
80
+                del_clone <- names(uns_cl_mut)
81
+                
82
+                inference$B <- inference$B[!(rownames(inference$B) %in% del_clone), !(colnames(inference$B) %in% del_mut)]
83
+                inference$clones_prevalence <- inference$clones_prevalence[!(rownames(inference$clones_prevalence) %in% del_clone),]
84
+                inference$clones_summary <- inference$clones_summary[!(names(inference$clones_summary) %in% del_clone)]
85
+                
86
+                # Repeate
87
+                adjMatrix_base <- as.adj.matrix.unsorted(inference$B, root = TRUE)
88
+                M_leafs <- which(apply(X = adjMatrix_base, MARGIN = 1, FUN = sum)==0)
89
+                Clone_Mut <- sapply(inference$clones_summary, function(x){tail(x,1)}, USE.NAMES = T)
90
+                C_leafs <- Clone_Mut[match(names(M_leafs), Clone_Mut)]
91
+                uns_cl_mut <- C_leafs[which(inference$clones_prevalence[match(names(C_leafs),rownames(inference$clones_prevalence)), "Total"] == 0)]
92
+            }
93
+    }
78 94
     
79 95
     cl_vertex <- data.frame(prevalance = as.vector(inference$clones_prevalence[,-ncol(inference$clones_prevalence)]))
80 96
     cl_vertex$clone <- rep(c(0:(nrow(inference$clones_prevalence)-1)),ncol(inference$clones_prevalence)-1)
81 97
     cl_vertex$TP <- rep(1:(ncol(inference$clones_prevalence)-1), each = nrow(inference$clones_prevalence))
82
-    cl_vertex$last_mutation <- rep(unlist(lapply(c("Root",inference$clones_summary), function(x){tail(x, 1)})), ncol(inference$clones_prevalence)-1)
83
-    
98
+    cl_vertex$last_mutation <- rep(c("Root",Clone_Mut), ncol(inference$clones_prevalence)-1)
99
+
84 100
     if(!is.null(clone_labels)) {
85 101
         if(length(clone_labels)!=length(inference$clones_summary)) {
86 102
             warning("Label number is different from the number of clones.")
... ...
@@ -100,7 +116,7 @@ longitudinal.tree.plot <- function( inference,
100 116
     cl_vertex$branch_level <- 0
101 117
     cl_vertex$names <- paste0("T", cl_vertex$TP, "-", cl_vertex$last_mutation)
102 118
     
103
-    # names must be the first column
119
+    # Names must be the first column
104 120
     cl_vertex <- cl_vertex[,order(ncol(cl_vertex):1)]
105 121
     
106 122
     cl_edges <- data.frame(stringsAsFactors = FALSE)
... ...
@@ -132,13 +148,12 @@ longitudinal.tree.plot <- function( inference,
132 148
             }
133 149
         }
134 150
     }
151
+
152
+    # Processing parental relations
153
+    cl_edges_parental <- data.frame(stringsAsFactors = FALSE)
135 154
     
136
-    # Processing parental relations    
137
-    adjMatrix_base <- as.adj.matrix.unsorted(inference$B, root = TRUE)
138
-    
139
-    # Start from one leaf
140
-    B_leaf <- which(apply(X = adjMatrix_base, MARGIN = 1, FUN = sum)==0)
141
-    for(cs_id in B_leaf) {
155
+    # Start from one leaf of M_leafs
156
+    for(cs_id in M_leafs) {
142 157
         curTP <- max(cl_vertex$TP)
143 158
         cp_id <- which(adjMatrix_base[,cs_id]==1)
144 159
         while(length(cp_id)>0) {
... ...
@@ -148,8 +163,7 @@ longitudinal.tree.plot <- function( inference,
148 163
             
149 164
             if(length(TPs)==0) {
150 165
                 cs_tp <- curTP
151
-            }
152
-            else {
166
+            } else {
153 167
                 cs_tp <- min(TPs)
154 168
             }
155 169
             
... ...
@@ -157,21 +171,20 @@ longitudinal.tree.plot <- function( inference,
157 171
             TPs <- cl_vertex$TP[cl_vertex$clone == (cp_id-1) & cl_vertex$prevalance > 0 & cl_vertex$TP <= cs_tp]
158 172
             
159 173
             if(length(TPs) == 0) {
160
-                # If the parental clone has ever had prevalence == 0 -> I use the same time point of the son clone
174
+                # If the parental clone has ever prevalence == 0 -> I use the same time point of the son clone
161 175
                 cp_tp = cs_tp
162
-            }
163
-            else {
176
+            } else {
164 177
                 cp_tp <- max(TPs)
165 178
             }
166 179
             
167 180
             from_cc <- cl_vertex$names[cl_vertex$clone == (cp_id-1) & cl_vertex$TP == cp_tp]
168 181
             to_cc <- cl_vertex$names[cl_vertex$clone == (cs_id-1) & cl_vertex$TP == cs_tp]
169 182
             mut <- cl_vertex$last_mutation[cl_vertex$clone == (cs_id-1) & cl_vertex$TP == cs_tp]
170
-            cl_edges <- rbind(cl_edges, data.frame(from = from_cc, 
171
-                                                   to = to_cc, 
172
-                                                   type = "parental", 
173
-                                                   extincion = FALSE, 
174
-                                                   stringsAsFactors = FALSE))
183
+            cl_edges_parental <- rbind(cl_edges_parental, data.frame(from = from_cc, 
184
+                                                                     to = to_cc, 
185
+                                                                     type = "parental", 
186
+                                                                     extincion = FALSE, 
187
+                                                                     stringsAsFactors = FALSE))
175 188
             
176 189
             # Now son clone becomes parental clone
177 190
             curTP <- cp_tp
... ...
@@ -181,30 +194,45 @@ longitudinal.tree.plot <- function( inference,
181 194
         }
182 195
     }
183 196
     
184
-    cl_edges <- cl_edges[!duplicated.data.frame(cl_edges[,c("from", "to", "type")]),]
197
+    # Fix duplicate parental relation (keep earliest) ones
198
+    
199
+    cl_edges_parental$from_cl <- cl_vertex$clone[match(cl_edges_parental$from, cl_vertex$names)]
200
+    cl_edges_parental$to_cl <- cl_vertex$clone[match(cl_edges_parental$to, cl_vertex$names)]
201
+    cl_edges_parental$to_tp <- cl_vertex$TP[match(cl_edges_parental$to, cl_vertex$names)]
202
+    
203
+    cl_edges_parental <- cl_edges_parental[order(cl_edges_parental$to_tp),]
204
+    
205
+    cl_edges_parental <- cl_edges_parental[!duplicated(cl_edges_parental[,c("from_cl", "to_cl")], fromLast = F), c("from","to","type","extincion")]
206
+    
207
+    cl_edges <- rbind(cl_edges, cl_edges_parental)
208
+    
209
+    # Fixing missing persistence relations
210
+    fixing_clones <- data.frame(names = unique(as.character(cl_edges$from)))
211
+    
212
+    fixing_clones$clones <- cl_vertex$clone[match(fixing_clones$names,cl_vertex$names)]
213
+    fixing_clones$TP <- cl_vertex$TP[match(fixing_clones$names,cl_vertex$names)]
185 214
     
186
-    # Fixing missing prevalence relations
187
-    included_clones_names <- unique(c(as.character(cl_edges$from), as.character(cl_edges$to)))
188
-    for(icn in included_clones_names) {
189
-        ic <- cl_vertex$clone[cl_vertex$names == icn]
190
-        ic_tp <- cl_vertex$TP[cl_vertex$names == icn]
215
+    fixing_clones <- fixing_clones[duplicated(fixing_clones$clones) | duplicated(fixing_clones$clones, fromLast = T),]
216
+    fixing_clones <- fixing_clones[order(fixing_clones$TP),]
217
+    
218
+    for(fxc in unique(fixing_clones$clones)){
191 219
         
192
-        next_cln <- cl_vertex$names[cl_vertex$clone == ic & cl_vertex$TP == (ic_tp + 1)]
193
-        if(length(next_cln) == 0) {
194
-            next
195
-        }
196
-        else {
197
-            if(sum(cl_edges$from == icn & cl_edges$to == next_cln) == 0 && next_cln %in% included_clones_names) {
198
-                cl_edges <- rbind(cl_edges, data.frame(from = icn, 
199
-                                                       to = next_cln, 
200
-                                                       type = "persistence", 
201
-                                                       extincion = FALSE, 
202
-                                                       stringsAsFactors = FALSE))
220
+        fixing_clones_i <- fixing_clones[fixing_clones$clones == fxc,]
221
+        for(i in 1:(nrow(fixing_clones_i)-1)) {
222
+            
223
+            if(sum(cl_edges$from == fixing_clones_i$names[i] & cl_edges$to == fixing_clones_i$names[i+1] & cl_edges$type ==  "persistence") == 0) {
224
+                cl_edges <- rbind(cl_edges, data.frame(from = fixing_clones_i$names[i], 
225
+                                                       to = fixing_clones_i$names[i+1],
226
+                                                       type = "persistence",
227
+                                                       extincion = FALSE,
228
+                                                       stringsAsFactors = FALSE)
229
+                )
203 230
             }
231
+            
204 232
         }
205 233
         
206 234
     }
207
-    
235
+
208 236
     # Setting edges labels
209 237
     cl_edges$label <- ""
210 238
     cl_edges$name <- ""
... ...
@@ -233,7 +261,7 @@ longitudinal.tree.plot <- function( inference,
233 261
     # Setting the size of the extincted clones
234 262
     cl_vertex$size[cl_vertex$names %in% as.character(cl_edges$to[cl_edges$extincion])] <- 2*sqrt(size*0.01)
235 263
     cl_vertex$size2[cl_vertex$names %in% as.character(cl_edges$to[cl_edges$extincion])] <- 2*sqrt(size2*0.01)
236
-    cl_vertex$shape[cl_vertex$names %in% as.character(cl_edges$to[cl_edges$extincion])] <- "rectangle"
264
+    cl_vertex$shape[cl_vertex$names %in% as.character(cl_edges$to[cl_edges$extincion])] <- "vrectangle"
237 265
     
238 266
     cl_vertex$label.dist <- -1
239 267
     cl_vertex$label.degree <- 0
... ...
@@ -256,6 +284,7 @@ longitudinal.tree.plot <- function( inference,
256 284
     if(show_prev) {
257 285
         num_str <- sub("^(-?)0.", "\\1.", sprintf("%.2f", cl_vertex$prevalance))
258 286
         cl_vertex$label <- paste0(cl_vertex$label, " (", num_str , ")")
287
+        cl_vertex$label[cl_vertex$prevalance == 0.0] <- ""
259 288
         
260 289
     }
261 290
     
... ...
@@ -272,13 +301,7 @@ longitudinal.tree.plot <- function( inference,
272 301
     cl_edges$lty <- ifelse(cl_edges$type == "persistence", yes = 2, no = 1)
273 302
     
274 303
     g <- igraph::graph_from_data_frame(cl_edges, directed=TRUE, vertices=cl_vertex)
275
-    
276
-    # get coordinate for each vertex
277
-    # org_coordinates <- layout_(g, as_tree())
278
-    # 
279
-    # cl_vertex$coord.x <- round(org_coordinates[,1], digits = 3)
280
-    # cl_vertex$coord.y <- round(org_coordinates[,2], digits = 3)
281
-    
304
+
282 305
     parental_clones <- which(apply(X = adjMatrix_base, MARGIN = 2, function(x) sum(x == 1))==0)
283 306
     
284 307
     c_br <- 1
... ...
@@ -345,110 +368,18 @@ longitudinal.tree.plot <- function( inference,
345 368
     igraph::vertex_attr(graph = g, name = "color") <- cl_vertex$color
346 369
     
347 370
     igraph::delete_edge_attr(graph = g, name = "extincion")
348
-    
349
-    
350
-    ### NEW LAYOUT
351
-    
371
+
352 372
     cl_vertex$coord.x <- NA
353 373
     cl_vertex$coord.y <- NA
354
-    
355
-    # Adding root
356
-    # cl_vertex <- rbind(data.frame(names = "Root", 
357
-    #                               branch_level = 0,
358
-    #                               branch = 0,
359
-    #                               label = root$label,
360
-    #                               last_mutation = "",
361
-    #                               TP = 1,
362
-    #                               clone = 0,
363
-    #                               prevalance = root$prev,
364
-    #                               size = root$size,
365
-    #                               size2 = root$size2,
366
-    #                               shape = "circle",
367
-    #                               label.dist = -2,
368
-    #                               label.degree = 45,
369
-    #                               extincion = 0,
370
-    #                               coord.x = 0,
371
-    #                               coord.y = 0,
372
-    #                               color = "#DDDDDD"
373
-    # ),cl_vertex)
374
-    
375
-    # #ADDING ROOT IN EACH TIME POINT
376
-    # root_vertexes <- data.frame()
377
-    # 
378
-    # for(TP in 1:length(inference$C)) {
379
-    #     root_vertexes <- rbind(root_vertexes, 
380
-    #                            data.frame(names = paste0("Root_t", TP), 
381
-    #                                       branch_level = 0,
382
-    #                                       branch = 0,
383
-    #                                       label = root$label,
384
-    #                                       last_mutation = "",
385
-    #                                       TP = TP,
386
-    #                                       clone = 0,
387
-    #                                       prevalance = root$prev,
388
-    #                                       size = root$size,
389
-    #                                       size2 = root$size2,
390
-    #                                       shape = "circle",
391
-    #                                       label.dist = -2,
392
-    #                                       label.degree = 45,
393
-    #                                       extincion = 0,
394
-    #                                       coord.x = 0,
395
-    #                                       coord.y = TP-1,
396
-    #                                       color = "#DDDDDD"
397
-    #                            ))
398
-    #     
399
-    # }
400
-    # 
401
-    # cl_vertex <- rbind(root_vertexes,cl_vertex)
402
-    # 
403
-    # root_edges <- data.frame()
404
-    # for(TP in 1:(length(inference$C)-1)) {
405
-    #     root_edges <- rbind(root_edges,
406
-    #                         data.frame(from = paste0("Root_t", TP), 
407
-    #                                    to = paste0("Root_t", (TP+1)),
408
-    #                                    type = "persistence",
409
-    #                                    extincion = FALSE,
410
-    #                                    label = "",
411
-    #                                    name = "",
412
-    #                                    lty = 2
413
-    #                         ))
414
-    # }
415
-    # 
416
-    # cl_edges <- rbind(root_edges,cl_edges)
417
-    # 
418
-    # adjMatrix_overall <- igraph::get.adjacency(g, sparse = F, attr = "type", names = T)
419
-    # ancestral_nodes <- colnames(adjMatrix_overall)[which(colSums(adjMatrix_overall != "")==0)] 
420
-    # 
421
-    # for(an in ancestral_nodes) {
422
-    #     cl_edges <- rbind(data.frame(from = "Root_t1",
423
-    #                                  to = an,
424
-    #                                  type = "Parental",
425
-    #                                  extincion = FALSE,
426
-    #                                  label = cl_vertex$last_mutation[cl_vertex$names == an],
427
-    #                                  name = cl_vertex$last_mutation[cl_vertex$names == an],
428
-    #                                  lty = 1
429
-    #     ),cl_edges)
430
-    # }
431
-    # 
432 374
 
433
-    # adjMatrix_overall <- igraph::get.adjacency(g, sparse = F, attr = "type", names = T)
434
-    # ancestral_nodes <- colnames(adjMatrix_overall)[which(colSums(adjMatrix_overall != "")==0)] 
435
-    # 
436
-    # for(an in ancestral_nodes) {
437
-    #     cl_edges <- rbind(data.frame(from = "Root",
438
-    #                                  to = an,
439
-    #                                  type = "Parental",
440
-    #                                  extincion = FALSE,
441
-    #                                  label = cl_vertex$last_mutation[cl_vertex$names == an],
442
-    #                                  name = cl_vertex$last_mutation[cl_vertex$names == an],
443
-    #                                  lty = 1
444
-    #     ),cl_edges)
445
-    # }
446
-    
447
-    
448
-    adjMatrix_base <- as.adj.matrix.unsorted(inference$B, root = T)
449 375
     g <- igraph::graph_from_data_frame(cl_edges, directed=TRUE, vertices=cl_vertex)
450 376
     adjMatrix_overall <- igraph::get.adjacency(g, sparse = F, attr = "type", names = TRUE)
451
-
377
+    
378
+    adjMatrix_overall[which(adjMatrix_overall=="")] <- 0
379
+    adjMatrix_overall[which(adjMatrix_overall=="persistence")] <- 2
380
+    adjMatrix_overall[which(adjMatrix_overall=="parental")] <- 1
381
+    storage.mode(adjMatrix_overall) <- "integer"
382
+    
452 383
     # Count total level number in each time point
453 384
     timepoints <- unique(cl_vertex$TP)
454 385
     
... ...
@@ -471,6 +402,7 @@ longitudinal.tree.plot <- function( inference,
471 402
                     adjM = adjMatrix_base_tp,
472 403
                     l_path = 0,
473 404
                     ind_lPath = 1,
405
+                    mut_list = NA,
474 406
                     row_v = idx
475 407
                 )
476 408
                 deep_tmp <- recursiveDescend(descend)$max_deep
... ...
@@ -479,11 +411,13 @@ longitudinal.tree.plot <- function( inference,
479 411
             mut_TP <- c(mut_TP, max_deep_tp)
480 412
         }
481 413
     }
414
+    
415
+    
482 416
     mut_TP <- cumsum(mut_TP) + 1:length(mut_TP)
483 417
     names(mut_TP) <- timepoints
484 418
     
485 419
     cl_df <- list(cl_vertex = cl_vertex, cl_edges = cl_edges)
486
-    idx_next_v <-  which(colSums(adjMatrix_overall != "") == 0)
420
+    idx_next_v <-  which(colSums(adjMatrix_overall != 0) == 0)
487 421
     
488 422
     # Root
489 423
     Xc = 0
... ...
@@ -497,99 +431,22 @@ longitudinal.tree.plot <- function( inference,
497 431
                                          adjMatrix_base=adjMatrix_base,
498 432
                                          adjMatrix_overall=adjMatrix_overall,
499 433
                                          mut_TP=mut_TP,
500
-                                         labels_show=labels_show)
434
+                                         labels_show=labels_show,
435
+                                         label_offset=label_offset)
501 436
     
502 437
     cl_vertex <- cl_df$cl_vertex[order(cl_df$cl_vertex$TP, cl_df$cl_vertex$coord.y),]
503 438
     cl_edges <- cl_df$cl_edges
504 439
     
505
-    g_mod <- igraph::graph_from_data_frame(d = cl_edges, directed=TRUE, vertices=cl_vertex)
506 440
     
507
-    # # fixing clone y position based on the time point 
508
-    # if(length(unique(cl_vertex$TP))>1) {
509
-    #     for(tp in seq(from = 1, to = max(cl_vertex$TP)-1)) {
510
-    #         m_c <- min(cl_vertex$coord.y[which(cl_vertex$TP == tp)]) - 1
511
-    #         cl_vertex$coord.y[which(cl_vertex$TP == tp+1 & cl_vertex$coord.y >= m_c)] <- m_c
512
-    #     }
513
-    # }
514
-    # 
515
-    # # Fixing overlapping points 
516
-    # for(c_x in unique(cl_vertex$coord.x)) {
517
-    #     idx_coord_y <- which(cl_vertex$coord.x == c_x)[order(org_coordinates[which(cl_vertex$coord.x == c_x,), 2], decreasing = TRUE)]
518
-    #     if(length(idx_coord_y) < 2) {
519
-    #         next;
520
-    #     }
521
-    #     for(i in 1:(length(idx_coord_y)-1)) {
522
-    #         if(cl_vertex$coord.y[idx_coord_y[i]] <= cl_vertex$coord.y[idx_coord_y[i+1]]) {
523
-    #             cl_vertex$coord.y[idx_coord_y[i+1]] = cl_vertex$coord.y[idx_coord_y[i]] - 1
524
-    #         }
525
-    #     }
526
-    # }
527
-    # 
528
-    # deltaX <- 2*(sum(abs(range(cl_vertex$coord.x))) / length(cl_vertex$coord.x))
529
-    # 
530
-    # # Fixing overlapping edges
531
-    # found = TRUE
532
-    # maxIter = iter_max
533
-    # while(found & maxIter > 0) {
534
-    #     found = FALSE
535
-    #     maxIter <- maxIter - 1
536
-    #     for(i in 1:(nrow(cl_edges)-1)) {
537
-    #         for(j in 2:nrow(cl_edges)) {
538
-    #             
539
-    #             if(i == j) {
540
-    #                 next;
541
-    #             }
542
-    #             
543
-    #             edgeA_1 = as.character(cl_edges$from[i])
544
-    #             edgeA_2 = as.character(cl_edges$to[i])
545
-    #             edgeB_1 = as.character(cl_edges$from[j])
546
-    #             edgeB_2 = as.character(cl_edges$to[j])
547
-    #             
548
-    #             ax1 <- cl_vertex$coord.x[which(cl_vertex$names == edgeA_1)]
549
-    #             ay1 <- cl_vertex$coord.y[which(cl_vertex$names == edgeA_1)]
550
-    #             ax2 <- cl_vertex$coord.x[which(cl_vertex$names == edgeA_2)]
551
-    #             ay2 <- cl_vertex$coord.y[which(cl_vertex$names == edgeA_2)]      
552
-    #             
553
-    #             bx1 <- cl_vertex$coord.x[which(cl_vertex$names == edgeB_1)]
554
-    #             by1 <- cl_vertex$coord.y[which(cl_vertex$names == edgeB_1)]
555
-    #             bx2 <- cl_vertex$coord.x[which(cl_vertex$names == edgeB_2)]
556
-    #             by2 <- cl_vertex$coord.y[which(cl_vertex$names == edgeB_2)]   
557
-    #             
558
-    #             # Check if two ends are on the same place (if truw, increase the Y values)
559
-    #             if(ax2 == bx2 && ay2 == by2) {
560
-    #                 ax2 <- ax2 + deltaX
561
-    #                 cl_vertex$coord.x[which(cl_vertex$names == edgeA_2)] <- ax2
562
-    #             }
563
-    #             
564
-    #             # Check if parental clone have y values minor respect to the son clones ones
565
-    #             if(ay1 <= ay2) {
566
-    #                 ay2 <- ay1 - 1
567
-    #                 cl_vertex$coord.y[which(cl_vertex$names == edgeA_2)] <- ay2
568
-    #             }
569
-    #             if(by1 <= by2) {
570
-    #                 by2 <- by1 - 1
571
-    #                 cl_vertex$coord.y[which(cl_vertex$names == edgeB_2)] <- by2
572
-    #             }      
573
-    #             
574
-    #             if(length(unique(c(edgeA_1,edgeA_2,edgeB_1,edgeB_2))) < 4 ) {
575
-    #                 next;
576
-    #             }
577
-    #             
578
-    #             if(checkSegmentIntersect(ax1,ay1,ax2,ay2,bx1,by1,bx2,by2)) {
579
-    #                 found = TRUE
580
-    #                 cl_vertex$coord.x[which(cl_vertex$names == edgeA_2)] <- bx2
581
-    #                 cl_vertex$coord.x[which(cl_vertex$names == edgeB_2)] <- ax2 
582
-    #             }
583
-    #         }
584
-    #     }
585
-    # }
586 441
     
442
+    
443
+    
444
+    g_mod <- igraph::graph_from_data_frame(d = cl_edges, directed=TRUE, vertices=cl_vertex)
445
+
587 446
     time_point_grp <- split(cl_vertex$names[cl_vertex$last_mutation!="Root"], cl_vertex$TP[cl_vertex$last_mutation!="Root"])
588
-    #time_point_grp[[1]] <- NULL
589 447
     
590 448
     ratio = par("din")[1] / par("din")[2]
591 449
     
592
-    #g$layout <- norm_coords(as.matrix(cl_vertex[,c("coord.x", "coord.y")]), xmin = -1*(ratio), xmax = 1*(ratio), ymin = -1, ymax = 1)
593 450
     g_mod$layout <- igraph::norm_coords(as.matrix(cl_vertex[,c("coord.x", "coord.y")]), xmin = -1*ratio, xmax = 1*ratio, ymin = 1, ymax = -1)
594 451
     
595 452
     if(tk_plot) {
... ...
@@ -6,13 +6,13 @@
6 6
 \usage{
7 7
 longitudinal.tree.plot(
8 8
   inference,
9
+  rem_unseen_leafs = TRUE,
9 10
   show_plot = TRUE,
10 11
   filename = "lg_output.xml",
11 12
   labels_show = "mutations",
12 13
   clone_labels = NULL,
13 14
   show_prev = TRUE,
14 15
   label.cex = 1,
15
-  iter_max = 100,
16 16
   size = 500,
17 17
   size2 = NULL,
18 18
   tk_plot = FALSE,
... ...
@@ -21,12 +21,15 @@ longitudinal.tree.plot(
21 21
   tp_mark_alpha = 0.5,
22 22
   legend = TRUE,
23 23
   legend_position = "topright",
24
+  label_offset = 4,
24 25
   legend_cex = 0.8
25 26
 )
26 27
 }
27 28
 \arguments{
28 29
 \item{inference}{Results of the inference by LACE.}
29 30
 
31
+\item{rem_unseen_leafs}{If TRUE (default) remove all the leafs that have never been observed (prevalence = 0 in each time point)}
32
+
30 33
 \item{show_plot}{If TRUE (default) output the longitudinal tree to the current graphical device.}
31 34
 
32 35
 \item{filename}{Specify the name of the file where to save the longitudinal tree. Dot or graphml formats are supported and are chosen based on the extenction of the filename (.dot or .xml).}
... ...
@@ -43,8 +46,6 @@ longitudinal.tree.plot(
43 46
 
44 47
 \item{label.cex}{Specify the size of the labels.}
45 48
 
46
-\item{iter_max}{Maximum number of iteration to be used to remove intersecting edges.}
47
-
48 49
 \item{size}{Specify size of the nodes. The final area is proportional with the node prevalence.}
49 50
 
50 51
 \item{size2}{Specify the size of the second dimension of the nodes. If NULL (default), it is set equal to "size".}
... ...
@@ -61,6 +62,8 @@ longitudinal.tree.plot(
61 62
 
62 63
 \item{legend_position}{Specify the legend position.}
63 64
 
65
+\item{label_offset}{Move the mutation labels horizontally (default = 4)}
66
+
64 67
 \item{legend_cex}{Specify size of the legend text.}
65 68
 }
66 69
 \value{
... ...
@@ -14,8 +14,6 @@ time points: (1) before treatment, (2) 4 days treatment, (3) 28 days treatment a
14 14
 library("LACE")
15 15
 data(longitudinal_sc_variants)
16 16
 names(longitudinal_sc_variants)
17
-
18
-## [1] "T1_before_treatment"  "T2_4_days_treatment"  "T3_28_days_treatment" "T4_57_days_treatment"
19 17
 ```
20 18
 
21 19
 We setup the main parameter in oder to perform the inference. First of all, as the four data points may potentially provide sequencing for an unbalanced 
... ...
@@ -36,9 +34,7 @@ beta = list()
36 34
 beta[[1]] = c(0.10,0.05,0.05,0.05)
37 35
 beta[[2]] = c(0.10,0.05,0.05,0.05)
38 36
 head(alpha)
39
-
40 37
 head(beta)
41
-
42 38
 ```
43 39
 
44 40
 ## Inference