]> git.donarmstrong.com Git - xtable.git/blob - pkg/R/table.attributes.R
718e41fc958a19b956c132ff7b4236014cdaf0d2
[xtable.git] / pkg / R / table.attributes.R
1 ### xtable package
2 ###
3 ### Produce LaTeX and HTML tables from R objects.
4 ###
5 ### Copyright 2000-2013 David B. Dahl <dahl@stat.byu.edu>
6 ###
7 ### This file is part of the `xtable' library for R and related languages.
8 ### It is made available under the terms of the GNU General Public
9 ### License, version 2, or at your option, any later version,
10 ### incorporated herein by reference.
11 ###
12 ### This program is distributed in the hope that it will be
13 ### useful, but WITHOUT ANY WARRANTY; without even the implied
14 ### warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR
15 ### PURPOSE.  See the GNU General Public License for more
16 ### details.
17 ###
18 ### You should have received a copy of the GNU General Public
19 ### License along with this program; if not, write to the Free
20 ### Software Foundation, Inc., 59 Temple Place - Suite 330, Boston,
21 ### MA 02111-1307, USA
22
23 "caption<-" <- function(x,value) UseMethod("caption<-")
24 "caption<-.xtable" <- function(x,value) {
25   if (length(value)>2)
26     stop("\"caption\" must have length 1 or 2")
27   attr(x,"caption") <- value
28   return(x)
29 }
30
31 caption <- function(x,...) UseMethod("caption")
32 caption.xtable <- function(x,...) {
33   return(attr(x,"caption",exact=TRUE))
34 }
35
36 "label<-" <- function(x,value) UseMethod("label<-")
37 "label<-.xtable" <- function(x,value) {
38   if (length(value)>1)
39     stop("\"label\" must have length 1")
40   attr(x,"label") <- value
41   return(x)
42 }
43
44 label <- function(x,...) UseMethod("label")
45 label.xtable <- function(x,...) {
46   return(attr(x,"label",exact=TRUE))
47 }
48
49 "align<-" <- function(x,value) UseMethod("align<-")
50
51 # Based on contribution from Jonathan Swinton <jonathan@swintons.net> in e-mail dated Wednesday, January 17, 2007
52 .alignStringToVector <- function(aString) {
53   # poor mans parsing - separating string of form "l{2in}llr|p{1in}c|{1in}"
54   # into "l{2in}" "l"      "l"      "r"      "|"      "p{1in}" "c"      "|{1in}"
55   aString.Align <- character(0);
56   aString.Width <- character(0);
57   wString <- aString
58   while( nchar(wString)>0) {
59     aString.Align <- c(aString.Align,substr(wString,1,1))
60     # is it followed by a brace?
61     thisWidth <- ""
62     if ( nchar(wString)>1 & substr(wString,2,2)=="{") {
63       beforeNextBrace <- regexpr("[^\\]\\}",wString)
64       if (beforeNextBrace <0 ) {
65         stop("No closing } in align string")
66       }
67       thisWidth <- substr(wString,2,beforeNextBrace+1)
68       wString <- substr(wString,beforeNextBrace+2,nchar(wString))
69     } else {
70       wString <- substr(wString,2,nchar(wString))
71     }
72     aString.Width <- c(aString.Width,thisWidth)
73   }
74
75   alignAllowed <- c("l","r","p","c","|","X")
76
77   if (any( !(aString.Align %in% alignAllowed))) {
78     warning("Nonstandard alignments in align string")
79   }
80   res <- paste(aString.Align,aString.Width,sep="")
81   res
82 }
83 #.alignStringToVector ("l{2in}llr|p{1in}c|{1in}")
84 #.alignStringToVector ("l{2in}llr|p{1in}c|")
85 #.alignStringToVector ("{2in}llr|p{1in}c|") # latex syntax error, but gives wrong alignment
86 #.alignStringToVector("llllp{3cm}")
87
88 "align<-.xtable" <- function(x,value) {
89 # Based on contribution from Benno <puetz@mpipsykl.mpg.de> in e-mail dated Wednesday, December 01, 2004
90 # Based on contribution from Jonathan Swinton <jonathan@swintons.net> in e-mail dated Wednesday, January 17, 2007
91   # cat("%",value,"\n")
92   if ( (!is.null(value)) && ( is.character(value) ) && ( length(value) == 1 ) && ( nchar(value) > 1 ) ) {
93         value <- .alignStringToVector(value)
94   } # That should have checked we had only lrcp|
95     # but what if the "if statement" is false?
96     # For simplicity, deleting check present in version 1.4-2 and earlier.
97   c.value <- if (any(!is.na(match(value,"|")))) {
98                 value[-which(value=='|')]
99              } else {
100                 value
101              }
102   if (length(c.value)!=ncol(x)+1)
103       stop(paste("\"align\" must have length equal to",ncol(x)+1,"( ncol(x) + 1 )"))
104
105   attr(x,"align") <- value
106   return(x)
107 }
108
109 align <- function(x,...) UseMethod("align")
110 align.xtable <- function(x,...) {
111   return(attr(x,"align",exact=TRUE))
112 }
113
114 "digits<-" <- function(x,value) UseMethod("digits<-")
115 "digits<-.xtable" <- function(x,value) {
116   if( is.matrix( value ) ) {
117     if( ncol( value ) != ncol(x)+1 || nrow( value ) != nrow(x) ) {
118       stop( "if argument 'digits' is a matrix, it must have columns equal",
119         " to ", ncol(x)+1, " ( ncol(x) + 1 ) and rows equal to ", nrow(x),
120         " ( nrow( x )" )
121     }
122   } else {
123     if( length(value)==1 ) { value <- rep(value, ncol(x)+1) }
124     if( length( value ) >1 & length( value ) != ncol(x)+1 ) {
125       stop( "if argument 'digits' is a vector of length more than one, it must have length equal",
126         " to ", ncol(x)+1, " ( ncol(x) + 1 )" )
127     }
128   }
129   if (!is.numeric(value))
130     stop("\"digits\" must be numeric")
131   attr(x,"digits") <- value
132   return(x)
133 }
134
135 digits <- function(x,...) UseMethod("digits")
136 digits.xtable <- function(x,...) {
137   return(attr(x,"digits",exact=TRUE))
138 }
139
140 "display<-" <- function(x,value) UseMethod("display<-")
141 "display<-.xtable" <- function(x,value) {
142   if (length(value)!=ncol(x)+1)
143     stop(paste("\"display\" must have length equal to",ncol(x)+1,"( ncol(x) + 1 )"))
144   if (!all(!is.na(match(value,c("d","f","e","E","g","G","fg","s")))))
145     stop("\"display\" must be in {\"d\",\"f\",\"e\",\"E\",\"g\",\"G\", \"fg\", \"s\"}")
146   attr(x,"display") <- value
147   return(x)
148 }
149
150 display <- function(x,...) UseMethod("display")
151 display.xtable <- function(x,...) {
152   return(attr(x,"display",exact=TRUE))
153 }
154