Skip to content

Commit

Permalink
Remove 'update_ylim' attribute from actions
Browse files Browse the repository at this point in the history
The 'ylim' belongs to the panel, not each individual action. The panel
constructor's 'use_fixed_ylim' argument determines whether or not the
panel 'ylim' can be modified by an action.

This changes how 'ylim' is determined when a new panel is added to a
plot. Previously, the 'ylim' for the new panel was calculated as the
range of the data provided when the panel was created, and the 'ylim'
for the new panel was always fixed. Adding more series to an existing
panel would not update the panel 'ylim' value, so added series values
outside the initial 'ylim' would not appear on the panel.
  • Loading branch information
joshuaulrich committed Oct 19, 2023
1 parent 26b604a commit 5fe3202
Showing 1 changed file with 9 additions and 12 deletions.
21 changes: 9 additions & 12 deletions R/plot.R
Original file line number Diff line number Diff line change
Expand Up @@ -462,7 +462,7 @@ plot.xts <- function(x,
use_log_yaxis = log)

# plot data
this_panel$add_action(exp, env = lenv, update_ylim = TRUE)
this_panel$add_action(exp, env = lenv)
}
} else {
if(type == "h" && NCOL(x) > 1)
Expand Down Expand Up @@ -620,7 +620,7 @@ addSeries <- function(x, main="", on=NA, type="l", col=NULL, lty=1, lwd=1, pch=1
use_log_yaxis = use_log)

# plot data
this_panel$add_action(exp, env = lenv, update_ylim = FALSE)
this_panel$add_action(exp, env = lenv)

} else {
for(i in on) {
Expand Down Expand Up @@ -719,7 +719,7 @@ addEventLines <- function(events, main="", on=0, lty=1, lwd=1, col=1, ...){
header = main)

# plot data
this_panel$add_action(exp, env = lenv, update_ylim = FALSE)
this_panel$add_action(exp, env = lenv)

} else {
for(i in on) {
Expand Down Expand Up @@ -793,7 +793,7 @@ addLegend <- function(legend.loc="topright", legend.names=NULL, col=NULL, ncol=1
header = "")

# legend data
this_panel$add_action(exp, env = lenv, update_ylim = FALSE)
this_panel$add_action(exp, env = lenv)

} else {
for(i in on) {
Expand Down Expand Up @@ -897,7 +897,7 @@ addPolygon <- function(x, y=NULL, main="", on=NA, col=NULL, ...){
header = main)

# plot data
this_panel$add_action(exp, env = lenv, update_ylim = FALSE)
this_panel$add_action(exp, env = lenv)

} else {
for(i in on) {
Expand Down Expand Up @@ -1166,15 +1166,13 @@ new.replot_xts <- function(panel=1,asp=1,xlim=c(1,10),ylim=list(structure(c(1,10
function(expr,
env = Env,
clip = TRUE,
update_ylim = TRUE,
...)
{
if (!is.expression(expr)) {
expr <- as.expression(expr)
}

action <- structure(expr, clip = clip, env = env,
update_ylim = update_ylim, ...)
action <- structure(expr, clip = clip, env = env, ...)
panel$actions <- append(panel$actions, list(action))

Env$last_action_panel_id <<- panel$id
Expand Down Expand Up @@ -1257,11 +1255,11 @@ new.replot_xts <- function(panel=1,asp=1,xlim=c(1,10),ylim=list(structure(c(1,10
# draw y-axis label
title(ylab = ylab[1], mgp = c(1, 1, 0))
})
panel$add_action(yaxis_expr, env = panel, update_ylim = FALSE)
panel$add_action(yaxis_expr, env = panel)

# x-axis grid
xaxis_action <- expression(x_grid_lines(xdata, grid.ticks.on, par("usr")[3:4]))
panel$add_action(xaxis_action, env = panel, update_ylim = FALSE)
panel$add_action(xaxis_action, env = panel)

# append the new panel to the panel list
Env$panels <- append(Env$panels, list(panel))
Expand All @@ -1285,11 +1283,10 @@ new.replot_xts <- function(panel=1,asp=1,xlim=c(1,10),ylim=list(structure(c(1,10
# calculate a new ylim based on all the panel's data
for (action in panel$actions) {

action_update_ylim <- attr(action, "update_ylim")
action_env <- attr(action, "env")
action_data <- action_env$xdata

if (!is.null(action_data) && action_update_ylim) {
if (!is.null(action_data)) {
# some actions (e.g. addLegend) do not have 'xdata'
dat.range <- create_ylim(action_data[Env$xsubset])

Expand Down

0 comments on commit 5fe3202

Please sign in to comment.