Skip to content

Commit

Permalink
Merge branch 'feature/facet-refresh' into develop
Browse files Browse the repository at this point in the history
  • Loading branch information
hadley committed May 23, 2011
2 parents 393ae7a + a6b74b2 commit ffea2ec
Show file tree
Hide file tree
Showing 94 changed files with 2,736 additions and 1,745 deletions.
13 changes: 9 additions & 4 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -14,12 +14,12 @@ Description: An implementation of the grammar of graphics
data to aesthetic attributes. See the ggplot2 website
for more information, documentation and examples.
Depends:
reshape (>= 0.8.0),
proto
Imports:
plyr (>= 1.0),
digest,
grid,
reshape2,
scales
Suggests:
quantreg,
Expand All @@ -44,15 +44,18 @@ Collate:
'bench.r'
'coord-.r'
'coord-cartesian-.r'
'coord-cartesian-equal.r'
'coord-cartesian-flipped.r'
'coord-fixed.r'
'coord-flip.r'
'coord-map.r'
'coord-munch.r'
'coord-polar.r'
'coord-transform.r'
'facet-.r'
'facet-grid-.r'
'facet-labels.r'
'facet-layout.r'
'facet-locate.r'
'facet-null.r'
'facet-viewports.r'
'facet-wrap.r'
'fortify-lm.r'
Expand Down Expand Up @@ -95,7 +98,6 @@ Collate:
'geom-vline.r'
'ggplot2.r'
'grob-absolute.r'
'grob-grid.r'
'grob-null.r'
'guides-axis.r'
'guides-grid.r'
Expand All @@ -104,6 +106,7 @@ Collate:
'layer.r'
'limits.r'
'matrix.r'
'panel.r'
'plot-build.r'
'plot-construction.r'
'plot-last.r'
Expand Down Expand Up @@ -170,6 +173,8 @@ Collate:
'utilities-matrix.r'
'utilities-position.r'
'utilities-resolution.r'
'utilities-table-template.r'
'utilities-table.r'
'utilities.r'
'xxx-codegen.r'
'xxx-digest.r'
Expand Down
64 changes: 53 additions & 11 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -8,18 +8,62 @@ export(aes_string)
export(aes_all)
export(annotate)
export(benchplot)
export(coord)
export(is.coord)
S3method(coord_render_bg, default)
S3method(coord_render_axis_h, default)
S3method(coord_render_axis_v, default)
export(coord_cartesian)
S3method(is.linear, cartesian)
S3method(coord_distance, cartesian)
S3method(coord_transform, cartesian)
S3method(coord_train, cartesian)
export(coord_fixed, coord_equal)
S3method(coord_aspect, fixed)
export(coord_flip)
S3method(is.linear, flip)
S3method(coord_transform, flip)
S3method(coord_train, flip)
S3method(coord_labels, flip)
export(coord_map)
S3method(coord_transform, map)
S3method(coord_distance, map)
S3method(coord_aspect, map)
S3method(coord_train, map)
S3method(coord_render_bg, map)
S3method(coord_render_axis_h, map)
S3method(coord_render_axis_v, map)
export(coord_polar)
S3method(coord_aspect, polar)
S3method(coord_distance, polar)
S3method(coord_train, polar)
S3method(coord_transform, polar)
S3method(coord_render_axis_v, polar)
S3method(coord_render_axis_h, polar)
S3method(coord_render_bg, polar)
S3method(coord_render_fg, polar)
export(coord_trans)
S3method(coord_distance, trans)
S3method(coord_transform, trans)
S3method(coord_train, trans)
export(facet)
export(is.facet)
export(facet_grid)
S3method(facet_train_layout, grid)
S3method(facet_map_layout, grid)
S3method(facet_render, grid)
export(label_value)
export(label_both)
export(label_parsed)
export(label_bquote)
export(facet_null)
S3method(facet_train_layout, null)
S3method(facet_map_layout, null)
S3method(facet_render, null)
export(facet_wrap)
S3method(facet_train_layout, wrap)
S3method(facet_map_layout, wrap)
S3method(facet_render, wrap)
S3method(fortify, lm)
S3method(fortify, map)
export(map_data)
Expand Down Expand Up @@ -66,21 +110,12 @@ export(geom_smooth)
export(geom_text)
export(geom_tile)
export(geom_vline)
import(plyr, digest, scales, grid)
import(plyr, digest, scales, grid, reshape2)
S3method(grobHeight, absoluteGrob)
S3method(grobWidth, absoluteGrob)
S3method(grobX, absoluteGrob)
S3method(grobY, absoluteGrob)
S3method(grid.draw, absoluteGrob)
S3method(print, grobGrid)
S3method(dim, grobGrid)
S3method(rbind, grobGrid)
S3method(as.list, unit)
S3method(interleave, unit)
S3method(rweave, grobGrid)
S3method(cbind, grobGrid)
S3method(cweave, grobGrid)
S3method(grid.draw, grobGrid)
S3method(widthDetails, zeroGrob)
S3method(heightDetails, zeroGrob)
S3method(grobWidth, zeroGrob)
Expand Down Expand Up @@ -127,17 +162,18 @@ S3method(scale_breaks, continuous)
S3method(scale_breaks, discrete)
S3method(scale_labels, continuous)
S3method(scale_labels, discrete)
S3method(scale_clone, continuous)
export(scale_alpha, scale_alpha_continuous)
export(scale_alpha_discrete)
export(scale_area)
export(scale_colour_brewer, scale_fill_brewer)
export(scale_x_continuous, scale_y_continuous, scale_x_log10, scale_y_log10, scale_x_reverse, scale_y_reverse, scale_x_sqrt, scale_y_sqrt)
S3method(scale_map, position_c)
S3method(scale_clone, position_c)
export(scale_x_date, scale_y_date)
export(scale_x_datetime, scale_y_datetime)
export(scale_x_discrete, scale_y_discrete)
S3method(scale_train, position_d)
S3method(scale_limits, position_d)
S3method(scale_reset, position_d)
S3method(scale_map, position_d)
S3method(scale_dimension, position_d)
Expand All @@ -147,6 +183,7 @@ export(scale_colour_gradientn, scale_fill_gradientn)
export(scale_colour_grey, scale_fill_grey)
export(scale_colour_hue, scale_fill_hue)
export(scale_colour_identity, scale_fill_identity, scale_shape_identity, scale_linetype_identity, scale_alpha_identity, scale_size_identity)
S3method(scale_map, identity)
export(scale_linetype, scale_linetype_continuous, scale_linetype_discrete)
export(scale_colour_manual, scale_fill_manual, scale_shape_manual, scale_linetype_manual, scale_alpha_manual, scale_size_manual)
export(scale_shape, scale_shape_discrete, scale_shape_continuous)
Expand Down Expand Up @@ -197,6 +234,11 @@ S3method(rweave, matrix)
S3method(cweave, list)
S3method(cweave, matrix)
S3method(interleave, list)
S3method(interleave, unit)
S3method(interleave, default)
S3method(print, gtable)
S3method(dim, gtable)
S3method(rbind, gtable)
S3method(cbind, gtable)
export(should_stop)
export(scale_colour_discrete, scale_colour_continuous, scale_fill_discrete, scale_fill_continuous, scale_color_brewer, scale_color_continuous, scale_color_discrete, scale_color_gradient, scale_color_grey, scale_color_hue, scale_color_identity, scale_color_manual, coord_equal)
30 changes: 29 additions & 1 deletion NEWS
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,10 @@ ggplot2 0.9.0 ----------------------------------------------------------------
about the plot computations, such as the range of all the scales, and the
exact data that is plotted.

