[R] Barchart in lattice - wrong order of groups, data labels on top of each other, and a legend question

Gabor Grothendieck ggrothendieck at gmail.com
Fri May 22 03:37:06 CEST 2009


If you are willing to go down one level and work at the grid level
then you can do it without modifying the panel function.

Below gg.ls$name lists the grid object names.  Within that
list look at the ones that have rect in their name.  Among
those are 5 in success (the 2nd through 6th rect objects).
Similarly look for a text object in that vicinity. That would
be the the third object of those with text in their name.  We
want to reset the positioning of the text in the text object
using the info from the rect objects that form the bars. Thus:

# first run your code as posted, then run this
library(grid)
gg <- grid.grab()
gg.ls <- grid.ls(gg)
# based on gg.ls$name we make the observations above

rect.names <- grep("rect", gg.ls$name, value = TRUE)[2:6]
text.names <- grep("text", gg.ls$name, value = TRUE)[3]

rect.x <- c(sapply(rect.names, function(x) grid.get(x)$x))
rect.height <- c(sapply(rect.names, function(x) grid.get(x)$height))
text.name <- grep("text", gg.ls$name, value = TRUE)[3]

grid.edit(text.name,
	x = unit(rect.x, "native"),
	y = unit(rect.height+1, "native"))

On Thu, May 21, 2009 at 3:58 PM, Dimitri Liakhovitski <ld7631 at gmail.com> wrote:
> Deepayan, thank you very much for your response.
> I have a general question. And please remember - I am really just a
> beginner in R.
> Is it truly the case that in order to build quite a basic bar chart
> with value labels attached to it I have to be a true R graphics guru -
> because the only way to do achieve what I am trying to achive is to
> modify the underlying R function (panel.barchart)?
> Really?
>
> Dimitri
>
>
> On Tue, May 19, 2009 at 7:53 PM, Deepayan Sarkar
> <deepayan.sarkar at gmail.com> wrote:
>> On Mon, May 18, 2009 at 11:47 AM, Dimitri Liakhovitski <ld7631 at gmail.com> wrote:
>>> Hello!
>>> I have a question about my lattice barchart that I am trying to build
>>> in Section 3 below. I can't figure out a couple of things:
>>> 1. When I look at the dataframe "test" that I am trying to plot, it
>>> looks right to me (the group "Total" is always the first out of 5).
>>> However, in the chart it is the last. Why?
>>> 2. How can I make sure the value labels (on y) are not sitting on top
>>> of each other but on top of the respective bar?
>>> 3. Is there any way to make the legend group items horizontally as
>>> opposed to now (vertically - taking up too much space)
>>
>> For 1 and 3, use
>>
>>         auto.key = list(points = FALSE,
>>                         rectangles = TRUE,
>>                         reverse.rows = TRUE,
>>                         columns = 2,
>>                         space = "bottom")
>>
>> From ?xyplot (under 'key'):
>>
>>               'reverse.rows' logical, defaulting to 'FALSE'.  If
>>                    'TRUE', all components are reversed _after_ being
>>                    replicated (the details of which may depend on the
>>                    value of 'rep').  This is useful in certain
>>                    situations, e.g. with a grouped 'barchart' with
>>                    'stack = FALSE' with the categorical variable on
>>                    the vertical axis, where the bars in the plot will
>>                    usually be ordered from bottom to top, but the
>>                    corresponding legend will have the levels from top
>>                    to bottom (unless, of course, 'reverse.rows =
>>                    TRUE').  Note that in this case, unless all columns
>>                    have the same number or rows, they will no longer
>>                    be aligned.
>>
>>               'columns' the number of columns column-blocks the key is
>>                    to be divided into, which are drawn side by side.
>>
>>
>> 2 is hard with a simple custom panel function, because you need to
>> replicate some fairly involved calculations that are performed in
>> panel.barchart. Your best bet is to start with a copy of
>> panel.barchart, and then add calls to panel.text at suitable places.
>>
>> -Deepayan
>>
>>
>>> Thanks a lot!
>>> Dimitri
>>>
>>> ### Section 1: generates my data set "data" - just run: #####
>>>
>>> N<-100
>>> myset1<-c(1,2,3,4,5)
>>> probs1<-c(.05,.10,.15,.40,.30)
>>> myset2<-c(0,1)
>>> probs2<-c(.65,.30)
>>> myset3<-c(1,2,3,4,5,6,7)
>>> probs3<-c(.02,.03,.10,.15,.20,.30,.20)
>>>
>>> group<-unlist(lapply(1:4,function(x){
>>>        out<-rep(x,25)
>>>        return(out)
>>> }))
>>> set.seed(1)
>>> a<-sample(myset1, N, replace = TRUE,probs1)
>>> a[which(rbinom(100,2,.01)==1)]<-NA
>>> set.seed(12)
>>> b<-sample(myset1, N, replace = TRUE,probs1)
>>> b[which(rbinom(100,2,.01)==1)]<-NA
>>> set.seed(123)
>>> c<-sample(myset2, N, replace = TRUE,probs2)
>>> set.seed(1234)
>>> d<-sample(myset2, N, replace = TRUE,probs2)
>>> set.seed(12345)
>>> e<-sample(myset3, N, replace = TRUE,probs3)
>>> e[which(rbinom(100,2,.01)==1)]<-NA
>>> set.seed(123456)
>>> f<-sample(myset3, N, replace = TRUE,probs3)
>>> f[which(rbinom(100,2,.01)==1)]<-NA
>>> data<-data.frame(group,a=a,b=b,c=c,d=d,e=e,f=f)
>>> data["group"]<-lapply(data["group"],function(x) {
>>>        x[x %in% 1]<-"Group 1"
>>>        x[x %in% 2]<-"Group 2"
>>>        x[x %in% 3]<-"Group 3"
>>>        x[x %in% 4]<-"Group 4"
>>>        return(x)
>>> })
>>> data$group<-as.factor(data$group)
>>> lapply(data,table,exclude=NULL)
>>>
>>> tables<-lapply(data,function(x){
>>>        out<-table(x)
>>>        out<-prop.table(out)
>>>        out<-round(out,3)*100
>>>        return(out)
>>> })
>>> str(tables[2])
>>>
>>> ##### Section 2: Generating a list of tables with percentages to be
>>> plotted in barcharts - just run: #####
>>>
>>> listoftables<-list()
>>> for(i in 1:(length(data)-1)) {
>>>  listoftables[[i]]<-data.frame()
>>> }
>>> for(i in 1:length(listoftables)) {
>>>    total<-table(data[[i+1]])
>>>    groups<-table(data[[1]],data[[i+1]])
>>>    total.percents<-as.data.frame(t(as.vector(round(total*100/sum(total),1))))
>>>    groups.percents<-as.data.frame(t(apply(groups,1,function(x){
>>>      out<-round(x*100/sum(x),1)
>>>     return(out)
>>>  })))
>>>  names(total.percents)<-names(groups.percents)
>>>  final.table<-rbind(total.percents,groups.percents)
>>>  row.names(final.table)[1]<-"Total"
>>>  final.table<-as.matrix(final.table)
>>>  listoftables[[i]]<-final.table
>>> }
>>> names(listoftables)<-names(data)[2:(length(listoftables)+1)]
>>>
>>>
>>> ### Section 3 - building the graph for the very first table of the
>>> "listoftables" ###
>>> library(lattice)
>>> i<-1
>>> test <- data.frame(Group = rep(row.names(listoftables[[i]]),5), a =
>>> rep(1:5,each=5),Percentage = as.vector(listoftables[[i]]))
>>> par.settings=trellis.par.set(reference.line = list(col = "gray", lty ="dotted"))
>>> barchart(Percentage~a, test, groups = Group, horizontal = F,
>>> auto.key = list(points = FALSE, rectangles = TRUE, space =
>>> "bottom"),ylim = c(0,50),
>>>    panel = function(y,x,...) {
>>>    panel.grid(h = -1, v = -1)
>>>    panel.barchart(x, y, ...)
>>>    ltext(x, y, labels=round(y,0),cex=.7,col="black",font=2,pos=3)
>>> })
>>>
>>>
>>> --
>>> Dimitri Liakhovitski
>>> MarketTools, Inc.
>>> Dimitri.Liakhovitski at markettools.com
>>>
>>> ______________________________________________
>>> R-help at r-project.org mailing list
>>> https://stat.ethz.ch/mailman/listinfo/r-help
>>> PLEASE do read the posting guide http://www.R-project.org/posting-guide.html
>>> and provide commented, minimal, self-contained, reproducible code.
>>>
>>
>
>
>
> --
> Dimitri Liakhovitski
> MarketTools, Inc.
> Dimitri.Liakhovitski at markettools.com
>
> ______________________________________________
> R-help at r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-help
> PLEASE do read the posting guide http://www.R-project.org/posting-guide.html
> and provide commented, minimal, self-contained, reproducible code.
>




More information about the R-help mailing list