From: nosson <jpaulson@umiacs.umd.edu>
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@122454 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -12,7 +12,8 @@ |
12 | 12 |
#' @seealso \code{\link{loadMeta}} |
13 | 13 |
#' @examples |
14 | 14 |
#' |
15 |
-#' # see vignette |
|
15 |
+#' dataDirectory <- system.file("extdata", package="metagenomeSeq") |
|
16 |
+#' clin = loadPhenoData(file.path(dataDirectory,"CHK_clinical.csv"),tran=TRUE) |
|
16 | 17 |
#' |
17 | 18 |
loadPhenoData <-function(file,tran=TRUE,sep="\t") |
18 | 19 |
{ |
Creating naming schemes consistency and deprecating the load_* functions.
From: Joseph N. Paulson <jpaulson@jimmy.harvard.edu>
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@121795 bc3139a8-67e5-0310-9ffc-ced21a209358
1 | 1 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,51 @@ |
1 |
+#' Load a clinical/phenotypic dataset associated with a study. |
|
2 |
+#' |
|
3 |
+#' Load a matrix of metadata associated with a study. |
|
4 |
+#' |
|
5 |
+#' |
|
6 |
+#' @aliases loadPhenoData phenoData |
|
7 |
+#' @param file Path and filename of the actual clinical file. |
|
8 |
+#' @param tran Boolean. If the covariates are along the columns and samples |
|
9 |
+#' along the rows, then tran should equal TRUE. |
|
10 |
+#' @param sep The separator for the file. |
|
11 |
+#' @return The metadata as a dataframe. |
|
12 |
+#' @seealso \code{\link{loadMeta}} |
|
13 |
+#' @examples |
|
14 |
+#' |
|
15 |
+#' # see vignette |
|
16 |
+#' |
|
17 |
+loadPhenoData <-function(file,tran=TRUE,sep="\t") |
|
18 |
+{ |
|
19 |
+ dat2 <- read.table(file,header=FALSE,sep=sep); |
|
20 |
+ |
|
21 |
+# no. of subjects |
|
22 |
+ subjects <- array(0,dim=c(ncol(dat2)-1)); |
|
23 |
+ for(i in 1:length(subjects)) { |
|
24 |
+ subjects[i] <- as.character(dat2[1,i+1]); |
|
25 |
+ } |
|
26 |
+# no. of rows |
|
27 |
+ rows <- nrow(dat2); |
|
28 |
+ |
|
29 |
+# load remaining counts |
|
30 |
+ matrix <- array(NA, dim=c(length(subjects),rows-1)); |
|
31 |
+ covar = array(NA,dim=c(rows-1,1)); |
|
32 |
+ |
|
33 |
+ for(i in 1:(rows)-1){ |
|
34 |
+ for(j in 1:(length(subjects))){ |
|
35 |
+ matrix[j,i] <- as.character(dat2[i+1,j+1]); |
|
36 |
+ } |
|
37 |
+ covar[i] = as.character(dat2[i+1,1]); |
|
38 |
+ } |
|
39 |
+ |
|
40 |
+ |
|
41 |
+ phenoData<-as.data.frame(matrix); |
|
42 |
+ |
|
43 |
+ colnames(phenoData) = covar; |
|
44 |
+ if(length(unique(subjects))==(length(subjects))){ |
|
45 |
+ rownames(phenoData) = subjects; |
|
46 |
+ } |
|
47 |
+ if(tran==TRUE){ |
|
48 |
+ phenoData = as.data.frame(t(phenoData)) |
|
49 |
+ } |
|
50 |
+ return(phenoData); |
|
51 |
+} |