]> git.donarmstrong.com Git - xtable.git/commitdiff
Reformatted print.xtable.Rd, xtable.Rd, and print.xtable.R for readability. Lines...
authordscott <dscott@edb9625f-4e0d-4859-8d74-9fd3b1da38cb>
Thu, 16 Aug 2012 02:59:02 +0000 (02:59 +0000)
committerdscott <dscott@edb9625f-4e0d-4859-8d74-9fd3b1da38cb>
Thu, 16 Aug 2012 02:59:02 +0000 (02:59 +0000)
git-svn-id: svn://scm.r-forge.r-project.org/svnroot/xtable@34 edb9625f-4e0d-4859-8d74-9fd3b1da38cb

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

index 94cb18d0b04340167e2c7f1d9050373b3ecd28fd..3145514e517f73fdcda0c4d7be5cd56dba47afa4 100644 (file)
 ### License along with this program; if not, write to the Free\r
 ### Software Foundation, Inc., 59 Temple Place - Suite 330, Boston,\r
 ### MA 02111-1307, USA\r
-print.xtable <- function(\r
-  x,\r
-  type=getOption("xtable.type", "latex"),\r
-  file=getOption("xtable.file", ""),\r
-  append=getOption("xtable.append", FALSE),\r
-  floating=getOption("xtable.floating", TRUE),\r
-  floating.environment=getOption("xtable.floating.environment", "table"),\r
-  table.placement=getOption("xtable.table.placement", "ht"),\r
-  caption.placement=getOption("xtable.caption.placement", "bottom"),\r
-  latex.environments=getOption("xtable.latex.environments", c("center")),\r
-  tabular.environment=getOption("xtable.tabular.environment", "tabular"),\r
-  size=getOption("xtable.size", NULL),\r
-  hline.after=getOption("xtable.hline.after", c(-1,0,nrow(x))),\r
-  NA.string=getOption("xtable.NA.string", ""),\r
-  include.rownames=getOption("xtable.include.rownames", TRUE),\r
-  include.colnames=getOption("xtable.include.colnames", TRUE),\r
-  only.contents=getOption("xtable.only.contents", FALSE),\r
-  add.to.row=getOption("xtable.add.to.row", NULL),\r
-  sanitize.text.function=getOption("xtable.sanitize.text.function", NULL),\r
-  sanitize.rownames.function=getOption("xtable.sanitize.rownames.function", \r
-    sanitize.text.function),\r
-  sanitize.colnames.function=getOption("xtable.sanitize.colnames.function", \r
-    sanitize.text.function),\r
-  math.style.negative=getOption("xtable.math.style.negative", FALSE),\r
-  html.table.attributes=getOption("xtable.html.table.attributes", "border=1"),\r
-  print.results=getOption("xtable.print.results", TRUE),\r
-  format.args=getOption("xtable.format.args", NULL),\r
-  rotate.rownames=getOption("xtable.rotate.rownames", FALSE),\r
-  rotate.colnames=getOption("xtable.rotate.colnames", FALSE),\r
+print.xtable <- function(x,\r
+  type = getOption("xtable.type", "latex"),\r
+  file = getOption("xtable.file", ""),\r
+  append = getOption("xtable.append", FALSE),\r
+  floating = getOption("xtable.floating", TRUE),\r
+  floating.environment = getOption("xtable.floating.environment", "table"),\r
+  table.placement = getOption("xtable.table.placement", "ht"),\r
+  caption.placement = getOption("xtable.caption.placement", "bottom"),\r
+  latex.environments = getOption("xtable.latex.environments", c("center")),\r
+  tabular.environment = getOption("xtable.tabular.environment", "tabular"),\r
+  size = getOption("xtable.size", NULL),\r
+  hline.after = getOption("xtable.hline.after", c(-1,0,nrow(x))),\r
+  NA.string = getOption("xtable.NA.string", ""),\r
+  include.rownames = getOption("xtable.include.rownames", TRUE),\r
+  include.colnames = getOption("xtable.include.colnames", TRUE),\r
+  only.contents = getOption("xtable.only.contents", FALSE),\r
+  add.to.row = getOption("xtable.add.to.row", NULL),\r
+  sanitize.text.function = getOption("xtable.sanitize.text.function", NULL),\r
+  sanitize.rownames.function = getOption("xtable.sanitize.rownames.function",\r
+                                         sanitize.text.function),\r
+  sanitize.colnames.function = getOption("xtable.sanitize.colnames.function",\r
+                                         sanitize.text.function),\r
+  math.style.negative = getOption("xtable.math.style.negative", FALSE),\r
+  html.table.attributes = getOption("xtable.html.table.attributes", "border=1"),\r
+  print.results = getOption("xtable.print.results", TRUE),\r
+  format.args = getOption("xtable.format.args", NULL),\r
+  rotate.rownames = getOption("xtable.rotate.rownames", FALSE),\r
+  rotate.colnames = getOption("xtable.rotate.colnames", FALSE),\r
   booktabs = getOption("xtable.booktabs", FALSE),\r
   scalebox = getOption("xtable.scalebox", NULL),\r
   width = getOption("xtable.width", NULL),\r
-  ...) {\r
-  # If caption is length 2, treat the second value as the "short caption"\r
-  caption <- attr(x,"caption",exact=TRUE)\r
-  short.caption <- NULL\r
-  if (!is.null(caption) && length(caption) > 1){\r
-    short.caption <- caption[2]\r
+  ...)\r
+{\r
+    ## If caption is length 2, treat the second value as the "short caption"\r
+    caption <- attr(x,"caption",exact = TRUE)\r
+    short.caption <- NULL\r
+    if (!is.null(caption) && length(caption) > 1){\r
+        short.caption <- caption[2]\r
        caption <- caption[1]\r
-  }\r
-  \r
-  # Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 hline.after\r
-  # By default it print an \hline before and after the columns names independently they are printed or not and at the end of the table\r
-  # Old code that set hline.after should include c(-1, 0, nrow(x)) in the hline.after vector\r
-  # If you do not want any \hline inside the data, set hline.after to NULL \r
-  # PHEADER instead the string '\\hline\n' is used in the code\r
-  # Now hline.after counts how many time a position appear  \r
-  # I left an automatic PHEADER in the longtable is this correct?\r
-\r
-  # Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 include.rownames, include.colnames  \r
-  pos <- 0\r
-  if (include.rownames) pos <- 1\r
-  \r
-  # Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 hline.after checks\r
-  if (any(hline.after < -1) | any(hline.after > nrow(x))) stop("'hline.after' must be inside [-1, nrow(x)]")\r
-  \r
-  # Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 add.to.row checks\r
-  if (!is.null(add.to.row)) {\r
-    if (is.list(add.to.row) && length(add.to.row)==2) {\r
-      if (is.null(names(add.to.row))) {\r
-        names(add.to.row) <- c('pos', 'command')\r
-      } else if (any(sort(names(add.to.row))!=c('command', 'pos'))) {\r
-        stop("the names of the elements of 'add.to.row' must be 'pos' and 'command'")\r
-      }\r
-      if (is.list(add.to.row$pos) && is.vector(add.to.row$command, mode='character')) {\r
-        if ((npos <- length(add.to.row$pos)) != length(add.to.row$command)) {\r
-          stop("the length of 'add.to.row$pos' must be equal to the length of 'add.to.row$command'")\r
-        }\r
-        if (any(unlist(add.to.row$pos) < -1) | any(unlist(add.to.row$pos) > nrow(x))) {\r
-          stop("the values in add.to.row$pos must be inside the interval [-1, nrow(x)]")\r
+    }\r
+\r
+    ## Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 hline.after\r
+    ## By default it print an \hline before and after the columns names independently they are printed or not and at the end of the table\r
+    ## Old code that set hline.after should include c(-1, 0, nrow(x)) in the hline.after vector\r
+    ## If you do not want any \hline inside the data, set hline.after to NULL\r
+    ## PHEADER instead the string '\\hline\n' is used in the code\r
+    ## Now hline.after counts how many time a position appear\r
+    ## I left an automatic PHEADER in the longtable is this correct?\r
+\r
+    ## Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 include.rownames, include.colnames\r
+    pos <- 0\r
+    if (include.rownames) pos <- 1\r
+\r
+    ## Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 hline.after checks\r
+    if (any(hline.after < -1) | any(hline.after > nrow(x))) {\r
+        stop("'hline.after' must be inside [-1, nrow(x)]")\r
+    }\r
+\r
+    ## Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 add.to.row checks\r
+    if (!is.null(add.to.row)) {\r
+        if (is.list(add.to.row) && length(add.to.row) == 2) {\r
+            if (is.null(names(add.to.row))) {\r
+                names(add.to.row) <- c('pos', 'command')\r
+            } else if (any(sort(names(add.to.row))!= c('command', 'pos'))) {\r
+                stop("the names of the elements of 'add.to.row' must be 'pos' and 'command'")\r
+            }\r
+            if (is.list(add.to.row$pos) && is.vector(add.to.row$command,\r
+                                                     mode = 'character')) {\r
+                if ((npos <- length(add.to.row$pos)) !=\r
+                    length(add.to.row$command)) {\r
+                    stop("the length of 'add.to.row$pos' must be equal to the length of 'add.to.row$command'")\r
+                }\r
+                if (any(unlist(add.to.row$pos) < -1) |\r
+                    any(unlist(add.to.row$pos) > nrow(x))) {\r
+                    stop("the values in add.to.row$pos must be inside the interval [-1, nrow(x)]")\r
+                }\r
+            } else {\r
+                stop("the first argument ('pos') of 'add.to.row' must be a list, the second argument ('command') must be a vector of mode character")\r
+            }\r
+        } else {\r
+            stop("'add.to.row' argument must be a list of length 2")\r
         }\r
-      } else {\r
-        stop("the first argument ('pos') of 'add.to.row' must be a list, the second argument ('command') must be a vector of mode character")\r
-      }\r
     } else {\r
-      stop("'add.to.row' argument must be a list of length 2")\r
+        add.to.row <- list(pos = list(),\r
+                           command = vector(length = 0, mode = "character"))\r
+        npos <- 0\r
     }\r
-  } else {\r
-     add.to.row <- list(pos=list(), command=vector(length=0, mode="character"))\r
-     npos <- 0\r
-  }\r
-\r
-  # Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 add.to.row\r
-  # Add further commands at the end of rows\r
-  if (type=="latex") {\r
-    ## Original code before changes in version 1.6-1\r
-    # PHEADER <- "\\hline\n"\r
-\r
-       # booktabs code from Matthieu Stigler <matthieu.stigler@gmail.com>, 1 Feb 2012\r
-    if(!booktabs){\r
-      PHEADER <- "\\hline\n"\r
+\r
+    ## Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 add.to.row\r
+    ## Add further commands at the end of rows\r
+    if (type == "latex") {\r
+        ## Original code before changes in version 1.6-1\r
+        ## PHEADER <- "\\hline\n"\r
+\r
+       ## booktabs code from Matthieu Stigler <matthieu.stigler@gmail.com>, 1 Feb 2012\r
+        if(!booktabs){\r
+            PHEADER <- "\\hline\n"\r
        } else {\r
-      PHEADER <- ifelse(-1%in%hline.after, "\\toprule\n", "") \r
-      if(0%in%hline.after) {\r
-        PHEADER <- c(PHEADER, "\\midrule\n")\r
-         }\r
-      if(nrow(x)%in%hline.after) {\r
-        PHEADER <- c(PHEADER, "\\bottomrule\n")\r
-         }\r
+            PHEADER <- ifelse(-1%in%hline.after, "\\toprule\n", "")\r
+            if(0%in%hline.after) {\r
+                PHEADER <- c(PHEADER, "\\midrule\n")\r
+            }\r
+            if(nrow(x)%in%hline.after) {\r
+                PHEADER <- c(PHEADER, "\\bottomrule\n")\r
+            }\r
+        }\r
+    } else {\r
+        PHEADER <- ""\r
     }\r
-  } else {\r
-     PHEADER <- ""\r
-  }\r
-   \r
-  lastcol <- rep(" ", nrow(x)+2)\r
-  if (!is.null(hline.after)) {\r
-    # booktabs change - Matthieu Stigler: fill the hline arguments separately, 1 Feb 2012\r
-       #\r
-    # Code before booktabs change was:\r
-       #    add.to.row$pos[[npos+1]] <- hline.after\r
-\r
-    if (!booktabs){\r
-       add.to.row$pos[[npos+1]] <- hline.after\r
+\r
+    lastcol <- rep(" ", nrow(x)+2)\r
+    if (!is.null(hline.after)) {\r
+        ## booktabs change - Matthieu Stigler: fill the hline arguments separately, 1 Feb 2012\r
+       ##\r
+        ## Code before booktabs change was:\r
+       ##    add.to.row$pos[[npos+1]] <- hline.after\r
+\r
+        if (!booktabs){\r
+            add.to.row$pos[[npos+1]] <- hline.after\r
        } else {\r
-       for(i in 1:length(hline.after)) {           \r
-             add.to.row$pos[[npos+i]] <- hline.after[i] \r
-          }\r
-    }     \r
-    add.to.row$command <- c(add.to.row$command, PHEADER)\r
-  }\r
-\r
-  if ( length(add.to.row$command) > 0 ) {\r
-    for (i in 1:length(add.to.row$command)) {\r
-      addpos <- add.to.row$pos[[i]]\r
-      freq <- table(addpos)\r
-      addpos <- unique(addpos)\r
-      for (j in 1:length(addpos)) {\r
-        lastcol[addpos[j]+2] <- paste(lastcol[addpos[j]+2], paste(rep(add.to.row$command[i], freq[j]), sep="", collapse=""), sep=" ")\r
-      }\r
-    }\r
-  }\r
-  \r
-  if (length(type)>1) stop("\"type\" must have length 1")\r
-  type <- tolower(type)\r
-  if (!all(!is.na(match(type,c("latex","html"))))) stop("\"type\" must be in {\"latex\", \"html\"}")\r
-  if (!all(!is.na(match(floating.environment,c("table","table*","sidewaystable"))))) stop("\"type\" must be in {\"table\", \"table*\", \"sidewaystable\"}")\r
-  if (!is.null(table.placement) && !all(!is.na(match(unlist(strsplit(table.placement, split="")),c("H","h","t","b","p","!"))))) {\r
-    stop("\"table.placement\" must contain only elements of {\"h\",\"t\",\"b\",\"p\",\"!\"}")\r
-  }\r
-  if (!all(!is.na(match(caption.placement,c("bottom","top"))))) stop("\"caption.placement\" must be either {\"bottom\",\"top\"}")\r
-\r
-  if (type=="latex") {\r
-    BCOMMENT <- "% "\r
-    ECOMMENT <- "\n"\r
-    # See e-mail from "John S. Walker <jsw9c@uic.edu>" dated 5-19-2003 regarding "texfloat"\r
-    # See e-mail form "Fernando Henrique Ferraz P. da Rosa" <academic@feferraz.net>" dated 10-28-2005 regarding "longtable"\r
-    if ( tabular.environment == "longtable" & floating == TRUE ) {\r
-      warning("Attempt to use \"longtable\" with floating=TRUE. Changing to FALSE.")\r
-      floating <- FALSE\r
-    }\r
-    if ( floating == TRUE ) {\r
-      # See e-mail from "Pfaff, Bernhard <Bernhard.Pfaff@drkw.com>" dated 7-09-2003 regarding "suggestion for an amendment of the source"\r
-      # See e-mail from "Mitchell, David" <David.Mitchell@dotars.gov.au>" dated 2003-07-09 regarding "Additions to R xtable package"\r
-      # See e-mail from "Garbade, Sven" <Sven.Garbade@med.uni-heidelberg.de> dated 2006-05-22 regarding the floating environment.\r
-      BTABLE <- paste("\\begin{", floating.environment, "}",ifelse(!is.null(table.placement),\r
-        paste("[",table.placement,"]",sep=""),""),"\n",sep="")\r
-      if ( is.null(latex.environments) || (length(latex.environments)==0) ) {\r
-        BENVIRONMENT <- ""\r
-        EENVIRONMENT <- ""\r
-      }\r
-      else {\r
-        BENVIRONMENT <- ""\r
-        EENVIRONMENT <- ""\r
-        for ( i in 1:length(latex.environments) ) {\r
-          if ( latex.environments[i] == "" ) next\r
-          BENVIRONMENT <- paste(BENVIRONMENT, "\\begin{",latex.environments[i],"}\n",sep="")\r
-          EENVIRONMENT <- paste("\\end{",latex.environments[i],"}\n",EENVIRONMENT,sep="")\r
+            for(i in 1:length(hline.after)) {\r
+                add.to.row$pos[[npos+i]] <- hline.after[i]\r
+            }\r
         }\r
-      }\r
-      ETABLE <- paste("\\end{", floating.environment, "}\n", sep="")\r
+        add.to.row$command <- c(add.to.row$command, PHEADER)\r
     }\r
-    else {\r
-      BTABLE <- ""\r
-      ETABLE <- ""\r
-      BENVIRONMENT <- ""\r
-      EENVIRONMENT <- ""\r
+\r
+    if ( length(add.to.row$command) > 0 ) {\r
+        for (i in 1:length(add.to.row$command)) {\r
+            addpos <- add.to.row$pos[[i]]\r
+            freq <- table(addpos)\r
+            addpos <- unique(addpos)\r
+            for (j in 1:length(addpos)) {\r
+                lastcol[addpos[j]+2] <- paste(lastcol[addpos[j]+2],\r
+                                              paste(rep(add.to.row$command[i],\r
+                                                        freq[j]),\r
+                                                    sep = "", collapse = ""),\r
+                                              sep = " ")\r
+            }\r
+        }\r
     }\r
 \r
-    tmp.index.start <- 1\r
-    if ( ! include.rownames ) {\r
-      while ( attr(x,"align",exact=TRUE)[tmp.index.start] == '|' ) tmp.index.start <- tmp.index.start + 1\r
-      tmp.index.start <- tmp.index.start + 1\r
+    if (length(type)>1) stop("\"type\" must have length 1")\r
+    type <- tolower(type)\r
+    if (!all(!is.na(match(type, c("latex","html"))))) {\r
+        stop("\"type\" must be in {\"latex\", \"html\"}")\r
+    }\r
+    if (!all(!is.na(match(floating.environment,\r
+                          c("table","table*","sidewaystable"))))) {\r
+        stop("\"type\" must be in {\"table\", \"table*\", \"sidewaystable\"}")\r
+    }\r
+    if (!is.null(table.placement) &&\r
+        !all(!is.na(match(unlist(strsplit(table.placement,  split = "")),\r
+                          c("H","h","t","b","p","!"))))) {\r
+        stop("\"table.placement\" must contain only elements of {\"h\",\"t\",\"b\",\"p\",\"!\"}")\r
+    }\r
+    if (!all(!is.na(match(caption.placement, c("bottom","top"))))) {\r
+        stop("\"caption.placement\" must be either {\"bottom\",\"top\"}")\r
     }\r
-       # Added "width" argument for use with "tabular*" or "tabularx" environments - CR, 7/2/12\r
+\r
+    if (type == "latex") {\r
+        BCOMMENT <- "% "\r
+        ECOMMENT <- "\n"\r
+        ## See e-mail from "John S. Walker <jsw9c@uic.edu>" dated 5-19-2003 regarding "texfloat"\r
+        ## See e-mail form "Fernando Henrique Ferraz P. da Rosa" <academic@feferraz.net>" dated 10-28-2005 regarding "longtable"\r
+        if ( tabular.environment == "longtable" & floating == TRUE ) {\r
+            warning("Attempt to use \"longtable\" with floating = TRUE. Changing to FALSE.")\r
+            floating <- FALSE\r
+        }\r
+        if ( floating == TRUE ) {\r
+            ## See e-mail from "Pfaff, Bernhard <Bernhard.Pfaff@drkw.com>" dated 7-09-2003 regarding "suggestion for an amendment of the source"\r
+            ## See e-mail from "Mitchell, David" <David.Mitchell@dotars.gov.au>" dated 2003-07-09 regarding "Additions to R xtable package"\r
+            ## See e-mail from "Garbade, Sven" <Sven.Garbade@med.uni-heidelberg.de> dated 2006-05-22 regarding the floating environment.\r
+            BTABLE <- paste("\\begin{", floating.environment, "}",\r
+                            ifelse(!is.null(table.placement),\r
+                                   paste("[", table.placement, "]", sep = ""),\r
+                                   ""), "\n", sep = "")\r
+            if ( is.null(latex.environments) ||\r
+                (length(latex.environments) == 0) ) {\r
+                BENVIRONMENT <- ""\r
+                EENVIRONMENT <- ""\r
+            } else {\r
+                BENVIRONMENT <- ""\r
+                EENVIRONMENT <- ""\r
+                for ( i in 1:length(latex.environments) ) {\r
+                    if ( latex.environments[i] == "" ) next\r
+                    BENVIRONMENT <- paste(BENVIRONMENT,\r
+                                          "\\begin{", latex.environments[i],\r
+                                          "}\n", sep = "")\r
+                    EENVIRONMENT <- paste("\\end{", latex.environments[i],\r
+                                          "}\n", EENVIRONMENT, sep = "")\r
+                }\r
+            }\r
+            ETABLE <- paste("\\end{", floating.environment, "}\n", sep = "")\r
+        } else {\r
+            BTABLE <- ""\r
+            ETABLE <- ""\r
+            BENVIRONMENT <- ""\r
+            EENVIRONMENT <- ""\r
+        }\r
+\r
+        tmp.index.start <- 1\r
+        if ( ! include.rownames ) {\r
+            while ( attr(x, "align", exact = TRUE)[tmp.index.start] == '|' )\r
+                tmp.index.start <- tmp.index.start + 1\r
+            tmp.index.start <- tmp.index.start + 1\r
+        }\r
+       ## Added "width" argument for use with "tabular*" or "tabularx" environments - CR, 7/2/12\r
        if (is.null(width)){\r
-         WIDTH <-""\r
-       } else if (is.element(tabular.environment, c("tabular", "longtable"))){\r
-         warning("Ignoring 'width' argument.  The 'tabular' and 'longtable' environments do not support a width specification.  Use another environment such as 'tabular*' or 'tabularx' to specify the width.")\r
-         WIDTH <- ""\r
+            WIDTH <-""\r
+       } else if (is.element(tabular.environment,\r
+                              c("tabular", "longtable"))){\r
+            warning("Ignoring 'width' argument.  The 'tabular' and 'longtable' environments do not support a width specification.  Use another environment such as 'tabular*' or 'tabularx' to specify the width.")\r
+            WIDTH <- ""\r
        } else {\r
-         WIDTH <- paste("{", width, "}", sep="")\r
+            WIDTH <- paste("{", width, "}", sep = "")\r
        }\r
-       \r
-    BTABULAR <- paste("\\begin{",tabular.environment,"}", WIDTH, "{",\r
-        paste(c(attr(x, "align",exact=TRUE)[tmp.index.start:length(attr(x,"align",\r
-                   exact=TRUE))], "}\n"), sep="", collapse=""),\r
-        sep="")\r
-\r
-    ## fix 10-26-09 (robert.castelo@upf.edu) the following 'if' condition is added here to support\r
-    ## a caption on the top of a longtable\r
-    if (tabular.environment == "longtable" && caption.placement=="top") {\r
-               if (is.null(short.caption)){\r
-                       BCAPTION <- "\\caption{"\r
-               } else {\r
-                       BCAPTION <- paste("\\caption[", short.caption, "]{", sep="")\r
-               }       \r
-        ECAPTION <- "} \\\\ \n"\r
-        if ((!is.null(caption)) && (type=="latex")) BTABULAR <- paste(BTABULAR,  BCAPTION, caption, ECAPTION, sep="")\r
-    }\r
-    # Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 add.to.row position -1\r
-    BTABULAR <- paste(BTABULAR,lastcol[1], sep="")\r
-    # the \hline at the end, if present, is set in full matrix    \r
-    ETABULAR <- paste("\\end{",tabular.environment,"}\n",sep="")\r
+\r
+        BTABULAR <-\r
+            paste("\\begin{", tabular.environment, "}",\r
+                  WIDTH, "{",\r
+                  paste(c(attr(x, "align",\r
+                               exact = TRUE)[\r
+                               tmp.index.start:length(attr(x, "align",\r
+                                                           exact = TRUE))],\r
+                          "}\n"),\r
+                        sep = "", collapse = ""),\r
+                  sep = "")\r
+\r
+        ## fix 10-26-09 (robert.castelo@upf.edu) the following 'if' condition is added here to support\r
+        ## a caption on the top of a longtable\r
+        if (tabular.environment == "longtable" && caption.placement == "top") {\r
+            if (is.null(short.caption)){\r
+                BCAPTION <- "\\caption{"\r
+            } else {\r
+                BCAPTION <- paste("\\caption[", short.caption, "]{", sep = "")\r
+            }\r
+            ECAPTION <- "} \\\\ \n"\r
+            if ((!is.null(caption)) && (type == "latex")) {\r
+                BTABULAR <- paste(BTABULAR,  BCAPTION, caption, ECAPTION,\r
+                                  sep = "")\r
+            }\r
+        }\r
+        ## Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 add.to.row position -1\r
+        BTABULAR <- paste(BTABULAR, lastcol[1], sep = "")\r
+        ## the \hline at the end, if present, is set in full matrix\r
+        ETABULAR <- paste("\\end{", tabular.environment, "}\n", sep = "")\r
 \r
        ## Add scalebox - CR, 7/2/12\r
        if (!is.null(scalebox)){\r
-         BTABULAR <- paste("\\scalebox{", scalebox, "}{\n", BTABULAR, sep="")\r
-         ETABULAR <- paste(ETABULAR, "}\n", sep="")\r
+            BTABULAR <- paste("\\scalebox{", scalebox, "}{\n", BTABULAR,\r
+                              sep = "")\r
+            ETABULAR <- paste(ETABULAR, "}\n", sep = "")\r
        }\r
-    \r
-    # BSIZE contributed by Benno <puetz@mpipsykl.mpg.de> in e-mail dated Wednesday, December 01, 2004\r
-    if (is.null(size) || !is.character(size)) {\r
-      BSIZE <- ""\r
-      ESIZE <- ""\r
+\r
+        ## BSIZE contributed by Benno <puetz@mpipsykl.mpg.de> in e-mail dated Wednesday, December 01, 2004\r
+        if (is.null(size) || !is.character(size)) {\r
+            BSIZE <- ""\r
+            ESIZE <- ""\r
+        } else {\r
+            if(length(grep("^\\\\", size)) == 0){\r
+                size <- paste("\\", size, sep = "")\r
+            }\r
+            BSIZE <- paste("{", size, "\n", sep = "")\r
+            ESIZE <- "}\n"\r
+        }\r
+        BLABEL <- "\\label{"\r
+        ELABEL <- "}\n"\r
+        if (is.null(short.caption)){\r
+        BCAPTION <- "\\caption{"\r
     } else {\r
-      if(length(grep("^\\\\",size))==0){\r
-        size <- paste("\\",size,sep="")\r
-      }\r
-      BSIZE <- paste("{",size,"\n",sep="")\r
-      ESIZE <- "}\n"\r
-    }\r
-    BLABEL <- "\\label{"\r
-    ELABEL <- "}\n"\r
-       if (is.null(short.caption)){\r
-               BCAPTION <- "\\caption{"\r
-       } else {\r
-               BCAPTION <- paste("\\caption[", short.caption, "]{", sep="")\r
-       }       \r
-    ECAPTION <- "}\n"\r
-    BROW <- ""\r
-    EROW <- " \\\\ \n"\r
-    BTH <- ""\r
-    ETH <- ""\r
-    STH <- " & "\r
-    BTD1 <- " & "\r
-    BTD2 <- ""\r
-    BTD3 <- ""\r
-    ETD  <- ""\r
-    # Based on contribution from Jonathan Swinton <jonathan@swintons.net> in e-mail dated Wednesday, January 17, 2007\r
-    sanitize <- function(str) {\r
-      result <- str\r
-      result <- gsub("\\\\","SANITIZE.BACKSLASH",result)\r
-      result <- gsub("$","\\$",result,fixed=TRUE)\r
-      result <- gsub(">","$>$",result,fixed=TRUE)\r
-      result <- gsub("<","$<$",result,fixed=TRUE)\r
-      result <- gsub("|","$|$",result,fixed=TRUE)\r
-      result <- gsub("{","\\{",result,fixed=TRUE)\r
-      result <- gsub("}","\\}",result,fixed=TRUE)\r
-      result <- gsub("%","\\%",result,fixed=TRUE)\r
-      result <- gsub("&","\\&",result,fixed=TRUE)\r
-      result <- gsub("_","\\_",result,fixed=TRUE)\r
-      result <- gsub("#","\\#",result,fixed=TRUE)\r
-      result <- gsub("^","\\verb|^|",result,fixed=TRUE)\r
-      result <- gsub("~","\\~{}",result,fixed=TRUE)\r
-      result <- gsub("SANITIZE.BACKSLASH","$\\backslash$",result,fixed=TRUE)\r
-      return(result)\r
+        BCAPTION <- paste("\\caption[", short.caption, "]{", sep = "")\r
     }\r
-    sanitize.numbers <- function(x) {\r
-      result <- x\r
-      if ( math.style.negative ) {\r
-        # Jake Bowers <jwbowers@illinois.edu> in e-mail from 2008-08-20 suggested\r
-        # disabling this feature to avoid problems with LaTeX's dcolumn package.\r
-        # by Florian Wickelmaier <florian.wickelmaier@uni-tuebingen.de> in e-mail\r
-        # from 2008-10-03 requested the ability to use the old behavior.\r
-        for(i in 1:length(x)) {\r
-          result[i] <- gsub("-","$-$",result[i],fixed=TRUE)\r
+        ECAPTION <- "}\n"\r
+        BROW <- ""\r
+        EROW <- " \\\\ \n"\r
+        BTH <- ""\r
+        ETH <- ""\r
+        STH <- " & "\r
+        BTD1 <- " & "\r
+        BTD2 <- ""\r
+        BTD3 <- ""\r
+        ETD  <- ""\r
+        ## Based on contribution from Jonathan Swinton <jonathan@swintons.net> in e-mail dated Wednesday, January 17, 2007\r
+        sanitize <- function(str) {\r
+            result <- str\r
+            result <- gsub("\\\\", "SANITIZE.BACKSLASH", result)\r
+            result <- gsub("$", "\\$", result, fixed = TRUE)\r
+            result <- gsub(">", "$>$", result, fixed = TRUE)\r
+            result <- gsub("<", "$<$", result, fixed = TRUE)\r
+            result <- gsub("|", "$|$", result, fixed = TRUE)\r
+            result <- gsub("{", "\\{", result, fixed = TRUE)\r
+            result <- gsub("}", "\\}", result, fixed = TRUE)\r
+            result <- gsub("%", "\\%", result, fixed = TRUE)\r
+            result <- gsub("&", "\\&", result, fixed = TRUE)\r
+            result <- gsub("_", "\\_", result, fixed = TRUE)\r
+            result <- gsub("#", "\\#", result, fixed = TRUE)\r
+            result <- gsub("^", "\\verb|^|", result, fixed = TRUE)\r
+            result <- gsub("~", "\\~{}", result, fixed = TRUE)\r
+            result <- gsub("SANITIZE.BACKSLASH", "$\\backslash$",\r
+                           result, fixed = TRUE)\r
+            return(result)\r
+        }\r
+        sanitize.numbers <- function(x) {\r
+            result <- x\r
+            if ( math.style.negative ) {\r
+                ## Jake Bowers <jwbowers@illinois.edu> in e-mail from 2008-08-20 suggested\r
+                ## disabling this feature to avoid problems with LaTeX's dcolumn package.\r
+                ## by Florian Wickelmaier <florian.wickelmaier@uni-tuebingen.de> in e-mail\r
+                ## from 2008-10-03 requested the ability to use the old behavior.\r
+                for(i in 1:length(x)) {\r
+                    result[i] <- gsub("-", "$-$", result[i], fixed = TRUE)\r
+                }\r
+            }\r
+            return(result)\r
+        }\r
+        sanitize.final <- function(result) {\r
+            return(result)\r
+        }\r
+    } else {\r
+        BCOMMENT <- "<!-- "\r
+        ECOMMENT <- " -->\n"\r
+        BTABLE <- paste("<TABLE ", html.table.attributes, ">\n", sep = "")\r
+        ETABLE <- "</TABLE>\n"\r
+        BENVIRONMENT <- ""\r
+        EENVIRONMENT <- ""\r
+        BTABULAR <- ""\r
+        ETABULAR <- ""\r
+        BSIZE <- ""\r
+        ESIZE <- ""\r
+        BLABEL <- "<A NAME="\r
+        ELABEL <- "></A>\n"\r
+        BCAPTION <- paste("<CAPTION ALIGN=\"", caption.placement, "\"> ",\r
+                          sep = "")\r
+        ECAPTION <- " </CAPTION>\n"\r
+        BROW <- "<TR>"\r
+        EROW <- " </TR>\n"\r
+        BTH <- " <TH> "\r
+        ETH <- " </TH> "\r
+        STH <- " </TH> <TH> "\r
+        BTD1 <- " <TD align=\""\r
+        align.tmp <- attr(x, "align", exact = TRUE)\r
+        align.tmp <- align.tmp[align.tmp!="|"]\r
+        BTD2 <- matrix(align.tmp[(2-pos):(ncol(x)+1)],\r
+                       nrow = nrow(x), ncol = ncol(x)+pos, byrow = TRUE)\r
+        ## Based on contribution from Jonathan Swinton <jonathan@swintons.net> in e-mail dated Wednesday, January 17, 2007\r
+        BTD2[regexpr("^p", BTD2)>0] <- "left"\r
+        BTD2[BTD2 == "r"] <- "right"\r
+        BTD2[BTD2 == "l"] <- "left"\r
+        BTD2[BTD2 == "c"] <- "center"\r
+        BTD3 <- "\"> "\r
+        ETD  <- " </TD>"\r
+        sanitize <- function(str) {\r
+            result <- str\r
+            result <- gsub("&", "&amp ", result, fixed = TRUE)\r
+            result <- gsub(">", "&gt ", result, fixed = TRUE)\r
+            result <- gsub("<", "&lt ", result, fixed = TRUE)\r
+            ## Kurt Hornik <Kurt.Hornik@wu-wien.ac.at> on 2006/10/05 recommended not escaping underscores.\r
+            ## result <- gsub("_", "\\_", result, fixed=TRUE)\r
+            return(result)\r
+        }\r
+        sanitize.numbers <- function(x) {\r
+            return(x)\r
+        }\r
+        sanitize.final <- function(result) {\r
+            ## Suggested by Uwe Ligges <ligges@statistik.uni-dortmund.de> in e-mail dated 2005-07-30.\r
+            result$text <- gsub("  *", " ",  result$text, fixed = TRUE)\r
+            result$text <- gsub(' align="left"',  "", result$text,\r
+                                fixed = TRUE)\r
+            return(result)\r
         }\r
-      }\r
-      return(result)\r
-    }\r
-    sanitize.final <- function(result) {\r
-      return(result)\r
-    }\r
-  } else {\r
-    BCOMMENT <- "<!-- "\r
-    ECOMMENT <- " -->\n"\r
-    BTABLE <- paste("<TABLE ",html.table.attributes,">\n",sep="")\r
-    ETABLE <- "</TABLE>\n"\r
-    BENVIRONMENT <- ""\r
-    EENVIRONMENT <- ""\r
-    BTABULAR <- ""\r
-    ETABULAR <- ""\r
-    BSIZE <- ""\r
-    ESIZE <- ""\r
-    BLABEL <- "<A NAME="\r
-    ELABEL <- "></A>\n"\r
-    BCAPTION <- paste("<CAPTION ALIGN=\"",caption.placement,"\"> ",sep="")\r
-    ECAPTION <- " </CAPTION>\n"\r
-    BROW <- "<TR>"\r
-    EROW <- " </TR>\n"\r
-    BTH <- " <TH> "\r
-    ETH <- " </TH> "\r
-    STH <- " </TH> <TH> "\r
-    BTD1 <- " <TD align=\""\r
-    align.tmp <- attr(x,"align",exact=TRUE)\r
-    align.tmp <- align.tmp[align.tmp!="|"]\r
-    BTD2 <- matrix(align.tmp[(2-pos):(ncol(x)+1)],nrow=nrow(x),ncol=ncol(x)+pos,byrow=TRUE)\r
-    # Based on contribution from Jonathan Swinton <jonathan@swintons.net> in e-mail dated Wednesday, January 17, 2007\r
-    BTD2[regexpr("^p",BTD2)>0] <- "left"\r
-    BTD2[BTD2=="r"] <- "right"\r
-    BTD2[BTD2=="l"] <- "left"\r
-    BTD2[BTD2=="c"] <- "center"\r
-    BTD3 <- "\"> "\r
-    ETD  <- " </TD>"\r
-    sanitize <- function(str) {\r
-      result <- str\r
-      result <- gsub("&","&amp ",result,fixed=TRUE)\r
-      result <- gsub(">","&gt ",result,fixed=TRUE)\r
-      result <- gsub("<","&lt ",result,fixed=TRUE)\r
-      # Kurt Hornik <Kurt.Hornik@wu-wien.ac.at> on 2006/10/05 recommended not escaping underscores.\r
-      # result <- gsub("_", "\\_", result, fixed=TRUE)\r
-      return(result)\r
-    }\r
-    sanitize.numbers <- function(x) {\r
-      return(x)\r
     }\r
-    sanitize.final <- function(result) {\r
-      # Suggested by Uwe Ligges <ligges@statistik.uni-dortmund.de> in e-mail dated 2005-07-30.\r
-      result$text <- gsub("  *"," ", result$text,fixed=TRUE)\r
-      result$text <- gsub(' align="left"', "", result$text,fixed=TRUE)\r
-      return(result)\r
+\r
+    result <- string("", file = file, append = append)\r
+    info <- R.Version()\r
+    ## modified Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 to set automatically the package version\r
+    result <- result + BCOMMENT + type + " table generated in " +\r
+        info$language + " " + info$major + "." + info$minor + " by xtable " + packageDescription('xtable')$Version + " package" + ECOMMENT\r
+    result <- result + BCOMMENT + date() + ECOMMENT\r
+  ## Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 only.contents\r
+    if (!only.contents) {\r
+        result <- result + BTABLE\r
+        result <- result + BENVIRONMENT\r
+        if ( floating == TRUE ) {\r
+            if ((!is.null(caption)) &&\r
+                (type == "html" ||caption.placement == "top")) {\r
+                result <- result + BCAPTION + caption + ECAPTION\r
+            }\r
+            if (!is.null(attr(x, "label", exact = TRUE)) &&\r
+                (type == "latex" && caption.placement == "top")) {\r
+                result <- result + BLABEL +\r
+                          attr(x, "label", exact = TRUE) + ELABEL\r
+            }\r
+        }\r
+        result <- result + BSIZE\r
+        result <- result + BTABULAR\r
     }\r
-  }\r
-\r
-  result <- string("",file=file,append=append)\r
-  info <- R.Version()\r
-  # modified Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 to set automatically the package version\r
-  result <- result + BCOMMENT + type + " table generated in " +\r
-            info$language + " " + info$major + "." + info$minor + " by xtable " + packageDescription('xtable')$Version + " package" + ECOMMENT\r
-  result <- result + BCOMMENT + date() + ECOMMENT\r
-  # Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 only.contents\r
-  if (!only.contents) {\r
-    result <- result + BTABLE\r
-    result <- result + BENVIRONMENT\r
-    if ( floating == TRUE ) {\r
-      if ((!is.null(caption)) && (type=="html" || caption.placement=="top")) result <- result + BCAPTION + caption + ECAPTION\r
-      if (!is.null(attr(x,"label",exact=TRUE)) && (type=="latex" && caption.placement=="top")) result <- result + BLABEL + attr(x,"label",exact=TRUE) + ELABEL  \r
+    ## Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 include.colnames, include.rownames\r
+    if (include.colnames) {\r
+        result <- result + BROW + BTH\r
+        if (include.rownames) {\r
+            result <- result + STH\r
+       }\r
+        ## David G. Whiting in e-mail 2007-10-09\r
+        if (is.null(sanitize.colnames.function)) {\r
+            CNAMES <- sanitize(names(x))\r
+       } else {\r
+            CNAMES <- sanitize.colnames.function(names(x))\r
+       }\r
+        if (rotate.colnames) {\r
+            ##added by Markus Loecher, 2009-11-16\r
+            CNAMES <- paste("\\begin{sideways}", CNAMES, "\\end{sideways}")\r
+       }\r
+        result <- result + paste(CNAMES, collapse = STH)\r
+\r
+        result <- result + ETH + EROW\r
     }\r
-    result <- result + BSIZE\r
-    result <- result + BTABULAR\r
-  }\r
-  # Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 include.colnames, include.rownames \r
-  if (include.colnames) {\r
-    result <- result + BROW + BTH\r
+\r
+    cols <- matrix("", nrow = nrow(x), ncol = ncol(x)+pos)\r
     if (include.rownames) {\r
-         result <- result + STH\r
-       }  \r
-    # David G. Whiting in e-mail 2007-10-09\r
-    if (is.null(sanitize.colnames.function)) {                                     \r
-         CNAMES <- sanitize(names(x))\r
-       } else {\r
-      CNAMES <- sanitize.colnames.function(names(x))\r
+        ## David G. Whiting in e-mail 2007-10-09\r
+        if (is.null(sanitize.rownames.function)) {\r
+            RNAMES <- sanitize(row.names(x))\r
+        } else {\r
+            RNAMES <- sanitize.rownames.function(row.names(x))\r
+        }\r
+        if (rotate.rownames) {\r
+            ##added by Markus Loecher, 2009-11-16\r
+            RNAMES <- paste("\\begin{sideways}", RNAMES, "\\end{sideways}")\r
        }\r
-    if (rotate.colnames) {\r
-         #added by Markus Loecher, 2009-11-16\r
-      CNAMES <- paste("\\begin{sideways}", CNAMES, "\\end{sideways}")\r
-       }       \r
-    result <- result + paste(CNAMES, collapse=STH)\r
-\r
-    result <- result + ETH + EROW\r
-  }\r
-\r
-  cols <- matrix("",nrow=nrow(x),ncol=ncol(x)+pos)\r
-  if (include.rownames) {\r
-    # David G. Whiting in e-mail 2007-10-09\r
-    if (is.null(sanitize.rownames.function)) {                                     \r
-      RNAMES <- sanitize(row.names(x))\r
-    } else {\r
-      RNAMES <- sanitize.rownames.function(row.names(x))                         \r
+       cols[, 1] <- RNAMES\r
     }\r
-    if (rotate.rownames) {\r
-         #added by Markus Loecher, 2009-11-16\r
-      RNAMES <- paste("\\begin{sideways}", RNAMES, "\\end{sideways}")\r
-       }       \r
-       cols[,1] <- RNAMES\r
-  }\r
 \r
 ## Begin vectorizing the formatting code by Ian Fellows [ian@fellstat.com]\r
 ## 06 Dec 2011\r
 ##\r
-#  disp <- function(y) {\r
-#    if (is.factor(y)) {\r
-#      y <- levels(y)[y]\r
-#    }\r
-#    if (is.list(y)) {\r
-#      y <- unlist(y)\r
-#    }\r
-#    return(y)\r
-#  }\r
-  varying.digits <- is.matrix( attr( x, "digits",exact=TRUE ) )\r
-  # Code for letting "digits" be a matrix was provided by Arne Henningsen <ahenningsen@agric-econ.uni-kiel.de> in e-mail dated 2005-06-04.\r
-  #if( !varying.digits ) {\r
-    # modified Claudio Agostinelli <claudio@unive.it> dated 2006-07-28\r
-  #  attr(x,"digits") <- matrix( attr( x, "digits",exact=TRUE ), nrow = nrow(x), ncol = ncol(x)+1, byrow = TRUE )\r
-  #}\r
-  for(i in 1:ncol(x)) {\r
-       xcol <- x[,i]\r
+##  disp <- function(y) {\r
+##    if (is.factor(y)) {\r
+##      y <- levels(y)[y]\r
+##    }\r
+##    if (is.list(y)) {\r
+##      y <- unlist(y)\r
+##    }\r
+##    return(y)\r
+##  }\r
+    varying.digits <- is.matrix( attr( x, "digits", exact = TRUE ) )\r
+    ## Code for letting "digits" be a matrix was provided by Arne Henningsen <ahenningsen@agric-econ.uni-kiel.de> in e-mail dated 2005-06-04.\r
+    ##if( !varying.digits ) {\r
+    ## modified Claudio Agostinelli <claudio@unive.it> dated 2006-07-28\r
+    ##  attr(x,"digits") <- matrix( attr( x, "digits",exact=TRUE ), nrow = nrow(x), ncol = ncol(x)+1, byrow = TRUE )\r
+  ##}\r
+    for(i in 1:ncol(x)) {\r
+       xcol <- x[, i]\r
        if(is.factor(xcol))\r
-               xcol <- as.character(xcol)\r
+            xcol <- as.character(xcol)\r
        if(is.list(xcol))\r
-               xcol <- sapply(xcol,unlist)\r
-    ina <- is.na(xcol)\r
-    is.numeric.column <- is.numeric(xcol)\r
+            xcol <- sapply(xcol, unlist)\r
+        ina <- is.na(xcol)\r
+        is.numeric.column <- is.numeric(xcol)\r
 \r
        if(is.character(xcol)) {\r
-               cols[,i+pos] <- xcol\r
+            cols[, i+pos] <- xcol\r
        } else {\r
-         if (is.null(format.args)){\r
-           format.args <- list()\r
-         }\r
-         if (is.null(format.args$decimal.mark)){\r
-           format.args$decimal.mark <- options()$OutDec\r
-         }\r
-         if(!varying.digits){\r
-               curFormatArgs <- c(list( \r
-                   x = xcol,\r
-                       format = 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
+            if (is.null(format.args)){\r
+                format.args <- list()\r
+            }\r
+            if (is.null(format.args$decimal.mark)){\r
+                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
+                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",exact=TRUE )[j,i+1] < 0, "E", \r
-              attr( x, "display",exact=TRUE )[i+1] ), \r
-            digits = abs( attr( x, "digits",exact=TRUE )[j,i+1] )),\r
-                       format.args)\r
-                 cols[j,i+pos] <- do.call("formatC", curFormatArgs)                    \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
+                    cols[j, i+pos] <- do.call("formatC", curFormatArgs)\r
                }\r
-      }        \r
+            }\r
        }\r
        ## End Ian Fellows changes\r
-       \r
-    if ( any(ina) ) cols[ina,i+pos] <- NA.string\r
-    # Based on contribution from Jonathan Swinton <jonathan@swintons.net> in e-mail dated Wednesday, January 17, 2007\r
-    if ( is.numeric.column ) {\r
-      cols[,i+pos] <- sanitize.numbers(cols[,i+pos])\r
-    } else {\r
-      if (is.null(sanitize.text.function)) {\r
-        cols[,i+pos] <- sanitize(cols[,i+pos])\r
-      } else {\r
-        cols[,i+pos] <- sanitize.text.function(cols[,i+pos])\r
-      }\r
-    }\r
-  }\r
-\r
-  multiplier <- 5\r
-  full <- matrix("",nrow=nrow(x),ncol=multiplier*(ncol(x)+pos)+2)\r
-  full[,1] <- BROW\r
-  full[,multiplier*(0:(ncol(x)+pos-1))+2] <- BTD1\r
-  full[,multiplier*(0:(ncol(x)+pos-1))+3] <- BTD2\r
-  full[,multiplier*(0:(ncol(x)+pos-1))+4] <- BTD3\r
-  full[,multiplier*(0:(ncol(x)+pos-1))+5] <- cols\r
-  full[,multiplier*(0:(ncol(x)+pos-1))+6] <- ETD\r
-\r
-  full[,multiplier*(ncol(x)+pos)+2] <- paste(EROW, lastcol[-(1:2)], sep=" ")\r
\r
-  if (type=="latex") full[,2] <- ""\r
-  result <- result + lastcol[2] + paste(t(full),collapse="")\r
-  if (!only.contents) {\r
-    if (tabular.environment == "longtable") {\r
-         # booktabs change added the if() - 1 Feb 2012\r
-         if(!booktabs) {\r
-           result <- result + PHEADER\r
-      }\r
-         \r
-      ## fix 10-27-09 Liviu Andronic (landronimirc@gmail.com) the following 'if' condition is inserted in order to avoid\r
-      ## that bottom caption interferes with a top caption of a longtable\r
-      if(caption.placement=="bottom"){\r
-        if ((!is.null(caption)) && (type=="latex")) result <- result + BCAPTION + caption + ECAPTION\r
-      }\r
-      if (!is.null(attr(x,"label",exact=TRUE))) result <- result + BLABEL + attr(x,"label",exact=TRUE) + ELABEL\r
-      ETABULAR <- "\\end{longtable}\n"\r
+\r
+        if ( any(ina) ) cols[ina, i+pos] <- NA.string\r
+        ## Based on contribution from Jonathan Swinton <jonathan@swintons.net> in e-mail dated Wednesday, January 17, 2007\r
+        if ( is.numeric.column ) {\r
+            cols[, i+pos] <- sanitize.numbers(cols[, i+pos])\r
+        } else {\r
+            if (is.null(sanitize.text.function)) {\r
+                cols[, i+pos] <- sanitize(cols[, i+pos])\r
+            } else {\r
+                cols[, i+pos] <- sanitize.text.function(cols[, i+pos])\r
+            }\r
+        }\r
     }\r
-    result <- result + ETABULAR\r
-    result <- result + ESIZE\r
-    if ( floating == TRUE ) {\r
-      if ((!is.null(caption)) && (type=="latex" && caption.placement=="bottom")) result <- result + BCAPTION + caption + ECAPTION\r
-      if (!is.null(attr(x,"label",exact=TRUE)) && caption.placement=="bottom") result <- result + BLABEL + attr(x,"label",exact=TRUE) + ELABEL  \r
+\r
+    multiplier <- 5\r
+    full <- matrix("", nrow = nrow(x), ncol = multiplier*(ncol(x)+pos)+2)\r
+    full[, 1] <- BROW\r
+    full[, multiplier*(0:(ncol(x)+pos-1))+2] <- BTD1\r
+    full[, multiplier*(0:(ncol(x)+pos-1))+3] <- BTD2\r
+    full[, multiplier*(0:(ncol(x)+pos-1))+4] <- BTD3\r
+    full[, multiplier*(0:(ncol(x)+pos-1))+5] <- cols\r
+    full[, multiplier*(0:(ncol(x)+pos-1))+6] <- ETD\r
+\r
+    full[, multiplier*(ncol(x)+pos)+2] <- paste(EROW, lastcol[-(1:2)],\r
+                                                sep = " ")\r
+\r
+    if (type == "latex") full[, 2] <- ""\r
+    result <- result + lastcol[2] + paste(t(full), collapse = "")\r
+    if (!only.contents) {\r
+        if (tabular.environment == "longtable") {\r
+            ## booktabs change added the if() - 1 Feb 2012\r
+            if(!booktabs) {\r
+                result <- result + PHEADER\r
+            }\r
+\r
+            ## fix 10-27-09 Liviu Andronic (landronimirc@gmail.com) the following 'if' condition is inserted in order to avoid\r
+            ## that bottom caption interferes with a top caption of a longtable\r
+            if(caption.placement == "bottom"){\r
+                if ((!is.null(caption)) && (type == "latex")) {\r
+                    result <- result + BCAPTION + caption + ECAPTION\r
+                }\r
+            }\r
+            if (!is.null(attr(x, "label", exact = TRUE))) {\r
+                result <- result + BLABEL + attr(x, "label", exact = TRUE) +\r
+                    ELABEL\r
+            }\r
+            ETABULAR <- "\\end{longtable}\n"\r
+        }\r
+        result <- result + ETABULAR\r
+        result <- result + ESIZE\r
+        if ( floating == TRUE ) {\r
+            if ((!is.null(caption)) &&\r
+                (type == "latex" && caption.placement == "bottom")) {\r
+                result <- result + BCAPTION + caption + ECAPTION\r
+            }\r
+            if (!is.null(attr(x, "label", exact = TRUE)) &&\r
+                caption.placement == "bottom") {\r
+                result <- result + BLABEL + attr(x, "label", exact = TRUE) +\r
+                    ELABEL\r
+            }\r
+        }\r
+        result <- result + EENVIRONMENT\r
+        result <- result + ETABLE\r
     }\r
-    result <- result + EENVIRONMENT\r
-    result <- result + ETABLE\r
-  }   \r
-  result <- sanitize.final(result)\r
-  \r
-  if (print.results){\r
+    result <- sanitize.final(result)\r
+\r
+    if (print.results){\r
        print(result)\r
-  }\r
-  \r
-  return(invisible(result$text))\r
-}\r
+    }\r
 \r
-"+.string" <- function(x,y) {\r
-  x$text <- paste(x$text,as.string(y)$text,sep="")\r
-  return(x)\r
+    return(invisible(result$text))\r
 }\r
 \r
-print.string <- function(x,...) {\r
-  cat(x$text,file=x$file,append=x$append)\r
-  return(invisible())\r
+"+.string" <- function(x, y) {\r
+    x$text <- paste(x$text, as.string(y)$text, sep = "")\r
+    return(x)\r
 }\r
 \r
-string <- function(text,file="",append=FALSE) {\r
-  x <- list(text=text,file=file,append=append)\r
-  class(x) <- "string"\r
-  return(x)\r
+print.string <- function(x, ...) {\r
+    cat(x$text, file = x$file, append = x$append)\r
+    return(invisible())\r
 }\r
 \r
-as.string <- function(x,file="",append=FALSE) {\r
-  if (is.null(attr(x,"class",exact=TRUE)))\r
-  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
-  if (class(x)=="string")\r
+string <- function(text, file = "", append = FALSE) {\r
+    x <- list(text = text, file = file, append = append)\r
+    class(x) <- "string"\r
     return(x)\r
-  stop("Cannot coerse argument to a string")\r
+}\r
+\r
+as.string <- function(x, file = "", append = FALSE) {\r
+    if (is.null(attr(x, "class", exact = TRUE)))\r
+        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
+    if (class(x) == "string")\r
+        return(x)\r
+    stop("Cannot coerse argument to a string")\r
 }\r
 \r
 is.string <- function(x) {\r
-  return(class(x)=="string")\r
+    return(class(x) == "string")\r
 }\r
 \r
index 26dfe98b632377bd8a9c19a9cebd90dab967aa0a..03e35897df63186447ccf082e8399d00f8490252 100644 (file)
 \name{print.xtable}\r
 \alias{print.xtable}\r
 \title{Print Export Tables}\r
-\description{Function returning and displaying or writing to disk the LaTeX or HTML code associated with the supplied object of class \code{xtable}.}\r
+\description{\r
+  Function returning and displaying or writing to disk the LaTeX or HTML\r
+  code associated with the supplied object of class \code{xtable}.\r
+}\r
 \usage{\r
 \method{print}{xtable}(x, \r
-  type=getOption("xtable.type", "latex"),\r
-  file=getOption("xtable.file", ""),\r
-  append=getOption("xtable.append", FALSE),\r
-  floating=getOption("xtable.floating", TRUE),\r
-  floating.environment=getOption("xtable.floating.environment", "table"),\r
-  table.placement=getOption("xtable.table.placement", "ht"),\r
-  caption.placement=getOption("xtable.caption.placement", "bottom"),\r
-  latex.environments=getOption("xtable.latex.environments", c("center")),\r
-  tabular.environment=getOption("xtable.tabular.environment", "tabular"),\r
-  size=getOption("xtable.size", NULL),\r
-  hline.after=getOption("xtable.hline.after", c(-1,0,nrow(x))),\r
-  NA.string=getOption("xtable.NA.string", ""),\r
-  include.rownames=getOption("xtable.include.rownames", TRUE),\r
-  include.colnames=getOption("xtable.include.colnames", TRUE),\r
-  only.contents=getOption("xtable.only.contents", FALSE),\r
-  add.to.row=getOption("xtable.add.to.row", NULL),\r
-  sanitize.text.function=getOption("xtable.sanitize.text.function", NULL),\r
-  sanitize.rownames.function=getOption("xtable.sanitize.rownames.function", \r
-    sanitize.text.function),\r
-  sanitize.colnames.function=getOption("xtable.sanitize.colnames.function", \r
-    sanitize.text.function),\r
-  math.style.negative=getOption("xtable.math.style.negative", FALSE),\r
-  html.table.attributes=getOption("xtable.html.table.attributes", "border=1"),\r
-  print.results=getOption("xtable.print.results", TRUE),\r
-  format.args=getOption("xtable.format.args", NULL),\r
-  rotate.rownames=getOption("xtable.rotate.rownames", FALSE),\r
-  rotate.colnames=getOption("xtable.rotate.colnames", FALSE),\r
+  type = getOption("xtable.type", "latex"),\r
+  file = getOption("xtable.file", ""),\r
+  append = getOption("xtable.append", FALSE),\r
+  floating = getOption("xtable.floating", TRUE),\r
+  floating.environment = getOption("xtable.floating.environment", "table"),\r
+  table.placement = getOption("xtable.table.placement", "ht"),\r
+  caption.placement = getOption("xtable.caption.placement", "bottom"),\r
+  latex.environments = getOption("xtable.latex.environments", c("center")),\r
+  tabular.environment = getOption("xtable.tabular.environment", "tabular"),\r
+  size = getOption("xtable.size", NULL),\r
+  hline.after = getOption("xtable.hline.after", c(-1,0,nrow(x))),\r
+  NA.string = getOption("xtable.NA.string", ""),\r
+  include.rownames = getOption("xtable.include.rownames", TRUE),\r
+  include.colnames = getOption("xtable.include.colnames", TRUE),\r
+  only.contents = getOption("xtable.only.contents", FALSE),\r
+  add.to.row = getOption("xtable.add.to.row", NULL),\r
+  sanitize.text.function = getOption("xtable.sanitize.text.function", NULL),\r
+  sanitize.rownames.function = getOption("xtable.sanitize.rownames.function", \r
+                                         sanitize.text.function),\r
+  sanitize.colnames.function = getOption("xtable.sanitize.colnames.function", \r
+                                         sanitize.text.function),\r
+  math.style.negative = getOption("xtable.math.style.negative", FALSE),\r
+  html.table.attributes = getOption("xtable.html.table.attributes",\r
+                                    "border=1"),\r
+  print.results = getOption("xtable.print.results", TRUE),\r
+  format.args = getOption("xtable.format.args", NULL),\r
+  rotate.rownames = getOption("xtable.rotate.rownames", FALSE),\r
+  rotate.colnames = getOption("xtable.rotate.colnames", FALSE),\r
   booktabs = getOption("xtable.booktabs", FALSE),\r
   scalebox = getOption("xtable.scalebox", NULL),\r
   width = getOption("xtable.width", NULL),\r
   ...)}\r
 \arguments{\r
   \item{x}{An object of class \code{"xtable"}.}\r
-  \item{type}{Type of table to produce.  Possible values for \code{type} are \code{"latex"} or \code{"html"}.\r
-              Default value is \code{"latex"}.}\r
-  \item{file}{Name of file where the resulting code should be saved.  If \code{file=""}, output is displayed on screen.  Note that\r
-              the function also (invisibly) returns a character vector of the results (which can be helpful for post-processing).\r
-              Default value is \code{""}.}\r
-  \item{append}{If \code{TRUE} and \code{file!=""}, code will be appended to \code{file} instead of overwriting \code{file}.\r
-                Default value is \code{FALSE}.}\r
-  \item{floating}{If \code{TRUE} and \code{type="latex"}, the resulting table will be a floating table (using, for example, \code{\\begin\{table\}} and \code{\\end\{table\}}).  See \code{floating.environment} below. Default value is \code{TRUE}.}\r
-  \item{floating.environment}{If \code{floating=TRUE} and \code{type="latex"}, the resulting table uses the specified floating environment.\r
-  Possible values are \code{"table"}, \code{"table*"}, or \code{"sidewaystable"} (defined in the LaTeX package 'rotating').\r
-                Default value is \code{"table"}.}\r
-  \item{table.placement}{If \code{floating=TRUE} and \code{type="latex"}, the floating table will have placement given by \code{table.placement} where \code{table.placement} must be \code{NULL} or contain only elements of \{"h","t","b","p","!","H"\}.\r
-                Default value is \code{"ht"}.}\r
-  \item{caption.placement}{The caption will be have placed at the bottom of the table if \code{caption.placement} is \code{"bottom"} and at the top of the table if it equals \code{"top"}.\r
-                Default value is \code{"bottom"}.}\r
-  \item{latex.environments}{If \code{floating=TRUE} and \code{type="latex"}, the specificed latex environments (provided as a character vector) will enclose the tabuluar environment.\r
-                Default value is \code{"center"}.}\r
-  \item{tabular.environment}{When \code{type="latex"}, the tabular environment that will be used. Defaults to \code{"tabular"}. When working with tables that extend more than one page, using \code{tabular.environment="longtable"} and the LaTeX package \code{"longtable"} (see Fairbairns, 2005) allows one to typeset them uniformly. Note that \code{"floating"}  should be set to \code{"FALSE"} when using the \code{"longtable"} environment.}\r
-  \item{size}{An arbitrary character vector intended to be used to set the font size in a LaTeX table.  The supplied value (if not \code{NULL}) is inserted just before the tabular environment starts. Default value is \code{NULL}.}\r
-  \item{hline.after}{When \code{type="latex"}, a vector of numbers between -1 and \code{"nrow(x)"}, inclusive, indicating the rows after which a horizontal line should appear.  If \code{NULL} is used no lines are produced. Default value is \code{c(-1,0,nrow(x))} which means draw a line before and after the columns names and at the end of the table. Repeated values are allowed.}\r
-  \item{NA.string}{String to be used for missing values in table entries.  Default value is \code{""}.}\r
-  \item{include.rownames}{logical. If \code{TRUE} the rows names is printed. Default value is \code{TRUE}.}\r
-  \item{include.colnames}{logical. If \code{TRUE} the columns names is printed. Default value is \code{TRUE}.}\r
-  \item{only.contents}{logical. If \code{TRUE} only the rows of the table is printed. Default value is \code{FALSE}.}\r
-  \item{add.to.row}{a list of two components. The first component (which should be called 'pos') is a list contains the position of rows on which extra commands should be added at the end, The second component (which should be called 'command') is a character vector of the same length of the first component which contains the command that should be added at the end of the specified rows. Default value is \code{NULL}, i.e. do not add commands.}\r
-  \item{sanitize.text.function}{All non-numeric enteries (except row and column names) are sanitised in an attempt to remove characters which have special meaning for the output format. If \code{sanitize.text.function} is not NULL (the default), it should be a function taking a character vector and returning one, and will be used for the sanitization instead of the default internal function.}\r
-  \item{sanitize.rownames.function}{Like the \code{sanitize.text.function}, but applicable to row names.  The default uses the \code{sanitize.text.function}.}\r
-  \item{sanitize.colnames.function}{Like the \code{sanitize.text.function}, but applicable to column names.  The default uses the \code{sanitize.text.function}.}\r
-  \item{math.style.negative}{In a LaTeX table, if \code{TRUE}, then use $-$ for the negative sign (as was the behavior prior to version 1.5-3).  Default value is \code{FALSE}.}\r
-  \item{html.table.attributes}{In an HTML table, attributes associated with the \code{<TABLE>} tag.  Default value is \code{border=1}.}\r
-  \item{print.results}{If \code{TRUE}, the generated table is printed to standard output.  Set this to \code{FALSE} if you will just be using the character vector that is returned invisibly.}\r
-  \item{format.args}{List of arguments for the \code{formatC} function.  For example, standard German number separators can be specified as \code{format.args=list(big.mark = "'", decimal.mark = ","))}.}\r
-  \item{rotate.rownames}{If \code{TRUE}, the row names are displayed vertically in LaTeX.}\r
-  \item{rotate.colnames}{If \code{TRUE}, the column names are displayed vertically in LaTeX.}\r
-  \item{booktabs}{If \code{TRUE}, the \code{toprule}, \code{midrule} and \code{bottomrule} tags from the LaTex "booktabs" package are used rather than \code{hline} for the horizontal line tags.}\r
-  \item{scalebox}{If not \code{NULL}, a \code{scalebox} clause will be added around the tabular environment with the specified value used as the scaling factor.}\r
-  \item{width}{If not \code{NULL}, the specified value is included in parenthesis between the tabular environment \code{begin} tag and the alignment specification.  This allows specification of the table width when using tabular environments such as \code{tabular*} and \code{tabularx}.  Note that table width specification is not supported with the \code{tabular} or \code{longtable} environments.}\r
+  \item{type}{Type of table to produce.  Possible values for \code{type}\r
+    are \code{"latex"} or \code{"html"}.\r
+    Default value is \code{"latex"}.}\r
+  \item{file}{Name of file where the resulting code should be saved.  If\r
+    \code{file=""}, output is displayed on screen.  Note that the\r
+    function also (invisibly) returns a character vector of the results\r
+    (which can be helpful for post-processing).\r
+    Default value is \code{""}.}\r
+  \item{append}{If \code{TRUE} and \code{file!=""}, code will be\r
+    appended to \code{file} instead of overwriting \code{file}.\r
+    Default value is \code{FALSE}.}\r
+  \item{floating}{If \code{TRUE} and \code{type="latex"}, the resulting\r
+    table will be a floating table (using, for example,\r
+    \code{\\begin\{table\}} and \code{\\end\{table\}}).  See\r
+    \code{floating.environment} below.\r
+    Default value is \code{TRUE}. }\r
+  \item{floating.environment}{If \code{floating=TRUE} and\r
+    \code{type="latex"}, the resulting table uses the specified floating\r
+    environment. Possible values are \code{"table"}, \code{"table*"}, or\r
+    \code{"sidewaystable"} (defined in the LaTeX package\r
+    'rotating').\r
+    Default value is \code{"table"}.}\r
+  \item{table.placement}{If \code{floating=TRUE} and\r
+    \code{type="latex"}, the floating table will have placement given by\r
+    \code{table.placement} where \code{table.placement} must be\r
+    \code{NULL} or contain only elements of\r
+    \{"h","t","b","p","!","H"\}.\r
+    Default value is \code{"ht"}.}\r
+  \item{caption.placement}{The caption will be have placed at the bottom\r
+    of the table if \code{caption.placement} is \code{"bottom"} and at\r
+    the top of the table if it equals \code{"top"}.\r
+    Default value is \code{"bottom"}.}\r
+  \item{latex.environments}{If \code{floating=TRUE} and\r
+    \code{type="latex"}, the specificed latex environments (provided as\r
+    a character vector) will enclose the tabular environment.\r
+    Default value is \code{"center"}. }\r
+  \item{tabular.environment}{When \code{type="latex"}, the tabular\r
+    environment that will be used.\r
+    Defaults to \code{"tabular"}.\r
+    When working with tables that extend more than one page, using\r
+    \code{tabular.environment="longtable"} and the LaTeX package\r
+    \code{"longtable"} (see Fairbairns, 2005) allows one to typeset them\r
+    uniformly. Note that \code{"floating"} should be set to\r
+    \code{"FALSE"} when using the \code{"longtable"} environment.}\r
+  \item{size}{An arbitrary character vector intended to be used to set\r
+    the font size in a LaTeX table.  The supplied value (if not\r
+    \code{NULL}) is inserted just before the tabular environment\r
+    starts.\r
+    Default value is \code{NULL}. }\r
+  \item{hline.after}{When \code{type="latex"}, a vector of numbers\r
+    between -1 and \code{"nrow(x)"}, inclusive, indicating the rows\r
+    after which a horizontal line should appear.  If \code{NULL} is used\r
+    no lines are produced.\r
+    Default value is \code{c(-1,0,nrow(x))} which means draw a line\r
+    before and after the columns names and at the end of the\r
+    table. Repeated values are allowed.}\r
+  \item{NA.string}{String to be used for missing values in table\r
+    entries.\r
+    Default value is \code{""}.}\r
+  \item{include.rownames}{logical. If \code{TRUE} the rows names is\r
+    printed.\r
+    Default value is \code{TRUE}.}\r
+  \item{include.colnames}{logical. If \code{TRUE} the columns names is\r
+    printed.\r
+    Default value is \code{TRUE}.}\r
+  \item{only.contents}{logical. If \code{TRUE} only the rows of the\r
+    table is printed.\r
+    Default value is \code{FALSE}. }\r
+  \item{add.to.row}{a list of two components. The first component (which\r
+    should be called 'pos') is a list contains the position of rows on\r
+    which extra commands should be added at the end, The second\r
+    component (which should be called 'command') is a character vector\r
+    of the same length of the first component which contains the command\r
+    that should be added at the end of the specified rows.\r
+    Default value is \code{NULL}, i.e. do not add commands.}\r
+  \item{sanitize.text.function}{All non-numeric enteries (except row and\r
+    column names) are sanitised in an attempt to remove characters which\r
+    have special meaning for the output format. If\r
+    \code{sanitize.text.function} is not NULL (the default), it should\r
+    be a function taking a character vector and returning one, and will\r
+    be used for the sanitization instead of the default internal\r
+    function.}\r
+  \item{sanitize.rownames.function}{Like the\r
+    \code{sanitize.text.function}, but applicable to row names.\r
+    The default uses the \code{sanitize.text.function}. }\r
+  \item{sanitize.colnames.function}{Like the\r
+    \code{sanitize.text.function}, but applicable to column names.\r
+    The default uses the \code{sanitize.text.function}. }\r
+  \item{math.style.negative}{In a LaTeX table, if \code{TRUE}, then use\r
+    $-$ for the negative sign (as was the behavior prior to version 1.5-3).\r
+    Default value is \code{FALSE}.}\r
+  \item{html.table.attributes}{In an HTML table, attributes associated\r
+    with the \code{<TABLE>}tag.\r
+    Default value is \code{border=1}.}\r
+  \item{print.results}{If \code{TRUE}, the generated table is printed to\r
+    standard output.  Set this to \code{FALSE} if you will just be using\r
+    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
+  \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
+    vertically in LaTeX. }\r
+  \item{booktabs}{If \code{TRUE}, the \code{toprule}, \code{midrule} and\r
+    \code{bottomrule} tags from the LaTex "booktabs" package are used\r
+    rather than \code{hline} for the horizontal line tags. }\r
+  \item{scalebox}{If not \code{NULL}, a \code{scalebox} clause will be\r
+    added around the tabular environment with the specified value used\r
+    as the scaling factor. }\r
+  \item{width}{If not \code{NULL}, the specified value is included in\r
+    parenthesis between the tabular environment \code{begin} tag and the\r
+    alignment specification.  This allows specification of the table\r
+    width when using tabular environments such as \code{tabular*} and\r
+    \code{tabularx}.  Note that table width specification is not\r
+    supported with the \code{tabular} or \code{longtable} environments. }\r
   \item{...}{Additional arguments.  (Currently ignored.)}\r
 }\r
 \details{\r
-  This function displays or writes to disk the code to produce a table associated with an object \code{x} of class \code{"xtable"}.\r
-  The resulting code is either a LaTeX or HTML table, depending on the value of \code{type}.  The function also (invisibly) returns a character vector\r
-  of the results (which can be helpful for post-processing).\r
+  This function displays or writes to disk the code to produce a table\r
+  associated with an object \code{x} of class \code{"xtable"}. \r
+  The resulting code is either a LaTeX or HTML table, depending on the\r
+  value of \code{type}.  The function also (invisibly) returns a\r
+  character vector of the results (which can be helpful for\r
+  post-processing).\r
 \r
-  Since version 1.4 the non default behavior of \code{hline.after} is changed. To obtain the same results as the previous versions add to the \code{hline.after} vector the vector \code{c(-1, 0, nrow(x))} where \code{nrow(x)} is the numbers of rows of the object.\r
+  Since version 1.4 the non default behavior of \code{hline.after} is\r
+  changed. To obtain the same results as the previous versions add to\r
+  the \code{hline.after} vector the vector \code{c(-1, 0, nrow(x))}\r
+  where \code{nrow(x)} is the numbers of rows of the object. \r
 \r
-  From version 1.4-3, all non-numeric columns are sanitized, and all LaTeX special characters are sanitised for LaTeX output.  See Section 3 of the \code{xtableGallery} vignette for an example of customising the sanitization.\r
-  From version 1.4-4, the sanitization also applies to column names.  To remove any text sanitization, specify \code{sanitize.text.function=function(x){x}}.\r
+  From version 1.4-3, all non-numeric columns are sanitized, and all\r
+  LaTeX special characters are sanitised for LaTeX output.  See Section\r
+  3 of the \code{xtableGallery} vignette for an example of customising\r
+  the sanitization. From version 1.4-4, the sanitization also applies to\r
+  column names.  To remove any text sanitization, specify\r
+  \code{sanitize.text.function=function(x){x}}.  \r
   \r
-  From version 1.6-1 the default values for the arguments other than \code{x} are obtainined using \code{getOption()}.  Hence the user can set the values once with \code{options()} rather than setting them in every call to \code{print.xtable()}.\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
+}\r
+\author{\r
+  David Dahl \email{dahl@stat.tamu.edu} with contributions and\r
+  suggestions from many others (see source code).\r
 }\r
-\author{David Dahl \email{dahl@stat.tamu.edu} with contributions and suggestions from many others (see source code).}\r
 \references{\r
-       Fairbairns, Robin (2005) \emph{Tables longer than a single page} The UK List of TeX Frequently Asked Questions on the Web. \url{http://www.tex.ac.uk/cgi-bin/texfaq2html?label=longtab}\r
+  Fairbairns, Robin (2005) \emph{Tables longer than a single page} The\r
+  UK List of TeX Frequently Asked Questions on the\r
+  Web. \url{http://www.tex.ac.uk/cgi-bin/texfaq2html?label=longtab}\r
+}\r
+\seealso{\r
+  \code{\link{xtable}}, \code{\link{caption}}, \code{\link{label}}, \r
+  \code{\link{align}}, \code{\link{digits}}, \code{\link{display}},\r
+  \code{\link{formatC}} \r
 }\r
-\seealso{\code{\link{xtable}}, \code{\link{caption}}, \code{\link{label}}, \r
-         \code{\link{align}}, \code{\link{digits}}, \code{\link{display}}, \code{\link{formatC}}}\r
 \r
 \keyword{print}\r
index b8a7f996d6b352b9ba7ae609b50e4431826b943b..52d91b9b6e0aa5b2a389dafc04b9b48f6f8aea08 100644 (file)
 \alias{xtable.table}
 \alias{xtable.zoo}
 \title{Create Export Tables}
-\description{Function converting an R object to an \code{xtable} object, which can then be printed as a LaTeX or HTML table.}
+\description{
+  Function converting an R object to an \code{xtable} object, which can
+  then be printed as a LaTeX or HTML table.
+}
 \usage{
-xtable(x, caption=NULL, label=NULL, align=NULL, digits=NULL,
-       display=NULL, ...)
+xtable(x, caption = NULL, label = NULL, align = NULL, digits = NULL,
+       display = NULL, ...)
 }
 \arguments{
-  \item{x}{An R object of class found among \code{methods(xtable)}.  See below on how to write additional method functions
-           for \code{xtable}.}
-  \item{caption}{Character vector of length 1 or 2 containing the table's caption or title.  If length 2, the second item 
-               is the "short caption" used when LaTeX generates a "List of Tables".
-                 Set to \code{NULL} to suppress the caption.  Default value is \code{NULL}.}
-  \item{label}{Character vector of length 1 containing the LaTeX label or HTML anchor.
-               Set to \code{NULL} to suppress the label.  Default value is \code{NULL}.}
-  \item{align}{Character vector of length equal to the number of columns of the resulting
-               table indicating the alignment of the corresponding columns.  Also, \code{"|"} may be used
-               to produce vertical lines between columns in LaTeX tables, but these are effectively ignored
-               when considering the required length of the supplied vector.  If a character vector of length one
-               is supplied, it is split as \code{strsplit(align,"")[[1]]} before processing.
-               Since the row names are printed in the first column, the length of \code{align}
-               is one greater than \code{ncol(x)} if \code{x} is a \code{data.frame}.
-               Use \code{"l"}, \code{"r"}, and \code{"c"} to denote left, right, and
-               center alignment, respectively.  Use \code{"p\{3cm\}"} etc for a LaTeX column of the specified width.
-               For HTML output the \code{"p"} alignment is interpreted as \code{"l"}, ignoring
-               the width request. Default depends on the class of \code{x}.}
-  \item{digits}{Numeric vector of length equal to one (in which case it will be replicated as necessary)
-                or to the number of columns of the resulting
-                table \bold{or} matrix of the same size as the resulting table 
-                indicating the number of digits to display in the corresponding columns.
-                Since the row names are printed in the first column, the length of the 
-                vector \code{digits} or the number of columns of the matrix \code{digits}
-                is one greater than \code{ncol(x)} if \code{x} is a \code{data.frame}.
-                Default depends of class of \code{x}.
-                If values of \code{digits} are negative, the corresponding values 
-                of \code{x} are displayed in scientific format with \code{abs(digits)}
-                digits.}
-  \item{display}{Character vector of length equal to the number of columns of the resulting
-                 table indicating the format for the corresponding columns.
-                 Since the row names are printed in the first column, the length of \code{display}
-                 is one greater than \code{ncol(x)} if \code{x} is a \code{data.frame}.
-                 These values are passed to the \code{formatC} function.  Use \code{"d"} (for integers),
-                 \code{"f"}, \code{"e"}, \code{"E"}, \code{"g"}, \code{"G"}, \code{"fg"} (for
-                 reals), or \code{"s"} (for strings).
-                 \code{"f"} gives numbers in the usual \code{xxx.xxx} format;  \code{"e"} and
-                 \code{"E"} give \code{n.ddde+nn} or \code{n.dddE+nn} (scientific format);
-                 \code{"g"} and \code{"G"} put \code{x[i]} into scientific format only if it saves
-                 space to do so.  \code{"fg"} uses fixed format as \code{"f"}, but \code{digits} as
-                 number of \emph{significant} digits.  Note that this can lead to
-                 quite long result strings.  Default depends on the class of \code{x}.}
+  \item{x}{An R object of class found among \code{methods(xtable)}.  See
+    below on how to write additional method functions for \code{xtable}.}
+  \item{caption}{Character vector of length 1 or 2 containing the
+    table's caption or title.  If length 2, the second item is the
+    "short caption" used when LaTeX generates a "List of Tables". Set to
+    \code{NULL} to suppress the caption.  Default value is \code{NULL}. }
+  \item{label}{Character vector of length 1 containing the LaTeX label
+    or HTML anchor. Set to \code{NULL} to suppress the label.  Default
+    value is \code{NULL}. }
+  \item{align}{Character vector of length equal to the number of columns
+    of the resulting table indicating the alignment of the corresponding
+    columns.  Also, \code{"|"} may be used to produce vertical lines
+    between columns in LaTeX tables, but these are effectively ignored
+    when considering the required length of the supplied vector.  If a
+    character vector of length one is supplied, it is split as
+    \code{strsplit(align, "")[[1]]} before processing. Since the row
+    names are printed in the first column, the length of \code{align} is
+    one greater than \code{ncol(x)} if \code{x} is a
+    \code{data.frame}. Use \code{"l"}, \code{"r"}, and \code{"c"} to
+    denote left, right, and center alignment, respectively.  Use
+    \code{"p\{3cm\}"} etc for a LaTeX column of the specified width. For
+    HTML output the \code{"p"} alignment is interpreted as \code{"l"},
+    ignoring the width request. Default depends on the class of
+    \code{x}. }
+  \item{digits}{
+    Numeric vector of length equal to one (in which case it will be
+    replicated as necessary) or to the number of columns of the
+    resulting table \bold{or} matrix of the same size as the resulting
+    table indicating the number of digits to display in the
+    corresponding columns. Since the row names are printed in the first
+    column, the length of the vector \code{digits} or the number of
+    columns of the matrix \code{digits} is one greater than
+    \code{ncol(x)} if \code{x} is a \code{data.frame}. Default depends
+    of class of \code{x}. If values of \code{digits} are negative, the
+    corresponding values of \code{x} are displayed in scientific format
+    with \code{abs(digits)} digits.}
+  \item{display}{
+    Character vector of length equal to the number of columns of the
+    resulting table indicating the format for the corresponding columns.
+    Since the row names are printed in the first column, the length of
+    \code{display} is one greater than \code{ncol(x)} if \code{x} is a
+    \code{data.frame}.  These values are passed to the \code{formatC}
+    function.  Use \code{"d"} (for integers), \code{"f"}, \code{"e"},
+    \code{"E"}, \code{"g"}, \code{"G"}, \code{"fg"} (for reals), or
+    \code{"s"} (for strings).  \code{"f"} gives numbers in the usual
+    \code{xxx.xxx} format; \code{"e"} and \code{"E"} give
+    \code{n.ddde+nn} or \code{n.dddE+nn} (scientific format); \code{"g"}
+    and \code{"G"} put \code{x[i]} into scientific format only if it
+    saves space to do so.  \code{"fg"} uses fixed format as \code{"f"},
+    but \code{digits} as number of \emph{significant} digits.  Note that
+    this can lead to quite long result strings.  Default depends on the
+    class of \code{x}.}
   \item{...}{Additional arguments.  (Currently ignored.)}
 }
 \details{
-  This function extracts tabular information from \code{x} and returns an object of class \code{"xtable"}.
-  The nature of the table generated depends on the class of \code{x}.
-  For example, \code{aov} objects produce
-  ANOVA tables while \code{data.frame} objects produce a table of the entire data.frame.  One can optionally provide a
-  caption (called a title in HTML) or label (called an anchor in HTML),
-  as well as formatting specifications.  Default
-  values for \code{align}, \code{digits}, and \code{display} are
-  class dependent.
+  
+  This function extracts tabular information from \code{x} and returns
+  an object of class \code{"xtable"}.  The nature of the table generated
+  depends on the class of \code{x}.  For example, \code{aov} objects
+  produce ANOVA tables while \code{data.frame} objects produce a table
+  of the entire data.frame.  One can optionally provide a caption
+  (called a title in HTML) or label (called an anchor in HTML), as well
+  as formatting specifications.  Default values for \code{align},
+  \code{digits}, and \code{display} are class dependent.
 
-  The available method functions for \code{xtable} are given by \code{methods(xtable)}.
-  Users can extend the list of available classes by writing methods for the generic function \code{xtable}.
+  The available method functions for \code{xtable} are given by
+  \code{methods(xtable)}.  Users can extend the list of available
+  classes by writing methods for the generic function \code{xtable}.
   These methods functions should have \code{x} as their first argument
-  with additional arguments to
-  specify \code{caption}, \code{label}, \code{align},
-  \code{digits}, and
-  \code{display}.  Optionally, other arguments
-  may be present to specify how the object \code{x} should be manipulated.
-  All method functions should return an object whose class if given by \code{c("xtable","data.frame")}.
-  The resulting object can have attributes \code{caption} and
-  \code{label}, but must have attributes \code{align},
-  \code{digits}, and \code{display}.  It is strongly recommened that you set these attributes through the 
-  provided replacement functions as they perform validity checks.
+  with additional arguments to specify \code{caption}, \code{label},
+  \code{align}, \code{digits}, and \code{display}.  Optionally, other
+  arguments may be present to specify how the object \code{x} should be
+  manipulated.  All method functions should return an object whose class
+  if given by \code{c("xtable","data.frame")}.  The resulting object can
+  have attributes \code{caption} and \code{label}, but must have
+  attributes \code{align}, \code{digits}, and \code{display}.  It is
+  strongly recommened that you set these attributes through the provided
+  replacement functions as they perform validity checks.
+  }
+  \value{An object of class \code{"xtable"} which inherits the
+  \code{data.frame} class and contains several additional attributes
+  specifying the table formatting options.  
 }
-\value{
-  An object of class \code{"xtable"} which inherits the \code{data.frame} class and contains several additional attributes
-  specifying the table formatting options.
+\author{David Dahl \email{dahl@stat.tamu.edu} with contributions and
+  suggestions from many others (see source code).
+}
+\seealso{\code{\link{print.xtable}}, \code{\link{caption}},
+  \code{\link{label}}, \code{\link{align}}, \code{\link{digits}},
+  \code{\link{display}}, \code{\link{formatC}}, \code{\link{methods}}
 }
-\author{David Dahl \email{dahl@stat.tamu.edu} with contributions and suggestions from many others (see source code).}
-\seealso{\code{\link{print.xtable}}, \code{\link{caption}}, \code{\link{label}},
-         \code{\link{align}}, \code{\link{digits}}, \code{\link{display}}, \code{\link{formatC}}, \code{\link{methods}}}
 \examples{
 
 ## Load example dataset
 data(tli)
 
 ## Demonstrate data.frame
-tli.table <- xtable(tli[1:20,])
-digits(tli.table)[c(2,6)] <- 0
+tli.table <- xtable(tli[1:20, ])
+digits(tli.table)[c(2, 6)] <- 0
 print(tli.table)
-print(tli.table,type="html")
+print(tli.table, type = "html")
 
 ## Demonstrate data.frame with different digits in cells
-tli.table <- xtable(tli[1:20,])
+tli.table <- xtable(tli[1:20, ])
 digits(tli.table) <- matrix( 0:4, nrow = 20, ncol = ncol(tli)+1 )
 print(tli.table)
-print(tli.table,type="html")
+print(tli.table, type = "html")
 
 ## Demonstrate matrix
-design.matrix <- model.matrix(~ sex*grade, data=tli[1:20,])
+design.matrix <- model.matrix(~ sex*grade, data = tli[1:20, ])
 design.table <- xtable(design.matrix)
 print(design.table)
-print(design.table,type="html")
+print(design.table, type = "html")
 
 ## Demonstrate aov
-fm1 <- aov(tlimth ~ sex + ethnicty + grade + disadvg, data=tli)
+fm1 <- aov(tlimth ~ sex + ethnicty + grade + disadvg, data = tli)
 fm1.table <- xtable(fm1)
 print(fm1.table)
-print(fm1.table,type="html")
+print(fm1.table, type = "html")
 
 ## Demonstrate lm
-fm2 <- lm(tlimth ~ sex*ethnicty, data=tli)
+fm2 <- lm(tlimth ~ sex*ethnicty, data = tli)
 fm2.table <- xtable(fm2)
 print(fm2.table)
-print(fm2.table,type="html")
+print(fm2.table, type = "html")
 print(xtable(anova(fm2)))
-print(xtable(anova(fm2)),type="html")
-fm2b <- lm(tlimth ~ ethnicty, data=tli)
-print(xtable(anova(fm2b,fm2)))
-print(xtable(anova(fm2b,fm2)),type="html")
+print(xtable(anova(fm2)), type = "html")
+fm2b <- lm(tlimth ~ ethnicty, data = tli)
+print(xtable(anova(fm2b, fm2)))
+print(xtable(anova(fm2b, fm2)), type = "html")
 
 ## Demonstrate glm
-fm3 <- glm(disadvg ~ ethnicty*grade, data=tli, family=binomial())
+fm3 <- glm(disadvg ~ ethnicty*grade, data = tli, family = binomial())
 fm3.table <- xtable(fm3)
 print(fm3.table)
-print(fm3.table,type="html")
+print(fm3.table, type = "html")
 print(xtable(anova(fm3)))
-print(xtable(anova(fm3)),type="html")
+print(xtable(anova(fm3)), type = "html")
 
 ## Demonstrate aov
 ## Taken from help(aov) in R 1.1.1
@@ -155,9 +173,10 @@ P <- c(1,1,0,0,0,1,0,1,1,1,0,0,0,1,0,1,1,0,0,1,0,1,1,0)
 K <- c(1,0,0,1,0,1,1,0,0,1,0,1,0,1,1,0,0,0,1,1,1,0,1,0)
 yield <- c(49.5,62.8,46.8,57.0,59.8,58.5,55.5,56.0,62.8,55.8,69.5,55.0,
            62.0,48.8,45.5,44.2,52.0,51.5,49.8,48.8,57.2,59.0,53.2,56.0)
-npk <- data.frame(block=gl(6,4), N=factor(N), P=factor(P), K=factor(K), yield=yield)
+npk <- data.frame(block = gl(6,4), N = factor(N), P = factor(P),
+                  K = factor(K), yield = yield)
 npk.aov <- aov(yield ~ block + N*P*K, npk)
-op <- options(contrasts=c("contr.helmert", "contr.treatment"))
+op <- options(contrasts = c("contr.helmert", "contr.treatment"))
 npk.aovE <- aov(yield ~  N*P*K + Error(block), npk)
 options(op)
 
@@ -167,8 +186,8 @@ print(xtable(anova(npk.aov)))
 print(xtable(summary(npk.aov)))
 
 summary(npk.aovE)
-print(xtable(npk.aovE),type="html")
-print(xtable(summary(npk.aovE)),type="html")
+print(xtable(npk.aovE), type = "html")
+print(xtable(summary(npk.aovE)), type = "html")
 
 ## Demonstrate lm
 ## Taken from help(lm) in R 1.1.1
@@ -176,7 +195,7 @@ print(xtable(summary(npk.aovE)),type="html")
 ## Page 9: Plant Weight Data.
 ctl <- c(4.17,5.58,5.18,6.11,4.50,4.61,5.17,4.53,5.33,5.14)
 trt <- c(4.81,4.17,4.41,3.59,5.87,3.83,6.03,4.89,4.32,4.69)
-group <- gl(2,10,20, labels=c("Ctl","Trt"))
+group <- gl(2,10,20, labels = c("Ctl","Trt"))
 weight <- c(ctl, trt)
 lm.D9 <- lm(weight ~ group)
 print(xtable(lm.D9))
@@ -190,34 +209,35 @@ counts <- c(18,17,15,20,10,20,25,13,12)
 outcome <- gl(3,1,9)
 treatment <- gl(3,3)
 d.AD <- data.frame(treatment, outcome, counts)
-glm.D93 <- glm(counts ~ outcome + treatment, family=poisson())
-print(xtable(glm.D93,align="r|llrc"))
-print(xtable(anova(glm.D93)),hline.after=c(1),size="small")
+glm.D93 <- glm(counts ~ outcome + treatment, family = poisson())
+print(xtable(glm.D93, align = "r|llrc"))
+print(xtable(anova(glm.D93)), hline.after = c(1), size = "small")
 
 ## Demonstration of additional formatC() arguments.
-print(fm1.table, format.args=list(big.mark = "'", decimal.mark = ","))
+print(fm1.table, format.args = list(big.mark = "'", decimal.mark = ","))
 
 ## Demonstration of "short caption" support.
-fm1sc <- aov(tlimth ~ sex + ethnicty + grade, data=tli)
+fm1sc <- aov(tlimth ~ sex + ethnicty + grade, data = tli)
 fm1sc.table <- xtable(fm1sc, 
-  caption=c("ANOVA Model with Predictors Sex, Ethnicity, and Grade",
+  caption = c("ANOVA Model with Predictors Sex, Ethnicity, and Grade",
     "ANOVA: Sex, Ethnicity, Grade"))
 print(fm1sc.table)
 
 ## Demonstration of longtable support.
 ## Remember to insert \usepackage{longtable} on your LaTeX preamble
 x <- matrix(rnorm(1000), ncol = 10)
-x.big <- xtable(x,label='tabbig',caption='Example of longtable spanning several pages')
-print(x.big,tabular.environment='longtable',floating=FALSE) 
-x <- x[1:30,]
-x.small <- xtable(x,label='tabsmall',caption='regular table env')
+x.big <- xtable(x, label = 'tabbig',
+                caption = 'Example of longtable spanning several pages')
+print(x.big, tabular.environment = 'longtable', floating = FALSE) 
+x <- x[1:30, ]
+x.small <- xtable(x, label = 'tabsmall', caption = 'regular table env')
 print(x.small)  # default, no longtable 
 
 ## Demonstration of sidewaystable support.
 ## Remember to insert \usepackage{rotating} on your LaTeX preamble
-print(x.small,floating.environment='sidewaystable') 
+print(x.small, floating.environment = 'sidewaystable') 
 
-if(require(stats,quietly=TRUE)) {
+if(require(stats, quietly = TRUE)) {
   ## Demonstrate prcomp
   ## Taken from help(prcomp) in mva package of R 1.1.1
   data(USArrests)
@@ -234,7 +254,7 @@ if(require(stats,quietly=TRUE)) {
 ## Demonstrate include.rownames, include.colnames, 
 ## only.contents and add.to.row arguments
 set.seed(2345)
-res <- matrix(sample(0:9, size=6*9, replace=TRUE), ncol=6, nrow=9)
+res <- matrix(sample(0:9, size = 6*9, replace = TRUE), ncol = 6, nrow = 9)
 xres <- xtable(res)
 digits(xres) <- rep(0, 7)
 addtorow <- list()
@@ -242,28 +262,29 @@ addtorow$pos <- list()
 addtorow$pos[[1]] <- c(0, 2)
 addtorow$pos[[2]] <- 4
 addtorow$command <- c('\\vspace{2mm} \n', '\\vspace{10mm} \n')
-print(xres, add.to.row=addtorow, include.rownames=FALSE, include.colnames=TRUE, 
-  only.contents=TRUE, hline.after=c(0, 0, 9, 9))
+print(xres, add.to.row = addtorow, include.rownames = FALSE,
+      include.colnames = TRUE, only.contents = TRUE,
+      hline.after = c(0, 0, 9, 9))
 
-## Demostrate include.rownames, include.colnames, 
+## Demonstrate include.rownames, include.colnames, 
 ## only.contents and add.to.row arguments in Rweave files
 
 \dontrun{
  \begin{small}
  \setlongtables % For longtable version 3.x or less
  \begin{longtable}{
- <<results=tex,fig=FALSE>>=
- cat(paste(c('c', rep('cc', 34/2-1), 'c'), collapse='@{\\hspace{2pt}}'))
+ <<results = tex, fig = FALSE>>=
+ cat(paste(c('c', rep('cc', 34/2-1), 'c'), collapse = '@{\\hspace{2pt}}'))
  @ 
  }
  \hline
  \endhead
  \hline
  \endfoot
- <<results=tex,fig=FALSE>>=
+ <<results = tex, fig = FALSE>>=
  library(xtable)
  set.seed(2345)
- res <- matrix(sample(0:9, size=34*90, replace=TRUE), ncol=34, nrow=90)
+ res <- matrix(sample(0:9, size = 34*90, replace = TRUE), ncol = 34, nrow = 90)
  xres <- xtable(res)
  digits(xres) <- rep(0, 35)
  addtorow <- list()
@@ -271,8 +292,8 @@ print(xres, add.to.row=addtorow, include.rownames=FALSE, include.colnames=TRUE,
  addtorow$pos[[1]] <- c(seq(4, 40, 5), seq(49, 85, 5))
  addtorow$pos[[2]] <- 45
  addtorow$command <- c('\\vspace{2mm} \n', '\\newpage \n')
- print(xres, add.to.row=addtorow, include.rownames=FALSE, include.colnames=FALSE, 
-   only.contents=TRUE, hline.after=NULL)
+ print(xres, add.to.row = addtorow, include.rownames = FALSE,
+       include.colnames = FALSE, only.contents = TRUE, hline.after = NULL)
  @
  \end{longtable}
  \end{small}
@@ -282,65 +303,80 @@ print(xres, add.to.row=addtorow, include.rownames=FALSE, include.colnames=TRUE,
 mat <- round(matrix(c(0.9, 0.89, 200, 0.045, 2.0), c(1, 5)), 4)
 rownames(mat) <- "$y_{t-1}$"
 colnames(mat) <- c("$R^2$", "$\\\bar{R}^2$", "F-stat", "S.E.E", "DW")
-print(xtable(mat), type="latex", sanitize.text.function = function(x){x})
+print(xtable(mat), type = "latex", sanitize.text.function = function(x){x})
 
 ## Demonstrate booktabs
 print(tli.table)
-print(tli.table , hline.after=c(-1,0))
-print(tli.table , hline.after=NULL)
-print(tli.table ,  add.to.row=list(pos=list(2), command=c("\\vspace{2mm} \n")))
+print(tli.table, hline.after = c(-1,0))
+print(tli.table, hline.after = NULL)
+print(tli.table,
+      add.to.row = list(pos = list(2), command = c("\\vspace{2mm} \n")))
 
-print(tli.table , booktabs=TRUE)
-print(tli.table , booktabs=TRUE, hline.after=c(-1,0))
-print(tli.table , booktabs=TRUE, hline.after=NULL)
-print(tli.table , booktabs=TRUE, 
-  add.to.row=list(pos=list(2), command=c("\\vspace{2mm} \n")))
-print(tli.table , booktabs=TRUE, add.to.row=list(pos=list(2), 
-  command=c("youhou\n")),tabular.environment = "longtable")
+print(tli.table, booktabs = TRUE)
+print(tli.table, booktabs = TRUE, hline.after = c(-1,0))
+print(tli.table, booktabs = TRUE, hline.after = NULL)
+print(tli.table, booktabs = TRUE, 
+  add.to.row = list(pos = list(2), command = c("\\vspace{2mm} \n")))
+print(tli.table, booktabs = TRUE, add.to.row = list(pos = list(2), 
+  command = c("youhou\n")), tabular.environment = "longtable")
 
 \testonly{
   for(i in c("latex","html")) {
-    outFileName <- paste("xtable.",ifelse(i=="latex","tex",i),sep="")
-    print(tli.table,type=i,file=outFileName,append=FALSE)
-    print(design.table,type=i,file=outFileName,append=TRUE)
-    print(fm1.table,type=i,file=outFileName,append=TRUE)
-    print(fm2.table,type=i,file=outFileName,append=TRUE)
-    print(fm2.table,type=i,file=outFileName,append=TRUE,math.style.negative=TRUE)
-    print(xtable(anova(fm2)),type=i,file=outFileName,append=TRUE)
-    print(xtable(anova(fm2b,fm2)),type=i,file=outFileName,append=TRUE)
-    print(fm3.table,type=i,file=outFileName,append=TRUE)
-    print(xtable(anova(fm3)),type=i,file=outFileName,append=TRUE)
-    print(xtable(npk.aov),type=i,file=outFileName,append=TRUE)
-    print(xtable(anova(npk.aov)),type=i,file=outFileName,append=TRUE)
-    print(xtable(summary(npk.aov)),type=i,file=outFileName,append=TRUE)
-    print(xtable(npk.aovE),type=i,file=outFileName,append=TRUE)
-    print(xtable(summary(npk.aovE)),type=i,file=outFileName,append=TRUE)
-    if(i=="latex") cat("\\\clearpage\n",file=outFileName,append=TRUE)
-    print(xtable(lm.D9),type=i,file=outFileName,append=TRUE,latex.environment=NULL)
-    print(xtable(lm.D9),type=i,file=outFileName,append=TRUE,latex.environment="")
-    print(xtable(lm.D9),type=i,file=outFileName,append=TRUE,latex.environment="center")
-    print(xtable(anova(lm.D9)),type=i,file=outFileName,append=TRUE)
-    print(xtable(glm.D93),type=i,file=outFileName,append=TRUE)
-    print(xtable(anova(glm.D93,test="Chisq")),type=i,file=outFileName,append=TRUE)
-    print(xtable(glm.D93,align="r|llrc"),include.rownames=FALSE,include.colnames=TRUE,
-      type=i,file=outFileName,append=TRUE)
-    print(xtable(glm.D93,align="r||llrc"),include.rownames=TRUE,include.colnames=FALSE,
-      type=i,file=outFileName,append=TRUE)
-    print(xtable(glm.D93,align="|r||llrc"),include.rownames=FALSE,include.colnames=FALSE,
-      type=i,file=outFileName,append=TRUE)
-    print(xtable(glm.D93,align="|r||llrc|"),type=i,file=outFileName,append=TRUE)
-    print(xtable(anova(glm.D93)),hline.after=c(1),size="small",type=i,file=outFileName, append=TRUE)
-    if(require(stats,quietly=TRUE)) {
-      print(xtable(pr1),type=i,file=outFileName,append=TRUE)
-      print(xtable(summary(pr1)),type=i,file=outFileName,append=TRUE)
-      # print(xtable(pr2),type=i,file=outFileName,append=TRUE)
+    outFileName <- paste("xtable.", ifelse(i=="latex", "tex", i), sep = "")
+    print(tli.table, type = i, file = outFileName, append = FALSE)
+    print(design.table, type = i, file = outFileName, append = TRUE)
+    print(fm1.table, type = i, file = outFileName, append = TRUE)
+    print(fm2.table, type = i, file = outFileName, append = TRUE)
+    print(fm2.table, type = i, file = outFileName, append = TRUE,
+          math.style.negative = TRUE)
+    print(xtable(anova(fm2)), type = i, file = outFileName, append = TRUE)
+    print(xtable(anova(fm2b, fm2)), type = i, file = outFileName, append = TRUE)
+    print(fm3.table, type = i, file = outFileName, append = TRUE)
+    print(xtable(anova(fm3)), type = i, file = outFileName, append = TRUE)
+    print(xtable(npk.aov), type = i, file = outFileName, append = TRUE)
+    print(xtable(anova(npk.aov)), type = i, file = outFileName, append = TRUE)
+    print(xtable(summary(npk.aov)), type = i, file = outFileName, append = TRUE)
+    print(xtable(npk.aovE), type = i, file = outFileName, append = TRUE)
+    print(xtable(summary(npk.aovE)),
+          type = i, file = outFileName, append = TRUE)
+    if(i=="latex") cat("\\\clearpage\n", file = outFileName, append = TRUE)
+    print(xtable(lm.D9),
+          type = i, file = outFileName, append = TRUE, latex.environment = NULL)
+    print(xtable(lm.D9),
+          type = i, file = outFileName, append = TRUE, latex.environment = "")
+    print(xtable(lm.D9),
+          type = i, file = outFileName, append = TRUE,
+          latex.environment = "center")
+    print(xtable(anova(lm.D9)), type = i, file = outFileName, append = TRUE)
+    print(xtable(glm.D93), type = i, file = outFileName, append = TRUE)
+    print(xtable(anova(glm.D93, test = "Chisq")),
+          type = i, file = outFileName, append = TRUE)
+    print(xtable(glm.D93, align = "r|llrc"),
+          include.rownames = FALSE, include.colnames = TRUE,
+          type = i, file = outFileName, append = TRUE)
+    print(xtable(glm.D93, align = "r||llrc"),
+          include.rownames = TRUE, include.colnames = FALSE,
+          type = i, file = outFileName, append = TRUE)
+    print(xtable(glm.D93, align = "|r||llrc"),
+          include.rownames = FALSE, include.colnames = FALSE,
+          type = i, file = outFileName, append = TRUE)
+    print(xtable(glm.D93, align = "|r||llrc|"),
+          type = i, file = outFileName, append = TRUE)
+    print(xtable(anova(glm.D93)),
+          hline.after = c(1), size = "small",
+          type = i, file = outFileName, append = TRUE)
+    if(require(stats, quietly = TRUE)) {
+      print(xtable(pr1), type = i, file = outFileName, append = TRUE)
+      print(xtable(summary(pr1)), type = i, file = outFileName, append = TRUE)
+      # print(xtable(pr2), type = i, file = outFileName, append = TRUE)
     }
-    temp.table <- xtable(ts(cumsum(1+round(rnorm(100), 2)), start = c(1954, 7), frequency=12))
+    temp.table <- xtable(ts(cumsum(1+round(rnorm(100), 2)),
+                            start = c(1954, 7), frequency = 12))
     caption(temp.table) <- "Time series example"
-    print(temp.table,type=i,file=outFileName,append=TRUE,caption.placement="top",
-      table.placement="h")
-    print(temp.table,type=i,file=outFileName,append=TRUE,caption.placement="bottom",
-      table.placement="htb")
+    print(temp.table, type = i, file = outFileName,
+          append = TRUE, caption.placement = "top", table.placement = "h")
+    print(temp.table, type = i, file = outFileName,
+          append = TRUE, caption.placement = "bottom", table.placement = "htb")
   }
 }