[R] Re: [R} stars graphs

Jim Lemon bitwrit at ozemail.com.au
Fri Aug 15 10:03:05 CEST 2003


I thought about that star graph again, and realized that it would be quite 
a handy thing for visualizing cyclic data like time or compass direction. 
Here is a cleaned up (and renamed) version to do a polar plot that starts 
at the right and goes counterclockwise or a 24 hour clock plot that starts 
at the top and goes clockwise. There are probably other varieties that 
would be interesting.

Jim

-------------- next part --------------
# scales a vector of numbers to a new range

rescale<-function(x,newrange) {
 if(is.numeric(x) && is.numeric(newrange)) {
  xrange<-range(x)
  if(xrange[1] == xrange[2]) stop("rescale: can't rescale a constant vector!")
  mfac<-(newrange[2]-newrange[1])/(xrange[2]-xrange[1])
  invisible(newrange[1]+(x-xrange[1])*mfac)
 }
 else {
  cat("Usage: rescale(x,newrange)\n")
  cat("\twhere x is a numeric object and newrange is the extent of the new range\n")
 }
}

# plots data as radial lines on a 24 hour "clockface" going clockwise

clock24.star<-function(lengths,radial.pos,radial.range) {
 if(missing(radial.range)) radial.range<-range(radial.pos)
 npos<-length(radial.pos)
 newrange<-c(2.5*pi,0.5*pi)
 # rescale to a range of 0 to 2pi
 # starting at "12 o'clock" and going clockwise
 clock.radial.pos<-rescale(c(radial.pos,radial.range),newrange)[1:npos]
 clock.labels<-as.character(seq(100,2400,by=100))
 clock.label.pos<-seq(29*pi/12,pi/2,by=-pi/12)
 radial.plot(lengths,clock.radial.pos,newrange,clock.labels,clock.label.pos)
}

# plots data as radial lines starting at the right and going counterclockwise

polar.star<-function(lengths,polar.pos,polar.range,labels,label.pos,
 main="",xlab="",ylab="",...) {
 if(missing(polar.range)) polar.range<-range(polar.pos)
 npos<-length(polar.pos)
 newrange<-c(0,2*pi)
 # rescale to a range of 0 to 2pi
 radial.pos<-rescale(c(polar.pos,polar.range),newrange)[1:npos]
 if(missing(labels)) labels<-as.character(polar.pos)
 if(missing(label.pos)) label.pos<-radial.pos
 else {
  newrange<-
   c(0,2*pi*(max(label.pos)-min(label.pos))/(polar.range[2]-polar.range[1]))
  label.pos<-rescale(label.pos,newrange)
 }
 radial.plot(lengths,radial.pos,newrange,labels,label.pos,...)
}

# plots radial lines from a central origin of length 'lengths'
# at the angles specified by 'radial.pos' in radians
# starts at the 'east' position and goes counterclockwise

radial.plot<-function(lengths,radial.pos,radial.range,labels,label.pos,
 main="",xlab="",ylab="",...) {
 maxlength<-1.1*max(lengths)
 if(missing(radial.range)) radial.range<-range(radial.pos)
 plot(c(-maxlength,maxlength),c(-maxlength,maxlength),type="n",axes=FALSE,
  main=main,xlab=xlab,ylab=ylab,...)
 # get the vector of x positions
 xpos<-cos(radial.pos)*lengths
 # get the vector of y positions
 ypos<-sin(radial.pos)*lengths
 segments(0,0,xpos,ypos)
 if(missing(labels)) labels<-as.character(radial.pos)
 if(missing(label.pos)) {
  xpos<-cos(radial.pos)*maxlength
  ypos<-sin(radial.pos)*maxlength
 }
 else {
  xpos<-cos(label.pos)*maxlength
  ypos<-sin(label.pos)*maxlength
 }
 text(xpos,ypos,labels)
}


More information about the R-help mailing list