[R] ordering x's and y's
Robin Hankin
r.hankin at auckland.ac.nz
Wed Dec 11 22:03:05 CET 2002
WNV writes
> [WNV] The original question had a single value for both x and y
> with variable repititions. I prefer to stick to this, but it could be
> generalized slightly.
>
> library(gregmisc)
> xy.sets <- function(nx, ny, x = "x", y = "y") {
> tt <- combinations(nx + ny, nx)
> answer <- matrix(y, nrow(tt), nx + ny)
> answer[cbind(as.vector(row(tt)), as.vector(tt))] <- x
> answer
> }
>
[rksh] Bill's solution is indeed vectorized and elegant; I spent some
time pondering the "trick" (as a reformed Matlab user, Bill's comment
about "matrix-as-index" techniques being surprising truly strikes
home, as the following code which I wrote years ago attests:
*****warning: Matlab code follows*********
function out=do_r(matrix,p)
%function out=do_r(matrix,p)
%
%example
%
% a=reshape(1:12,3,4)
% p=[1 1;1 4; 2 2]
% do_r(a,p) %consider 2nd row of p (=1,4); a(1,4)=10 as reqd.
%
% see assign
[n m]=size(matrix);
a=reshape(matrix,n*m,1);
places=(p(:,2)-1)*n+p(:,1);
out=a(places);
function out=assign(matrix,p,values);
%does what a(p)=values should do:
%a=reshape(1:12,3,4)
%p=[1 2;1 3 ;3 4]
%assign(a,p,0)
%assign(a,p,-[99 99 99])
%
%
%see do_r
[n m]=size(matrix);
a=reshape(matrix,1,n*m);
places=p(:,1)+n*(p(:,2)-1);
a(places)=values;
out=reshape(a,n,m);
*****matlab code ends******
).
I spent a bit of time trying to generalize Bill's xy.sets() but the
best I could come up with was
xy <- function(x, y) {
nx <- length(x)
ny <- length(y)
tt <- combinations(nx + ny, nx)
placeholder <- matrix(rep(FALSE,nx+ny), nrow(tt), nx + ny,byrow=F)
answer <- placeholder
placeholder[cbind(as.vector(row(tt)), as.vector(tt))] <- TRUE
answer <- t(answer)
placeholder <- t(placeholder)
answer[placeholder== TRUE] <- x
answer[placeholder==FALSE] <- y
t(answer)
}
then xy(1:3,10:11) works. xy() has to deal with the transpose of
answer and placeholder in order to put the elements of x and y in
their correct places. Is there a better way?
Oh yes, I had omitted to point out that do.thing2() could solve the
original problem with something like
R> do.thing2(rep("x",2),rep("y",3))
best
rksh
> >
> > This was asked a few days ago (but I posted my offering offline)..
> > Try:
> >
> > library(gregmisc)
> > do.thing2 <- function(x,y) {
> > a <- c(x,y)
> > tt <- combinations(length(a),length(x))
> > answer <- matrix(NA,nrow(tt),length(a))
> > for(i in 1:nrow(tt)) {
> > answer[i, tt[i,]] <- x
> > answer[i,-tt[i,]] <- y
> > }
> > return(answer)
> > }
> >
> > [anyone got a vectorized version?]
[check deleted]
>
> The trick is the old matrix-as-index thing that surprises so many
> people.
>
> Bill Venables.
>
>
Robin K. S. Hankin, Lecturer,
School of Geography and Environmental Science
Tamaki Campus
Private Bag 92019 Auckland
New Zealand
r.hankin at auckland.ac.nz
tel 0064-9-373-7599 x6820; FAX 0064-9-373-7042
as of: Thu Dec 12 09:00:00 NZDT 2002
This (linux) system up continuously for: 469 days, 14 hours, 42 minutes
--
Robin Hankin, Lecturer,
School of Geography and Environmental Science
Tamaki Campus
Private Bag 92019 Auckland
New Zealand
r.hankin at auckland.ac.nz
tel 0064-9-373-7599 x6820; FAX 0064-9-373-7042
as of: Thu Dec 12 09:49:00 NZDT 2002
This (linux) system up continuously for: 469 days, 15 hours, 31 minutes
More information about the R-help
mailing list