]> git.donarmstrong.com Git - xtable.git/blobdiff - pkg/R/print.xtable.R
Changed documentation to advise on bug #4770
[xtable.git] / pkg / R / print.xtable.R
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