... | ... |
@@ -303,7 +303,7 @@ appendGDSgenotypeMat <- function(gds, matG) { |
303 | 303 |
generateGDS1KGgenotypeFromSNPPileup <- function(pathGeno, |
304 | 304 |
listSamples, listPos, offset, minCov=10, minProb=0.999, |
305 | 305 |
seqError=0.001, pedStudy, batch, studyDF, PATHGDSSAMPLE=NULL, |
306 |
- genoSource = c("snp-pileup", "generic"), verbose) { |
|
306 |
+ genoSource=c("snp-pileup", "generic"), verbose) { |
|
307 | 307 |
|
308 | 308 |
# File with the description of the SNP keep |
309 | 309 |
listMat <- dir(pathGeno, pattern = ".+.txt.gz") |
... | ... |
@@ -322,7 +322,7 @@ generateGDS1KGgenotypeFromSNPPileup <- function(pathGeno, |
322 | 322 |
if(genoSource == "snp-pileup") { |
323 | 323 |
matSample <- readSNVPileupFile(file.path(pathGeno, |
324 | 324 |
listMat[pos]), offset) |
325 |
- } else if(genoTypeSource == "generic") { |
|
325 |
+ } else if(genoSource == "generic") { |
|
326 | 326 |
matSample <- readSNVFileGeneric(file.path(pathGeno, |
327 | 327 |
listMat[pos]), offset) |
328 | 328 |
} |
... | ... |
@@ -53,6 +53,15 @@ |
53 | 53 |
#' the directory where the Profile GDS files will be created. |
54 | 54 |
#' Default: \code{NULL}. |
55 | 55 |
#' |
56 |
+#' @param genoSource a \code{stirng} with two possible values: |
|
57 |
+#' snp-pileup and generic. It specify if the genotype files |
|
58 |
+#' are generate by snp-pileup(Facets) or generic format csv |
|
59 |
+#' with the column at least the columns: |
|
60 |
+#' Chromosome,Position,Ref,Alt,Count,File1R,File1A |
|
61 |
+#' where Count is the deep at the position, |
|
62 |
+#' FileR is the deep of the reference allele, and |
|
63 |
+#' File1A is the deep of the specific alternative allele |
|
64 |
+#' |
|
56 | 65 |
#' @param verbose a \code{logical} indicating if message information should be |
57 | 66 |
#' printed. Default: \code{FALSE}. |
58 | 67 |
#' |
... | ... |
@@ -87,7 +96,9 @@ |
87 | 96 |
#' result <- createStudy2GDS1KG(pathGeno=dataDir, |
88 | 97 |
#' pedStudy=samplePED, fileNameGDS=fileGDS, |
89 | 98 |
#' studyDF=studyDF, listProfiles=c("ex1"), |
90 |
-#' pathProfileGDS=dataDir, verbose=FALSE) |
|
99 |
+#' pathProfileGDS=dataDir, |
|
100 |
+#' genoSource="snp-pileup", |
|
101 |
+#' verbose=FALSE) |
|
91 | 102 |
#' |
92 | 103 |
#' ## The function returns OL when successful |
93 | 104 |
#' result |
... | ... |
@@ -107,7 +118,9 @@ |
107 | 118 |
createStudy2GDS1KG <- function(pathGeno=file.path("data", "sampleGeno"), |
108 | 119 |
fileNamePED=NULL, pedStudy=NULL, fileNameGDS, |
109 | 120 |
batch=1, studyDF, listProfiles=NULL, |
110 |
- pathProfileGDS=NULL, verbose=FALSE) { |
|
121 |
+ pathProfileGDS=NULL, |
|
122 |
+ genoSource=c("snp-pileup", "generic"), |
|
123 |
+ verbose=FALSE) { |
|
111 | 124 |
|
112 | 125 |
## When fileNamePED is defined and pedStudy is null |
113 | 126 |
if (!(is.null(fileNamePED)) && is.null(pedStudy)) { |
... | ... |
@@ -130,7 +143,9 @@ createStudy2GDS1KG <- function(pathGeno=file.path("data", "sampleGeno"), |
130 | 143 |
validateCreateStudy2GDS1KG(pathGeno=pathGeno, pedStudy=pedStudy, |
131 | 144 |
fileNameGDS=fileNameGDS, batch=batch, studyDF=studyDF, |
132 | 145 |
listProfiles=listProfiles, pathProfileGDS=pathProfileGDS, |
133 |
- verbose=verbose) |
|
146 |
+ genoSource=genoSource, verbose=verbose) |
|
147 |
+ |
|
148 |
+ genoSource <- match.arg(genoSource) |
|
134 | 149 |
|
135 | 150 |
## Read the 1KG GDS file |
136 | 151 |
gds <- snpgdsOpen(filename=fileNameGDS) |
... | ... |
@@ -151,7 +166,8 @@ createStudy2GDS1KG <- function(pathGeno=file.path("data", "sampleGeno"), |
151 | 166 |
generateGDS1KGgenotypeFromSNPPileup(pathGeno=pathGeno, |
152 | 167 |
listSamples=listProfiles, listPos=listPos, offset=-1, minCov=10, |
153 | 168 |
minProb=0.999, seqError=0.001, pedStudy=pedStudy, batch=batch, |
154 |
- studyDF=studyDF, PATHGDSSAMPLE=pathProfileGDS, verbose=verbose) |
|
169 |
+ studyDF=studyDF, PATHGDSSAMPLE=pathProfileGDS, |
|
170 |
+ genoSource=genoSource, verbose=verbose) |
|
155 | 171 |
|
156 | 172 |
if(verbose) { |
157 | 173 |
message("Genotype DONE ", Sys.time()) |
... | ... |
@@ -2177,6 +2193,15 @@ computeAncestryFromSyntheticFile <- function(gds, gdsSample, |
2177 | 2193 |
#' super-population assigned to the sample. } |
2178 | 2194 |
#' } |
2179 | 2195 |
#' |
2196 |
+#' @param genoSource a \code{stirng} with two possible values: |
|
2197 |
+#' snp-pileup and generic. It specify if the genotype files |
|
2198 |
+#' are generate by snp-pileup(Facets) or generic format csv |
|
2199 |
+#' with the column at least the columns: |
|
2200 |
+#' Chromosome,Position,Ref,Alt,Count,File1R,File1A |
|
2201 |
+#' where Count is the deep at the position, |
|
2202 |
+#' FileR is the deep of the reference allele, and |
|
2203 |
+#' File1A is the deep of the specific alternative allele |
|
2204 |
+#' |
|
2180 | 2205 |
#' @return The integer \code{0L} when successful. See details section for |
2181 | 2206 |
#' more information about the generated output files. |
2182 | 2207 |
#' |
... | ... |
@@ -2285,7 +2310,8 @@ computeAncestryFromSyntheticFile <- function(gds, gdsSample, |
2285 | 2310 |
#' fileReferenceGDS=fileReferenceGDS, |
2286 | 2311 |
#' fileReferenceAnnotGDS=fileAnnotGDS, |
2287 | 2312 |
#' chrInfo=chrInfo, |
2288 |
-#' dataRefSyn=dataRef) |
|
2313 |
+#' dataRefSyn=dataRef, |
|
2314 |
+#' genoSource="snp-pileup") |
|
2289 | 2315 |
#' |
2290 | 2316 |
#' unlink(pathProfileGDS, recursive=TRUE, force=TRUE) |
2291 | 2317 |
#' unlink(pathOut, recursive=TRUE, force=TRUE) |
... | ... |
@@ -2297,19 +2323,23 @@ computeAncestryFromSyntheticFile <- function(gds, gdsSample, |
2297 | 2323 |
#' @export |
2298 | 2324 |
runExomeAncestry <- function(pedStudy, studyDF, pathProfileGDS, |
2299 | 2325 |
pathGeno, pathOut, fileReferenceGDS, fileReferenceAnnotGDS, |
2300 |
- chrInfo, dataRefSyn) { |
|
2326 |
+ chrInfo, dataRefSyn, |
|
2327 |
+ genoSource=c("snp-pileup", "generic")) { |
|
2301 | 2328 |
|
2302 | 2329 |
## Validate parameters |
2303 | 2330 |
validateRunExomeAncestry(pedStudy, studyDF, pathProfileGDS, |
2304 | 2331 |
pathGeno=pathGeno, pathOut=pathOut, fileReferenceGDS=fileReferenceGDS, |
2305 | 2332 |
fileReferenceAnnotGDS=fileReferenceAnnotGDS, chrInfo=chrInfo, |
2306 |
- dataRefSyn=dataRefSyn) |
|
2333 |
+ dataRefSyn=dataRefSyn, genoSource=genoSource) |
|
2334 |
+ |
|
2335 |
+ genoSource <- match.arg(genoSource) |
|
2307 | 2336 |
|
2308 | 2337 |
listProfiles <- pedStudy[, "Name.ID"] |
2309 | 2338 |
|
2310 | 2339 |
createStudy2GDS1KG(pathGeno=pathGeno, pedStudy=pedStudy, |
2311 | 2340 |
fileNameGDS=fileReferenceGDS, listProfiles=listProfiles, |
2312 |
- studyDF=studyDF, pathProfileGDS=pathProfileGDS) |
|
2341 |
+ studyDF=studyDF, pathProfileGDS=pathProfileGDS, |
|
2342 |
+ genoSource=genoSource, verbose=FALSE) |
|
2313 | 2343 |
|
2314 | 2344 |
## Open the 1KG GDS file (demo version) |
2315 | 2345 |
gds1KG <- snpgdsOpen(fileReferenceGDS) |
... | ... |
@@ -501,14 +501,16 @@ validateEstimateAllelicFraction <- function(gds, gdsSample, currentProfile, |
501 | 501 |
#' RAIDS:::validateCreateStudy2GDS1KG(pathGeno=dataDir, pedStudy=ped, |
502 | 502 |
#' fileNameGDS=gds1KG, batch=1, studyDF=studyInfo, |
503 | 503 |
#' listProfiles=c("Sample_01", "Sample_02"), |
504 |
-#' pathProfileGDS=dataDir, verbose=TRUE) |
|
504 |
+#' pathProfileGDS=dataDir, |
|
505 |
+#' genoSource="snp-pileup", verbose=TRUE) |
|
505 | 506 |
#' |
506 | 507 |
#' @author Pascal Belleau, Astrid Deschênes and Alexander Krasnitz |
507 | 508 |
#' @importFrom S4Vectors isSingleNumber |
508 | 509 |
#' @encoding UTF-8 |
509 | 510 |
#' @keywords internal |
510 | 511 |
validateCreateStudy2GDS1KG <- function(pathGeno, pedStudy, fileNameGDS, batch, |
511 |
- studyDF, listProfiles, pathProfileGDS, verbose) { |
|
512 |
+ studyDF, listProfiles, pathProfileGDS, |
|
513 |
+ genoSource, verbose) { |
|
512 | 514 |
|
513 | 515 |
## The pathGeno must be a existing directory |
514 | 516 |
if (!dir.exists(pathGeno)) { |
... | ... |
@@ -544,6 +546,11 @@ validateCreateStudy2GDS1KG <- function(pathGeno, pedStudy, fileNameGDS, batch, |
544 | 546 |
" the path where the Profile GDS files will be generated.") |
545 | 547 |
} |
546 | 548 |
|
549 |
+ ## The genoSource must be a character string |
|
550 |
+ if(!(is.character(genoSource))) { |
|
551 |
+ stop("The \'genoSource\' parameter must be a character string.") |
|
552 |
+ } |
|
553 |
+ |
|
547 | 554 |
## The verbose parameter must be a logical |
548 | 555 |
validateLogical(logical=verbose, "verbose") |
549 | 556 |
|
... | ... |
@@ -1052,14 +1059,14 @@ validateAdd1KG2SampleGDS <- function(gds, gdsProfileFile, currentProfile, |
1052 | 1059 |
#' RAIDS:::validateRunExomeAncestry(pedStudy=ped, studyDF=study, |
1053 | 1060 |
#' pathProfileGDS=dataDir, pathGeno=dataDir, pathOut=pathOut, |
1054 | 1061 |
#' fileReferenceGDS=gds1KG, fileReferenceAnnotGDS=gdsAnnot1KG, |
1055 |
-#' chrInfo=chrInfo, dataRefSyn=dataRefSyn) |
|
1062 |
+#' chrInfo=chrInfo, dataRefSyn=dataRefSyn, genoSource="snp-pileup") |
|
1056 | 1063 |
#' |
1057 | 1064 |
#' @author Pascal Belleau, Astrid Deschênes and Alexander Krasnitz |
1058 | 1065 |
#' @encoding UTF-8 |
1059 | 1066 |
#' @keywords internal |
1060 | 1067 |
validateRunExomeAncestry <- function(pedStudy, studyDF, pathProfileGDS, |
1061 | 1068 |
pathGeno, pathOut, fileReferenceGDS, fileReferenceAnnotGDS, |
1062 |
- chrInfo, dataRefSyn) { |
|
1069 |
+ chrInfo, dataRefSyn, genoSource) { |
|
1063 | 1070 |
|
1064 | 1071 |
## The PED study must have the mandatory columns |
1065 | 1072 |
validatePEDStudyParameter(pedStudy=pedStudy) |
... | ... |
@@ -1093,12 +1100,18 @@ validateRunExomeAncestry <- function(pedStudy, studyDF, pathProfileGDS, |
1093 | 1100 |
"The file must exist.") |
1094 | 1101 |
} |
1095 | 1102 |
|
1103 |
+ |
|
1096 | 1104 |
## The chrInfo must be a vector of integer |
1097 | 1105 |
validatePositiveIntegerVector(chrInfo, "chrInfo") |
1098 | 1106 |
|
1099 | 1107 |
## The dataRefSyn must have the madatory columns |
1100 | 1108 |
validateDataRefSynParameter(dataRefSyn=dataRefSyn) |
1101 | 1109 |
|
1110 |
+ ## The genoSource must be a character string |
|
1111 |
+ if(!(is.character(genoSource))) { |
|
1112 |
+ stop("The \'genoSource\' parameter must be a character string.") |
|
1113 |
+ } |
|
1114 |
+ |
|
1102 | 1115 |
return(0L) |
1103 | 1116 |
} |
1104 | 1117 |
|
... | ... |
@@ -16,6 +16,7 @@ createStudy2GDS1KG( |
16 | 16 |
studyDF, |
17 | 17 |
listProfiles = NULL, |
18 | 18 |
pathProfileGDS = NULL, |
19 |
+ genoSource = c("snp-pileup", "generic"), |
|
19 | 20 |
verbose = FALSE |
20 | 21 |
) |
21 | 22 |
} |
... | ... |
@@ -66,6 +67,15 @@ Default: \code{NULL}.} |
66 | 67 |
the directory where the Profile GDS files will be created. |
67 | 68 |
Default: \code{NULL}.} |
68 | 69 |
|
70 |
+\item{genoSource}{a \code{stirng} with two possible values: |
|
71 |
+snp-pileup and generic. It specify if the genotype files |
|
72 |
+are generate by snp-pileup(Facets) or generic format csv |
|
73 |
+with the column at least the columns: |
|
74 |
+Chromosome,Position,Ref,Alt,Count,File1R,File1A |
|
75 |
+where Count is the deep at the position, |
|
76 |
+FileR is the deep of the reference allele, and |
|
77 |
+File1A is the deep of the specific alternative allele} |
|
78 |
+ |
|
69 | 79 |
\item{verbose}{a \code{logical} indicating if message information should be |
70 | 80 |
printed. Default: \code{FALSE}.} |
71 | 81 |
} |
... | ... |
@@ -107,7 +117,9 @@ rownames(samplePED) <- samplePED$Name.ID |
107 | 117 |
result <- createStudy2GDS1KG(pathGeno=dataDir, |
108 | 118 |
pedStudy=samplePED, fileNameGDS=fileGDS, |
109 | 119 |
studyDF=studyDF, listProfiles=c("ex1"), |
110 |
- pathProfileGDS=dataDir, verbose=FALSE) |
|
120 |
+ pathProfileGDS=dataDir, |
|
121 |
+ genoSource="snp-pileup", |
|
122 |
+ verbose=FALSE) |
|
111 | 123 |
|
112 | 124 |
## The function returns OL when successful |
113 | 125 |
result |
... | ... |
@@ -14,7 +14,8 @@ runExomeAncestry( |
14 | 14 |
fileReferenceGDS, |
15 | 15 |
fileReferenceAnnotGDS, |
16 | 16 |
chrInfo, |
17 |
- dataRefSyn |
|
17 |
+ dataRefSyn, |
|
18 |
+ genoSource = c("snp-pileup", "generic") |
|
18 | 19 |
) |
19 | 20 |
} |
20 | 21 |
\arguments{ |
... | ... |
@@ -63,6 +64,15 @@ subcontinental population assigned to the sample. } |
63 | 64 |
\item{superPop} { a \code{character} string representing the |
64 | 65 |
super-population assigned to the sample. } |
65 | 66 |
}} |
67 |
+ |
|
68 |
+\item{genoSource}{a \code{stirng} with two possible values: |
|
69 |
+snp-pileup and generic. It specify if the genotype files |
|
70 |
+are generate by snp-pileup(Facets) or generic format csv |
|
71 |
+with the column at least the columns: |
|
72 |
+Chromosome,Position,Ref,Alt,Count,File1R,File1A |
|
73 |
+where Count is the deep at the position, |
|
74 |
+FileR is the deep of the reference allele, and |
|
75 |
+File1A is the deep of the specific alternative allele} |
|
66 | 76 |
} |
67 | 77 |
\value{ |
68 | 78 |
The integer \code{0L} when successful. See details section for |
... | ... |
@@ -168,7 +178,8 @@ runExomeAncestry(pedStudy=ped, studyDF=studyDF, |
168 | 178 |
fileReferenceGDS=fileReferenceGDS, |
169 | 179 |
fileReferenceAnnotGDS=fileAnnotGDS, |
170 | 180 |
chrInfo=chrInfo, |
171 |
- dataRefSyn=dataRef) |
|
181 |
+ dataRefSyn=dataRef, |
|
182 |
+ genoSource="snp-pileup") |
|
172 | 183 |
|
173 | 184 |
unlink(pathProfileGDS, recursive=TRUE, force=TRUE) |
174 | 185 |
unlink(pathOut, recursive=TRUE, force=TRUE) |
... | ... |
@@ -13,6 +13,7 @@ validateCreateStudy2GDS1KG( |
13 | 13 |
studyDF, |
14 | 14 |
listProfiles, |
15 | 15 |
pathProfileGDS, |
16 |
+ genoSource, |
|
16 | 17 |
verbose |
17 | 18 |
) |
18 | 19 |
} |
... | ... |
@@ -86,7 +87,8 @@ ped <- data.frame(Name.ID=c("Sample_01", "Sample_02"), |
86 | 87 |
RAIDS:::validateCreateStudy2GDS1KG(pathGeno=dataDir, pedStudy=ped, |
87 | 88 |
fileNameGDS=gds1KG, batch=1, studyDF=studyInfo, |
88 | 89 |
listProfiles=c("Sample_01", "Sample_02"), |
89 |
- pathProfileGDS=dataDir, verbose=TRUE) |
|
90 |
+ pathProfileGDS=dataDir, |
|
91 |
+ genoSource="snp-pileup", verbose=TRUE) |
|
90 | 92 |
|
91 | 93 |
} |
92 | 94 |
\author{ |
... | ... |
@@ -14,7 +14,8 @@ validateRunExomeAncestry( |
14 | 14 |
fileReferenceGDS, |
15 | 15 |
fileReferenceAnnotGDS, |
16 | 16 |
chrInfo, |
17 |
- dataRefSyn |
|
17 |
+ dataRefSyn, |
|
18 |
+ genoSource |
|
18 | 19 |
) |
19 | 20 |
} |
20 | 21 |
\arguments{ |
... | ... |
@@ -112,7 +113,7 @@ dataRefSyn <- data.frame(sample.id=c("HG00150", "HG00138", "HG00330", |
112 | 113 |
RAIDS:::validateRunExomeAncestry(pedStudy=ped, studyDF=study, |
113 | 114 |
pathProfileGDS=dataDir, pathGeno=dataDir, pathOut=pathOut, |
114 | 115 |
fileReferenceGDS=gds1KG, fileReferenceAnnotGDS=gdsAnnot1KG, |
115 |
- chrInfo=chrInfo, dataRefSyn=dataRefSyn) |
|
116 |
+ chrInfo=chrInfo, dataRefSyn=dataRefSyn, genoSource="snp-pileup") |
|
116 | 117 |
|
117 | 118 |
} |
118 | 119 |
\author{ |
... | ... |
@@ -1413,7 +1413,8 @@ test_that(paste0("createStudy2GDS1KG() must return error when fileNamePED is", |
1413 | 1413 |
expect_error(createStudy2GDS1KG(pathGeno=dataDir, |
1414 | 1414 |
fileNamePED=33, pedStudy=NULL, fileNameGDS=NULL, |
1415 | 1415 |
batch=1, studyDF=NULL, listProfiles=NULL, |
1416 |
- pathProfileGDS=NULL, verbose=TRUE), error_message) |
|
1416 |
+ pathProfileGDS=NULL, |
|
1417 |
+ genoSource="snp-pileup", verbose=TRUE), error_message) |
|
1417 | 1418 |
}) |
1418 | 1419 |
|
1419 | 1420 |
|
... | ... |
@@ -1425,7 +1426,8 @@ test_that("createStudy2GDS1KG() must return error when fileNamePED is NULL and p |
1425 | 1426 |
expect_error(createStudy2GDS1KG(pathGeno=file.path("data", "sampleGeno"), |
1426 | 1427 |
fileNamePED=NULL, pedStudy=NULL, fileNameGDS=NULL, |
1427 | 1428 |
batch=1, studyDF=NULL, listProfiles=NULL, |
1428 |
- pathProfileGDS=NULL, verbose=TRUE), error_message) |
|
1429 |
+ pathProfileGDS=NULL, |
|
1430 |
+ genoSource="snp-pileup", verbose=TRUE), error_message) |
|
1429 | 1431 |
}) |
1430 | 1432 |
|
1431 | 1433 |
|
... | ... |
@@ -1444,7 +1446,8 @@ test_that("createStudy2GDS1KG() must return error when pedDF is missing mandator |
1444 | 1446 |
expect_error(createStudy2GDS1KG(pathGeno=dataDir, |
1445 | 1447 |
fileNamePED=NULL, pedStudy=pedDF, fileNameGDS=NULL, |
1446 | 1448 |
batch=1, studyDF=NULL, listProfiles=NULL, |
1447 |
- pathProfileGDS=NULL, verbose=TRUE), error_message) |
|
1449 |
+ pathProfileGDS=NULL, |
|
1450 |
+ genoSource="snp-pileup", verbose=TRUE), error_message) |
|
1448 | 1451 |
}) |
1449 | 1452 |
|
1450 | 1453 |
|
... | ... |
@@ -1464,7 +1467,8 @@ test_that("createStudy2GDS1KG() must return error when fileNameGDS is numerical |
1464 | 1467 |
expect_error(createStudy2GDS1KG(pathGeno=dataDir, |
1465 | 1468 |
fileNamePED=NULL, pedStudy=pedDF, fileNameGDS=33, |
1466 | 1469 |
batch=1, studyDF=NULL, listProfiles=NULL, |
1467 |
- pathProfileGDS=NULL, verbose=TRUE), error_message) |
|
1470 |
+ pathProfileGDS=NULL, |
|
1471 |
+ genoSource="snp-pileup", verbose=TRUE), error_message) |
|
1468 | 1472 |
}) |
1469 | 1473 |
|
1470 | 1474 |
|
... | ... |
@@ -1484,7 +1488,8 @@ test_that("createStudy2GDS1KG() must return error when batch is character string |
1484 | 1488 |
expect_error(createStudy2GDS1KG(pathGeno=dataDir, |
1485 | 1489 |
fileNamePED=NULL, pedStudy=pedDF, fileNameGDS=fileGDS, |
1486 | 1490 |
batch="1", studyDF=NULL, listProfiles=NULL, |
1487 |
- pathProfileGDS=NULL, verbose=TRUE), error_message) |
|
1491 |
+ pathProfileGDS=NULL, |
|
1492 |
+ genoSource="snp-pileup", verbose=TRUE), error_message) |
|
1488 | 1493 |
}) |
1489 | 1494 |
|
1490 | 1495 |
|
... | ... |
@@ -1504,7 +1509,8 @@ test_that("createStudy2GDS1KG() must return error when batch is vector of numeri |
1504 | 1509 |
expect_error(createStudy2GDS1KG(pathGeno=dataDir, |
1505 | 1510 |
fileNamePED=NULL, pedStudy=pedDF, fileNameGDS=fileGDS, |
1506 | 1511 |
batch=c(1,2), studyDF=NULL, listProfiles=NULL, |
1507 |
- pathProfileGDS=NULL, verbose=TRUE), error_message) |
|
1512 |
+ pathProfileGDS=NULL, |
|
1513 |
+ genoSource="snp-pileup", verbose=TRUE), error_message) |
|
1508 | 1514 |
}) |
1509 | 1515 |
|
1510 | 1516 |
|
... | ... |
@@ -1528,7 +1534,8 @@ test_that("createStudy2GDS1KG() must return error when listSamples is vector of |
1528 | 1534 |
expect_error(createStudy2GDS1KG(pathGeno=dataDir, |
1529 | 1535 |
fileNamePED=NULL, pedStudy=pedDF, fileNameGDS=fileGDS, |
1530 | 1536 |
batch=1, studyDF=studyDF, listProfiles=c(1,2), |
1531 |
- pathProfileGDS=NULL, verbose=TRUE), error_message, fixed=TRUE) |
|
1537 |
+ pathProfileGDS=NULL, |
|
1538 |
+ genoSource="snp-pileup", verbose=TRUE), error_message, fixed=TRUE) |
|
1532 | 1539 |
}) |
1533 | 1540 |
|
1534 | 1541 |
|
... | ... |
@@ -1552,7 +1559,8 @@ test_that("createStudy2GDS1KG() must return error when listProfiles is numeric", |
1552 | 1559 |
expect_error(createStudy2GDS1KG(pathGeno=dataDir, |
1553 | 1560 |
fileNamePED=NULL, pedStudy=pedDF, fileNameGDS=fileGDS, |
1554 | 1561 |
batch=1, studyDF=studyDF, listProfiles=1, |
1555 |
- pathProfileGDS=NULL, verbose=TRUE), error_message, fixed=TRUE) |
|
1562 |
+ pathProfileGDS=NULL, |
|
1563 |
+ genoSource="snp-pileup", verbose=TRUE), error_message, fixed=TRUE) |
|
1556 | 1564 |
}) |
1557 | 1565 |
|
1558 | 1566 |
|
... | ... |
@@ -1577,7 +1585,8 @@ test_that("createStudy2GDS1KG() must return error when studyDF is missing column |
1577 | 1585 |
expect_error(createStudy2GDS1KG(pathGeno=dataDir, |
1578 | 1586 |
fileNamePED=NULL, pedStudy=pedDF, fileNameGDS=fileGDS, |
1579 | 1587 |
batch=1, studyDF=studyDF, listProfiles=1, |
1580 |
- pathProfileGDS=NULL, verbose=TRUE), error_message, fixed=TRUE) |
|
1588 |
+ pathProfileGDS=NULL, |
|
1589 |
+ genoSource="snp-pileup", verbose=TRUE), error_message, fixed=TRUE) |
|
1581 | 1590 |
}) |
1582 | 1591 |
|
1583 | 1592 |
|
... | ... |
@@ -1600,7 +1609,8 @@ test_that("createStudy2GDS1KG() must return error when verbose is numeric", { |
1600 | 1609 |
expect_error(createStudy2GDS1KG(pathGeno=dataDir, |
1601 | 1610 |
fileNamePED=NULL, pedStudy=pedDF, fileNameGDS=fileGDS, |
1602 | 1611 |
batch=1, studyDF=studyDF, listProfiles=NULL, |
1603 |
- pathProfileGDS=dataDir, verbose=22), error_message, fixed=TRUE) |
|
1612 |
+ pathProfileGDS=dataDir, |
|
1613 |
+ genoSource="snp-pileup", verbose=22), error_message, fixed=TRUE) |
|
1604 | 1614 |
}) |
1605 | 1615 |
|
1606 | 1616 |
|
... | ... |
@@ -1625,7 +1635,8 @@ test_that("createStudy2GDS1KG() must return error when pathProfileGDS is numeric |
1625 | 1635 |
expect_error(createStudy2GDS1KG(pathGeno=dataDir, |
1626 | 1636 |
fileNamePED=NULL, pedStudy=pedDF, fileNameGDS=gdsFile, |
1627 | 1637 |
batch=1, studyDF=studyDF, listProfiles=NULL, |
1628 |
- pathProfileGDS=33, verbose=FALSE), error_message, fixed=TRUE) |
|
1638 |
+ pathProfileGDS=33, |
|
1639 |
+ genoSource="snp-pileup", verbose=FALSE), error_message, fixed=TRUE) |
|
1629 | 1640 |
}) |
1630 | 1641 |
|
1631 | 1642 |
|
... | ... |
@@ -1649,7 +1660,8 @@ test_that("createStudy2GDS1KG() must return error when both fileNamePED and pedS |
1649 | 1660 |
expect_error(createStudy2GDS1KG(pathGeno=file.path("data", "sampleGeno"), |
1650 | 1661 |
fileNamePED=fileGDS, pedStudy=pedDF, fileNameGDS=fileGDS, |
1651 | 1662 |
batch=1, studyDF=studyDF, listProfiles=NULL, |
1652 |
- pathProfileGDS=dataDir, verbose=22), error_message, fixed=TRUE) |
|
1663 |
+ pathProfileGDS=dataDir, |
|
1664 |
+ genoSource="snp-pileup", verbose=22), error_message, fixed=TRUE) |
|
1653 | 1665 |
}) |
1654 | 1666 |
|
1655 | 1667 |
|
... | ... |
@@ -1675,7 +1687,8 @@ test_that("createStudy2GDS1KG() must return expected results when all parameters |
1675 | 1687 |
result <- createStudy2GDS1KG(pathGeno=dataDir, |
1676 | 1688 |
pedStudy=pedDF, fileNameGDS=fileGDS, |
1677 | 1689 |
batch=1, studyDF=studyDF, listProfiles=c("ex1"), |
1678 |
- pathProfileGDS=dataDir, verbose=FALSE) |
|
1690 |
+ pathProfileGDS=dataDir, |
|
1691 |
+ genoSource="snp-pileup", verbose=FALSE) |
|
1679 | 1692 |
|
1680 | 1693 |
expect_true(file.exists(file.path(dataDir, "ex1.gds"))) |
1681 | 1694 |
expect_equal(result, 0L) |
... | ... |
@@ -2332,7 +2345,8 @@ test_that(paste0("runExomeAncestry() must return error when pathOut is numeric") |
2332 | 2345 |
pathProfileGDS=pathOut, |
2333 | 2346 |
pathGeno=pathOut, pathOut=33, fileReferenceGDS=fileGDS, |
2334 | 2347 |
fileReferenceAnnotGDS=gdsFileAnnot, chrInfo=chrInfo, |
2335 |
- dataRefSyn=dataRefSyn), error_message) |
|
2348 |
+ dataRefSyn=dataRefSyn, |
|
2349 |
+ genoSource="snp-pileup"), error_message) |
|
2336 | 2350 |
}) |
2337 | 2351 |
|
2338 | 2352 |
|
... | ... |
@@ -2364,7 +2378,8 @@ test_that(paste0("runExomeAncestry() must return error when fileReferenceGDS is |
2364 | 2378 |
expect_error(runExomeAncestry(pedStudy=ped, studyDF=studyDF, |
2365 | 2379 |
pathProfileGDS=pathOut, pathGeno=pathOut, pathOut=pathOut, |
2366 | 2380 |
fileReferenceGDS=33, fileReferenceAnnotGDS=gdsFileAnnot, |
2367 |
- chrInfo=chrInfo, dataRefSyn), error_message) |
|
2381 |
+ chrInfo=chrInfo, dataRefSyn, |
|
2382 |
+ genoSource="snp-pileup"), error_message) |
|
2368 | 2383 |
}) |
2369 | 2384 |
|
2370 | 2385 |
|
... | ... |
@@ -2397,7 +2412,8 @@ test_that(paste0("runExomeAncestry() must return error when fileReferenceAnnotGD |
2397 | 2412 |
expect_error(runExomeAncestry(pedStudy=ped, studyDF=studyDF, |
2398 | 2413 |
pathProfileGDS=pathOut, pathGeno=pathOut, pathOut=pathOut, |
2399 | 2414 |
fileReferenceGDS=fileGDS, fileReferenceAnnotGDS=32, |
2400 |
- chrInfo=chrInfo, dataRefSyn=dataRefSyn), error_message) |
|
2415 |
+ chrInfo=chrInfo, dataRefSyn=dataRefSyn, |
|
2416 |
+ genoSource="snp-pileup"), error_message) |
|
2401 | 2417 |
}) |
2402 | 2418 |
|
2403 | 2419 |
|
... | ... |
@@ -2428,7 +2444,8 @@ test_that(paste0("runExomeAncestry() must return error when chrInfo is vector of |
2428 | 2444 |
expect_error(runExomeAncestry(pedStudy=ped, studyDF=studyDF, |
2429 | 2445 |
pathProfileGDS=pathOut, pathGeno=pathOut, pathOut=pathOut, |
2430 | 2446 |
fileReferenceGDS=fileGDS, fileReferenceAnnotGDS=gdsFileAnnot, |
2431 |
- chrInfo=c("ALLO", "TEST"), dataRefSyn=dataRefSyn), error_message) |
|
2447 |
+ chrInfo=c("ALLO", "TEST"), dataRefSyn=dataRefSyn, |
|
2448 |
+ genoSource="snp-pileup"), error_message) |
|
2432 | 2449 |
}) |
2433 | 2450 |
|
2434 | 2451 |
|
... | ... |
@@ -2461,7 +2478,8 @@ test_that(paste0("runExomeAncestry() must return error when dataRefSyn missing c |
2461 | 2478 |
expect_error(runExomeAncestry(pedStudy=ped, studyDF=studyDF, |
2462 | 2479 |
pathProfileGDS=pathOut, pathGeno=pathOut, pathOut=pathOut, |
2463 | 2480 |
fileReferenceGDS=fileGDS, fileReferenceAnnotGDS=gdsFileAnnot, |
2464 |
- chrInfo=c(100L, 200L), dataRefSyn=dataRefSyn), error_message) |
|
2481 |
+ chrInfo=c(100L, 200L), dataRefSyn=dataRefSyn, |
|
2482 |
+ genoSource="snp-pileup"), error_message) |
|
2465 | 2483 |
}) |
2466 | 2484 |
|
2467 | 2485 |
|
... | ... |
@@ -2491,5 +2509,6 @@ test_that(paste0("runExomeAncestry() must return error when pathGeno does not ex |
2491 | 2509 |
expect_error(runExomeAncestry(pedStudy=ped, studyDF=studyDF, |
2492 | 2510 |
pathProfileGDS=pathOut, pathGeno="DONOTEXISTDIR", pathOut=pathOut, |
2493 | 2511 |
fileReferenceGDS=fileGDS, fileReferenceAnnotGDS=gdsFileAnnot, |
2494 |
- chrInfo=c(100L, 200L), dataRefSyn=dataRefSyn), error_message) |
|
2512 |
+ chrInfo=c(100L, 200L), dataRefSyn=dataRefSyn, |
|
2513 |
+ genoSource="snp-pileup"), error_message) |
|
2495 | 2514 |
}) |
... | ... |
@@ -80,7 +80,7 @@ test_that("validateCreateStudy2GDS1KG() must return expected results when all in |
80 | 80 |
result1 <- RAIDS:::validateCreateStudy2GDS1KG(pathGeno=dataDir, |
81 | 81 |
pedStudy=ped, fileNameGDS=fileGDS, batch=12, studyDF=studyInfo, |
82 | 82 |
listProfiles=c("TCGA-H01", "TCGA-H02"), pathProfileGDS=dataDir, |
83 |
- verbose=TRUE) |
|
83 |
+ genoSource="snp-pileup", verbose=TRUE) |
|
84 | 84 |
|
85 | 85 |
expect_identical(result1, 0L) |
86 | 86 |
}) |
... | ... |
@@ -224,7 +224,7 @@ test_that("validateRunExomeAncestry() must return expected results when all inpu |
224 | 224 |
result <- RAIDS:::validateRunExomeAncestry(pedStudy=ped, studyDF=studyInfo, |
225 | 225 |
pathProfileGDS=dataDir, pathGeno=dataDir, pathOut=dataDir, |
226 | 226 |
fileReferenceGDS=gdsRefFile, fileReferenceAnnotGDS=gdsRefAnnotFile, |
227 |
- chrInfo=chrInfo, dataRefSyn=dataRefSyn) |
|
227 |
+ chrInfo=chrInfo, dataRefSyn=dataRefSyn, genoSource="snp-pileup") |
|
228 | 228 |
|
229 | 229 |
expect_identical(result, 0L) |
230 | 230 |
}) |
... | ... |
@@ -421,7 +421,8 @@ createStudy2GDS1KG(pathGeno = pathGeno, |
421 | 421 |
fileNameGDS = file.GDS, |
422 | 422 |
listProfiles = listSamples, |
423 | 423 |
studyDF = studyDF, |
424 |
- pathProfileGDS = pathProfileGDS) |
|
424 |
+ pathProfileGDS = pathProfileGDS, |
|
425 |
+ genoSource="snp-pileup") |
|
425 | 426 |
|
426 | 427 |
################################################################# |
427 | 428 |
## The Sample GDS file has been created in the |
... | ... |
@@ -1096,7 +1097,8 @@ runExomeAncestry(pedStudy=ped, studyDF=studyDF, |
1096 | 1097 |
fileReferenceGDS=fileGDS, |
1097 | 1098 |
fileReferenceAnnotGDS=fileAnnotGDS, |
1098 | 1099 |
chrInfo=chrInfo, |
1099 |
- dataRefSyn=dataRef) |
|
1100 |
+ dataRefSyn=dataRef, |
|
1101 |
+ genoSource="snp-pileup") |
|
1100 | 1102 |
list.files(pathOut) |
1101 | 1103 |
list.files(file.path(pathOut, ped$Name.ID[1])) |
1102 | 1104 |
|