]> git.donarmstrong.com Git - xtable.git/blob - pkg/R/xtableFtable.R
Working version of xtable with support for flat tables
[xtable.git] / pkg / R / xtableFtable.R
1 ### ftable objects, requested by Charles Roosen
2 ### Feature request #2248, 2/9/2012
3 xtableFtable <- function(x, caption = NULL, label = NULL, align = NULL,
4                          digits = NULL, display = NULL,
5                          quote = FALSE,
6                          method = c("non.compact", "row.compact",
7                                     "col.compact", "compact"),
8                          lsep = " | ", ...) {
9   method <- match.arg(method)
10   saveMethod <- method
11   xDim <- dim(x)
12   nRowVars <- length(attr(x, "row.vars"))
13   nColVars <- length(attr(x, "col.vars"))
14   if (nRowVars ==0){
15     if (method =="col.compact"){
16       method <- "non.compact"
17     } else if (method == "compact"){
18       method <- "row.compact"
19     }
20   }
21   if (nColVars ==0){
22     if (method =="row.compact"){
23       method <- "non.compact"
24     } else if (method == "compact"){
25       method <- "col.compact"
26     }
27   }
28   if (method == "non.compact"){
29     nCharCols <- nRowVars + 2
30     nCharRows <- nColVars + 1
31   }
32   if (method == "row.compact"){
33     nCharCols <- nRowVars + 2
34     nCharRows <- nColVars
35   }
36   if (method == "col.compact"){
37     nCharCols <- nRowVars + 1
38     nCharRows <- nColVars + 1
39   }
40   if (method == "compact"){
41     nCharCols <- nRowVars + 1
42     nCharRows <- nColVars
43   }
44
45   if(is.null(align)) {
46     align <- c(rep("l", nCharCols - 1), "l |", rep("r", xDim[2]))
47   }
48   if(is.null(display)) {
49     display <- c(rep("s", nCharCols), rep("d", xDim[2]))
50   }
51
52   attr(x, "ftableCaption") <- caption
53   attr(x, "ftableLabel") <- label
54   attr(x, "ftableAlign") <- align
55   attr(x, "ftableDigits") <- digits
56   attr(x, "quote") <- quote
57   attr(x, "ftableDisplay") <- display
58   attr(x, "method") <- method
59   attr(x, "lsep") <- lsep
60   attr(x, "nChars") <- c(nCharRows, nCharCols)
61   class(x) <- c("xtableFtable", "ftable")
62   return(x)
63 }
64
65 print.xtableFtable <- function(x,
66   type = getOption("xtable.type", "latex"),
67   file = getOption("xtable.file", ""),
68   append = getOption("xtable.append", FALSE),
69   floating = getOption("xtable.floating", TRUE),
70   floating.environment = getOption("xtable.floating.environment", "table"),
71   table.placement = getOption("xtable.table.placement", "ht"),
72   caption.placement = getOption("xtable.caption.placement", "bottom"),
73   caption.width = getOption("xtable.caption.width", NULL),
74   latex.environments = getOption("xtable.latex.environments", c("center")),
75   tabular.environment = getOption("xtable.tabular.environment", "tabular"),
76   size = getOption("xtable.size", NULL),
77   hline.after = getOption("xtable.hline.after", NULL),
78   NA.string = getOption("xtable.NA.string", ""),
79   only.contents = getOption("xtable.only.contents", FALSE),
80   add.to.row = getOption("xtable.add.to.row", NULL),
81   sanitize.rownames.function = getOption("xtable.sanitize.rownames.function",
82                                          sanitize.text.function),
83   sanitize.colnames.function = getOption("xtable.sanitize.colnames.function",
84                                          sanitize.text.function),
85   math.style.negative = getOption("xtable.math.style.negative", FALSE),
86   math.style.exponents = getOption("xtable.math.style.exponents", FALSE),
87   html.table.attributes = getOption("xtable.html.table.attributes", "border=1"),
88   print.results = getOption("xtable.print.results", TRUE),
89   format.args = getOption("xtable.format.args", NULL),
90   rotate.rownames = getOption("xtable.rotate.rownames", FALSE),
91   rotate.colnames = getOption("xtable.rotate.colnames", FALSE),
92   booktabs = getOption("xtable.booktabs", FALSE),
93   scalebox = getOption("xtable.scalebox", NULL),
94   width = getOption("xtable.width", NULL),
95   comment = getOption("xtable.comment", TRUE),
96   timestamp = getOption("xtable.timestamp", date()),
97   ...) {
98   if (type == "latex"){
99     caption <- attr(x, "ftableCaption")
100     label <- attr(x, "ftableLabel")
101     align <- attr(x, "ftableAlign")
102     digits <- attr(x, "ftableDigits")
103     quote <- attr(x, "quote")
104     digits <- attr(x, "ftabelDigits")
105     method <- attr(x, "method")
106     lsep <- attr(x, "lsep")
107     nCharRows <- attr(x, "nChars")[1]
108     fmtFtbl <- stats:::format.ftable(x, quote = quote, digits = digits,
109                                      method = method, lsep = lsep)
110     attr(fmtFtbl, "caption") <- caption
111     attr(fmtFtbl, "label") <- label
112     attr(fmtFtbl, "align") <- align
113     attr(fmtFtbl, "digits") <- digits
114     attr(fmtFtbl, "quote") <- quote
115     attr(fmtFtbl, "display") <- display
116     print.xtable(fmtFtbl, hline.after = c(-1, nCharRows, dim(fmtFtbl)[1]),
117                  include.rownames = FALSE, include.colnames = FALSE)
118   } else {
119     stop("print.xtableFtable not yet implemented for this type")
120   }
121 }
122