R/stat-binhex.R

#' @rdname Stat
#' @format NULL
#' @usage NULL
#' @export
StatBinhex <- ggproto(
  "StatBinhex", Stat,
  default_aes = aes(weight = 1, fill = after_stat(count)),

  required_aes = c("x", "y"),

  compute_group = function(data, scales, binwidth = NULL, bins = 30,
                           na.rm = FALSE) {
    check_installed("hexbin", reason = "for `stat_bin_hex()`.")

    binwidth <- binwidth %||% hex_binwidth(bins, scales)
    wt <- data$weight %||% rep(1L, nrow(data))
    out <- hexBinSummarise(data$x, data$y, wt, binwidth, sum)
    out$density <- as.vector(out$value / sum(out$value, na.rm = TRUE))
    out$ndensity <- out$density / max(out$density, na.rm = TRUE)
    out$count <- out$value
    out$ncount <- out$count / max(out$count, na.rm = TRUE)
    out$value <- NULL

    out
  },

  # weight is no longer available after transformation
  dropped_aes = "weight"
)

#' @export
#' @rdname geom_hex
#' @inheritParams stat_bin_2d
#' @eval rd_computed_vars(
#'   count    = "number of points in bin.",
#'   density  = "density of points in bin, scaled to integrate to 1.",
#'   ncount   = "count, scaled to maximum of 1.",
#'   ndensity = "density, scaled to maximum of 1."
#' )
#' @section Controlling binning parameters for the x and y directions:
#' The arguments `bins` and `binwidth` can
#' be set separately for the x and y directions. When given as a scalar, one
#' value applies to both directions. When given as a vector of length two,
#' the first is applied to the x direction and the second to the y direction.
#' Alternatively, these can be a named list containing `x` and `y` elements,
#' for example `list(x = 10, y = 20)`.
stat_bin_hex <- make_constructor(StatBinhex, geom = "hex")

#' @export
#' @rdname geom_hex
#' @usage NULL
stat_binhex <- stat_bin_hex

Try the ggplot2 package in your browser

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

ggplot2 documentation built on Sept. 11, 2025, 9:10 a.m.