]> git.donarmstrong.com Git - xtable.git/blob - pkg/R/print.xtable.R
Introduced John Leonard's change regarding the inclusion of newline and hline when...
[xtable.git] / pkg / R / print.xtable.R
1 ### xtable package\r
2 ###\r
3 ### Produce LaTeX and HTML tables from R objects.\r
4 ###\r
5 ### Copyright 2000-2012 David B. Dahl <dahl@stat.tamu.edu>\r
6 ###\r
7 ### Maintained by Charles Roosen <croosen@mango-solutions.com>\r
8 ###\r
9 ### This file is part of the `xtable' library for R and related languages.\r
10 ### It is made available under the terms of the GNU General Public\r
11 ### License, version 2, or at your option, any later version,\r
12 ### incorporated herein by reference.\r
13 ###\r
14 ### This program is distributed in the hope that it will be\r
15 ### useful, but WITHOUT ANY WARRANTY; without even the implied\r
16 ### warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR\r
17 ### PURPOSE.  See the GNU General Public License for more\r
18 ### details.\r
19 ###\r
20 ### You should have received a copy of the GNU General Public\r
21 ### License along with this program; if not, write to the Free\r
22 ### Software Foundation, Inc., 59 Temple Place - Suite 330, Boston,\r
23 ### MA 02111-1307, USA\r
24 print.xtable <- function(\r
25   x,\r
26   type="latex",\r
27   file="",\r
28   append=FALSE,\r
29   floating=TRUE,\r
30   floating.environment="table",\r
31   table.placement="ht",\r
32   caption.placement="bottom",\r
33   latex.environments=c("center"),\r
34   tabular.environment="tabular",\r
35   size=NULL,\r
36   hline.after=c(-1,0,nrow(x)),\r
37   NA.string="",\r
38   include.rownames=TRUE,\r
39   include.colnames=TRUE,\r
40   only.contents=FALSE,\r
41   add.to.row=NULL,\r
42   sanitize.text.function=NULL,\r
43   sanitize.rownames.function=sanitize.text.function,\r
44   sanitize.colnames.function=sanitize.text.function,\r
45   math.style.negative=FALSE,\r
46   html.table.attributes="border=1",\r
47   print.results=TRUE,\r
48   format.args=NULL,\r
49   short.caption=NULL,\r
50   ...) {\r
51   # Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 hline.after\r
52   # 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
53   # Old code that set hline.after should include c(-1, 0, nrow(x)) in the hline.after vector\r
54   # If you do not want any \hline inside the data, set hline.after to NULL \r
55   # PHEADER instead the string '\\hline\n' is used in the code\r
56   # Now hline.after counts how many time a position appear  \r
57   # I left an automatic PHEADER in the longtable is this correct?\r
58 \r
59   # Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 include.rownames, include.colnames  \r
60   pos <- 0\r
61   if (include.rownames) pos <- 1\r
62   \r
63   # Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 hline.after checks\r
64   if (any(hline.after < -1) | any(hline.after > nrow(x))) stop("'hline.after' must be inside [-1, nrow(x)]")\r
65   \r
66   # Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 add.to.row checks\r
67   if (!is.null(add.to.row)) {\r
68     if (is.list(add.to.row) && length(add.to.row)==2) {\r
69       if (is.null(names(add.to.row))) {\r
70         names(add.to.row) <- c('pos', 'command')\r
71       } else if (any(sort(names(add.to.row))!=c('command', 'pos'))) {\r
72         stop("the names of the elements of 'add.to.row' must be 'pos' and 'command'")\r
73       }\r
74       if (is.list(add.to.row$pos) && is.vector(add.to.row$command, mode='character')) {\r
75         if ((npos <- length(add.to.row$pos)) != length(add.to.row$command)) {\r
76           stop("the length of 'add.to.row$pos' must be equal to the length of 'add.to.row$command'")\r
77         }\r
78         if (any(unlist(add.to.row$pos) < -1) | any(unlist(add.to.row$pos) > nrow(x))) {\r
79           stop("the values in add.to.row$pos must be inside the interval [-1, nrow(x)]")\r
80         }\r
81       } else {\r
82         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
83       }\r
84     } else {\r
85       stop("'add.to.row' argument must be a list of length 2")\r
86     }\r
87   } else {\r
88      add.to.row <- list(pos=list(), command=vector(length=0, mode="character"))\r
89      npos <- 0\r
90   }\r
91 \r
92   # Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 add.to.row\r
93   # Add further commands at the end of rows\r
94   if (type=="latex") {\r
95      PHEADER <- "\\hline\n"\r
96          # John Leonard <jleonard99@gmail.com> October 21, 2011\r
97          # The extra \hline gets in the way when using longtable and add.to.row\r
98          if(tabular.environment=="longtable" && !is.null(add.to.row) ) {\r
99            PHEADER <- ""\r
100      }     \r
101   } else {\r
102      PHEADER <- ""\r
103   }\r
104    \r
105   lastcol <- rep(" ", nrow(x)+2)\r
106   if (!is.null(hline.after)) {\r
107      add.to.row$pos[[npos+1]] <- hline.after\r
108      add.to.row$command <- c(add.to.row$command, PHEADER)\r
109   }\r
110   if ( length(add.to.row$command) > 0 ) {\r
111     for (i in 1:length(add.to.row$command)) {\r
112       addpos <- add.to.row$pos[[i]]\r
113       freq <- table(addpos)\r
114       addpos <- unique(addpos)\r
115       for (j in 1:length(addpos)) {\r
116         lastcol[addpos[j]+2] <- paste(lastcol[addpos[j]+2], paste(rep(add.to.row$command[i], freq[j]), sep="", collapse=""), sep=" ")\r
117       }\r
118     }\r
119   }\r
120   \r
121   if (length(type)>1) stop("\"type\" must have length 1")\r
122   type <- tolower(type)\r
123   if (!all(!is.na(match(type,c("latex","html"))))) stop("\"type\" must be in {\"latex\", \"html\"}")\r
124   if (!all(!is.na(match(floating.environment,c("table","table*","sidewaystable"))))) stop("\"type\" must be in {\"table\", \"table*\", \"sidewaystable\"}")\r
125   if (!is.null(table.placement) && !all(!is.na(match(unlist(strsplit(table.placement, split="")),c("H","h","t","b","p","!"))))) {\r
126     stop("\"table.placement\" must contain only elements of {\"h\",\"t\",\"b\",\"p\",\"!\"}")\r
127   }\r
128   if (!all(!is.na(match(caption.placement,c("bottom","top"))))) stop("\"caption.placement\" must be either {\"bottom\",\"top\"}")\r
129 \r
130   if (type=="latex") {\r
131     BCOMMENT <- "% "\r
132     ECOMMENT <- "\n"\r
133     # See e-mail from "John S. Walker <jsw9c@uic.edu>" dated 5-19-2003 regarding "texfloat"\r
134     # See e-mail form "Fernando Henrique Ferraz P. da Rosa" <academic@feferraz.net>" dated 10-28-2005 regarding "longtable"\r
135     if ( tabular.environment == "longtable" & floating == TRUE ) {\r
136       warning("Attempt to use \"longtable\" with floating=TRUE. Changing to FALSE.")\r
137       floating <- FALSE\r
138     }\r
139     if ( floating == TRUE ) {\r
140       # See e-mail from "Pfaff, Bernhard <Bernhard.Pfaff@drkw.com>" dated 7-09-2003 regarding "suggestion for an amendment of the source"\r
141       # See e-mail from "Mitchell, David" <David.Mitchell@dotars.gov.au>" dated 2003-07-09 regarding "Additions to R xtable package"\r
142       # See e-mail from "Garbade, Sven" <Sven.Garbade@med.uni-heidelberg.de> dated 2006-05-22 regarding the floating environment.\r
143       BTABLE <- paste("\\begin{", floating.environment, "}",ifelse(!is.null(table.placement),\r
144         paste("[",table.placement,"]",sep=""),""),"\n",sep="")\r
145       if ( is.null(latex.environments) || (length(latex.environments)==0) ) {\r
146         BENVIRONMENT <- ""\r
147         EENVIRONMENT <- ""\r
148       }\r
149       else {\r
150         BENVIRONMENT <- ""\r
151         EENVIRONMENT <- ""\r
152         for ( i in 1:length(latex.environments) ) {\r
153           if ( latex.environments[i] == "" ) next\r
154           BENVIRONMENT <- paste(BENVIRONMENT, "\\begin{",latex.environments[i],"}\n",sep="")\r
155           EENVIRONMENT <- paste("\\end{",latex.environments[i],"}\n",EENVIRONMENT,sep="")\r
156         }\r
157       }\r
158       ETABLE <- paste("\\end{", floating.environment, "}\n", sep="")\r
159     }\r
160     else {\r
161       BTABLE <- ""\r
162       ETABLE <- ""\r
163       BENVIRONMENT <- ""\r
164       EENVIRONMENT <- ""\r
165     }\r
166 \r
167     tmp.index.start <- 1\r
168     if ( ! include.rownames ) {\r
169       while ( attr(x,"align",exact=TRUE)[tmp.index.start] == '|' ) tmp.index.start <- tmp.index.start + 1\r
170       tmp.index.start <- tmp.index.start + 1\r
171     }\r
172     BTABULAR <- paste("\\begin{",tabular.environment,"}{",\r
173                       paste(c(attr(x, "align",exact=TRUE)[tmp.index.start:length(attr(x,"align",exact=TRUE))], "}\n"),\r
174                             sep="", collapse=""),\r
175                       sep="")\r
176     \r
177     ## fix 10-26-09 (robert.castelo@upf.edu) the following 'if' condition is added here to support\r
178     ## a caption on the top of a longtable\r
179     if (tabular.environment == "longtable" && caption.placement=="top") {\r
180                 if (is.null(short.caption)){\r
181                         BCAPTION <- "\\caption{"\r
182                 } else {\r
183                         BCAPTION <- paste("\\caption[", short.caption, "]{", sep="")\r
184                 }       \r
185         ECAPTION <- "} \\\\ \n"\r
186         if ((!is.null(attr(x,"caption",exact=TRUE))) && (type=="latex")) BTABULAR <- paste(BTABULAR,  BCAPTION, attr(x,"caption",exact=TRUE), ECAPTION, sep="")\r
187     }\r
188     # Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 add.to.row position -1\r
189     BTABULAR <- paste(BTABULAR,lastcol[1], sep="")\r
190     # the \hline at the end, if present, is set in full matrix    \r
191     ETABULAR <- paste("\\end{",tabular.environment,"}\n",sep="")\r
192     \r
193     # BSIZE contributed by Benno <puetz@mpipsykl.mpg.de> in e-mail dated Wednesday, December 01, 2004\r
194     if (is.null(size) || !is.character(size)) {\r
195       BSIZE <- ""\r
196       ESIZE <- ""\r
197     } else {\r
198       if(length(grep("^\\\\",size))==0){\r
199         size <- paste("\\",size,sep="")\r
200       }\r
201       BSIZE <- paste("{",size,"\n",sep="")\r
202       ESIZE <- "}\n"\r
203     }\r
204     BLABEL <- "\\label{"\r
205     ELABEL <- "}\n"\r
206         if (is.null(short.caption)){\r
207                 BCAPTION <- "\\caption{"\r
208         } else {\r
209                 BCAPTION <- paste("\\caption[", short.caption, "]{", sep="")\r
210         }       \r
211     ECAPTION <- "}\n"\r
212     BROW <- ""\r
213     EROW <- " \\\\ \n"\r
214     BTH <- ""\r
215     ETH <- ""\r
216     STH <- " & "\r
217     BTD1 <- " & "\r
218     BTD2 <- ""\r
219     BTD3 <- ""\r
220     ETD  <- ""\r
221     # Based on contribution from Jonathan Swinton <jonathan@swintons.net> in e-mail dated Wednesday, January 17, 2007\r
222     sanitize <- function(str) {\r
223       result <- str\r
224       result <- gsub("\\\\","SANITIZE.BACKSLASH",result)\r
225       result <- gsub("$","\\$",result,fixed=TRUE)\r
226       result <- gsub(">","$>$",result,fixed=TRUE)\r
227       result <- gsub("<","$<$",result,fixed=TRUE)\r
228       result <- gsub("|","$|$",result,fixed=TRUE)\r
229       result <- gsub("{","\\{",result,fixed=TRUE)\r
230       result <- gsub("}","\\}",result,fixed=TRUE)\r
231       result <- gsub("%","\\%",result,fixed=TRUE)\r
232       result <- gsub("&","\\&",result,fixed=TRUE)\r
233       result <- gsub("_","\\_",result,fixed=TRUE)\r
234       result <- gsub("#","\\#",result,fixed=TRUE)\r
235       result <- gsub("^","\\verb|^|",result,fixed=TRUE)\r
236       result <- gsub("~","\\~{}",result,fixed=TRUE)\r
237       result <- gsub("SANITIZE.BACKSLASH","$\\backslash$",result,fixed=TRUE)\r
238       return(result)\r
239     }\r
240     sanitize.numbers <- function(x) {\r
241       result <- x\r
242       if ( math.style.negative ) {\r
243         # Jake Bowers <jwbowers@illinois.edu> in e-mail from 2008-08-20 suggested\r
244         # disabling this feature to avoid problems with LaTeX's dcolumn package.\r
245         # by Florian Wickelmaier <florian.wickelmaier@uni-tuebingen.de> in e-mail\r
246         # from 2008-10-03 requested the ability to use the old behavior.\r
247         for(i in 1:length(x)) {\r
248           result[i] <- gsub("-","$-$",result[i],fixed=TRUE)\r
249         }\r
250       }\r
251       return(result)\r
252     }\r
253     sanitize.final <- function(result) {\r
254       return(result)\r
255     }\r
256   } else {\r
257     BCOMMENT <- "<!-- "\r
258     ECOMMENT <- " -->\n"\r
259     BTABLE <- paste("<TABLE ",html.table.attributes,">\n",sep="")\r
260     ETABLE <- "</TABLE>\n"\r
261     BENVIRONMENT <- ""\r
262     EENVIRONMENT <- ""\r
263     BTABULAR <- ""\r
264     ETABULAR <- ""\r
265     BSIZE <- ""\r
266     ESIZE <- ""\r
267     BLABEL <- "<A NAME="\r
268     ELABEL <- "></A>\n"\r
269     BCAPTION <- paste("<CAPTION ALIGN=\"",caption.placement,"\"> ",sep="")\r
270     ECAPTION <- " </CAPTION>\n"\r
271     BROW <- "<TR>"\r
272     EROW <- " </TR>\n"\r
273     BTH <- " <TH> "\r
274     ETH <- " </TH> "\r
275     STH <- " </TH> <TH> "\r
276     BTD1 <- " <TD align=\""\r
277     align.tmp <- attr(x,"align",exact=TRUE)\r
278     align.tmp <- align.tmp[align.tmp!="|"]\r
279     BTD2 <- matrix(align.tmp[(2-pos):(ncol(x)+1)],nrow=nrow(x),ncol=ncol(x)+pos,byrow=TRUE)\r
280     # Based on contribution from Jonathan Swinton <jonathan@swintons.net> in e-mail dated Wednesday, January 17, 2007\r
281     BTD2[regexpr("^p",BTD2)>0] <- "left"\r
282     BTD2[BTD2=="r"] <- "right"\r
283     BTD2[BTD2=="l"] <- "left"\r
284     BTD2[BTD2=="c"] <- "center"\r
285     BTD3 <- "\"> "\r
286     ETD  <- " </TD>"\r
287     sanitize <- function(str) {\r
288       result <- str\r
289       result <- gsub("&","&amp ",result,fixed=TRUE)\r
290       result <- gsub(">","&gt ",result,fixed=TRUE)\r
291       result <- gsub("<","&lt ",result,fixed=TRUE)\r
292       # Kurt Hornik <Kurt.Hornik@wu-wien.ac.at> on 2006/10/05 recommended not escaping underscores.\r
293       # result <- gsub("_", "\\_", result, fixed=TRUE)\r
294       return(result)\r
295     }\r
296     sanitize.numbers <- function(x) {\r
297       return(x)\r
298     }\r
299     sanitize.final <- function(result) {\r
300       # Suggested by Uwe Ligges <ligges@statistik.uni-dortmund.de> in e-mail dated 2005-07-30.\r
301       result$text <- gsub("  *"," ", result$text,fixed=TRUE)\r
302       result$text <- gsub(' align="left"', "", result$text,fixed=TRUE)\r
303       return(result)\r
304     }\r
305   }\r
306 \r
307   result <- string("",file=file,append=append)\r
308   info <- R.Version()\r
309   # modified Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 to set automatically the package version\r
310   result <- result + BCOMMENT + type + " table generated in " +\r
311             info$language + " " + info$major + "." + info$minor + " by xtable " + packageDescription('xtable')$Version + " package" + ECOMMENT\r
312   result <- result + BCOMMENT + date() + ECOMMENT\r
313   # Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 only.contents\r
314   if (!only.contents) {\r
315     result <- result + BTABLE\r
316     result <- result + BENVIRONMENT\r
317     if ( floating == TRUE ) {\r
318       if ((!is.null(attr(x,"caption",exact=TRUE))) && (type=="html" || caption.placement=="top")) result <- result + BCAPTION + attr(x,"caption",exact=TRUE) + ECAPTION\r
319       if (!is.null(attr(x,"label",exact=TRUE)) && (type=="latex" && caption.placement=="top")) result <- result + BLABEL + attr(x,"label",exact=TRUE) + ELABEL  \r
320     }\r
321     result <- result + BSIZE\r
322     result <- result + BTABULAR\r
323   }\r
324   # Claudio Agostinelli <claudio@unive.it> dated 2006-07-28 include.colnames, include.rownames \r
325   if (include.colnames) {\r
326     result <- result + BROW + BTH\r
327     if (include.rownames) result <- result + STH\r
328     if (is.null(sanitize.colnames.function)) {                                     # David G. Whiting in e-mail 2007-10-09\r
329       result <- result + paste(sanitize(names(x)),collapse=STH)\r
330     } else {\r
331       result <- result + paste(sanitize.colnames.function(names(x)), collapse=STH) # David G. Whiting in e-mail 2007-10-09\r
332     }\r
333     result <- result + ETH + EROW\r
334   }\r
335 \r
336   cols <- matrix("",nrow=nrow(x),ncol=ncol(x)+pos)\r
337   if (include.rownames) {\r
338     if (is.null(sanitize.rownames.function)) {                                     # David G. Whiting in e-mail 2007-10-09\r
339       cols[,1] <- sanitize(row.names(x))\r
340     } else {\r
341       cols[,1] <- sanitize.rownames.function(row.names(x))                         # David G. Whiting in e-mail 2007-10-09\r
342     }\r
343   }\r
344 \r
345 ## Begin vectorizing the formatting code by Ian Fellows [ian@fellstat.com]\r
346 ## 06 Dec 2011\r
347 ##\r
348 #  disp <- function(y) {\r
349 #    if (is.factor(y)) {\r
350 #      y <- levels(y)[y]\r
351 #    }\r
352 #    if (is.list(y)) {\r
353 #      y <- unlist(y)\r
354 #    }\r
355 #    return(y)\r
356 #  }\r
357   varying.digits <- is.matrix( attr( x, "digits",exact=TRUE ) )\r
358   # 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
359   #if( !varying.digits ) {\r
360     # modified Claudio Agostinelli <claudio@unive.it> dated 2006-07-28\r
361   #  attr(x,"digits") <- matrix( attr( x, "digits",exact=TRUE ), nrow = nrow(x), ncol = ncol(x)+1, byrow = TRUE )\r
362   #}\r
363   for(i in 1:ncol(x)) {\r
364         xcol <- x[,i]\r
365         if(is.factor(xcol))\r
366                 xcol <- as.character(xcol)\r
367         if(is.list(xcol))\r
368                 xcol <- sapply(xcol,unlist)\r
369     ina <- is.na(xcol)\r
370     is.numeric.column <- is.numeric(xcol)\r
371 \r
372         if(is.character(xcol)) {\r
373                 cols[,i+pos] <- xcol\r
374         } else {\r
375           if (is.null(format.args)){\r
376             format.args <- list()\r
377           }\r
378           if (is.null(format.args$decimal.mark)){\r
379             format.args$decimal.mark <- options()$OutDec\r
380           }\r
381           if(!varying.digits){\r
382                 curFormatArgs <- c(list( \r
383                     x = xcol,\r
384                         format = ifelse( attr( x, "digits",exact=TRUE )[i+1] < 0, "E", \r
385                           attr( x, "display",exact=TRUE )[i+1] ), \r
386                         digits = abs( attr( x, "digits",exact=TRUE )[i+1] )),\r
387                         format.args)\r
388             cols[,i+pos] <- do.call("formatC", curFormatArgs)\r
389       }else{\r
390                 for( j in 1:nrow( cols ) ) {\r
391                   curFormatArgs <- c(list( \r
392             x = xcol[j],\r
393                         format = ifelse( attr( x, "digits",exact=TRUE )[j,i+1] < 0, "E", \r
394               attr( x, "display",exact=TRUE )[i+1] ), \r
395             digits = abs( attr( x, "digits",exact=TRUE )[j,i+1] )),\r
396                         format.args)\r
397                   cols[j,i+pos] <- do.call("formatC", curFormatArgs)                    \r
398                 }\r
399       } \r
400         }\r
401         ## End Ian Fellows changes\r
402         \r
403     if ( any(ina) ) cols[ina,i+pos] <- NA.string\r
404     # Based on contribution from Jonathan Swinton <jonathan@swintons.net> in e-mail dated Wednesday, January 17, 2007\r
405     if ( is.numeric.column ) {\r
406       cols[,i+pos] <- sanitize.numbers(cols[,i+pos])\r
407     } else {\r
408       if (is.null(sanitize.text.function)) {\r
409         cols[,i+pos] <- sanitize(cols[,i+pos])\r
410       } else {\r
411         cols[,i+pos] <- sanitize.text.function(cols[,i+pos])\r
412       }\r
413     }\r
414   }\r
415 \r
416   multiplier <- 5\r
417   full <- matrix("",nrow=nrow(x),ncol=multiplier*(ncol(x)+pos)+2)\r
418   full[,1] <- BROW\r
419   full[,multiplier*(0:(ncol(x)+pos-1))+2] <- BTD1\r
420   full[,multiplier*(0:(ncol(x)+pos-1))+3] <- BTD2\r
421   full[,multiplier*(0:(ncol(x)+pos-1))+4] <- BTD3\r
422   full[,multiplier*(0:(ncol(x)+pos-1))+5] <- cols\r
423   full[,multiplier*(0:(ncol(x)+pos-1))+6] <- ETD\r
424 \r
425   full[,multiplier*(ncol(x)+pos)+2] <- paste(EROW, lastcol[-(1:2)], sep=" ")\r
426   \r
427   # John Leonard <jleonard99@gmail.com> October 21, 2011\r
428   # Removes the "\\" from the last row of the contents so that \r
429   # booktabs (\bottomline) appears in the correct position.\r
430   if(tabular.environment=="longtable" & !is.null(add.to.row)) {\r
431     full[dim(full)[1],multiplier*(ncol(x)+pos)+2] <- "%\n" \r
432   }\r
433   \r
434   if (type=="latex") full[,2] <- ""\r
435   result <- result + lastcol[2] + paste(t(full),collapse="")\r
436   if (!only.contents) {\r
437     if (tabular.environment == "longtable") {\r
438       result <- result + PHEADER\r
439       ## fix 10-27-09 Liviu Andronic (landronimirc@gmail.com) the following 'if' condition is inserted in order to avoid\r
440       ## that bottom caption interferes with a top caption of a longtable\r
441       if(caption.placement=="bottom"){\r
442         if ((!is.null(attr(x,"caption",exact=TRUE))) && (type=="latex")) result <- result + BCAPTION + attr(x,"caption",exact=TRUE) + ECAPTION\r
443       }\r
444       if (!is.null(attr(x,"label",exact=TRUE))) result <- result + BLABEL + attr(x,"label",exact=TRUE) + ELABEL\r
445       ETABULAR <- "\\end{longtable}\n"\r
446     }\r
447     result <- result + ETABULAR\r
448     result <- result + ESIZE\r
449     if ( floating == TRUE ) {\r
450       if ((!is.null(attr(x,"caption",exact=TRUE))) && (type=="latex" && caption.placement=="bottom")) result <- result + BCAPTION + attr(x,"caption",exact=TRUE) + ECAPTION\r
451       if (!is.null(attr(x,"label",exact=TRUE)) && caption.placement=="bottom") result <- result + BLABEL + attr(x,"label",exact=TRUE) + ELABEL  \r
452     }\r
453     result <- result + EENVIRONMENT\r
454     result <- result + ETABLE\r
455   }   \r
456   result <- sanitize.final(result)\r
457   if (print.results){\r
458         print(result)\r
459   }\r
460   \r
461   return(invisible(result$text))\r
462 }\r
463 \r
464 "+.string" <- function(x,y) {\r
465   x$text <- paste(x$text,as.string(y)$text,sep="")\r
466   return(x)\r
467 }\r
468 \r
469 print.string <- function(x,...) {\r
470   cat(x$text,file=x$file,append=x$append)\r
471   return(invisible())\r
472 }\r
473 \r
474 string <- function(text,file="",append=FALSE) {\r
475   x <- list(text=text,file=file,append=append)\r
476   class(x) <- "string"\r
477   return(x)\r
478 }\r
479 \r
480 as.string <- function(x,file="",append=FALSE) {\r
481   if (is.null(attr(x,"class",exact=TRUE)))\r
482   switch(data.class(x),\r
483       character=return(string(x,file,append)),\r
484       numeric=return(string(as.character(x),file,append)),\r
485       stop("Cannot coerse argument to a string"))\r
486   if (class(x)=="string")\r
487     return(x)\r
488   stop("Cannot coerse argument to a string")\r
489 }\r
490 \r
491 is.string <- function(x) {\r
492   return(class(x)=="string")\r
493 }\r
494 \r