... | ... |
@@ -3,7 +3,6 @@ |
3 | 3 |
export(annotateTargets) |
4 | 4 |
export(bootstrapResults) |
5 | 5 |
export(calculateBamCoverageByInterval) |
6 |
-export(calculateGCContentByInterval) |
|
7 | 6 |
export(calculateLogRatio) |
8 | 7 |
export(calculateMappingBiasVcf) |
9 | 8 |
export(calculatePowerDetectSomatic) |
... | ... |
@@ -20,12 +19,10 @@ export(filterTargets) |
20 | 19 |
export(filterVcfBasic) |
21 | 20 |
export(filterVcfMuTect) |
22 | 21 |
export(filterVcfMuTect2) |
23 |
-export(findBestNormal) |
|
24 | 22 |
export(findFocal) |
25 | 23 |
export(getSexFromCoverage) |
26 | 24 |
export(getSexFromVcf) |
27 | 25 |
export(plotAbs) |
28 |
-export(plotBestNormal) |
|
29 | 26 |
export(poolCoverage) |
30 | 27 |
export(predictSomatic) |
31 | 28 |
export(preprocessIntervals) |
... | ... |
@@ -42,7 +42,7 @@ globalVariables(names=c("..level..")) |
42 | 42 |
#' scale_alpha_continuous scale_y_sqrt geom_abline |
43 | 43 |
#' coord_trans |
44 | 44 |
#' @importFrom gridExtra grid.arrange |
45 |
-#' @importFrom stats loess lm |
|
45 |
+#' @importFrom stats loess lm predict |
|
46 | 46 |
#' @importFrom utils write.table |
47 | 47 |
correctCoverageBias <- function(coverage.file, interval.file, |
48 | 48 |
output.file = NULL, plot.bias = FALSE, plot.max.density = 50000, |
... | ... |
@@ -111,12 +111,13 @@ min.coverage = 0.25, max.missing = 0.03, low.coverage = 15, ...) { |
111 | 111 |
} |
112 | 112 |
|
113 | 113 |
list( |
114 |
- normal.coverage.files = normal.coverage.files, |
|
114 |
+ normal.coverage.files = normal.coverage.files, |
|
115 |
+ intervals = as.character(normals[[1]]), |
|
115 | 116 |
groups = groups, |
116 | 117 |
intervals.used = intervals.used, |
117 | 118 |
sex = sex, |
118 | 119 |
low.coverage.targets = low.coverage.targets, |
119 |
- version = 5 |
|
120 |
+ version = 6 |
|
120 | 121 |
) |
121 | 122 |
} |
122 | 123 |
|
... | ... |
@@ -100,8 +100,12 @@ filterTargets <- function(normal, tumor, log.ratio, seg.file, |
100 | 100 |
!length(normalDB$normal.coverage.files)) { |
101 | 101 |
.stopUserError("normalDB appears to be empty.") |
102 | 102 |
} |
103 |
- tmp <- readCoverageFile(normalDB$normal.coverage.files[1]) |
|
104 |
- return(identical(as.character(tmp), as.character(tumor))) |
|
103 |
+ intervals <- normalDB$intervals |
|
104 |
+ # TODO remove in PureCN 1.14 |
|
105 |
+ if (is.null(intervals)) { |
|
106 |
+ intervals <- as.character(readCoverageFile(normalDB$normal.coverage.files[1])) |
|
107 |
+ } |
|
108 |
+ return(identical(intervals, as.character(tumor))) |
|
105 | 109 |
} |
106 | 110 |
|
107 | 111 |
.filterTargetsNotNA <- function(log.ratio) { |
... | ... |
@@ -1,51 +1,9 @@ |
1 | 1 |
#' Find best normal sample in database |
2 | 2 |
#' |
3 | 3 |
#' Function to find the best matching normal for a provided tumor sample. |
4 |
-#' This function is deprecated and most features are not relevant with |
|
5 |
-#' the replacement function \code{\link{calculateTangentNormal}}. |
|
4 |
+#' This function is defunct and replaced by |
|
5 |
+#' \code{\link{calculateTangentNormal}}. |
|
6 | 6 |
#' |
7 |
-#' |
|
8 |
-#' @param tumor.coverage.file Coverage file or data of a tumor sample. |
|
9 |
-#' @param normalDB Database of normal samples, created with |
|
10 |
-#' \code{\link{createNormalDatabase}}. |
|
11 |
-#' @param pcs Principal components to use for distance calculation. |
|
12 |
-#' @param num.normals Return the \code{num.normals} best normals. |
|
13 |
-#' @param ignore.sex If \code{FALSE}, detects sex of sample and returns best |
|
14 |
-#' normals with matching sex. |
|
15 |
-#' @param sex Sex of sample. If \code{NULL}, determine with |
|
16 |
-#' \code{\link{getSexFromCoverage}} and default parameters. Valid values are |
|
17 |
-#' \code{F} for female, \code{M} for male. If all chromosomes are diploid, |
|
18 |
-#' specify \code{diploid}. |
|
19 |
-#' @param normal.coverage.files Only consider these normal samples. If |
|
20 |
-#' \code{NULL}, use all in the database. Must match |
|
21 |
-#' \code{normalDB$normal.coverage.files}. |
|
22 |
-#' @param pool If \code{TRUE}, use \code{\link{poolCoverage}} to pool best |
|
23 |
-#' normals. |
|
24 |
-#' @param pool.weights Either find good pooling weights by optimization or |
|
25 |
-#' weight all best normals equally. |
|
26 |
-#' @param plot.pool Allows the pooling function to create plots. |
|
27 |
-#' @param \dots Additional arguments passed to \code{\link{poolCoverage}}. |
|
28 |
-#' @return Filename of the best matching normal. |
|
29 |
-#' @author Markus Riester |
|
30 |
-#' @seealso \code{\link{createNormalDatabase} \link{getSexFromCoverage}} |
|
31 |
-#' @export findBestNormal |
|
32 |
-#' @importFrom stats dist predict |
|
33 |
-findBestNormal <- function(tumor.coverage.file, normalDB, pcs=1:3, |
|
34 |
- num.normals = 1, ignore.sex = FALSE, sex = NULL, |
|
35 |
- normal.coverage.files = NULL, pool = FALSE, |
|
36 |
- pool.weights = c("voom", "equal"), plot.pool = FALSE, |
|
37 |
- ...) { |
|
38 |
- .Deprecated("calculateTangentNormal") |
|
39 |
- calculateTangentNormal(tumor.coverage.file, normalDB, ignore.sex = ignore.sex, |
|
40 |
- sex = sex) |
|
41 |
-} |
|
42 |
- |
|
43 |
- |
|
44 |
-#' Plot the PCA of tumor and its best normal(s) |
|
45 |
-#' |
|
46 |
-#' This method is defunct with no replacement |
|
47 |
-#' |
|
48 |
-#' @export plotBestNormal |
|
49 |
-plotBestNormal <- function() { |
|
50 |
- .Defunct() |
|
7 |
+findBestNormal <- function() { |
|
8 |
+ .Defunct("calculateTangentNormal") |
|
51 | 9 |
} |
... | ... |
@@ -124,12 +124,8 @@ preprocessIntervals <- function(interval.file, reference.file, |
124 | 124 |
#' |
125 | 125 |
#' This function was renamed to \code{\link{preprocessIntervals}}. |
126 | 126 |
#' |
127 |
-#' @param ... Arguments passed to \code{\link{preprocessIntervals}}. |
|
128 |
-#' |
|
129 |
-#' @export calculateGCContentByInterval |
|
130 |
-calculateGCContentByInterval <- function(...) { |
|
131 |
- .Deprecated("preprocessIntervals") |
|
132 |
- preprocessIntervals(...) |
|
127 |
+calculateGCContentByInterval <- function() { |
|
128 |
+ .Defunct("preprocessIntervals") |
|
133 | 129 |
} |
134 | 130 |
|
135 | 131 |
# this function removes short chromosomes that have no probes (mainly a |
... | ... |
@@ -68,7 +68,7 @@ |
68 | 68 |
#' fun.segmentation=segmentationCBS, args.segmentation=list(alpha=0.001)) |
69 | 69 |
#' |
70 | 70 |
#' @export segmentationCBS |
71 |
-#' @importFrom stats t.test hclust cutree |
|
71 |
+#' @importFrom stats t.test hclust cutree dist |
|
72 | 72 |
segmentationCBS <- function(normal, tumor, log.ratio, seg, plot.cnv, |
73 | 73 |
sampleid, target.weight.file = NULL, alpha = 0.005, undo.SD = |
74 | 74 |
NULL, vcf = NULL, tumor.id.in.vcf = 1, normal.id.in.vcf = NULL, |
... | ... |
@@ -11,8 +11,10 @@ |
11 | 11 |
the replacement indicated below: |
12 | 12 |
\itemize{ |
13 | 13 |
\item{autoCurateResults: no replacement} |
14 |
+ \item{calculateGCContentByInterval: \code{\link{preprocessIntervals}}} |
|
14 | 15 |
\item{createExonWeightFile: \code{\link{createTargetWeights}}} |
15 | 16 |
\item{createSNPBlacklist: \code{\link{setMappingBiasVcf}}} |
17 |
+ \item{findBestNormal: \code{\link{calculateTangentNormal}}} |
|
16 | 18 |
\item{getDiploid: no replacement} |
17 | 19 |
\item{plotBestNormal: no replacement} |
18 | 20 |
\item{readCoverageGatk: \code{\link{readCoverageFile}}} |
... | ... |
@@ -11,7 +11,6 @@ |
11 | 11 |
The following functions are deprecated and will be made defunct; use |
12 | 12 |
the replacement indicated below: |
13 | 13 |
\itemize{ |
14 |
- \item{calculateGCContentByInterval: \code{\link{preprocessIntervals}}} |
|
15 |
- \item{findBestNormal: \code{\link{calculateTangentNormal}}} |
|
14 |
+ \item{none} |
|
16 | 15 |
} |
17 | 16 |
} |
... | ... |
@@ -4,10 +4,7 @@ |
4 | 4 |
\alias{calculateGCContentByInterval} |
5 | 5 |
\title{Calculates GC content by interval} |
6 | 6 |
\usage{ |
7 |
-calculateGCContentByInterval(...) |
|
8 |
-} |
|
9 |
-\arguments{ |
|
10 |
-\item{...}{Arguments passed to \code{\link{preprocessIntervals}}.} |
|
7 |
+calculateGCContentByInterval() |
|
11 | 8 |
} |
12 | 9 |
\description{ |
13 | 10 |
This function was renamed to \code{\link{preprocessIntervals}}. |
... | ... |
@@ -4,53 +4,10 @@ |
4 | 4 |
\alias{findBestNormal} |
5 | 5 |
\title{Find best normal sample in database} |
6 | 6 |
\usage{ |
7 |
-findBestNormal(tumor.coverage.file, normalDB, pcs = 1:3, num.normals = 1, |
|
8 |
- ignore.sex = FALSE, sex = NULL, normal.coverage.files = NULL, |
|
9 |
- pool = FALSE, pool.weights = c("voom", "equal"), plot.pool = FALSE, ...) |
|
10 |
-} |
|
11 |
-\arguments{ |
|
12 |
-\item{tumor.coverage.file}{Coverage file or data of a tumor sample.} |
|
13 |
- |
|
14 |
-\item{normalDB}{Database of normal samples, created with |
|
15 |
-\code{\link{createNormalDatabase}}.} |
|
16 |
- |
|
17 |
-\item{pcs}{Principal components to use for distance calculation.} |
|
18 |
- |
|
19 |
-\item{num.normals}{Return the \code{num.normals} best normals.} |
|
20 |
- |
|
21 |
-\item{ignore.sex}{If \code{FALSE}, detects sex of sample and returns best |
|
22 |
-normals with matching sex.} |
|
23 |
- |
|
24 |
-\item{sex}{Sex of sample. If \code{NULL}, determine with |
|
25 |
-\code{\link{getSexFromCoverage}} and default parameters. Valid values are |
|
26 |
-\code{F} for female, \code{M} for male. If all chromosomes are diploid, |
|
27 |
-specify \code{diploid}.} |
|
28 |
- |
|
29 |
-\item{normal.coverage.files}{Only consider these normal samples. If |
|
30 |
-\code{NULL}, use all in the database. Must match |
|
31 |
-\code{normalDB$normal.coverage.files}.} |
|
32 |
- |
|
33 |
-\item{pool}{If \code{TRUE}, use \code{\link{poolCoverage}} to pool best |
|
34 |
-normals.} |
|
35 |
- |
|
36 |
-\item{pool.weights}{Either find good pooling weights by optimization or |
|
37 |
-weight all best normals equally.} |
|
38 |
- |
|
39 |
-\item{plot.pool}{Allows the pooling function to create plots.} |
|
40 |
- |
|
41 |
-\item{\dots}{Additional arguments passed to \code{\link{poolCoverage}}.} |
|
42 |
-} |
|
43 |
-\value{ |
|
44 |
-Filename of the best matching normal. |
|
7 |
+findBestNormal() |
|
45 | 8 |
} |
46 | 9 |
\description{ |
47 | 10 |
Function to find the best matching normal for a provided tumor sample. |
48 |
-This function is deprecated and most features are not relevant with |
|
49 |
-the replacement function \code{\link{calculateTangentNormal}}. |
|
50 |
-} |
|
51 |
-\seealso{ |
|
52 |
-\code{\link{createNormalDatabase} \link{getSexFromCoverage}} |
|
53 |
-} |
|
54 |
-\author{ |
|
55 |
-Markus Riester |
|
11 |
+This function is defunct and replaced by |
|
12 |
+\code{\link{calculateTangentNormal}}. |
|
56 | 13 |
} |
57 | 14 |
deleted file mode 100644 |
... | ... |
@@ -1,11 +0,0 @@ |
1 |
-% Generated by roxygen2: do not edit by hand |
|
2 |
-% Please edit documentation in R/findBestNormal.R |
|
3 |
-\name{plotBestNormal} |
|
4 |
-\alias{plotBestNormal} |
|
5 |
-\title{Plot the PCA of tumor and its best normal(s)} |
|
6 |
-\usage{ |
|
7 |
-plotBestNormal() |
|
8 |
-} |
|
9 |
-\description{ |
|
10 |
-This method is defunct with no replacement |
|
11 |
-} |
... | ... |
@@ -15,6 +15,7 @@ test_that("NormalDB of example data matches expectated values", { |
15 | 15 |
|
16 | 16 |
n <- lapply(normal.coverage.files, readCoverageFile) |
17 | 17 |
expect_equal(length(pool), length(n[[1]])) |
18 |
+ expect_equal(as.character(n[[1]]), normalDB$intervals) |
|
18 | 19 |
}) |
19 | 20 |
|
20 | 21 |
test_that("Provided sex is handled correctly", { |
... | ... |
@@ -37,7 +37,7 @@ test_that("skipping base quality works", { |
37 | 37 |
f1 <- filterVcfBasic(vcf, min.base.quality=NULL) |
38 | 38 |
f2 <- filterVcfBasic(vcf, min.base.quality=0) |
39 | 39 |
expect_equal(length(f1$vcf), length(f2$vcf)) |
40 |
-} |
|
40 |
+}) |
|
41 | 41 |
|
42 | 42 |
test_that("M2 VCF with POP_AF flag is annotated with DB flag", { |
43 | 43 |
# first check that the POP_AF field is parsed |