[Rd] Please make lowess() generic (was: Reorganization of pac kagesin the R distribution)

Bill.Venables at csiro.au Bill.Venables at csiro.au
Wed Jan 21 09:14:21 MET 2004


I don't really see the point.  lowess() is a two-dimensional smoother only
so the main point would only be to allow lowess(y ~ x, dat) instead of
lowess(dat$x, dat$y).

Bill V.



-----Original Message-----
From: r-devel-bounces at stat.math.ethz.ch
[mailto:r-devel-bounces at stat.math.ethz.ch] On Behalf Of Warnes, Gregory R
Sent: Wednesday, 21 January 2004 4:48 PM
To: 'R-devel'
Subject: [Rd] Please make lowess() generic (was: Reorganization of
packagesin the R distribution)



As I've mentioned a number of times.  I find it very useful to have lowess()
become a generic function so that a lowess.formula() can be defined.

Below is a patch that makes both changes, as well as updating the
corresponding help documentation.

Gregory R. Warnes
Manager, Non-Clinical Statistics
Pfizer Global Research and Development
Tel: 860-715-3536

? DESCRIPTION
? Makefile
? lowess.generic.patch
? R/mean.R
? man/logLik.glm.Rd
? man/logLik.lm.Rd
? man/mean.Rd
? src/Makefile
Index: R/lowess.R
===================================================================
RCS file: /cvs/R/src/library/stats/R/lowess.R,v
retrieving revision 1.1
diff -u -r1.1 lowess.R
--- R/lowess.R  2003/12/09 07:24:23     1.1
+++ R/lowess.R  2004/01/21 06:42:58
@@ -1,4 +1,10 @@
-lowess <- function(x, y=NULL, f=2/3, iter=3,
delta=.01*diff(range(xy$x[o]))) {
+
+
+lowess  <- function(x,...)
+      UseMethod("lowess")
+
+lowess.default <-
+function(x, y=NULL, f=2/3, iter=3, delta=.01*diff(range(xy$x[o]))) {
     xy <- xy.coords(x,y)
     n <- length(xy$x)
     if(n == 0) stop("x is empty")
@@ -14,3 +20,25 @@
        double(n),
        double(n), PACKAGE="base")[c("x","y")]
 }
+
+
+
+"lowess.formula" <-  function (formula,
+                               data = parent.frame(), subset, na.action, 
+                               f=2/3,  iter=3,
+                               delta=.01*diff(range(mf[-response])), 
+... ) {
+  if (missing(formula) || (length(formula) != 3)) 
+    stop("formula missing or incorrect")
+  if (missing(na.action)) 
+    na.action <- getOption("na.action")
+  m <- match.call(expand.dots = FALSE)
+  if (is.matrix(eval(m$data, parent.frame()))) 
+    m$data <- as.data.frame(data)
+  m$...  <- m$f <- m$iter <- m$delta <- NULL
+  m[[1]] <- as.name("model.frame")
+  mf <- eval(m, parent.frame())
+  response <- attr(attr(mf, "terms"), "response")
+  lowess.default(mf[[-response]], mf[[response]], f=f, iter=iter,
delta=delta)
+}
+
Index: man/lowess.Rd
===================================================================
RCS file: /cvs/R/src/library/stats/man/lowess.Rd,v
retrieving revision 1.2
diff -u -r1.2 lowess.Rd
--- man/lowess.Rd       2003/12/09 18:32:33     1.2
+++ man/lowess.Rd       2004/01/21 06:44:18
@@ -1,10 +1,23 @@
 \name{lowess}
+\alias{lowess}
+\alias{lowess.default}
+\alias{lowess.formula}
 \title{Scatter Plot Smoothing}
 \usage{
-lowess(x, y = NULL, f = 2/3, iter=3, delta = 0.01 * diff(range(xy$x[o])))
+lowess(x, ...)
+\method{lowess}{default}(x, y = NULL, f = 2/3, iter = 3, delta = 0.01 *
+                  diff(range(xy$x[o])), ...) 
+\method{lowess}{formula}(formula,data = parent.frame(), subset, na.action,
+               f=2/3,  iter=3, delta=.01*diff(range(mf[-response])), 
+... )
 }
-\alias{lowess}
 \arguments{
+  \item{formula}{ formula providing a single dependent variable (y) and
+    an single independent variable (x) to use as coordinates in the
+    scatter plot.}
+  \item{data}{a data.frame (or list) from which the variables in `formula'
+          should be taken.}
+  \item{subset}{ an optional vector specifying a subset of observations 
+ to
be
+          used in the fitting process. }
   \item{x, y}{vectors giving the coordinates of the points in the scatter
plot.
     Alternatively a single plotting structure can be specified.}
   \item{f}{the smoother span. This gives the proportion of points in @@
-16,6 +29,11 @@
   \item{delta}{values of \code{x} which lie within \code{delta}
     of each other are replaced by a single value in the output from
     \code{lowess}.  Defaults to 1/100th of the range of \code{x}.}
+  \item{na.action}{a function which indicates what should happen when 
+ the
data
+          contain `NA's.  The default is set by the `na.action' setting
+          of `options', and is `na.fail' if that is unset. The
+          ``factory-fresh'' default is `na.omit'.}  
+ \item{...}{parameters for methods.}
 }
 \description{
   This function performs the computations for the
@@ -43,9 +61,17 @@
 }
 \examples{
 data(cars)
+
+# default method
 plot(cars, main = "lowess(cars)")
 lines(lowess(cars), col = 2)
 lines(lowess(cars, f=.2), col = 3)
+legend(5, 120, c(paste("f = ", c("2/3", ".2"))), lty = 1, col = 2:3)
+
+# formula method
+plot(dist ~ speed, data=cars, main = "lowess(cars)") lines(lowess(dist 
+~ speed, data=cars), col = 2) lines(lowess(dist ~ speed, data=cars, 
+f=.2), col = 3)
 legend(5, 120, c(paste("f = ", c("2/3", ".2"))), lty = 1, col = 2:3)  }
\keyword{smooth}


LEGAL NOTICE\ Unless expressly stated otherwise, this messag...{{dropped}}

______________________________________________
R-devel at stat.math.ethz.ch mailing list
https://www.stat.math.ethz.ch/mailman/listinfo/r-devel



More information about the R-devel mailing list