]> git.donarmstrong.com Git - xtable.git/blobdiff - pkg/R/xtableFtable.R
Fixed passing of arguments to print.xtableFtable
[xtable.git] / pkg / R / xtableFtable.R
index 41870042cae3521a898d6ca396d15e135e88af88..3dc83d388bab6a7cc6bd8d7cfb68fb06a11314e8 100644 (file)
@@ -5,7 +5,7 @@ xtableFtable <- function(x, caption = NULL, label = NULL, align = NULL,
                          quote = FALSE,
                          method = c("non.compact", "row.compact",
                                     "col.compact", "compact"),
-                         lsep = " | ", ...) {
+                         lsep = " $\\vert$ ", ...) {
   method <- match.arg(method)
   saveMethod <- method
   xDim <- dim(x)
@@ -78,7 +78,7 @@ print.xtableFtable <- function(x,
   NA.string = getOption("xtable.NA.string", ""),
   only.contents = getOption("xtable.only.contents", FALSE),
   add.to.row = getOption("xtable.add.to.row", NULL),
-  sanitize.text.function = getOption("xtable.sanitize.text.function", NULL),
+  sanitize.text.function = getOption("xtable.sanitize.text.function", as.is),
   sanitize.rownames.function = getOption("xtable.sanitize.rownames.function",
                                          sanitize.text.function),
   sanitize.colnames.function = getOption("xtable.sanitize.colnames.function",
@@ -97,7 +97,7 @@ print.xtableFtable <- function(x,
   timestamp = getOption("xtable.timestamp", date()),
   ...) {
   if (type == "latex"){
-
+    ## extract the information in the attributes
     caption <- attr(x, "ftableCaption")
     label <- attr(x, "ftableLabel")
     align <- attr(x, "ftableAlign")
@@ -110,15 +110,14 @@ print.xtableFtable <- function(x,
     nCharCols <- attr(x, "nChars")[2]
     nRowVars <- length(attr(x, "row.vars"))
     nColVars <- length(attr(x, "col.vars"))
-    fmtFtbl <- stats:::format.ftable(x, quote = quote, digits = digits,
-                                     method = method, lsep = lsep)
+
+    ## change class so format method will find format.ftable
+    ## even though format.ftable is not exported from 'stats'
+    class(x) <- "ftable"
+    fmtFtbl <- format(x, quote = quote, digits = digits,
+                      method = method, lsep = lsep)
     attr(fmtFtbl, "caption") <- caption
     attr(fmtFtbl, "label") <- label
-    ## if method is "compact", rotate both if either requested
-    ## if (method == "compact"){
-    ##   if (rotate.rownames) rotate.colnames <- TRUE
-    ##   if (rotate.colnames) rotate.rownames <- TRUE
-    ## }
 
     ## sanitization is possible for row names and/or column names
     ## row names
@@ -137,7 +136,7 @@ print.xtableFtable <- function(x,
     } else {
       fmtFtbl[1:nColVars, nCharCols - 1] <-
         sanitize.colnames.function(fmtFtbl[1:nColVars, nCharCols - 1])
-    }    
+    }
     ## rotations are possible
     if (rotate.rownames){
       fmtFtbl[1:dim(fmtFtbl)[1], 1:(nCharCols - 1)] <-
@@ -181,7 +180,29 @@ print.xtableFtable <- function(x,
     print.xtable(fmtFtbl, hline.after = hline.after,
                  include.rownames = FALSE, include.colnames = FALSE,
                  booktabs = booktabs,
-                 sanitize.text.function = function(x){x})
+                 sanitize.text.function = as.is,
+                 file = file,
+                 append = append,
+                 floating = floating,
+                 floating.environment = floating.environment,
+                 table.placement = table.placement,
+                 caption.placement = caption.placement,
+                 caption.width = caption.width,
+                 latex.environments = latex.environments,
+                 tabular.environment = tabular.environment,
+                 size = size,
+                 NA.string = NA.string,
+                 only.contents = only.contents,
+                 add.to.row = add.to.row,,
+                 math.style.negative = math.style.negative,
+                 math.style.exponents = math.style.exponents,
+                 print.results = print.results,
+                 format.args = format.args,
+                 scalebox = scalebox,
+                 width = width,
+                 comment = comment,
+                 timestamp = timestamp,
+                 ...)
   } else {
     stop("print.xtableFtable not yet implemented for this type")
   }