... | ... |
@@ -1,6 +1,6 @@ |
1 | 1 |
Package: crisprDesign |
2 | 2 |
Title: Comprehensive design of CRISPR gRNAs for nucleases and base editors |
3 |
-Version: 1.1.6 |
|
3 |
+Version: 1.1.7 |
|
4 | 4 |
Authors@R: c( |
5 | 5 |
person("Jean-Philippe", "Fortin", email = "[email protected]", role = c("aut", "cre")), |
6 | 6 |
person("Luke", "Hoberecht", email = "[email protected]", role = c("aut")) |
... | ... |
@@ -133,6 +133,9 @@ exportMethods(targetOrigin) |
133 | 133 |
exportMethods(tssAnnotation) |
134 | 134 |
importClassesFrom(GenomeInfoDb,Seqinfo) |
135 | 135 |
importClassesFrom(GenomicRanges,GRanges) |
136 |
+importClassesFrom(GenomicRanges,GRangesList) |
|
137 |
+importClassesFrom(IRanges,DataFrameList) |
|
138 |
+importClassesFrom(IRanges,IRanges) |
|
136 | 139 |
importFrom(AnnotationDbi,select) |
137 | 140 |
importFrom(BSgenome,getBSgenome) |
138 | 141 |
importFrom(BSgenome,getSeq) |
... | ... |
@@ -353,9 +353,12 @@ setMethod("cutSites", "GuideSet", |
353 | 353 |
pamSites <- mcols(object)[["pam_site"]] |
354 | 354 |
nuc <- metadata(object)[["CrisprNuclease"]] |
355 | 355 |
strand <- as.character(strand(object)) |
356 |
- out <- getCutSiteFromPamSite(pam_site=pamSites, |
|
357 |
- strand=strand, |
|
358 |
- nuclease=nuc) |
|
356 |
+ ambiguousStrand <- strand == "*" |
|
357 |
+ out <- rep(NA, length(object)) |
|
358 |
+ out[!ambiguousStrand] <- getCutSiteFromPamSite( |
|
359 |
+ pam_site=pamSites[!ambiguousStrand], |
|
360 |
+ strand=strand[!ambiguousStrand], |
|
361 |
+ nuclease=nuc) |
|
359 | 362 |
names(out) <- names(object) |
360 | 363 |
return(out) |
361 | 364 |
}) |
... | ... |
@@ -80,10 +80,18 @@ addEditedAlleles <- function(guideSet, |
80 | 80 |
"each gRNA target site.") |
81 | 81 |
} |
82 | 82 |
alleles <- lapply(seq_along(guideSet), function(guide){ |
83 |
- .getEditedAllelesPerGuide(gs=guideSet[guide], |
|
84 |
- baseEditor=baseEditor, |
|
85 |
- editingWindow=editingWindow, |
|
86 |
- nMaxAlleles=nMaxAlleles) |
|
83 |
+ seqname <- as.character(GenomeInfoDb::seqnames(guideSet[guide])) |
|
84 |
+ genome <- GenomeInfoDb::genome(guideSet[guide]) |
|
85 |
+ genome <- genome[seqname] |
|
86 |
+ if (genome == "ntc"){ |
|
87 |
+ S4Vectors::DataFrame(seq=DNAStringSet(character(0)), |
|
88 |
+ score=numeric(0)) |
|
89 |
+ } else { |
|
90 |
+ .getEditedAllelesPerGuide(gs=guideSet[guide], |
|
91 |
+ baseEditor=baseEditor, |
|
92 |
+ editingWindow=editingWindow, |
|
93 |
+ nMaxAlleles=nMaxAlleles) |
|
94 |
+ } |
|
87 | 95 |
}) |
88 | 96 |
if (addFunctionalConsequence){ |
89 | 97 |
if (verbose){ |
... | ... |
@@ -175,7 +183,6 @@ addEditedAlleles <- function(guideSet, |
175 | 183 |
editingWindow) |
176 | 184 |
nucChanges <- .getPossibleNucChanges(ws) |
177 | 185 |
|
178 |
- |
|
179 | 186 |
# Getting gRNA information: |
180 | 187 |
pamSite <- pamSites(gs) |
181 | 188 |
strand <- as.character(strand(gs)) |
... | ... |
@@ -188,7 +195,7 @@ addEditedAlleles <- function(guideSet, |
188 | 195 |
pos <- seq(editingWindow[1], |
189 | 196 |
editingWindow[2]) |
190 | 197 |
names(nucs) <- pos |
191 |
- |
|
198 |
+ |
|
192 | 199 |
|
193 | 200 |
# Getting scores for the edited nucleotides: |
194 | 201 |
nucsReduced <- nucs[nucs %in% names(nucChanges)] |
... | ... |
@@ -423,6 +430,12 @@ addEditedAlleles <- function(guideSet, |
423 | 430 |
.addFunctionalConsequences <- function(editedAlleles, |
424 | 431 |
txTable |
425 | 432 |
){ |
433 |
+ if (nrow(editedAlleles) == 0){ |
|
434 |
+ editedAlleles$variant <- character(0) |
|
435 |
+ editedAlleles$aa <- character(0) |
|
436 |
+ return(editedAlleles) |
|
437 |
+ } |
|
438 |
+ |
|
426 | 439 |
if (txTable$chr[[1]]!=metadata(editedAlleles)$chr){ |
427 | 440 |
stop("editedAlleles are not on the same chromosome.") |
428 | 441 |
} |
... | ... |
@@ -519,8 +532,8 @@ addEditedAlleles <- function(guideSet, |
519 | 532 |
){ |
520 | 533 |
ws <- editingWeights(baseEditor) |
521 | 534 |
ws <- .rescaleWeights(ws) |
522 |
- ws <- ws[, as.numeric(colnames(ws))>=editingWindow[1],drop=FALSE] |
|
523 |
- ws <- ws[, as.numeric(colnames(ws))<=editingWindow[2],drop=FALSE] |
|
535 |
+ ws <- ws[, as.numeric(colnames(ws)) >= editingWindow[1], drop=FALSE] |
|
536 |
+ ws <- ws[, as.numeric(colnames(ws)) <= editingWindow[2], drop=FALSE] |
|
524 | 537 |
ws <- crisprBase:::.getReducedEditingMatrix(ws) |
525 | 538 |
ws <- .addWildtypeWeights(ws) |
526 | 539 |
return(ws) |
... | ... |
@@ -30,10 +30,13 @@ setMethod("addEditingSites", |
30 | 30 |
} |
31 | 31 |
pamSites <- pamSites(object) |
32 | 32 |
strand <- as.character(strand(object)) |
33 |
- editingSite <- getEditingSiteFromPamSite(pam_site=pamSites, |
|
34 |
- strand=strand, |
|
35 |
- baseEditor=nuc, |
|
36 |
- substitution=substitution) |
|
33 |
+ ambiguousStrand <- strand == "*" |
|
34 |
+ editingSite <- rep(NA, length(object)) |
|
35 |
+ editingSite[!ambiguousStrand] <- getEditingSiteFromPamSite( |
|
36 |
+ pam_site=pamSites[!ambiguousStrand], |
|
37 |
+ strand=strand[!ambiguousStrand], |
|
38 |
+ baseEditor=nuc, |
|
39 |
+ substitution=substitution) |
|
37 | 40 |
mcols(object)$editing_site <- editingSite |
38 | 41 |
return(object) |
39 | 42 |
}) |
... | ... |
@@ -185,6 +185,8 @@ setMethod("addNtcs", "NULL", function(object, |
185 | 185 |
|
186 | 186 |
#' @importFrom S4Vectors mcols mcols<- |
187 | 187 |
#' @importFrom methods is |
188 |
+#' @importClassesFrom GenomicRanges GRangesList |
|
189 |
+#' @importClassesFrom IRanges DataFrameList |
|
188 | 190 |
.mergeNtcGuideSet <- function(object, |
189 | 191 |
ntcGuideSet |
190 | 192 |
){ |
... | ... |
@@ -196,15 +198,15 @@ setMethod("addNtcs", "NULL", function(object, |
196 | 198 |
if (!is.atomic(dataColumn)){ |
197 | 199 |
S4Vectors::mcols(ntcGuideSet)[[i]] <- |
198 | 200 |
lapply(seq_along(ntcGuideSet), function(x){ |
199 |
- x <- S4Vectors::mcols(object)[[i]][0] |
|
200 |
- if (methods::is(x, "GRangesList")){ |
|
201 |
- x <- unlist(x) |
|
202 |
- } |
|
203 |
- x |
|
201 |
+ unlist(S4Vectors::mcols(object)[[i]][0]) |
|
204 | 202 |
}) |
205 |
- if (is(dataColumn, "GRangesList")){ |
|
203 |
+ ## set generic list to appropriate type |
|
204 |
+ if (methods::is(dataColumn, "GRangesList")){ |
|
206 | 205 |
S4Vectors::mcols(ntcGuideSet)[[i]] <- |
207 |
- GRangesList(S4Vectors::mcols(ntcGuideSet)[[i]]) |
|
206 |
+ GenomicRanges::GRangesList(S4Vectors::mcols(ntcGuideSet)[[i]]) |
|
207 |
+ } else if (methods::is(dataColumn, "DFrameList")){ |
|
208 |
+ S4Vectors::mcols(ntcGuideSet)[[i]] <- |
|
209 |
+ IRanges::DataFrameList(S4Vectors::mcols(ntcGuideSet)[[i]]) |
|
208 | 210 |
} |
209 | 211 |
} |
210 | 212 |
} |
... | ... |
@@ -241,11 +241,11 @@ convertToProtospacerGRanges <- function(guideSet){ |
241 | 241 |
|
242 | 242 |
|
243 | 243 |
|
244 |
-#' @title Convert a GuideSet object into a GRanges storing the range of |
|
245 |
-#' all gRNAs. |
|
244 |
+#' @title Convert a GuideSet object into a GRanges containing the range of |
|
245 |
+#' all targeting gRNAs. |
|
246 | 246 |
|
247 | 247 |
#' @description Convert a GuideSet object into a GRanges object containing |
248 |
-#' the minimum and maximum coordinates of all gRNAs. |
|
248 |
+#' the minimum and maximum coordinates for all targeting gRNAs. |
|
249 | 249 |
#' |
250 | 250 |
#' @param guideSet A \linkS4class{GuideSet} object. |
251 | 251 |
#' @param anchor A character string specifying which gRNA-specific coordinate |
... | ... |
@@ -260,18 +260,25 @@ convertToProtospacerGRanges <- function(guideSet){ |
260 | 260 |
#' data(guideSetExample, package="crisprDesign") |
261 | 261 |
#' gr <- convertToMinMaxGRanges(guideSetExample) |
262 | 262 |
#' |
263 |
-#' @author Jean-Philippe Fortin |
|
263 |
+#' @author Jean-Philippe Fortin, Luke Hoberecht |
|
264 | 264 |
#' |
265 |
-#' @importFrom GenomicRanges GRanges |
|
266 |
-#' @importFrom IRanges IRanges |
|
267 |
-#' @importFrom GenomeInfoDb seqlevels seqlevels<- |
|
268 |
-#' @importFrom GenomeInfoDb seqinfo seqinfo<- |
|
265 |
+#' @importClassesFrom GenomicRanges GRanges |
|
266 |
+#' @importClassesFrom IRanges IRanges |
|
267 |
+#' @importFrom GenomeInfoDb seqlevels seqlevels<- genome dropSeqlevels |
|
268 |
+#' @importFrom GenomeInfoDb seqinfo seqinfo<- seqnames |
|
269 | 269 |
#' @export |
270 | 270 |
convertToMinMaxGRanges <- function(guideSet, |
271 | 271 |
anchor=c("cut_site", "pam_site") |
272 | 272 |
){ |
273 | 273 |
anchor <- match.arg(anchor) |
274 |
- grs <- split(guideSet, f=as.character(seqnames(guideSet))) |
|
274 |
+ genomeSeqlevels <- GenomeInfoDb::genome(guideSet) |
|
275 |
+ ntc_seqs <- names(genomeSeqlevels)[genomeSeqlevels == "ntc"] |
|
276 |
+ if (length(ntc_seqs) > 0){ |
|
277 |
+ guideSet <- GenomeInfoDb::dropSeqlevels(guideSet, |
|
278 |
+ ntc_seqs, |
|
279 |
+ pruning.mode="coarse") |
|
280 |
+ } |
|
281 |
+ grs <- split(guideSet, f=as.character(GenomeInfoDb::seqnames(guideSet))) |
|
275 | 282 |
grs <- lapply(grs, function(gr){ |
276 | 283 |
if (anchor=="cut_site"){ |
277 | 284 |
start <- min(cutSites(gr), na.rm=TRUE) |
... | ... |
@@ -281,11 +288,11 @@ convertToMinMaxGRanges <- function(guideSet, |
281 | 288 |
end <- max(pamSites(gr), na.rm=TRUE) |
282 | 289 |
} |
283 | 290 |
|
284 |
- chr <- as.character(seqnames(gr))[1] |
|
285 |
- out <- GRanges(chr, |
|
286 |
- IRanges(start=start,end=end)) |
|
287 |
- seqlevels(out) <- seqlevels(gr) |
|
288 |
- seqinfo(out) <- seqinfo(gr) |
|
291 |
+ chr <- as.character(GenomeInfoDb::seqnames(gr))[1] |
|
292 |
+ out <- GenomicRanges::GRanges(chr, |
|
293 |
+ IRanges::IRanges(start=start,end=end)) |
|
294 |
+ GenomeInfoDb::seqlevels(out) <- GenomeInfoDb::seqlevels(gr) |
|
295 |
+ GenomeInfoDb::seqinfo(out) <- GenomeInfoDb::seqinfo(gr) |
|
289 | 296 |
out |
290 | 297 |
}) |
291 | 298 |
gr <- Reduce(c,grs) |
... | ... |
@@ -2,8 +2,8 @@ |
2 | 2 |
% Please edit documentation in R/completeSpacers.R |
3 | 3 |
\name{convertToMinMaxGRanges} |
4 | 4 |
\alias{convertToMinMaxGRanges} |
5 |
-\title{Convert a GuideSet object into a GRanges storing the range of |
|
6 |
- all gRNAs.} |
|
5 |
+\title{Convert a GuideSet object into a GRanges containing the range of |
|
6 |
+ all targeting gRNAs.} |
|
7 | 7 |
\usage{ |
8 | 8 |
convertToMinMaxGRanges(guideSet, anchor = c("cut_site", "pam_site")) |
9 | 9 |
} |
... | ... |
@@ -21,7 +21,7 @@ A GRanges object with start and end coordinates |
21 | 21 |
} |
22 | 22 |
\description{ |
23 | 23 |
Convert a GuideSet object into a GRanges object containing |
24 |
- the minimum and maximum coordinates of all gRNAs. |
|
24 |
+ the minimum and maximum coordinates for all targeting gRNAs. |
|
25 | 25 |
} |
26 | 26 |
\examples{ |
27 | 27 |
data(guideSetExample, package="crisprDesign") |
... | ... |
@@ -29,5 +29,5 @@ gr <- convertToMinMaxGRanges(guideSetExample) |
29 | 29 |
|
30 | 30 |
} |
31 | 31 |
\author{ |
32 |
-Jean-Philippe Fortin |
|
32 |
+Jean-Philippe Fortin, Luke Hoberecht |
|
33 | 33 |
} |
... | ... |
@@ -98,7 +98,11 @@ test_that("added ntcs have NA or empty list annotations", { |
98 | 98 |
out_ntcs <- out[intersect(names(out), names(all_ntcs))] |
99 | 99 |
lapply(listcols, function(i){ |
100 | 100 |
lapply(seq_along(out_ntcs), function(ii){ |
101 |
- expect_equal(length(mcols(out_ntcs)[[i]][[ii]]), 0) |
|
101 |
+ if (is(mcols(out_ntcs)[[i]], "GRangesList")){ |
|
102 |
+ expect_equal(length(mcols(out_ntcs)[[i]][[ii]]), 0) |
|
103 |
+ } else { |
|
104 |
+ expect_equal(nrow(mcols(out_ntcs)[[i]][[ii]]), 0) |
|
105 |
+ } |
|
102 | 106 |
}) |
103 | 107 |
}) |
104 | 108 |
lapply(atomicCols, function(x){ |
... | ... |
@@ -129,9 +133,8 @@ test_that("ntcs names must be unique and distinct from object ids, seqnames", { |
129 | 133 |
|
130 | 134 |
test_that("crisprDesign computational functions handle ntcs in GuideSet", { |
131 | 135 |
out <- addNtcs(guideSetExample, all_ntcs) |
132 |
- # getPAMSequence(seqnames(out), pamSites(out), strand(out)) # error |
|
133 |
- # getSpacerSequence(seqnames(out), pamSites(out), strand(out)) # error |
|
134 |
- # convertToMinMaxGRanges(out) # issue with strand |
|
136 |
+ expect_error(convertToMinMaxGRanges(out), |
|
137 |
+ regex=NA) |
|
135 | 138 |
expect_error(convertToProtospacerGRanges(out), |
136 | 139 |
regexp=NA) # no error, but meaningless output for ntcs |
137 | 140 |
}) |
... | ... |
@@ -147,8 +150,63 @@ out <- addNtcs(head(guideSetExample), all_ntcs[1]) |
147 | 150 |
out_full <- addNtcs(head(guideSetExampleFullAnnotation), all_ntcs[1]) |
148 | 151 |
|
149 | 152 |
|
153 |
+## ACCESSOR FUNCTIONS ========================================================= |
|
154 |
+ |
|
155 |
+test_that("atomic accessor functions handle ntcs in GuideSet gracefully", { |
|
156 |
+ expect_error(spacers(out_full), regexp=NA) |
|
157 |
+ expect_error(pams(out_full), regexp=NA) |
|
158 |
+ expect_error(pamSites(out_full), regexp=NA) |
|
159 |
+ expect_error(cutSites(out_full), regexp=NA) |
|
160 |
+ expect_error(protospacers(out_full), regexp=NA) |
|
161 |
+}) |
|
162 |
+ |
|
163 |
+test_that("snps accessor handles ntcs in GuideSet gracefully", { |
|
164 |
+ expect_error(snps(out_full), |
|
165 |
+ regexp=NA) |
|
166 |
+ expect_false(is.null(snps(out_full))) |
|
167 |
+}) |
|
168 |
+ |
|
169 |
+test_that("alignments accessors handles ntcs in GuideSet gracefully", { |
|
170 |
+ expect_error(alignments(out_full), |
|
171 |
+ regexp=NA) |
|
172 |
+ expect_error(onTargets(out_full), |
|
173 |
+ regexp=NA) |
|
174 |
+ expect_error(offTargets(out_full), |
|
175 |
+ regexp=NA) |
|
176 |
+ expect_false(is.null(alignments(out_full))) |
|
177 |
+ expect_false(is.null(onTargets(out_full))) |
|
178 |
+ expect_false(is.null(offTargets(out_full))) |
|
179 |
+}) |
|
180 |
+ |
|
181 |
+test_that("geneAnnotation accessor handles ntcs in GuideSet gracefully", { |
|
182 |
+ expect_error(geneAnnotation(out_full), |
|
183 |
+ regexp=NA) |
|
184 |
+ expect_false(is.null(geneAnnotation(out_full))) |
|
185 |
+}) |
|
186 |
+ |
|
187 |
+test_that("tssAnnotation accessor handles ntcs in GuideSet gracefully", { |
|
188 |
+ expect_error(tssAnnotation(out_full), |
|
189 |
+ regexp=NA) |
|
190 |
+ expect_false(is.null(tssAnnotation(out_full))) |
|
191 |
+}) |
|
192 |
+ |
|
193 |
+test_that("enzymeAnnotation accessor handles ntcs in GuideSet gracefully", { |
|
194 |
+ expect_error(enzymeAnnotation(out_full), |
|
195 |
+ regexp=NA) |
|
196 |
+ expect_false(is.null(enzymeAnnotation(out_full))) |
|
197 |
+}) |
|
198 |
+ |
|
199 |
+## guideSetExampleFullAnnotation lacks editedAlleles annotation |
|
200 |
+# test_that("editedAlleles accessor handles ntcs in GuideSet gracefully", { |
|
201 |
+# expect_error(editedAlleles(out_full), |
|
202 |
+# regexp=NA) |
|
203 |
+# expect_false(is.null(editedAlleles(out_full))) |
|
204 |
+# }) |
|
205 |
+ |
|
150 | 206 |
|
151 | 207 |
|
208 |
+## ANNOTATION FUNCTIONS ======================================================= |
|
209 |
+ |
|
152 | 210 |
## split for each crisprDesign function (so more helpful message if test fails) |
153 | 211 |
test_that("addCutSites handles ntcs in GuideSet gracefully", { |
154 | 212 |
expect_error(addCutSites(out), |
... | ... |
@@ -167,20 +225,29 @@ test_that("addSNPAnnotation handles ntcs in GuideSet gracefully", { |
167 | 225 |
VCF_PATH <- system.file("extdata", |
168 | 226 |
file="common_snps_dbsnp151_example.vcf.gz", |
169 | 227 |
package="crisprDesign") |
170 |
- expect_error(addSNPAnnotation(out, vcf=VCF_PATH), |
|
228 |
+ expect_error(res <- addSNPAnnotation(out, vcf=VCF_PATH), |
|
229 |
+ regexp=NA) |
|
230 |
+ expect_error(snps(res), |
|
171 | 231 |
regexp=NA) |
232 |
+ expect_false(is.null(snps(res))) |
|
172 | 233 |
}) |
173 | 234 |
|
174 | 235 |
|
175 | 236 |
test_that("addGeneAnnotation handles ntcs in GuideSet gracefully", { |
176 |
- expect_error(addGeneAnnotation(out, txObject=txdb_human), |
|
237 |
+ expect_error(res <- addGeneAnnotation(out, txObject=txdb_human), |
|
177 | 238 |
regexp=NA) |
239 |
+ expect_error(geneAnnotation(res), |
|
240 |
+ regexp=NA) |
|
241 |
+ expect_false(is.null(geneAnnotation(res))) |
|
178 | 242 |
}) |
179 | 243 |
|
180 | 244 |
|
181 | 245 |
test_that("addTssAnnotation handles ntcs in GuideSet gracefully", { |
182 |
- expect_error(addTssAnnotation(out, tssObject=tss_human), |
|
246 |
+ expect_error(res <- addTssAnnotation(out, tssObject=tss_human), |
|
247 |
+ regexp=NA) |
|
248 |
+ expect_error(tssAnnotation(res), |
|
183 | 249 |
regexp=NA) |
250 |
+ expect_false(is.null(tssAnnotation(res))) |
|
184 | 251 |
}) |
185 | 252 |
|
186 | 253 |
|
... | ... |
@@ -197,8 +264,11 @@ test_that("addPamScores handles ntcs in GuideSet gracefully", { |
197 | 264 |
|
198 | 265 |
|
199 | 266 |
test_that("addRestrictionEnzymes handles ntcs in GuideSet gracefully", { |
200 |
- expect_error(addRestrictionEnzymes(out), |
|
267 |
+ expect_error(res <- addRestrictionEnzymes(out), |
|
201 | 268 |
regexp=NA) |
269 |
+ expect_error(enzymeAnnotation(res), |
|
270 |
+ regexp=NA) |
|
271 |
+ expect_false(is.null(enzymeAnnotation(res))) |
|
202 | 272 |
}) |
203 | 273 |
|
204 | 274 |
|
... | ... |
@@ -211,7 +281,7 @@ test_that("addSpacerAlignments/Iterative handles ntcs in GuideSet gracefully", { |
211 | 281 |
force=TRUE, |
212 | 282 |
prefix="tempIndex") |
213 | 283 |
index <- file.path(outdir, "tempIndex") |
214 |
- expect_error(addSpacerAlignments( |
|
284 |
+ expect_error(res <- addSpacerAlignments( |
|
215 | 285 |
out, |
216 | 286 |
txObject=txdb_human, |
217 | 287 |
tssObject=tss_human, |
... | ... |
@@ -225,12 +295,15 @@ test_that("addSpacerAlignments/Iterative handles ntcs in GuideSet gracefully", { |
225 | 295 |
aligner_index=index, |
226 | 296 |
bsgenome=BSgenome.Hsapiens.UCSC.hg38), |
227 | 297 |
regexp=NA) |
298 |
+ expect_error(alignments(res), |
|
299 |
+ regexp=NA) |
|
300 |
+ expect_false(is.null(alignments(res))) |
|
228 | 301 |
}) |
229 | 302 |
|
230 | 303 |
|
231 | 304 |
test_that("addOnTargetScores handles ntcs in GuideSet gracefully", { |
232 | 305 |
expect_error(addOnTargetScores(out, methods=c("deephf")), |
233 |
- regexp=NA) # need to test all methods? |
|
306 |
+ regexp=NA) # need to test all methods |
|
234 | 307 |
}) |
235 | 308 |
|
236 | 309 |
|
... | ... |
@@ -246,20 +319,99 @@ test_that("GuideSet with ntcs can be converted to data.frame", { |
246 | 319 |
}) |
247 | 320 |
|
248 | 321 |
|
322 |
+test_that("addEditingSites handles ntcs in GuideSet gracefully", { |
|
323 |
+ gs <- out |
|
324 |
+ metadata(gs)$CrisprNuclease <- BE4max |
|
325 |
+ expect_error(addEditingSites(gs, "C2T"), |
|
326 |
+ regexp=NA) |
|
327 |
+}) |
|
328 |
+ |
|
329 |
+ |
|
330 |
+test_that("addExonTable handles ntcs in the GuideSet gracefully", { |
|
331 |
+ outga <- addGeneAnnotation(out, txObject=txdb_human) |
|
332 |
+ expect_error(addExonTable(outga, |
|
333 |
+ gene_id="ENSG00000120645", |
|
334 |
+ txObject=txdb_human), |
|
335 |
+ regexp=NA) |
|
336 |
+}) |
|
337 |
+ |
|
338 |
+ |
|
339 |
+## uses local file |
|
340 |
+# test_that("addConservationScores handles ntcs in the GuideSet gracefully", { |
|
341 |
+# conservationFile <- getConservationFiles("human") |
|
342 |
+# expect_error(addConservationScores(out, |
|
343 |
+# conservationFile=conservationFile), |
|
344 |
+# regexp=NA) |
|
345 |
+# }) |
|
346 |
+ |
|
347 |
+ |
|
348 |
+test_that("addDistanceToTss handles ntcs in the GuideSet gracefully", { |
|
349 |
+ tss_id <- "ENSG00000120645_P1" |
|
350 |
+ expect_error(addDistanceToTss(out_full, tss_id), |
|
351 |
+ regexp=NA) |
|
352 |
+}) |
|
353 |
+ |
|
354 |
+ |
|
355 |
+test_that("addTxTable handles ntcs in the GuideSet gracefully", { |
|
356 |
+ gene_id <- "ENSG00000120645" |
|
357 |
+ expect_error(addTxTable(out_full, gene_id, txdb_human), |
|
358 |
+ regexp=NA) |
|
359 |
+}) |
|
360 |
+ |
|
361 |
+ |
|
362 |
+## uses local files |
|
363 |
+test_that("addCrispraiScores handles ntcs in the GuideSet gracefully", { |
|
364 |
+ # gr <- queryTss(tss_human, |
|
365 |
+ # "gene_symbol", |
|
366 |
+ # "IQSEC3") |
|
367 |
+ # gs <- findSpacers(gr, |
|
368 |
+ # crisprNuclease=SpCas9, |
|
369 |
+ # bsgenome=BSgenome.Hsapiens.UCSC.hg38) |
|
370 |
+ # gs <- addNtcs(head(gs), all_ntcs[1]) |
|
371 |
+ # chromatinFiles <- "~/crisprIndices/chromatin/hg38" |
|
372 |
+ # chromatinFiles <- file.path(chromatinFiles, list.files(chromatinFiles)) |
|
373 |
+ # names(chromatinFiles) <- c("dnase", "faire", "mnase") |
|
374 |
+ # fastaFile <- "~/crisprIndices/genomes/hg38/hg38.fa.gz" |
|
375 |
+ # addCrispraiScores(gs, |
|
376 |
+ # gr=gr, |
|
377 |
+ # tssObject=tss_human, |
|
378 |
+ # chromatinFiles=chromatinFiles, |
|
379 |
+ # fastaFile=fastaFile) |
|
380 |
+}) |
|
381 |
+ |
|
382 |
+ |
|
383 |
+test_that("addEditedAlleles handles ntcs in the GuideSet gracefully", { |
|
384 |
+ gs <- out |
|
385 |
+ metadata(gs)$CrisprNuclease <- BE4max |
|
386 |
+ txTable <- getTxInfoDataFrame(tx_id="ENST00000538872", |
|
387 |
+ txObject=txdb_human, |
|
388 |
+ bsgenome=BSgenome.Hsapiens.UCSC.hg38) |
|
389 |
+ |
|
390 |
+ expect_error(res <- addEditedAlleles(gs, |
|
391 |
+ baseEditor=BE4max, |
|
392 |
+ txTable=txTable, |
|
393 |
+ editingWindow=c(-20, -8)), |
|
394 |
+ regexp=NA) |
|
395 |
+ expect_error(editedAlleles(res), |
|
396 |
+ regexp=NA) |
|
397 |
+ expect_false(is.null(editedAlleles(res))) |
|
398 |
+}) |
|
399 |
+ |
|
249 | 400 |
|
401 |
+test_that("addIsoformAnnotation handles ntcs in the GuideSet gracefully", { |
|
402 |
+ tx_id <- "ENST00000538872" |
|
403 |
+ expect_error(addIsoformAnnotation(out_full, |
|
404 |
+ tx_id="ENST00000538872"), |
|
405 |
+ regexp=NA) |
|
406 |
+}) |
|
250 | 407 |
|
251 | 408 |
|
252 |
-## other crisprDesign functions that may need testing |
|
253 |
-# addEditingSites |
|
254 |
-# addExonTable_consensusIsoform |
|
255 |
-# addConservationScores |
|
256 |
-# addDistanceToTss |
|
257 |
-# addExonTable |
|
258 |
-# addTxTable |
|
259 |
-# addCrispraiScores |
|
260 |
-# addEditedAlleles |
|
261 |
-# addExonTable_allIsoforms |
|
262 |
-# addIsoformAnnotation |
|
263 |
-# addPfamDomains |
|
409 |
+test_that("addPfamDomains handles ntcs in the GuideSet gracefully", { |
|
410 |
+ pfamTable <- preparePfamTable(txdb_human, |
|
411 |
+ mart_dataset="hsapiens_gene_ensembl") |
|
412 |
+ expect_error(addPfamDomains(out_full, |
|
413 |
+ pfamTable=pfamTable), |
|
414 |
+ regexp=NA) |
|
415 |
+ |
|
416 |
+}) |
|
264 | 417 |
|
265 |
-## check that function can also handle PairedGuideSet? |