DOCUMENTATION
* `scale_shape` finally returns an error when you try and use it with a
continuous variable

DEVELOPMENT

* ggplot2 has moved away from the two (!!) homegrown documentation systems
that it previously relied on, and now uses roxygen extensively. The current
Expand All @@ -39,6 +42,11 @@ DOCUMENTATION
load `plyr` (and other packages) if you are using them elsewhere in your
code.

* ggplot2 now has a start on a set of automated tests. As this test suite
expands it will help me ensure that bugs stay fixed, and that old bugs don't
come back in new versions. A test suite also gives me more confidence when
I'm modifying code, which should help with general code quality.

SCALES

* scales have been rewritten to use the new `scales` package, which does a
Expand Down Expand Up @@ -83,6 +91,26 @@ SCALES
scale_colour_discrete <- scale_colour_brewer
p

FACETS

* Converted from proto to S3 objects, and class methods (somewhat) documented
in `facet.r`. This should make it easier to develop new types of facetting
specifications.

* New `facet_null` used when for no facetting. This special case is
implemented more efficiently and results in substantial performance
improvements for un-facetted plots.

* Facetting variables will no longer interfere with aesthetic mappings -
`facet_wrap(~ colour)` will no longer affect the colour of points.

COORDS

* Converted from proto to S3 objects, and class methods (somewhat) documented
in `coord.r`. This should make it easier to develop new types of coordinate
systems.


ggplot2 0.8.9 (2010-12-24) ---------------------------------------------------

