[R] High/low level: Plot 2 time series with different axis (left and ri ght)
SÍ Björn Hauksson
bjorn.hauksson at sedlabanki.is
Wed Mar 24 12:08:44 CET 2004
Sun, 14 Mar 2004, Jan Verbesselt wrote:
> Dear R specialists,
>
> I have two time series in a data.frame and want to plot them in the same
> plot(), with the left axis scaled to time series 1 (-700,0) and the
> right axis scaled to time series 2 (-0.2, 0.4).
>
> plot(timeserie1)
> lines(timeserie2, col=c(2)) => this one should be scaled differently
> with a new axis on the right handside.
>
> How can these be visualised such that the fit is optimal for
> visualisation of the two time series? Which commands can I use?
I have composed a simple R function to do this. See usage example in the function description.
##
## Description: A simple function which plots two time series on one plot where
## the series can have different value intervals over the same time interval.
## Usage: ts.plot.2Axis(xleft, xright)
## Arguments: xleft is the time series for the left vertical axis and xright
## is for the right axis. xleft and xright are defined as time series with
## the 'ts' function in package ts.
## ts.plot function must be available, do library(ts) to ensure this if
## necessary.
## In addition the usual 'ts.plot' and 'plot' parameters can be set
## directly (mar, main, xlab, ylab, lwd) or through gpars as in ts.plot.
## Also parameter digits is the preferred number of decimal digits on right
## axis and ticks is the preferred number of tick marks on right axis.
## Details: The time series for the right vertical axis is scaled with a simple
## rule of thumb scaling.
## The ts.plot function is used to plot the series.
## Value: None.
## Note: When scaling is not acceptable try switching the series parameters.
## If a ylabel is to be set it is here only possible for the left axis.
## See also: 'ts.plot', 'ts', 'legend'.
## Author and date: Hauksson, Bjorn Arnar. March 2004.
## Example:
## First paste this function into the R console or use 'source'.
#library(ts)
#data(UKLungDeaths)
#x <- ldeaths
#y <- fdeaths/mdeaths
#ts.plot.2Axis(x, y)
#legTxt <- c("UK lung deaths", "UK female/male deaths (rhs)")
#legend(1976.5, 3950, legTxt, lty=c(1:2), col=c(1:2), lwd=2, bty="n")
##
ts.plot.2Axis <- function(xleft, xright, digits=1, ticks=5,
mar=(c(4,4,4,4)+0.1), main="",
xlab="", ylab="", lwd=2, gpars=list()) {
# Settings for other parameters than those in the function parameter list
par(mar=mar) # Margins
k <- ncol(as.matrix(xleft)) # Number of time series on left vertical scale
lty <- c(1:(k+1)) # Line types
col <- c(1:(k+1)) # Line colors
# Scale time series on right vertical axis
scale <- (max(xleft)-min(xleft))/(max(xright)-min(xright))
xright2 <- xright*scale
meanScale <- mean(xleft) - mean(xright2)
xright2 <- xright2 + meanScale
# Plot the series
ts.plot(xleft, xright2, lty=lty, col=col, main=main, ylab=ylab, xlab=xlab,
lwd=lwd, gpars=gpars)
# Add the right vertical axis labels
lab <- seq(round(min(xright), digits), round(max(xright), digits),
length=ticks)
labAt <- seq(min(xright2), max(xright2), length=ticks)
axis(side=4, labels=lab, at=labAt)
}
Comments and suggestions for this function would be helpful. A text file with the function is available at my website, http://www.bjornarnar.net/hugbunadur/R/ts.plot.2Axis.R
Best regards,
Bjorn Arnar Hauksson
bjorn.hauksson at sedlabanki.is
http://www.bjornarnar.net/english.php
More information about the R-help
mailing list