Skip to content

Commit

Permalink
#73: Rework options for stat_position and re-doc
Browse files Browse the repository at this point in the history
  • Loading branch information
jacobpwagner committed Oct 29, 2020
1 parent 0cdb186 commit f0a4d42
Show file tree
Hide file tree
Showing 15 changed files with 144 additions and 58 deletions.
3 changes: 2 additions & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -66,4 +66,5 @@ Collate:
'stat_position.R'
'transform_gate.R'
'utility.R'
RoxygenNote: 7.1.0
RoxygenNote: 7.1.1
Roxygen: list(markdown=TRUE)
14 changes: 7 additions & 7 deletions R/geom_stats.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,13 +7,12 @@
#' @param gate a 'filterList` or character (represent as a population node in GatingSet)
#' if not supplied, ggcyto then tries to parse the gate from the first geom_gate layer.
#' @param negated whether the gate needs to be negated
#' @param adjust adjust the position of the centroid. from 0 to 1.
#' @param abs If TRUE, the centroid will be calculated based on the full data range rather than
#' the particular gate. This allows the adjust parameter to start from the center of the plot as opposed
#' to the center of the gate.
#' @param adjust see details for \code{\link{stat_position}}
#' @param location see details for \code{\link{stat_position}}
#' @param label.padding,label.size arguments passed to geom_label layer
#' @param digits control the stats format
#' @param ... other arguments passed to geom_label layer
#' @param ... other arguments passed to geom_label layer
#'
#' @inheritParams compute_stats
#' @export
#' @return a geom_popStats layer
Expand All @@ -30,11 +29,12 @@
#' # display gate name and percent
#' p + geom_gate(c("CD4", "CD8")) + geom_stats(type = c("gate_name", "percent"))
geom_stats <- function(gate = NULL, ..., value = NULL, type = "percent", negated = FALSE, adjust = 0.5
, abs = FALSE, label.padding = unit(0.05, "lines"), label.size = 0, digits = 3){
, location = "gate", label.padding = unit(0.05, "lines"), label.size = 0, digits = 3){
type <- unlist(lapply(type, function(stat_type)match.arg(stat_type, c("percent", "count", "gate_name"))))
location <- unlist(lapply(location, function(location_type)match.arg(location_type, c("gate", "data", "plot", "fixed"))))

structure(
list(gate = gate, value = value, type = type, negated = negated, adjust = adjust, abs = abs, digits = digits
list(gate = gate, value = value, type = type, negated = negated, adjust = adjust, location = location, digits = digits
, geom_label_params = list(label.padding = label.padding
, label.size = label.size
, ...
Expand Down
12 changes: 7 additions & 5 deletions R/ggcyto.R
Original file line number Diff line number Diff line change
Expand Up @@ -365,7 +365,7 @@ as.ggplot <- function(x, pre_binning = FALSE){

negated <- e2[["negated"]]
adjust <- e2[["adjust"]]
abs <- e2[["abs"]]
location <- e2[["location"]]
digits <- e2[["digits"]]
if(length(trans)>0)
{
Expand All @@ -381,10 +381,12 @@ as.ggplot <- function(x, pre_binning = FALSE){
if(length(trans)>0)
gate <- transform(gate, translist)

# Honor manual choice of abs == TRUE
if(!abs){
# Honor manual choice of location == "data", "plot", or "fixed"
if(location == "gate"){
#TODO: compute the actual data range from population data
abs <- is(gate[[1]], "booleanFilter")#bypass stats_postion computing by set abs to true to use data_range as gate_range(as a hack for now)
if(is(gate[[1]], "booleanFilter"))
#bypass stats_postion computing to use data_range as gate_range(as a hack for now)
location <- "data"
}

stats <- compute_stats(fs, gate
Expand All @@ -395,7 +397,7 @@ as.ggplot <- function(x, pre_binning = FALSE){
, negated = negated
, adjust = adjust
, digits = digits
, abs = abs)
, location = location)

#restore the stats dimensions to raw scale
if(length(trans)>0)
Expand Down
4 changes: 2 additions & 2 deletions R/ggcyto_GatingSet.R
Original file line number Diff line number Diff line change
Expand Up @@ -109,7 +109,7 @@ add_ggcyto_gs <- function(e1, e2){

}else if(is(e2, "GeomStats")){
adjust <- e2[["adjust"]]
abs <- e2[["abs"]]
location <- e2[["location"]]

#grab the nodes info from previous gate layers
nodes.geom_gate <- e1[["nodes"]]
Expand Down Expand Up @@ -150,7 +150,7 @@ add_ggcyto_gs <- function(e1, e2){
, type = stat_type
, negated = negated
, adjust = adjust
, abs = abs
, location = location
, digits = digits
)
, e2[["geom_label_params"]]
Expand Down
75 changes: 57 additions & 18 deletions R/stat_position.R
Original file line number Diff line number Diff line change
Expand Up @@ -8,10 +8,44 @@
#' @param negated logical indicating whether position needs to be moved to negative side of gate
#' @param limits used to fix the gate range
#' @param ... other arguments
#' @param adjust adjust the position of the centroid. This can be a length-2 vector with an adjustment in each dimension.
#' @param abs logical
#' @param adjust see details
#' @param location see details
#' @param data_range a two-row data.frame representing the actual data range. Each column is a a range for a specific channel. First row is min, Second row is max.
#'
#' @details
#' ## Specifying location for statistical annotation
#'
#' The \code{adjust} and \code{location} arguments allow for a few different ways to adjust the location of the statistical
#' annotation for a gate on a \code{ggcyto} plot. The valid values for \code{location} are "gate" (default), "data", "plot", and "fixed".
#'
#' ### Relative location
#'
#' If \code{location} is not "fixed", the starting position of the annotation will be determined with respect to a rectangular window whose
#' bounds are determined in the following way:
#' * For \code{location = "gate"}, the window will be set by the range of the data in the gate
#' * For \code{location = "data"}, the window will be set by the range of values in all of the data on the plot (provided by \code{data_range})
#' * For \code{location = "plot"}, the window will be set by the axis limits of the plot (adjusted by \code{\link{ggcyto_par_set}})
#'
#' This starting position can then be adjusted by passing values in a vector to the \code{adjust} parameter, where they will be
#' interpreted as relative proportions of the window dimension, where 0.0 represents the lower bound of the dimension and 1.0 represents
#' the upper bound. So, for a 2-D plot, \code{adjust=c(0,0)} places the annotation at the lower left corner of this window and \code{adjust=c(1,1)} places
#' it at the upper right corner.
#'
#' As another example, for a 2-D gate, if \code{location = "gate"} and \code{adjust=c(0.25, 0.75)}, the statistical annotation will be
#' placed 1/4 of the way across the x-range of the gate and 3/4 of the way across the y-range of the gate.
#'
#' ### Fixed location
#'
#' If \code{location = "fixed"}, the numeric vector passed to \code{adjust} will be interpreted as values on the data scales of the plot to provide
#' an explicit location for the annotation.
#'
#' For example, if the annotation should be at the location 3000, 5000 on the plot, that could be done with \code{location="fixed"} and
#' \code{adjust = c(3000,5000)}.
#'
#' ### Default
#'
#' The default behavior if no values are provided to \code{location} or \code{adjust} will be to place the annotation at
#' the center of the range of the data in the gate.
#'
#' @return a data.table of gate centroid coordinates
#' @export
#' @examples
Expand Down Expand Up @@ -47,14 +81,12 @@ stat_position <- function(gate, ...)UseMethod("stat_position")

#' @rdname stat_position
#' @export
stat_position.filter <- function(gate, negated = FALSE, adjust = 0.5, abs = FALSE, data_range = NULL, limits = NULL, ...){
stat_position.filter <- function(gate, negated = FALSE, adjust = 0.5, location = "gate", data_range = NULL, limits = NULL, ...){

params <- parameters(gate)
if(abs)#plot label whithin the boundary by default
{
gate_range <- data_range
}else #specify location by absolute position of the current window
{
location <- match.arg(location, c("gate", "data", "plot", "fixed"))

if(location == "gate"){
df <- fortify(gate, data = data_range)
gate_range <- apply(df, 2, range)

Expand Down Expand Up @@ -87,17 +119,24 @@ stat_position <- function(gate, ...)UseMethod("stat_position")
})
}

}else if(location == "data"){
gate_range <- data_range
}else if(location == "plot"){
gate_range <- limits[,params]
}

#calculate centroid
centroids <- colMeans(gate_range)

# adjust the position
# adjust <- rep(adjust, length=2)[1:2]
diffs <- apply(gate_range,2, diff)
not_density <- names(centroids) != "density"
centroids[not_density] <- centroids[not_density] + diffs[not_density] * (adjust - 0.5)

if(location == "fixed"){
centroids <- setNames(adjust, params)
}else{
#calculate centroid
centroids <- colMeans(gate_range)

# adjust the location
# adjust <- rep(adjust, length=2)[1:2]
diffs <- apply(gate_range,2, diff)
not_density <- names(centroids) != "density"
centroids[not_density] <- centroids[not_density] + diffs[not_density] * (adjust - 0.5)
}

as.data.table(t(centroids))

Expand Down
2 changes: 1 addition & 1 deletion man/as.ggplot.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion man/axis_x_inverse_trans.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

8 changes: 4 additions & 4 deletions man/geom_gate.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion man/geom_hvline.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion man/geom_overlay.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

5 changes: 4 additions & 1 deletion man/geom_stats.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

8 changes: 4 additions & 4 deletions man/ggcyto.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion man/ggcyto_add.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

14 changes: 7 additions & 7 deletions man/ggcyto_par_set.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

Loading

0 comments on commit f0a4d42

Please sign in to comment.