Mercurial > repos > azomics > edit_fcs_markers
comparison editFCSmarkers.R @ 0:02b2412598b6 draft default tip
"planemo upload for repository https://github.com/ImmPortDB/immport-galaxy-tools/tree/master/flowtools/edit_fcs_marker commit 05dd0e3c6e8eff9383d3f755ade2ca8557ebe7e7"
| author | azomics |
|---|---|
| date | Mon, 22 Jun 2020 20:07:30 -0400 |
| parents | |
| children |
comparison
equal
deleted
inserted
replaced
| -1:000000000000 | 0:02b2412598b6 |
|---|---|
| 1 #!/usr/bin/Rscript | |
| 2 # modify channels and marker names in FCS | |
| 3 # | |
| 4 ###################################################################### | |
| 5 # Copyright (c) 2017 Northrop Grumman. | |
| 6 # All rights reserved. | |
| 7 ###################################################################### | |
| 8 # | |
| 9 # Cristel Thomas | |
| 10 # Version 2 - May 2018 | |
| 11 # Modified to take in marker/channel names by name rather than index | |
| 12 # | |
| 13 library(flowCore) | |
| 14 | |
| 15 checkCandM <- function(m_set, channels=vector(), markers=vector()){ | |
| 16 if (m_set[[3]]){ | |
| 17 in_file <- m_set[[1]] %in% channels | |
| 18 } else { | |
| 19 in_file <- m_set[[1]] %in% markers | |
| 20 } | |
| 21 if (sum(in_file)==0) { | |
| 22 warning("Given original columns are either not in the channels or in the markers of the read object. Will fail.") | |
| 23 return(FALSE) | |
| 24 } | |
| 25 return(TRUE) | |
| 26 } | |
| 27 | |
| 28 modifyMarkersFCS <- function(input, output="", report="", flag_fcs=F, | |
| 29 marker_sets=list()) { | |
| 30 | |
| 31 fcs <- read.FCS(input, transformation=F) | |
| 32 original_channels <- colnames(fcs) | |
| 33 original_markers <- as.vector(pData(parameters(fcs))$desc) | |
| 34 nb <- length(original_channels) | |
| 35 ## check if markers are in FCS files | |
| 36 check_markers <- sapply(marker_sets, checkCandM, channels=original_channels, | |
| 37 markers=original_markers) | |
| 38 if (sum(check_markers)==0) { | |
| 39 quit(save = "no", status = 13, runLast = FALSE) | |
| 40 } | |
| 41 | |
| 42 post_channels <- colnames(fcs) | |
| 43 post_markers <- as.vector(pData(parameters(fcs))$desc) | |
| 44 | |
| 45 for (m_set in marker_sets) { | |
| 46 if (m_set[[3]]){ | |
| 47 chan_to_replace <- post_channels %in% m_set[[1]] | |
| 48 for (i in 1:nb){ | |
| 49 if (chan_to_replace[[i]]){ | |
| 50 post_channels[[i]] <- m_set[[2]][[match(post_channels[[i]], m_set[[1]])[1]]] | |
| 51 } | |
| 52 } | |
| 53 } else { | |
| 54 marker_to_replace <- post_markers %in% m_set[[1]] | |
| 55 for (i in 1:nb){ | |
| 56 if (marker_to_replace[[i]]){ | |
| 57 post_markers[[i]] <- m_set[[2]][[match(post_markers[[i]], m_set[[1]])[1]]] | |
| 58 pm <- paste("$P", as.character(i), "S", sep="") | |
| 59 fcs@description[[pm]] <- post_markers[[i]] | |
| 60 } | |
| 61 } | |
| 62 } | |
| 63 } | |
| 64 | |
| 65 colnames(fcs) <- post_channels | |
| 66 pData(parameters(fcs))$desc <- post_markers | |
| 67 | |
| 68 # write report | |
| 69 sink(report) | |
| 70 cat("###########################\n") | |
| 71 cat("## BEFORE RENAMING ##\n") | |
| 72 cat("###########################\nFCS Channels\n") | |
| 73 cat("---------------------------\n") | |
| 74 cat(original_channels,"---------------------------", "FCS Markers","---------------------------",original_markers, sep="\n") | |
| 75 cat("\n###########################\n") | |
| 76 cat("## AFTER RENAMING ##\n") | |
| 77 cat("###########################\nFCS Channels\n") | |
| 78 cat("---------------------------\n") | |
| 79 cat(post_channels,"---------------------------","FCS Markers","---------------------------", post_markers, sep="\n") | |
| 80 sink() | |
| 81 | |
| 82 # output fcs | |
| 83 if (flag_fcs) { | |
| 84 write.FCS(fcs, output) | |
| 85 } else { | |
| 86 saveRDS(fcs, file = output) | |
| 87 } | |
| 88 } | |
| 89 | |
| 90 checkFCS <- function(fcsfile, out_file ="", report="", flag_fcs=FALSE, | |
| 91 marker_sets=list()) { | |
| 92 isValid <- F | |
| 93 tryCatch({ | |
| 94 isValid <- isFCSfile(fcsfile) | |
| 95 }, error = function(ex) { | |
| 96 print(paste(ex)) | |
| 97 }) | |
| 98 | |
| 99 if (isValid) { | |
| 100 modifyMarkersFCS(fcsfile, out_file, report, flag_fcs, marker_sets) | |
| 101 } else { | |
| 102 quit(save = "no", status = 10, runLast = FALSE) | |
| 103 } | |
| 104 } | |
| 105 | |
| 106 ################################################################################ | |
| 107 ################################################################################ | |
| 108 args <- commandArgs(trailingOnly = TRUE) | |
| 109 flag_fcs <- if (args[3]=="FCS") TRUE else FALSE | |
| 110 | |
| 111 items <- args[5:length(args)] | |
| 112 marker_sets <- list() | |
| 113 j <- 1 | |
| 114 for (i in seq(1, length(items), 3)) { | |
| 115 if (items[i]=="None" || items[i]== "" || items[i]== "i.e.:TLR 6, TLR6PE") { | |
| 116 quit(save = "no", status = 11, runLast = FALSE) | |
| 117 } | |
| 118 if (items[i+1]=="None" || items[i+1]=="" || items[i+1]=="i.e.:TLR6") { | |
| 119 quit(save = "no", status = 12, runLast = FALSE) | |
| 120 } | |
| 121 | |
| 122 old_names <- strsplit(items[i], ",")[[1]] | |
| 123 to_replace <- sapply(old_names, trimws) | |
| 124 replacement <- sapply(strsplit(items[i+1], ",")[[1]], trimws) | |
| 125 flag_channel <- if (items[i+2]=="C") TRUE else FALSE | |
| 126 m_set <- list(to_replace, replacement, flag_channel) | |
| 127 marker_sets[[j]] <- m_set | |
| 128 j <- j + 1 | |
| 129 } | |
| 130 | |
| 131 checkFCS(args[1], args[2], args[4], flag_fcs, marker_sets) |
