[R] matrix values linked to vector index
    arun 
    smartpink111 at yahoo.com
       
    Fri Oct 11 23:43:51 CEST 2013
    
    
  
Seems like a bug in the code:
x<- c(3,4,1)
n<- 3
 matrix(rep(rep(c(1,0),n),rbind(x,n-x)),nc=n,byr=TRUE)
#Error in rep(rep(c(1, 0), n), rbind(x, n - x)) : invalid 'times' argument
 n<- 4
 matrix(rep(rep(c(1,0),n),rbind(x,n-x)),nc=n,byr=TRUE)
#Error in rep(rep(c(1, 0), n), rbind(x, n - x)) : invalid 'times' argument
x2
[1] 2 0 4 3 1
> matrix(rep(rep(c(1,0),n),rbind(x2,n-x2)),nc=n,byr=TRUE)
Error in rep(rep(c(1, 0), n), rbind(x2, n - x2)) : 
  invalid 'times' argument
A.K.
On Friday, October 11, 2013 5:17 PM, Bert Gunter <gunter.berton at gene.com> wrote:
simpler (and sloppier) but with **no looping or apply's **
**IFF* the matrix is structured as in the OP's example, then lower.tri
(or upper.tri) should be used:
n <- 4 ## number of columns in matrix -- note that I changed it from
the example; does not have to be square
x <- 1:3 ## the number of 1's per row
lower.tri(matrix(0,nr=length(x),nc=n),diagA=TRUE)+0
A general, fast, but **tricky** way to do it that depends on knowing
that a matrix is just a vector in column major order is to generate
the vector using rep and then structure it as a matrix. eg.
x <- c(3,2,1,4) ## your vector of indices
n <- 4 ## number of columns in matrix ## does not have to be square
matrix(rep(rep(c(1,0),n),rbind(x,n-x)),nc=n,byr=TRUE)
    [,1] [,2] [,3] [,4]
[1,]    1    1    1    0
[2,]    1    1    0    0
[3,]    1    0    0    0
[4,]    1    1    1    1
Cheers,
Bert
On Fri, Oct 11, 2013 at 1:41 PM, Dennis Murphy <djmuser at gmail.com> wrote:
> Attempting to follow the OP's conditions and assuming I understood
> them correctly, here is one way to wrap this up into a function:
>
> makeMat <- function(x)
> {
>     stopifnot(is.integer(x))
>     nr <- length(x)
>     nc <- max(x)
>
>     # Initialize a matrix of zeros
>     m <- matrix(0, nr, nc)
>     # Conditionally replace with ones
>     for(i in seq_len(nr)) if(x[i] != 0)  m[i, 1:x[i]] <- 1
>     m
> }
>
> ## Examples:
> x1 <- 1:3
> x2 <- as.integer(c(2, 0, 4, 3, 1))
> x3 <- c(2, 1, 2.2)
>
> makeMat(x1)
> makeMat(x2)
> makeMat(x3)
> makeMat(4:6)
>
>
> On Fri, Oct 11, 2013 at 9:49 AM, arun <smartpink111 at yahoo.com> wrote:
>> Hi,
>>
>> In the example you showed:
>>
>> m1<- matrix(0,length(vec),max(vec))
>> 1*!upper.tri(m1)
>>
>> #or
>>  m1[!upper.tri(m1)] <-  rep(rep(1,length(vec)),vec)
>>
>> #But, in a case like below, perhaps:
>> vec1<- c(3,4,5)
>>
>>  m2<- matrix(0,length(vec1),max(vec1))
>>  indx <- cbind(rep(seq_along(vec1),vec1),unlist(tapply(vec1,list(vec1),FUN=seq),use.names=FALSE))
>> m2[indx]<- 1
>>  m2
>> #     [,1] [,2] [,3] [,4] [,5]
>> #[1,]    1    1    1    0    0
>> #[2,]    1    1    1    1    0
>> #[3,]    1    1    1    1    1
>>
>>
>>
>>
>> A.K.
>>
>>
>> Hi-
>>
>> I'd like to create a matrix of 0's and 1's where the number of
>> 1's in each row defined by the value indexed in another vector, and
>> where the (value-1) is back-filled by 0's.
>>
>> For example, given the following vector:
>> vec= c(1,2,3)
>>
>> I'd like to produce a matrix with dimensions (length(vec), max(vec)):
>>
>> 1,0,0
>> 1,1,0
>> 1,1,1
>>
>> Thank you!
>>
>> ______________________________________________
>> 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.
>
> ______________________________________________
> 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.
-- 
Bert Gunter
Genentech Nonclinical Biostatistics
(650) 467-7374
    
    
More information about the R-help
mailing list