A big thanks to Koshke Takahashi, who supplied the majority of improvements in this release!
Expand Down
2 changes: 1 addition & 1 deletion R/aes.r
Original file line number Diff line number Diff line change
Expand Up @@ -126,7 +126,7 @@ aes_all <- function(vars) {
# @param params. user specified values
# @value a data.frame, with all factors converted to character strings
aesdefaults <- function(data, y., params.) {
updated <- updatelist(y., params.)
updated <- modifyList(y., params. %||% list())

cols <- tryapply(defaults(data, updated), function(x) eval(x, data, globalenv()))

Expand Down
2 changes: 1 addition & 1 deletion R/bench.r
Original file line number Diff line number Diff line change
Expand Up @@ -21,4 +21,4 @@ benchplot <- function(x) {
unrowname(data.frame(
step = c("construct", "build", "render", "draw", "TOTAL"),
rbind(times, colSums(times))))
}
}
135 changes: 71 additions & 64 deletions R/coord-.r
Original file line number Diff line number Diff line change
@@ -1,64 +1,71 @@
Coord <- proto(TopLevel, expr={
limits <- list()
class <- function(.) "coord"

muncher <- function(.) FALSE

# Rescaling at coord level should not be clipped: this is what
# makes zooming work
rescale_var <- function(., data, range, clip = FALSE) {
rescale(data, 0:1, range)
}

munch <- function(., data, details, segment_length = 0.01) {
if (!.$muncher()) return(.$transform(data, details))

# Calculate distances using coord distance metric
dist <- .$distance(data$x, data$y, details)
dist[data$group[-1] != data$group[-nrow(data)]] <- NA

# Munch and then transform result
munched <- munch_data(data, dist, segment_length)
.$transform(munched, details)
}

distance <- function(., x, y, details) {
max_dist <- dist_euclidean(details$x.range, details$y.range)
dist_euclidean(x, y) / max_dist
}

compute_aspect <- function(., ranges) {
NULL
}

labels <- function(., scales) {
scales
}

pprint <- function(., newline=TRUE) {
args <- formals(get("new", .))
args <- args[!names(args) %in% c(".", "...")]

cat("coord_", .$objname, ": ", clist(args), sep="")

if (newline) cat("\n")
}

guide_foreground <- function(., scales, theme) {
theme_render(theme, "panel.border")
}
# Html defaults

html_returns <- function(.) {
ps(
"<h2>Returns</h2>\n",
"<p>This function returns a coordinate system object.</p>"
)
}

parameters <- function(.) {
params <- formals(get("new", .))
params[setdiff(names(params), c("."))]
}

})
#' New coordinate system.
#'
#' Internal use only.
#'
#' @param ... object fields
#' @keywords internal
#' @export
coord <- function(..., subclass = c()) {
structure(list(...), class = c(subclass, "coord"))
}

#' Is this object a coordinate system?
#'
#' @export is.coord
#' @keywords internal
is.coord <- function(x) inherits(x, "coord")

distance <- function(., x, y, details) {
max_dist <- dist_euclidean(details$x.range, details$y.range)
dist_euclidean(x, y) / max_dist
}

coord_aspect <- function(coord, ranges)
UseMethod("coord_aspect")
coord_aspect.default <- function(coord, ranges) NULL

coord_labels <- function(coord, scales) UseMethod("coord_labels")
coord_labels.default <- function(coord, scales) scales

coord_render_fg <- function(coord, scales, theme)
UseMethod("coord_render_fg")
coord_render_fg.default <- function(coord, scales, theme)
theme_render(theme, "panel.border")

coord_render_bg <- function(coord, scales, theme)
UseMethod("coord_render_bg")
#' @S3method coord_render_bg default
coord_render_bg.default <- function(coord, details, theme) {
x.major <- unit(details$x.major, "native")
x.minor <- unit(details$x.minor, "native")
y.major <- unit(details$y.major, "native")
y.minor <- unit(details$y.minor, "native")

guide_grid(theme, x.minor, x.major, y.minor, y.major)
}

coord_render_axis_h <- function(coord, scales, theme)
UseMethod("coord_render_axis_h")
#' @S3method coord_render_axis_h default
coord_render_axis_h.default <- function(coord, details, theme) {
guide_axis(details$x.major, details$x.labels, "bottom", theme)
}

coord_render_axis_v <- function(coord, scales, theme)
UseMethod("coord_render_axis_v")
#' @S3method coord_render_axis_v default
coord_render_axis_v.default <- function(coord, details, theme) {
guide_axis(details$y.major, details$y.labels, "left", theme)
}

coord_train <- function(coord, scales)
UseMethod("coord_train")

coord_transform <- function(coord, data, range)
UseMethod("coord_transform")

coord_distance <- function(coord, x, y, details)
UseMethod("coord_distance")

is.linear <- function(coord) UseMethod("is.linear")
is.linear.default <- function(coord) FALSE
Loading

0 comments on commit ffea2ec

Please sign in to comment.