]> git.donarmstrong.com Git - xtable.git/commitdiff
Changed documentation to advise on bug #4770
authordscott <dscott@edb9625f-4e0d-4859-8d74-9fd3b1da38cb>
Wed, 28 Aug 2013 05:23:52 +0000 (05:23 +0000)
committerdscott <dscott@edb9625f-4e0d-4859-8d74-9fd3b1da38cb>
Wed, 28 Aug 2013 05:23:52 +0000 (05:23 +0000)
git-svn-id: svn://scm.r-forge.r-project.org/svnroot/xtable@42 edb9625f-4e0d-4859-8d74-9fd3b1da38cb

pkg/NEWS
pkg/R/print.xtable.R
pkg/man/print.xtable.Rd
pkg/man/toLatex.Rd

index 12d00d938f06e069f43257525c2a19a2efeef01c..5dd0e4c8eab913d8efe2cb71e921913616943c7a 100644 (file)
--- a/pkg/NEWS
+++ b/pkg/NEWS
@@ -1,5 +1,8 @@
 1.7-2 (NOT YET RELEASED)
   * Fixed HTML gsub bug (#2795)
+  * Dealt with format.args bug (#4770). No code changes, but the
+    documentation of print.xtable was changed to warn of the problem
+    and to give a workaround as an example
 
 1.7-1 (2013-02-24)
   * Fixed logicals bug (Req #1911)
     to exclude the version and timestamp comment. (Req #2246)
   * Added "caption.width" argument.  If not NULL then the caption
     is placed in a "parbox" of the specified width. (Req #2247)
-  * Remove the check on whether the "floating.environment" is
-    in a list of known floating environments. Users want to use
-       floating environments from multiple options LaTeX 
-       packages (Req #2488, #2578)
+  * Remove the check on whether the "floating.environment" is in a
+    list of known floating environments. Users want to use floating
+    environments from multiple options LaTeX packages (Req #2488,
+    #2578)
        
 1.7-0 (2012-02-10)
   * Added some vectorization code to improve performance.
index 35d4c4611bcce6ae00f3d7bd2edf885ac3fbf54c..d057595376cc67e47925c7fe826550bb9d3284d3 100644 (file)
@@ -123,7 +123,7 @@ print.xtable <- function(x,
         ## Original code before changes in version 1.6-1\r
         ## PHEADER <- "\\hline\n"\r
 \r
-           ## booktabs code from Matthieu Stigler <matthieu.stigler@gmail.com>,\r
+        ## booktabs code from Matthieu Stigler <matthieu.stigler@gmail.com>,\r
         ## 1 Feb 2012\r
         if(!booktabs){\r
             PHEADER <- "\\hline\n"\r
@@ -144,9 +144,9 @@ print.xtable <- function(x,
     if (!is.null(hline.after)) {\r
         ## booktabs change - Matthieu Stigler: fill the hline arguments\r
         ## separately, 1 Feb 2012\r
-           ##\r
+        ##\r
         ## Code before booktabs change was:\r
-           ##    add.to.row$pos[[npos+1]] <- hline.after\r
+        ##    add.to.row$pos[[npos+1]] <- hline.after\r
 \r
         if (!booktabs){\r
             add.to.row$pos[[npos+1]] <- hline.after\r
@@ -178,8 +178,8 @@ print.xtable <- function(x,
     if (!all(!is.na(match(type, c("latex","html"))))) {\r
         stop("\"type\" must be in {\"latex\", \"html\"}")\r
     }\r
-    ## Disabling the check on known floating environments as many users \r
-    ## want to use additional environments.    \r
+    ## Disabling the check on known floating environments as many users\r
+    ## want to use additional environments.\r
     #    if (!all(!is.na(match(floating.environment,\r
     #                          c("table","table*","sidewaystable",\r
     #                            "margintable"))))) {\r
@@ -324,7 +324,7 @@ print.xtable <- function(x,
             ESIZE <- "}\n"\r
         }\r
         BLABEL <- "\\label{"\r
-        ELABEL <- "}\n"                \r
+        ELABEL <- "}\n"\r
         ## Added caption width (jeff.laake@nooa.gov)\r
            if(!is.null(caption.width)){\r
                BCAPTION <- paste("\\parbox{",caption.width,"}{",sep="")\r
@@ -332,13 +332,13 @@ print.xtable <- function(x,
            } else {\r
                BCAPTION <- NULL\r
                ECAPTION <- NULL\r
-           }             \r
+           }\r
            if (is.null(short.caption)){\r
                   BCAPTION <- paste(BCAPTION,"\\caption{",sep="")\r
            } else {\r
                   BCAPTION <- paste(BCAPTION,"\\caption[", short.caption, "]{", sep="")\r
-           }   \r
-        ECAPTION <- paste(ECAPTION,"} \n",sep="")                              \r
+           }\r
+        ECAPTION <- paste(ECAPTION,"} \n",sep="")\r
         BROW <- ""\r
         EROW <- " \\\\ \n"\r
         BTH <- ""\r
@@ -459,10 +459,10 @@ print.xtable <- function(x,
               info$language + " " + info$major + "." + info$minor +\r
               " by xtable " +  packageDescription('xtable')$Version +\r
               " package" + ECOMMENT\r
-        if (!is.null(timestamp)){                \r
+        if (!is.null(timestamp)){\r
             result <- result + BCOMMENT + timestamp + ECOMMENT\r
         }\r
-    }          \r
+    }\r
     ## Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 only.contents\r
     if (!only.contents) {\r
         result <- result + BTABLE\r
@@ -558,26 +558,26 @@ print.xtable <- function(x,
                 format.args$decimal.mark <- options()$OutDec\r
             }\r
             if(!varying.digits){\r
-               curFormatArgs <- c(list(\r
-                                   x = xcol,\r
-                                   format = ifelse( attr( x, "digits",\r
-                                   exact = TRUE )[i+1] < 0, "E",\r
-                                   attr( x, "display", exact = TRUE )[i+1] ),\r
-                                   digits = abs( attr( x, "digits",\r
-                                   exact = TRUE )[i+1] )),\r
-                                   format.args)\r
+               curFormatArgs <-\r
+                    c(list(\r
+                      x = xcol,\r
+                      format =\r
+                      ifelse(attr(x, "digits", exact = TRUE )[i+1] < 0, "E",\r
+                                   attr(x, "display", exact = TRUE )[i+1]),\r
+                      digits = abs(attr(x, "digits", exact = TRUE )[i+1])),\r
+                      format.args)\r
                 cols[, i+pos] <- do.call("formatC", curFormatArgs)\r
             }else{\r
                for( j in 1:nrow( cols ) ) {\r
-                    curFormatArgs <- c(list(\r
-                                       x = xcol[j],\r
-                                       format = ifelse( attr( x, "digits",\r
-                                       exact = TRUE )[j, i+1] < 0, "E",\r
-                                       attr( x, "display",\r
-                                            exact = TRUE )[i+1] ),\r
-                                       digits = abs( attr( x, "digits",\r
-                                       exact = TRUE )[j, i+1] )),\r
-                                       format.args)\r
+                    curFormatArgs <-\r
+                        c(list(\r
+                          x = xcol[j],\r
+                          format =\r
+                          ifelse(attr(x, "digits", exact = TRUE )[j, i+1] < 0,\r
+                                 "E", attr(x, "display", exact = TRUE )[i+1]),\r
+                          digits =\r
+                          abs(attr(x, "digits", exact = TRUE )[j, i+1])),\r
+                          format.args)\r
                     cols[j, i+pos] <- do.call("formatC", curFormatArgs)\r
                }\r
             }\r
@@ -679,10 +679,10 @@ as.string <- function(x, file = "", append = FALSE) {
         switch(data.class(x),\r
                character = return(string(x, file, append)),\r
                numeric = return(string(as.character(x), file, append)),\r
-               stop("Cannot coerse argument to a string"))\r
+               stop("Cannot coerce argument to a string"))\r
     if (class(x) == "string")\r
         return(x)\r
-    stop("Cannot coerse argument to a string")\r
+    stop("Cannot coerce argument to a string")\r
 }\r
 \r
 is.string <- function(x) {\r
index efb537f36c87ff5b4d93bd899407d614d7bab311..33a5f5d73f147bec73b60d74d00fd2c3fb33b814 100644 (file)
     the character vector that is returned invisibly.}\r
   \item{format.args}{List of arguments for the \code{formatC} function.\r
     For example, standard German number separators can be specified as\r
-    \code{format.args=list(big.mark = "'", decimal.mark = ","))}. }\r
+    \code{format.args=list(big.mark = "'", decimal.mark =\r
+      ","))}. \code{digits} and \code{format} arguments should not be\r
+    included in this list. See details. }\r
   \item{rotate.rownames}{If \code{TRUE}, the row names are displayed\r
     vertically in LaTeX. }\r
   \item{rotate.colnames}{If \code{TRUE}, the column names are displayed\r
   From version 1.6-1 the default values for the arguments other than\r
   \code{x} are obtainined using \code{getOption()}.  Hence the user can\r
   set the values once with \code{options()} rather than setting them in\r
-  every call to \code{print.xtable()}. \r
+  every call to \code{print.xtable()}.\r
+\r
+  The argument \code{format.args} is used to supply arguments to the\r
+  \code{formatC} function, but will throw an error if values for\r
+  \code{digits} or \code{format} are included in the list of\r
+  arguments. The recommended approach is to specify \code{digits} supply\r
+  the argument \code{digits} to \code{xtable}, and to specify\r
+  \code{format} supply the argument \code{display} to \code{xtable}. See\r
+  the examples.  \r
 }\r
 \author{\r
   David Dahl \email{dahl@stat.tamu.edu} with contributions and\r
   \code{\link{formatC}} \r
 }\r
 \r
+\examples{\r
+df <- data.frame(A = c(1.00123, 33.1, 6),\r
+                 B = c(111111, 3333333, 3123.233))\r
+## The following code gives the error\r
+## formal argument "digits" matched by multiple actual arguments\r
+## print(xtable(df, display = c("s","e","e")),\r
+##       format.args = list(digits = 3, big.mark = " ", decimal.mark = ","))\r
+## specify digits as argument to xtable instead\r
+print(xtable(df, display = c("s","f","f"), digits = 4),\r
+      format.args = list(big.mark = " ", decimal.mark = ","))\r
+## The following code gives the error\r
+## formal argument "format" matched by multiple actual arguments\r
+## print(xtable(df, digits = 4),\r
+##       format.args = list(format = c("s","e","e"),\r
+##                          big.mark = " ", decimal.mark = ","))\r
+## specify format using display argument in xtable\r
+print(xtable(df, display = c("s","e","e"), digits = 4),\r
+      format.args = list(big.mark = " ", decimal.mark = ","))\r
+\r
+}\r
+\r
 \keyword{print}\r
index e0cc1cca6ba7e1915334d3b4488e3fec7985f152..bdf6c59fecf97a9fc18bf454b0234374e60c109b 100644 (file)
@@ -1,17 +1,26 @@
 \name{toLatex.xtable}
 \alias{toLatex.xtable}
 \title{Convert Table to Latex}
-\description{Function creating a LaTeX representation of an object of class \code{xtable}.}
+\description{
+  Function creating a LaTeX representation of an object of class
+  \code{xtable}.
+}
 \usage{
-       \method{toLatex}{xtable}(object, ...)}
+\method{toLatex}{xtable}(object, ...)
+}
 \arguments{
   \item{object}{An object of class \code{"xtable"}.}
   \item{...}{Other arguments to \code{print.xtable}.}  
 }
 \details{
-  This function creates a LaTeX representation of an object of class \code{"xtable"}.  This is a method for the generic \code{"toLatex"} in the core R package \code{"utils"}. 
+  This function creates a LaTeX representation of an object of class
+  \code{"xtable"}.  This is a method for the generic \code{"toLatex"} in
+  the core R package \code{"utils"}.
+}
+\author{
+  Charles Roosen \email{roosen@gmail.com} with contributions and
+  suggestions from many others (see source code).
 }
-\author{Charles Roosen \email{roosen@gmail.com} with contributions and suggestions from many others (see source code).}
 \seealso{\code{\link{print.xtable}}}
 
 \keyword{toLatex}