[R] Lattice: panel superpose with groups

2007-09-04 Thread Folkes, Michael
The example code below allows the plotting of three different groups per panel. 
 I can't fathom how to write the panel function to add an additional line for 
each group, which in this case is just the mean Y value for each group within  
each panel.  (i.e. there'd be six lines per panel.)
Spent all day working on it and searching the archives to no avail!  Yikes.
Any help would be greatly appreciated!
Michael Folkes

#
#This builds fake dataset

years-2000:2006
weeks-1:20
yr-rep(years,rep(length(weeks)*6,length(years)))
wk-rep(weeks,rep(6,length(weeks)))
temp-rep(4:9,length(years)*length(weeks))
yvar-round(rnorm(length(years)*length(weeks)*6,mean=30,sd=4),0)
xvar-(rnorm(length(years)*length(weeks)*6)+5)/10

df-data.frame(year=yr,week=wk,temp=temp,   yvar=yvar,  xvar=xvar)
#

library(lattice)
df$year2-as.factor(df$year)
df$week2-as.factor(df$week)
df-df[df$temp %in% c(5,7,9),]
xyplot(yvar~year|week2,data=df,layout = c(4, 5), as.table=TRUE,
type='l',
groups=temp ,
  panel = function(x, y,groups, ...) {
panel.superpose(x,y,groups,...)
panel.xyplot(x,rep(mean(y),length(x)),type='l',lty=3) #- only 
generates the panel mean
  }
)

___
Michael Folkes
Salmon Stock Assessment
Canadian Dept. of Fisheries  Oceans 
Pacific Biological Station
3190 Hammond Bay Rd.
Nanaimo, B.C., Canada
V9T-6N7
Ph (250) 756-7264 Fax (250) 756-7053  [EMAIL PROTECTED]


[[alternative HTML version deleted]]

__
R-help@stat.math.ethz.ch 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.


Re: [R] Lattice: panel superpose with groups

2007-09-04 Thread hadley wickham
Hi Michael,

It's not lattice, but you can easily do this with ggplot2:

install.packages(ggplot2)
library(ggplot2)
qplot(year, yvar, data=df, facets = . ~ week, colour=factor(temp),
geom=line) +
stat_summary(aes(group=1), geom=line, fun=mean, size=2)

Although you don't (currently) get the nice tabular layout of the
panels like in lattice.  You can find out more about ggplot2 at
http://had.co.nz/ggplot2

Hadley

On 9/4/07, Folkes, Michael [EMAIL PROTECTED] wrote:
 The example code below allows the plotting of three different groups per 
 panel.  I can't fathom how to write the panel function to add an additional 
 line for each group, which in this case is just the mean Y value for each 
 group within  each panel.  (i.e. there'd be six lines per panel.)
 Spent all day working on it and searching the archives to no avail!  Yikes.
 Any help would be greatly appreciated!
 Michael Folkes

 #
 #This builds fake dataset

 years-2000:2006
 weeks-1:20
 yr-rep(years,rep(length(weeks)*6,length(years)))
 wk-rep(weeks,rep(6,length(weeks)))
 temp-rep(4:9,length(years)*length(weeks))
 yvar-round(rnorm(length(years)*length(weeks)*6,mean=30,sd=4),0)
 xvar-(rnorm(length(years)*length(weeks)*6)+5)/10

 df-data.frame(year=yr,week=wk,temp=temp,   yvar=yvar,  xvar=xvar)
 #

 library(lattice)
 df$year2-as.factor(df$year)
 df$week2-as.factor(df$week)
 df-df[df$temp %in% c(5,7,9),]
 xyplot(yvar~year|week2,data=df,layout = c(4, 5), as.table=TRUE,
 type='l',
 groups=temp ,
   panel = function(x, y,groups, ...) {
 panel.superpose(x,y,groups,...)
 panel.xyplot(x,rep(mean(y),length(x)),type='l',lty=3) #- 
 only generates the panel mean
   }
 )

 ___
 Michael Folkes
 Salmon Stock Assessment
 Canadian Dept. of Fisheries  Oceans
 Pacific Biological Station
 3190 Hammond Bay Rd.
 Nanaimo, B.C., Canada
 V9T-6N7
 Ph (250) 756-7264 Fax (250) 756-7053  [EMAIL PROTECTED]


 [[alternative HTML version deleted]]

 __
 R-help@stat.math.ethz.ch 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.



-- 
http://had.co.nz/

__
R-help@stat.math.ethz.ch 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.


Re: [R] Lattice: panel superpose with groups

2007-09-04 Thread Deepayan Sarkar
On 9/4/07, Folkes, Michael [EMAIL PROTECTED] wrote:
 The example code below allows the plotting of three different groups per 
 panel.  I can't fathom how to write the panel function to add an additional 
 line for each group, which in this case is just the mean Y value for each 
 group within  each panel.  (i.e. there'd be six lines per panel.)
 Spent all day working on it and searching the archives to no avail!  Yikes.
 Any help would be greatly appreciated!


xyplot(yvar~year|week2,data=df,layout = c(4, 5), as.table=TRUE,
   type='l',
   groups = temp ,
   panel = panel.superpose,
   panel.groups = function(x, y, ..., lty) {
   panel.xyplot(x, y, ..., lty = lty)
   #panel.lines(x, rep(mean(y),length(x)), lty=3, ...) # or
   panel.abline(h = mean(y), lty=3, ...)
   })

(see ?panel.superpose for explanation)

-Deepayan

 Michael Folkes

 #
 #This builds fake dataset

 years-2000:2006
 weeks-1:20
 yr-rep(years,rep(length(weeks)*6,length(years)))
 wk-rep(weeks,rep(6,length(weeks)))
 temp-rep(4:9,length(years)*length(weeks))
 yvar-round(rnorm(length(years)*length(weeks)*6,mean=30,sd=4),0)
 xvar-(rnorm(length(years)*length(weeks)*6)+5)/10

 df-data.frame(year=yr,week=wk,temp=temp,   yvar=yvar,  xvar=xvar)
 #

 library(lattice)
 df$year2-as.factor(df$year)
 df$week2-as.factor(df$week)
 df-df[df$temp %in% c(5,7,9),]
 xyplot(yvar~year|week2,data=df,layout = c(4, 5), as.table=TRUE,
 type='l',
 groups=temp ,
   panel = function(x, y,groups, ...) {
 panel.superpose(x,y,groups,...)
 panel.xyplot(x,rep(mean(y),length(x)),type='l',lty=3) #- 
 only generates the panel mean
   }
 )




 ___
 Michael Folkes
 Salmon Stock Assessment
 Canadian Dept. of Fisheries  Oceans
 Pacific Biological Station
 3190 Hammond Bay Rd.
 Nanaimo, B.C., Canada
 V9T-6N7
 Ph (250) 756-7264 Fax (250) 756-7053  [EMAIL PROTECTED]


 [[alternative HTML version deleted]]

 __
 R-help@stat.math.ethz.ch 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.


__
R-help@stat.math.ethz.ch 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.


Re: [R] Lattice: panel superpose with groups

2007-09-04 Thread Folkes, Michael
Thank you again Deepayan.  I was failing to grasp that I could use
panel.groups as a function.  But additionally it's still not intuitive
to me where and when I should use ... to pass arguments on.
Additionally, as to why the panel.group function needs to pass the 'lty'
argument isn't terribly clear to me! Perhaps it will become clear with
time.
I greatly appreciate your patience and assistance.
Thanks all,
Michael Folkes

-Original Message-
From: Deepayan Sarkar [mailto:[EMAIL PROTECTED] 
Sent: September 4, 2007 5:11 PM
To: Folkes, Michael
Cc: r-help@stat.math.ethz.ch
Subject: Re: [R] Lattice: panel superpose with groups


On 9/4/07, Folkes, Michael [EMAIL PROTECTED] wrote:
 The example code below allows the plotting of three different groups 
 per panel.  I can't fathom how to write the panel function to add an 
 additional line for each group, which in this case is just the mean Y 
 value for each group within  each panel.  (i.e. there'd be six lines 
 per panel.) Spent all day working on it and searching the archives to 
 no avail!  Yikes. Any help would be greatly appreciated!


xyplot(yvar~year|week2,data=df,layout = c(4, 5), as.table=TRUE,
   type='l',
   groups = temp ,
   panel = panel.superpose,
   panel.groups = function(x, y, ..., lty) {
   panel.xyplot(x, y, ..., lty = lty)
   #panel.lines(x, rep(mean(y),length(x)), lty=3, ...) # or
   panel.abline(h = mean(y), lty=3, ...)
   })

(see ?panel.superpose for explanation)

-Deepayan

 Michael Folkes

 #
 #This builds fake dataset

 years-2000:2006
 weeks-1:20
 yr-rep(years,rep(length(weeks)*6,length(years)))
 wk-rep(weeks,rep(6,length(weeks)))
 temp-rep(4:9,length(years)*length(weeks))
 yvar-round(rnorm(length(years)*length(weeks)*6,mean=30,sd=4),0)
 xvar-(rnorm(length(years)*length(weeks)*6)+5)/10

 df-data.frame(year=yr,week=wk,temp=temp,   yvar=yvar,
xvar=xvar)
 #

 library(lattice)
 df$year2-as.factor(df$year)
 df$week2-as.factor(df$week)
 df-df[df$temp %in% c(5,7,9),] xyplot(yvar~year|week2,data=df,layout =

 c(4, 5), as.table=TRUE,
 type='l',
 groups=temp ,
   panel = function(x, y,groups, ...) {
 panel.superpose(x,y,groups,...)
 panel.xyplot(x,rep(mean(y),length(x)),type='l',lty=3)
#- only generates the panel mean
   }
 )




 ___
 Michael Folkes
 Salmon Stock Assessment
 Canadian Dept. of Fisheries  Oceans
 Pacific Biological Station
 3190 Hammond Bay Rd.
 Nanaimo, B.C., Canada
 V9T-6N7
 Ph (250) 756-7264 Fax (250) 756-7053  [EMAIL PROTECTED]


 [[alternative HTML version deleted]]

 __
 R-help@stat.math.ethz.ch 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.


__
R-help@stat.math.ethz.ch 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.


Re: [R] Lattice: panel superpose with groups

2007-09-04 Thread Deepayan Sarkar
On 9/4/07, Folkes, Michael [EMAIL PROTECTED] wrote:

 Thank you again Deepayan.  I was failing to grasp that I could use
 panel.groups as a function.  But additionally it's still not intuitive
 to me where and when I should use ... to pass arguments on.

In most cases, it's used to pass on graphical parameters, so I tend to
have the ... by default (which means you can supply graphical
parameters directly as arguments to xyplot). This is particularly
non-trivial in panel.groups, because panel.superpose does a lot of
work to replicate the parameters and pass on a different one for each
call to panel.groups.

 Additionally, as to why the panel.group function needs to pass the 'lty'
 argument isn't terribly clear to me!

Try not having it and you will find out. Basically, if you don't have
it, the explicit lty=3 in the call to panel.abline will conflict with
the lty passed on through ...

-Deepayan

__
R-help@stat.math.ethz.ch 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.