# HG changeset patch # User azomics # Date 1592862843 14400 # Node ID bd35f3b66a1e8d78dcc593210ad3b73ebbe81ff3 "planemo upload for repository https://github.com/ImmPortDB/immport-galaxy-tools/tree/master/flowtools/flowsom_compare commit a1755b91905a2a95ebb0d6dd4a2b3d42c7e19f05" diff -r 000000000000 -r bd35f3b66a1e FlowSOMCompare.R --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/FlowSOMCompare.R Mon Jun 22 17:54:03 2020 -0400 @@ -0,0 +1,234 @@ +#!/usr/bin/Rscript +# Module for Galaxy +# Compares groups of FCS to FlowSOM reference tree +# with FlowSOM +###################################################################### +# Copyright (c) 2017 Northrop Grumman. +# All rights reserved. +###################################################################### +# +# Version 1 +# Cristel Thomas +# +# +library(FlowSOM) +library(flowCore) + +checkFiles <- function(groups){ + all_files <- unlist(groups) + all_unique <- unique(all_files) + if (length(all_unique) != length(all_files)) { + quit(save = "no", status = 14, runLast = FALSE) + } +} + +compareLists <- function(m1, m2){ + listCheck <- T + if (is.na(all(m1==m2))) { + mm1 <- is.na(m1) + mm2 <- is.na(m2) + if (all(mm1==mm2)){ + if (!all(m1==m2, na.rm=TRUE)){ + listCheck <- F + } + } else { + listCheck <- F + } + } else if (!all(m1==m2)) { + listCheck <- F + } + return(listCheck) +} + +prettyMarkerNames <- function(flowFrame){ + n <- flowFrame@parameters@data[, "name"] + d <- flowFrame@parameters@data[, "desc"] + d[is.na(d)] <- n[is.na(d)] + prettyNames <- list() + if(any(grepl("#",d))){ + # Support for hashtag notation: + # antibody#fluorochrome -> antibody (fluorochrome) + prettyNames <- gsub("#(.*)$"," (\\1)",d) + } else { + prettyNames <- paste(d, " <", n, ">", sep="") + } + return(prettyNames) +} + +compareToTree <- function(fst, wilc_thresh=0.05, output="", plot="", stats, + comp_groups, filenames) { + groupRes <- CountGroups(fst, groups=comp_groups, plot=FALSE) + pdf(plot, useDingbats=FALSE, onefile=TRUE) + tresh <- wilc_thresh + pg <- PlotGroups(fst, groupRes, p_tresh=tresh) + dev.off() + + nb_nodes <- length(pg[[1]]) + nb_comp <- length(pg) + m <- matrix(0, nrow=nb_nodes, ncol=nb_comp+1) + s <- seq_len(nb_nodes) + m[,1]<- as.character(s) + for (i in 1:nb_comp){ + m[s,i+1]<- as.character(pg[[i]]) + } + groupnames <- attr(comp_groups,"names") + out_colnames <- paste(groupnames, collapse="-") + colnames(m) <- c("Node",out_colnames) + write.table(m, file=output, quote=F, row.names=F, col.names=T, sep='\t', + append=F) + + ## get filenames + filepaths <- unlist(comp_groups) + fnames <- unlist(filenames) + nb_files <- length(filepaths) + comp_files <- list() + for (i in 1:length(filepaths)){ + comp_files[[filepaths[[i]]]] <- fnames[[i]] + } + + group_list <- list() + for (grp in attr(comp_groups, "names")) { + for (f in comp_groups[[grp]]){ + group_list[[f]] <- grp + } + } + out_stats <- attr(stats, "names") + if ("counts" %in% out_stats){ + gp_counts <- as.matrix(groupRes$counts) + tpc <- matrix("", nrow=nb_files, ncol=2) + tpc[,1] <- as.character(lapply(rownames(gp_counts), function(x) comp_files[[x]])) + tpc[,2] <- as.character(lapply(rownames(gp_counts), function(x) group_list[[x]])) + gp_counts <- cbind(tpc, gp_counts) + colnames(gp_counts)[[1]] <- "Filename" + colnames(gp_counts)[[2]] <- "Group" + t_gp_counts <- t(gp_counts) + write.table(t_gp_counts, file=stats[["counts"]], quote=F, row.names=T, col.names=F, sep='\t', + append=F) + } + if ("pctgs" %in% out_stats){ + gp_prop <- as.matrix(groupRes$pctgs) + tpp <- matrix("", nrow=nb_files, ncol=2) + tpp[,1] <- as.character(lapply(rownames(gp_prop), function(x) comp_files[[x]])) + tpp[,2] <- as.character(lapply(rownames(gp_prop), function(x) group_list[[x]])) + gp_prop <- cbind(tpp, gp_prop) + colnames(gp_prop)[[1]] <- "Filename" + colnames(gp_prop)[[2]] <- "Group" + t_gp_prop <- t(gp_prop) + write.table(t_gp_prop, file=stats[["pctgs"]], quote=F, row.names=T, col.names=F, sep='\t', + append=F) + } + if ("means" %in% out_stats){ + gp_mean <- as.matrix(groupRes$means) + t_gp_mean <- t(gp_mean) + tpm <- matrix(0, nrow=nb_nodes, ncol=1) + tpm[,1] <- seq_len(nb_nodes) + t_gp_mean <- cbind(tpm, t_gp_mean) + colnames(t_gp_mean)[[1]] <- "Nodes" + write.table(t_gp_mean, file=stats[["means"]], quote=F, row.names=F, col.names=T, sep='\t', + append=F) + } + if ("medians" %in% out_stats){ + gp_med <- as.matrix(groupRes$medians) + t_gp_med <- t(gp_med) + tpd <- matrix(0, nrow=nb_nodes, ncol=1) + tpd[,1] <- seq_len(nb_nodes) + t_gp_med <- cbind(tpd, t_gp_med) + colnames(t_gp_med)[[1]] <- "Nodes" + write.table(t_gp_med, file=stats[["medians"]], quote=F, row.names=F, col.names=T, sep='\t', + append=F) + } +} + +checkFCS <- function(tree, output="", plot="", thresh = 0.05, stats, groups, + filenames) { + + fcsfiles <- unlist(groups) + tree_valid <- F + markerCheck <- T + tryCatch({ + fsomtree <- readRDS(tree) + tree_valid <- T + }, error = function(ex) { + print(paste(ex)) + }) + + fst <- if (length(fsomtree)==2) fsomtree[[1]] else fsomtree + + if (tree_valid){ + tree_markers <- as.vector(fst$prettyColnames) + tree_channels <- as.vector(colnames(fst$data)) + if (length(tree_markers) < 1){ + quit(save = "no", status = 11, runLast = FALSE) + } + } else { + quit(save = "no", status = 11, runLast = FALSE) + } + + for (i in 1:length(fcsfiles)){ + is_file_valid <- F + tryCatch({ + fcs <- read.FCS(fcsfiles[i], transformation=FALSE) + is_file_valid <- T + }, error = function(ex) { + print(paste(ex)) + }) + if (i == 1) { + m1 <- as.vector(pData(parameters(fcs))$desc) + c1 <- colnames(fcs) + # compare to tree markers + pm <- prettyMarkerNames(fcs) + if (!all(tree_markers %in% pm)){ + quit(save = "no", status = 13, runLast = FALSE) + } + } else { + m2 <- as.vector(pData(parameters(fcs))$desc) + c2 <- colnames(fcs) + markerCheck <- compareLists(m1,m2) + markerChannel <- compareLists(c1,c2) + } + } + if (markerCheck && markerChannel) { + compareToTree(fst, thresh, output, plot, stats, groups, filenames) + } else { + quit(save = "no", status = 12, runLast = FALSE) + } +} + +args <- commandArgs(trailingOnly = TRUE) + +first_g1 <- 5 +tot_args <- length(args) +g <- list() +tmplist <- c("counts", "means", "medians", "pctgs") + +for (i in 5:13){ + if (args[i] %in% tmplist){ + first_g1 <- first_g1 + 2 + g[[args[i]]] <- args[i+1] + } +} + +tmpargs <- paste(args[first_g1:tot_args], collapse="=%=") +tmpgroups <- strsplit(tmpargs, "=%=DONE=%=") + +groups <- list() +filenames <- list() +for (gps in tmpgroups[[1]]) { + tmpgroup <- strsplit(gps, "=%=") + nb_files <- (length(tmpgroup[[1]]) - 1 ) /2 + tmplist <- character(nb_files) + tmpnames <- character(nb_files) + j <- 1 + for (i in 2:length(tmpgroup[[1]])){ + if (!i%%2){ + tmplist[[j]] <- tmpgroup[[1]][i] + tmpnames[[j]]<- tmpgroup[[1]][i+1] + j <- j + 1 + } + } + groups[[tmpgroup[[1]][1]]] <- tmplist + filenames[[tmpgroup[[1]][1]]] <- tmpnames +} + +checkFiles(groups) +checkFCS(args[1], args[2], args[3], args[4], g, groups, filenames) diff -r 000000000000 -r bd35f3b66a1e FlowSOMCompare.xml --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/FlowSOMCompare.xml Mon Jun 22 17:54:03 2020 -0400 @@ -0,0 +1,195 @@ + + using a FlowSOM tree + + bioconductor-flowsom + + + + + + + + + + + + + + + + + + + + + + + + + + + (count) + + + (med) + + + (mean) + + + (prctg) + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + 10.1002/cyto.a.22625 + + diff -r 000000000000 -r bd35f3b66a1e test-data/count.tabular --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/count.tabular Mon Jun 22 17:54:03 2020 -0400 @@ -0,0 +1,102 @@ +Filename input1.fcs input3.fcs input2.fcs +Group Group 1 Group 2 Group 2 +1 620 1311 937 +2 674 790 795 +3 492 474 753 +4 49 179 79 +5 231 199 51 +6 528 402 39 +7 523 490 58 +8 465 528 93 +9 278 481 90 +10 206 402 53 +11 571 876 539 +12 952 555 539 +13 721 876 997 +14 731 192 248 +15 119 120 60 +16 88 1 78 +17 51 2 137 +18 49 6 177 +19 41 3 157 +20 153 392 140 +21 567 553 487 +22 825 497 467 +23 630 579 734 +24 368 195 382 +25 28 1 51 +26 29 1 79 +27 16 2 211 +28 16 0 294 +29 11 0 240 +30 169 158 151 +31 139 235 134 +32 475 246 295 +33 364 194 277 +34 65 58 191 +35 90 21 253 +36 14 0 75 +37 7 1 204 +38 2 0 134 +39 11 0 116 +40 184 20 27 +41 203 207 274 +42 111 183 183 +43 101 87 102 +44 45 107 105 +45 76 49 248 +46 28 17 149 +47 17 10 185 +48 11 1 157 +49 20 0 4 +50 202 2 2 +51 207 258 234 +52 202 212 246 +53 131 37 95 +54 255 142 192 +55 36 13 44 +56 18 13 78 +57 41 43 93 +58 98 0 4 +59 154 1 1 +60 687 8 4 +61 168 244 173 +62 85 252 202 +63 60 14 39 +64 45 16 80 +65 11 6 196 +66 3 9 271 +67 27 4 5 +68 111 1 3 +69 156 0 1 +70 528 4 0 +71 56 421 337 +72 23 417 347 +73 59 13 53 +74 15 1 62 +75 10 3 136 +76 1 1 294 +77 24 3 4 +78 442 1 1 +79 526 0 0 +80 788 1 2 +81 7 470 338 +82 0 302 228 +83 4 475 350 +84 4 471 387 +85 3 604 438 +86 0 382 287 +87 16 1 8 +88 205 1 0 +89 598 1 1 +90 712 0 0 +91 2 314 247 +92 0 381 312 +93 3 480 391 +94 5 612 465 +95 1 535 425 +96 0 624 414 +97 2 504 281 +98 122 0 0 +99 473 1 0 +100 510 1 0 diff -r 000000000000 -r bd35f3b66a1e test-data/input1.fcs Binary file test-data/input1.fcs has changed diff -r 000000000000 -r bd35f3b66a1e test-data/input2.fcs Binary file test-data/input2.fcs has changed diff -r 000000000000 -r bd35f3b66a1e test-data/input3.fcs Binary file test-data/input3.fcs has changed diff -r 000000000000 -r bd35f3b66a1e test-data/mean.tabular --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/mean.tabular Mon Jun 22 17:54:03 2020 -0400 @@ -0,0 +1,101 @@ +Nodes Group 1 Group 2 +1 0.031 0.0562 +2 0.0337 0.039625 +3 0.0246 0.030675 +4 0.00245 0.00645 +5 0.01155 0.00625 +6 0.0264 0.011025 +7 0.02615 0.0137 +8 0.02325 0.015525 +9 0.0139 0.014275 +10 0.0103 0.011375 +11 0.02855 0.035375 +12 0.0476 0.02735 +13 0.03605 0.046825 +14 0.03655 0.011 +15 0.00595 0.0045 +16 0.0044 0.001975 +17 0.00255 0.003475 +18 0.00245 0.004575 +19 0.00205 0.004 +20 0.00765 0.0133 +21 0.02835 0.026 +22 0.04125 0.0241 +23 0.0315 0.032825 +24 0.0184 0.014425 +25 0.0014 0.0013 +26 0.00145 0.002 +27 8e-04 0.005325 +28 8e-04 0.00735 +29 0.00055 0.006 +30 0.00845 0.007725 +31 0.00695 0.009225 +32 0.02375 0.013525 +33 0.0182 0.011775 +34 0.00325 0.006225 +35 0.0045 0.00685 +36 7e-04 0.001875 +37 0.00035 0.005125 +38 1e-04 0.00335 +39 0.00055 0.0029 +40 0.0092 0.001175 +41 0.01015 0.012025 +42 0.00555 0.00915 +43 0.00505 0.004725 +44 0.00225 0.0053 +45 0.0038 0.007425 +46 0.0014 0.00415 +47 0.00085 0.004875 +48 0.00055 0.00395 +49 0.001 1e-04 +50 0.0101 1e-04 +51 0.01035 0.0123 +52 0.0101 0.01145 +53 0.00655 0.0033 +54 0.01275 0.00835 +55 0.0018 0.001425 +56 9e-04 0.002275 +57 0.00205 0.0034 +58 0.0049 1e-04 +59 0.0077 5e-05 +60 0.03435 3e-04 +61 0.0084 0.010425 +62 0.00425 0.01135 +63 0.003 0.001325 +64 0.00225 0.0024 +65 0.00055 0.00505 +66 0.00015 0.007 +67 0.00135 0.000225 +68 0.00555 1e-04 +69 0.0078 2.5e-05 +70 0.0264 1e-04 +71 0.0028 0.01895 +72 0.00115 0.0191 +73 0.00295 0.00165 +74 0.00075 0.001575 +75 5e-04 0.003475 +76 5e-05 0.007375 +77 0.0012 0.000175 +78 0.0221 5e-05 +79 0.0263 1e-20 +80 0.0394 7.5e-05 +81 0.00035 0.0202 +82 1e-20 0.01325 +83 2e-04 0.020625 +84 2e-04 0.02145 +85 0.00015 0.02605 +86 1e-20 0.016725 +87 8e-04 0.000225 +88 0.01025 2.5e-05 +89 0.0299 5e-05 +90 0.0356 1e-20 +91 1e-04 0.014025 +92 1e-20 0.017325 +93 0.00015 0.021775 +94 0.00025 0.026925 +95 5e-05 0.024 +96 1e-20 0.02595 +97 1e-04 0.019625 +98 0.0061 1e-20 +99 0.02365 2.5e-05 +100 0.0255 2.5e-05 diff -r 000000000000 -r bd35f3b66a1e test-data/median.tabular --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/median.tabular Mon Jun 22 17:54:03 2020 -0400 @@ -0,0 +1,101 @@ +Nodes Group 1 Group 2 +1 0.031 0.0562 +2 0.0337 0.039625 +3 0.0246 0.030675 +4 0.00245 0.00645 +5 0.01155 0.00625 +6 0.0264 0.011025 +7 0.02615 0.0137 +8 0.02325 0.015525 +9 0.0139 0.014275 +10 0.0103 0.011375 +11 0.02855 0.035375 +12 0.0476 0.02735 +13 0.03605 0.046825 +14 0.03655 0.011 +15 0.00595 0.0045 +16 0.0044 0.001975 +17 0.00255 0.003475 +18 0.00245 0.004575 +19 0.00205 0.004 +20 0.00765 0.0133 +21 0.02835 0.026 +22 0.04125 0.0241 +23 0.0315 0.032825 +24 0.0184 0.014425 +25 0.0014 0.0013 +26 0.00145 0.002 +27 8e-04 0.005325 +28 8e-04 0.00735 +29 0.00055 0.006 +30 0.00845 0.007725 +31 0.00695 0.009225 +32 0.02375 0.013525 +33 0.0182 0.011775 +34 0.00325 0.006225 +35 0.0045 0.00685 +36 7e-04 0.001875 +37 0.00035 0.005125 +38 1e-04 0.00335 +39 0.00055 0.0029 +40 0.0092 0.001175 +41 0.01015 0.012025 +42 0.00555 0.00915 +43 0.00505 0.004725 +44 0.00225 0.0053 +45 0.0038 0.007425 +46 0.0014 0.00415 +47 0.00085 0.004875 +48 0.00055 0.00395 +49 0.001 1e-04 +50 0.0101 1e-04 +51 0.01035 0.0123 +52 0.0101 0.01145 +53 0.00655 0.0033 +54 0.01275 0.00835 +55 0.0018 0.001425 +56 9e-04 0.002275 +57 0.00205 0.0034 +58 0.0049 1e-04 +59 0.0077 5e-05 +60 0.03435 3e-04 +61 0.0084 0.010425 +62 0.00425 0.01135 +63 0.003 0.001325 +64 0.00225 0.0024 +65 0.00055 0.00505 +66 0.00015 0.007 +67 0.00135 0.000225 +68 0.00555 1e-04 +69 0.0078 2.5e-05 +70 0.0264 1e-04 +71 0.0028 0.01895 +72 0.00115 0.0191 +73 0.00295 0.00165 +74 0.00075 0.001575 +75 5e-04 0.003475 +76 5e-05 0.007375 +77 0.0012 0.000175 +78 0.0221 5e-05 +79 0.0263 1e-20 +80 0.0394 7.5e-05 +81 0.00035 0.0202 +82 1e-20 0.01325 +83 2e-04 0.020625 +84 2e-04 0.02145 +85 0.00015 0.02605 +86 1e-20 0.016725 +87 8e-04 0.000225 +88 0.01025 2.5e-05 +89 0.0299 5e-05 +90 0.0356 1e-20 +91 1e-04 0.014025 +92 1e-20 0.017325 +93 0.00015 0.021775 +94 0.00025 0.026925 +95 5e-05 0.024 +96 1e-20 0.02595 +97 1e-04 0.019625 +98 0.0061 1e-20 +99 0.02365 2.5e-05 +100 0.0255 2.5e-05 diff -r 000000000000 -r bd35f3b66a1e test-data/out1.pdf Binary file test-data/out1.pdf has changed diff -r 000000000000 -r bd35f3b66a1e test-data/out1.tabular --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/out1.tabular Mon Jun 22 17:54:03 2020 -0400 @@ -0,0 +1,101 @@ +Node Group 1-Group 2 +1 -- +2 -- +3 -- +4 -- +5 -- +6 -- +7 -- +8 -- +9 -- +10 -- +11 -- +12 -- +13 -- +14 -- +15 -- +16 -- +17 -- +18 -- +19 -- +20 -- +21 -- +22 -- +23 -- +24 -- +25 -- +26 -- +27 -- +28 -- +29 -- +30 -- +31 -- +32 -- +33 -- +34 -- +35 -- +36 -- +37 -- +38 -- +39 -- +40 -- +41 -- +42 -- +43 -- +44 -- +45 -- +46 -- +47 -- +48 -- +49 -- +50 -- +51 -- +52 -- +53 -- +54 -- +55 -- +56 -- +57 -- +58 -- +59 -- +60 -- +61 -- +62 -- +63 -- +64 -- +65 -- +66 -- +67 -- +68 -- +69 -- +70 -- +71 -- +72 -- +73 -- +74 -- +75 -- +76 -- +77 -- +78 -- +79 -- +80 -- +81 -- +82 -- +83 -- +84 -- +85 -- +86 -- +87 -- +88 -- +89 -- +90 -- +91 -- +92 -- +93 -- +94 -- +95 -- +96 -- +97 -- +98 -- +99 -- +100 -- diff -r 000000000000 -r bd35f3b66a1e test-data/out2.pdf Binary file test-data/out2.pdf has changed diff -r 000000000000 -r bd35f3b66a1e test-data/out2.tabular --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/out2.tabular Mon Jun 22 17:54:03 2020 -0400 @@ -0,0 +1,101 @@ +Node Group 1-Group 2 +1 -- +2 -- +3 -- +4 -- +5 -- +6 -- +7 -- +8 -- +9 -- +10 -- +11 -- +12 -- +13 -- +14 -- +15 -- +16 -- +17 -- +18 -- +19 -- +20 -- +21 -- +22 -- +23 -- +24 -- +25 -- +26 -- +27 -- +28 -- +29 -- +30 -- +31 -- +32 -- +33 -- +34 -- +35 -- +36 -- +37 -- +38 -- +39 -- +40 -- +41 -- +42 -- +43 -- +44 -- +45 -- +46 -- +47 -- +48 -- +49 -- +50 -- +51 -- +52 -- +53 -- +54 -- +55 -- +56 -- +57 -- +58 -- +59 -- +60 -- +61 -- +62 -- +63 -- +64 -- +65 -- +66 -- +67 -- +68 -- +69 -- +70 -- +71 -- +72 -- +73 -- +74 -- +75 -- +76 -- +77 -- +78 -- +79 -- +80 -- +81 -- +82 -- +83 -- +84 -- +85 -- +86 -- +87 -- +88 -- +89 -- +90 -- +91 -- +92 -- +93 -- +94 -- +95 -- +96 -- +97 -- +98 -- +99 -- +100 -- diff -r 000000000000 -r bd35f3b66a1e test-data/prop.tabular --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/prop.tabular Mon Jun 22 17:54:03 2020 -0400 @@ -0,0 +1,102 @@ +Filename input1.fcs input3.fcs input2.fcs +Group Group 1 Group 2 Group 2 +1 0.031 0.06555 0.04685 +2 0.0337 0.0395 0.03975 +3 0.0246 0.0237 0.03765 +4 0.00245 0.00895 0.00395 +5 0.01155 0.00995 0.00255 +6 0.0264 0.0201 0.00195 +7 0.02615 0.0245 0.0029 +8 0.02325 0.0264 0.00465 +9 0.0139 0.02405 0.0045 +10 0.0103 0.0201 0.00265 +11 0.02855 0.0438 0.02695 +12 0.0476 0.02775 0.02695 +13 0.03605 0.0438 0.04985 +14 0.03655 0.0096 0.0124 +15 0.00595 0.006 0.003 +16 0.0044 5e-05 0.0039 +17 0.00255 1e-04 0.00685 +18 0.00245 3e-04 0.00885 +19 0.00205 0.00015 0.00785 +20 0.00765 0.0196 0.007 +21 0.02835 0.02765 0.02435 +22 0.04125 0.02485 0.02335 +23 0.0315 0.02895 0.0367 +24 0.0184 0.00975 0.0191 +25 0.0014 5e-05 0.00255 +26 0.00145 5e-05 0.00395 +27 8e-04 1e-04 0.01055 +28 8e-04 0 0.0147 +29 0.00055 0 0.012 +30 0.00845 0.0079 0.00755 +31 0.00695 0.01175 0.0067 +32 0.02375 0.0123 0.01475 +33 0.0182 0.0097 0.01385 +34 0.00325 0.0029 0.00955 +35 0.0045 0.00105 0.01265 +36 7e-04 0 0.00375 +37 0.00035 5e-05 0.0102 +38 1e-04 0 0.0067 +39 0.00055 0 0.0058 +40 0.0092 0.001 0.00135 +41 0.01015 0.01035 0.0137 +42 0.00555 0.00915 0.00915 +43 0.00505 0.00435 0.0051 +44 0.00225 0.00535 0.00525 +45 0.0038 0.00245 0.0124 +46 0.0014 0.00085 0.00745 +47 0.00085 5e-04 0.00925 +48 0.00055 5e-05 0.00785 +49 0.001 0 2e-04 +50 0.0101 1e-04 1e-04 +51 0.01035 0.0129 0.0117 +52 0.0101 0.0106 0.0123 +53 0.00655 0.00185 0.00475 +54 0.01275 0.0071 0.0096 +55 0.0018 0.00065 0.0022 +56 9e-04 0.00065 0.0039 +57 0.00205 0.00215 0.00465 +58 0.0049 0 2e-04 +59 0.0077 5e-05 5e-05 +60 0.03435 4e-04 2e-04 +61 0.0084 0.0122 0.00865 +62 0.00425 0.0126 0.0101 +63 0.003 7e-04 0.00195 +64 0.00225 8e-04 0.004 +65 0.00055 3e-04 0.0098 +66 0.00015 0.00045 0.01355 +67 0.00135 2e-04 0.00025 +68 0.00555 5e-05 0.00015 +69 0.0078 0 5e-05 +70 0.0264 2e-04 0 +71 0.0028 0.02105 0.01685 +72 0.00115 0.02085 0.01735 +73 0.00295 0.00065 0.00265 +74 0.00075 5e-05 0.0031 +75 5e-04 0.00015 0.0068 +76 5e-05 5e-05 0.0147 +77 0.0012 0.00015 2e-04 +78 0.0221 5e-05 5e-05 +79 0.0263 0 0 +80 0.0394 5e-05 1e-04 +81 0.00035 0.0235 0.0169 +82 0 0.0151 0.0114 +83 2e-04 0.02375 0.0175 +84 2e-04 0.02355 0.01935 +85 0.00015 0.0302 0.0219 +86 0 0.0191 0.01435 +87 8e-04 5e-05 4e-04 +88 0.01025 5e-05 0 +89 0.0299 5e-05 5e-05 +90 0.0356 0 0 +91 1e-04 0.0157 0.01235 +92 0 0.01905 0.0156 +93 0.00015 0.024 0.01955 +94 0.00025 0.0306 0.02325 +95 5e-05 0.02675 0.02125 +96 0 0.0312 0.0207 +97 1e-04 0.0252 0.01405 +98 0.0061 0 0 +99 0.02365 5e-05 0 +100 0.0255 5e-05 0 diff -r 000000000000 -r bd35f3b66a1e test-data/reftree.fsom Binary file test-data/reftree.fsom has changed