]> git.donarmstrong.com Git - xtable.git/blob - pkg/R/xtableFtable.R
46c7f7b8d482c1a880a6f6415b600380ad790444
[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.text.function = getOption("xtable.sanitize.text.function", NULL),
82   sanitize.rownames.function = getOption("xtable.sanitize.rownames.function",
83                                          sanitize.text.function),
84   sanitize.colnames.function = getOption("xtable.sanitize.colnames.function",
85                                          sanitize.text.function),
86   math.style.negative = getOption("xtable.math.style.negative", FALSE),
87   math.style.exponents = getOption("xtable.math.style.exponents", FALSE),
88   html.table.attributes = getOption("xtable.html.table.attributes", "border=1"),
89   print.results = getOption("xtable.print.results", TRUE),
90   format.args = getOption("xtable.format.args", NULL),
91   rotate.rownames = getOption("xtable.rotate.rownames", FALSE),
92   rotate.colnames = getOption("xtable.rotate.colnames", FALSE),
93   booktabs = getOption("xtable.booktabs", FALSE),
94   scalebox = getOption("xtable.scalebox", NULL),
95   width = getOption("xtable.width", NULL),
96   comment = getOption("xtable.comment", TRUE),
97   timestamp = getOption("xtable.timestamp", date()),
98   ...) {
99   if (type == "latex"){
100
101     caption <- attr(x, "ftableCaption")
102     label <- attr(x, "ftableLabel")
103     align <- attr(x, "ftableAlign")
104     digits <- attr(x, "ftableDigits")
105     quote <- attr(x, "quote")
106     digits <- attr(x, "ftabelDigits")
107     method <- attr(x, "method")
108     lsep <- attr(x, "lsep")
109     nCharRows <- attr(x, "nChars")[1]
110     nCharCols <- attr(x, "nChars")[2]
111     fmtFtbl <- stats:::format.ftable(x, quote = quote, digits = digits,
112                                      method = method, lsep = lsep)
113     attr(fmtFtbl, "caption") <- caption
114     attr(fmtFtbl, "label") <- label
115     ## if method is "compact", rotate both if either requested
116     ## if (method == "compact"){
117     ##   if (rotate.rownames) rotate.colnames <- TRUE
118     ##   if (rotate.colnames) rotate.rownames <- TRUE
119     ## }
120
121     ## rotations are possible
122     if (rotate.rownames){
123       fmtFtbl[1:dim(fmtFtbl)[1], 1:(nCharCols - 1)] <-
124         paste0("\\begin{sideways} ",
125                fmtFtbl[1:dim(fmtFtbl)[1], 1:(nCharCols - 1)],
126                "\\end{sideways}")
127     }
128     if (rotate.colnames){
129       if (rotate.rownames){
130         fmtFtbl[1:(nCharRows), (nCharCols):dim(fmtFtbl)[2]] <-
131           paste0("\\begin{sideways} ",
132                  fmtFtbl[1:(nCharRows), (nCharCols):dim(fmtFtbl)[2]],
133                  "\\end{sideways}")
134       } else {
135         fmtFtbl[1:(nCharRows), 1:dim(fmtFtbl)[2]] <-
136           paste0("\\begin{sideways} ",
137                  fmtFtbl[1:(nCharRows), 1:dim(fmtFtbl)[2]],
138                  "\\end{sideways}")
139       }
140     }
141
142
143     ## booktabs is incompatible with vertical lines in tables
144     if (booktabs) align <- gsub("|","", align, fixed = TRUE)
145     attr(fmtFtbl, "align") <- align
146     attr(fmtFtbl, "digits") <- digits
147     attr(fmtFtbl, "quote") <- quote
148     attr(fmtFtbl, "display") <- display
149
150     ## labels should be left aligned
151     for (i in 1:nCharRows){
152       fmtFtbl[i, nCharCols:dim(fmtFtbl)[2]] <-
153         paste0("\\multicolumn{1}{l}{ ",
154                fmtFtbl[i, nCharCols:dim(fmtFtbl)[2]], "}")
155     }
156
157
158     print.xtable(fmtFtbl, hline.after = c(-1, nCharRows, dim(fmtFtbl)[1]),
159                  include.rownames = FALSE, include.colnames = FALSE,
160                  booktabs = booktabs,
161                  sanitize.text.function = function(x){x})
162   } else {
163     stop("print.xtableFtable not yet implemented for this type")
164   }
165 }
166