f7060c99 | #' Load a clinical/phenotypic dataset associated with a study. |
1f4053bb | #' |
f7060c99 | #' Load a matrix of metadata associated with a study. |
1f4053bb | #' #' |
552624f1 | #' @aliases loadPhenoData phenoData |
f7060c99 | #' @param file Path and filename of the actual clinical file. |
1f4053bb | #' @param tran Boolean. If the covariates are along the columns and samples #' along the rows, then tran should equal TRUE. |
f7060c99 | #' @param sep The separator for the file. #' @return The metadata as a dataframe. |
552624f1 | #' @seealso \code{\link{loadMeta}} |
f7060c99 | #' @examples |
1f4053bb | #' |
5d15f814 | #' dataDirectory <- system.file("extdata", package="metagenomeSeq") #' clin = loadPhenoData(file.path(dataDirectory,"CHK_clinical.csv"),tran=TRUE) |
1f4053bb | #' |
552624f1 | loadPhenoData <-function(file,tran=TRUE,sep="\t") |
f7060c99 | { dat2 <- read.table(file,header=FALSE,sep=sep); # no. of subjects subjects <- array(0,dim=c(ncol(dat2)-1)); for(i in 1:length(subjects)) { subjects[i] <- as.character(dat2[1,i+1]); } # no. of rows rows <- nrow(dat2); # load remaining counts matrix <- array(NA, dim=c(length(subjects),rows-1)); covar = array(NA,dim=c(rows-1,1)); for(i in 1:(rows)-1){ for(j in 1:(length(subjects))){ matrix[j,i] <- as.character(dat2[i+1,j+1]); } covar[i] = as.character(dat2[i+1,1]); } phenoData<-as.data.frame(matrix); colnames(phenoData) = covar; if(length(unique(subjects))==(length(subjects))){ rownames(phenoData) = subjects; } if(tran==TRUE){ phenoData = as.data.frame(t(phenoData)) } return(phenoData); } |