git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@74113 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -10,7 +10,7 @@ Description: GSNAP and GMAP are a pair of tools to align short-read |
10 | 10 |
to work with GMAP and GSNAP from within R. In addition, it provides |
11 | 11 |
methods to tally alignment results on a per-nucleotide basis using |
12 | 12 |
the bam_tally tool. |
13 |
-Version: 1.1.10 |
|
13 |
+Version: 1.1.11 |
|
14 | 14 |
Depends: R (>= 2.15.0), methods, GenomicRanges |
15 | 15 |
Imports: IRanges, Rsamtools (>= 1.7.4), rtracklayer (>= 1.17.15), GenomicRanges, |
16 | 16 |
GenomicFeatures, Biostrings, VariantAnnotation, tools, Biobase |
... | ... |
@@ -2,7 +2,7 @@ test_snps <- function() { |
2 | 2 |
## FIXME: rewrite this test to use the output of bam_tally, once we |
3 | 3 |
## can convert those results to a VCF. |
4 | 4 |
library(gmapR) |
5 |
- genome <- GmapGenome("hg19_IGIS21", create = TRUE) |
|
5 |
+ genome <- GmapGenome("hg19_IGIS21", create = TRUE, k = 12) |
|
6 | 6 |
dir <- GmapSnpDirectory(genome) |
7 | 7 |
gr <- as(seqinfo(genome), "GenomicRanges") |
8 | 8 |
gr <- GRanges("3", IRanges(3e6,4e6)) |
... | ... |
@@ -28,6 +28,8 @@ test_bam_tally_C <- function() { |
28 | 28 |
which <- RangesList("1" = IRanges(1e6, 2e6)) |
29 | 29 |
bam <- "~/share/data/R1047_LIB6635_SAM636095_L1_NXG2449.analyzed.bam" |
30 | 30 |
bf <- Rsamtools::BamFile(bam) |
31 |
- gr <- bam_tally(bf, BamTallyParam(genome, which = which, variant_strand = 1L)) |
|
31 |
+ gr <- bam_tally(bf, BamTallyParam(genome, which = which, variant_strand = 1L, |
|
32 |
+ cycle_breaks = c(0L, 10L, 75L), |
|
33 |
+ indels = TRUE)) |
|
32 | 34 |
|
33 | 35 |
} |
... | ... |
@@ -1,7 +1,7 @@ |
1 | 1 |
test_GmapGenome_constructor_DNAStringSet_noCreate <- function() { |
2 | 2 |
dna <- Biostrings::DNAStringSet("ACTGTGTCAG") |
3 | 3 |
names(dna) <- "test" |
4 |
- gmapGenome <- GmapGenome(genome=dna, name="thing", create=FALSE) |
|
4 |
+ gmapGenome <- GmapGenome(genome=dna, name="thing", create=FALSE, k = 12) |
|
5 | 5 |
checkTrue(is(gmapGenome, "GmapGenome")) |
6 | 6 |
} |
7 | 7 |
|
... | ... |
@@ -15,10 +15,10 @@ test_GmapGenome_constructor_DNAStringSet_create <- function() { |
15 | 15 |
dir.create(genomeDir, recursive=TRUE) |
16 | 16 |
on.exit(unlink(genomeDir, recursive=TRUE)) |
17 | 17 |
checkException(GmapGenome(genome=dna, directory=genomeDir, |
18 |
- name="thing", create=TRUE)) |
|
18 |
+ name="thing", create=TRUE, k=12)) |
|
19 | 19 |
names(dna) <- "sampleDNAStringSet" |
20 | 20 |
gmapGenome <- GmapGenome(genome=dna, directory=genomeDir, |
21 |
- name="thing", create=TRUE) |
|
21 |
+ name="thing", create=TRUE, k=12) |
|
22 | 22 |
checkTrue(is(gmapGenome, "GmapGenome")) |
23 | 23 |
} |
24 | 24 |
|
... | ... |
@@ -30,14 +30,14 @@ test_GmapGenome_constructor_BSgenome_create <- function() { |
30 | 30 |
dir.create(genomeDir, recursive=TRUE) |
31 | 31 |
on.exit(unlink(genomeDir, recursive=TRUE)) |
32 | 32 |
gmapGenome <- GmapGenome(genome=Scerevisiae, directory=genomeDir, |
33 |
- name=genomeName, create=TRUE) |
|
33 |
+ name=genomeName, create=TRUE, k=12) |
|
34 | 34 |
checkTrue(is(gmapGenome, "GmapGenome")) |
35 | 35 |
} |
36 | 36 |
|
37 | 37 |
testGmapGenome_constructor_FastaFile_create <- function() { |
38 | 38 |
fa <- system.file("extdata/hg19.p53.fasta", package="gmapR", mustWork=TRUE) |
39 | 39 |
fastaFile <- rtracklayer::FastaFile(fa) |
40 |
- gmapGenome <- GmapGenome(fastaFile, create=TRUE) |
|
40 |
+ gmapGenome <- GmapGenome(fastaFile, create=TRUE, k=12) |
|
41 | 41 |
checkTrue(is(gmapGenome, "GmapGenome")) |
42 | 42 |
} |
43 | 43 |
|
... | ... |
@@ -50,7 +50,7 @@ test_GmapGenome_accessors <- function() { |
50 | 50 |
dir.create(genomeDir, recursive=TRUE) |
51 | 51 |
on.exit(unlink(genomeDir, recursive=TRUE)) |
52 | 52 |
gmapGenome <- GmapGenome(genome=dna, directory=genomeDir, |
53 |
- name=genomeName, create=FALSE) |
|
53 |
+ name=genomeName, create=FALSE, k=12) |
|
54 | 54 |
checkIdentical(path(gmapGenome), file.path(genomeDir, genomeName)) |
55 | 55 |
checkTrue(is(directory(gmapGenome), "GmapGenomeDirectory")) |
56 | 56 |
checkIdentical(genome(gmapGenome), genomeName) |
... | ... |
@@ -2,7 +2,7 @@ test_GsnapParam_constructor <- function() { |
2 | 2 |
|
3 | 3 |
fa <- system.file("extdata/hg19.p53.fasta", package="gmapR", mustWork=TRUE) |
4 | 4 |
fastaFile <- rtracklayer::FastaFile(fa) |
5 |
- gmapGenome <- GmapGenome(fastaFile, create=TRUE) |
|
5 |
+ gmapGenome <- GmapGenome(fastaFile, create=TRUE, k = 12) |
|
6 | 6 |
|
7 | 7 |
gsnapParam <- GsnapParam(genome = gmapGenome, |
8 | 8 |
unique_only = FALSE, |
... | ... |
@@ -8,7 +8,8 @@ test_makeGmapGenomePackage_sacCer3 <- function() { |
8 | 8 |
gmapGenome <- GmapGenome(genome=Scerevisiae, |
9 | 9 |
directory = ggd, |
10 | 10 |
name = "yeast", |
11 |
- create = TRUE) |
|
11 |
+ create = TRUE, |
|
12 |
+ k = 12) |
|
12 | 13 |
|
13 | 14 |
packageDestDir <- file.path(tempdir(), as.integer(runif(1) * 100000)) |
14 | 15 |
on.exit(unlink(packageDestDir, recursive=TRUE), add=TRUE) |