R/calc_coordinates.R

#' Calculate Array Coordinates
#' 
#' Calculates coordinates of points on plot to represent a digital PCR array.
#' 
#' @param array A single array, as generated by \code{\link{adpcr2panel}}.
#' @param half If \code{left} or \code{right}, every well is represented only
#' by the adequate half of the rectangle.
#' @return Returns two sets of coordinates of each microfluidic well:
#' \code{coords} is a list of coordinates suitable for usage with functions from
#' \code{\link{graphics}} package. The second element is a data frame of coordinates 
#' useful for users utilizing ggplot2 package.
#' @export
#' @author Michal Burdukiewicz, Stefan Roediger.
#' @seealso \code{\link{plot_panel}} - plots \code{\linkS4class{adpcr}} data.
#' \code{\link{adpcr2panel}} - converts \code{\linkS4class{adpcr}} object to arrays.
#' @keywords manip
calc_coordinates <- function(array, half) {
  nx_a <- ncol(array) 
  ny_a <- nrow(array)
  
  half <- tolower(half)
  #half value for normal plot data
  half_val <- switch(half,
                     none =  c(0.25, 0.25),
                     left = c(0.25, 0),
                     right = c(0, 0.25))
  #half value for ggplot data
  half_val_ggplot <- switch(half,
                            none =  0,
                            left = -0.25,
                            right = 0.25)
  
  # ggplot_coords <- data.frame(t(do.call(cbind, lapply(1L:nx_a, function(x) 
  #   sapply(ny_a:1L, function(y) 
  #     c(x = x + half_val_ggplot, y = y))))), value = as.vector(array))
  # ggplot_coords[["col"]] <- factor(ggplot_coords[["x"]])
  # levels(ggplot_coords[["col"]]) <- colnames(array)
  # ggplot_coords[["row"]] <- factor(ggplot_coords[["y"]])
  # levels(ggplot_coords[["row"]]) <- rownames(array)
  # if(is.numeric(ggplot_coords[["value"]]))
  #   ggplot_coords[["value"]] <- factor(ggplot_coords[["value"]])
  # 
  # value_order <- order(as.numeric(sub("(", "", sapply(strsplit(levels(ggplot_coords[["value"]]), ","), function(i) 
  #   i[1]), fixed = TRUE)))
  # 
  # ggplot_coords[["value"]] <- factor(ggplot_coords[["value"]], levels = levels(ggplot_coords[["value"]])[value_order])
  
  ggplot_coords <- data.frame(x = as.vector(col(array)),
                              y = as.vector(row(array)),
                              row = factor(as.vector(row(array))), 
                              col = factor(as.vector(col(array))), 
                              value = if(length(unique(as.vector(array))) < 3) { 
                                           as.factor(as.vector(array))
                              } else {
                                as.vector(array)
                              })
  
  coords <- unlist(lapply(1L:nx_a, function(x) 
    lapply(ny_a:1L, function(y) 
      c(xleft = x - half_val[1], ybottom = y - 0.25, xright = x + half_val[2], 
        ytop = y + 0.25))), recursive = FALSE)
  list(coords = coords, ggplot_coords = ggplot_coords)
}

Try the dpcR package in your browser

Any scripts or data that you put into this service are public.

dpcR documentation built on May 2, 2019, 7:04 a.m.