Skip to content

Commit 98abe2a

Browse files
committed
1.27.6 testthat bugfix
1 parent 6cf7446 commit 98abe2a

File tree

7 files changed

+170
-179
lines changed

7 files changed

+170
-179
lines changed

DESCRIPTION

+3-2
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
Package: phyloseq
2-
Version: 1.27.2
3-
Date: 2019-02-16
2+
Version: 1.27.6
3+
Date: 2019-04-23
44
Title: Handling and analysis of high-throughput microbiome
55
census data
66
Description: phyloseq provides a set of classes and tools
@@ -36,6 +36,7 @@ Suggests:
3636
DESeq2 (>= 1.16.1),
3737
genefilter (>= 1.58),
3838
knitr (>= 1.16),
39+
magrittr (>= 1.5),
3940
metagenomeSeq (>= 1.14),
4041
rmarkdown (>= 1.6),
4142
testthat (>= 1.0.2)

R/transform_filter-methods.R

+2-2
Original file line numberDiff line numberDiff line change
@@ -159,8 +159,8 @@ rarefy_even_depth <- function(physeq, sample.size=min(sample_sums(physeq)),
159159
message(length(rmsamples), " samples removed",
160160
"because they contained fewer reads than `sample.size`.")
161161
message("Up to first five removed samples are: \n")
162-
message(rmsamples[1:min(5, length(rmsamples))], sep="\t")
163-
message("...")
162+
message(paste(rmsamples[1:min(5, length(rmsamples))], sep="\t"))
163+
message("...")
164164
}
165165
# Now done with notifying user of pruning, actually prune.
166166
physeq = prune_samples(setdiff(sample_names(physeq), rmsamples), physeq)

tests/testthat/test-IO.R

+79-77
Original file line numberDiff line numberDiff line change
@@ -90,36 +90,38 @@ rs_file <- system.file("extdata", "qiime500-refseq.fasta", package="phyloseq")
9090

9191
t0 <- import_qiime(otufile, mapfile, trefile, rs_file, verbose=FALSE)
9292
test_that("Class of import result is phyloseq-class", {
93-
expect_that(t0, is_a("phyloseq"))
93+
expect_is(t0, "phyloseq")
9494
})
9595

9696
test_that("Classes of components are as expected", {
97-
expect_that(otu_table(t0), is_a("otu_table"))
98-
expect_that(tax_table(t0), is_a("taxonomyTable"))
99-
expect_that(sample_data(t0), is_a("sample_data"))
100-
expect_that(phy_tree(t0), is_a("phylo"))
101-
expect_that(refseq(t0), is_a("DNAStringSet"))
97+
expect_is(otu_table(t0), ("otu_table"))
98+
expect_is(tax_table(t0), ("taxonomyTable"))
99+
expect_is(sample_data(t0), ("sample_data"))
100+
expect_is(phy_tree(t0), ("phylo"))
101+
expect_is(refseq(t0), ("DNAStringSet"))
102102
})
103103

104104
test_that("Features of the abundance data are consistent, match known values", {
105-
expect_that(sum(taxa_sums(t0)), equals(1269671L))
106-
expect_that(sum(taxa_sums(t0)==0), equals(5L))
107-
expect_that(sum(taxa_sums(t0)>=100), equals(183L))
108-
expect_that(sum(taxa_sums(t0)), equals(sum(sample_sums(t0))))
109-
expect_that(sum(sample_sums(t0) > 10000L), equals(20L))
110-
expect_that(nsamples(t0), equals(26L))
111-
expect_that(ntaxa(t0), equals(500L))
112-
expect_that(length(rank_names(t0)), equals(7L))
105+
expect_equal(sum(taxa_sums(t0)), (1269671L))
106+
expect_equal(sum(taxa_sums(t0)==0), (5L))
107+
expect_equal(sum(taxa_sums(t0)>=100), (183L))
108+
expect_equal(sum(taxa_sums(t0)), (sum(sample_sums(t0))))
109+
expect_equal(sum(sample_sums(t0) > 10000L), (20L))
110+
expect_equal(nsamples(t0), (26L))
111+
expect_equal(ntaxa(t0), (500L))
112+
expect_equal(length(rank_names(t0)), (7L))
113113
})
114114

115115
test_that("Features of the taxonomy table match expected values", {
116-
expect_that(length(rank_names(t0)), equals(7L))
116+
expect_equal(length(rank_names(t0)), (7L))
117117
expect_equal(rank_names(t0),
118118
c("Kingdom", "Phylum", "Class", "Order", "Family", "Genus", "Species"))
119119
tax53 = as(tax_table(t0), "matrix")[53, ]
120-
expect_that(tax53, is_equivalent_to(c("Bacteria", "Proteobacteria", "Deltaproteobacteria",
121-
"Desulfovibrionales", "Desulfomicrobiaceae",
122-
"Desulfomicrobium", "Desulfomicrobiumorale")))
120+
expect_equivalent(
121+
tax53,
122+
c("Bacteria", "Proteobacteria", "Deltaproteobacteria",
123+
"Desulfovibrionales", "Desulfomicrobiaceae",
124+
"Desulfomicrobium", "Desulfomicrobiumorale"))
123125
})
124126
################################################################################
125127
# parse function tests - note, these are also used by import_biom
@@ -188,119 +190,119 @@ refseqfilename = system.file("extdata", "biom-refseq.fasta", package="phyloseq"
188190

189191
test_that("Importing biom files yield phyloseq objects", {
190192
library("biomformat")
191-
rdbiom = read_biom(rich_sparse_biom)
193+
rdbiom = read_biom(rich_dense_biom)
192194
rsbiom = read_biom(rich_sparse_biom)
193195

194196
rich_dense = import_biom(rdbiom)
195197
rich_sparse = import_biom(rsbiom)
196198

197-
expect_that(rich_dense, is_a("phyloseq"))
198-
expect_that(rich_sparse, is_a("phyloseq"))
199+
expect_is(rich_dense, ("phyloseq"))
200+
expect_is(rich_sparse, ("phyloseq"))
199201

200-
expect_that(ntaxa(rich_dense), equals(5L))
201-
expect_that(ntaxa(rich_sparse), equals(5L))
202+
expect_equal(ntaxa(rich_dense), (5L))
203+
expect_equal(ntaxa(rich_sparse), (5L))
202204

203205
# # Component classes
204206
# sample_data
205-
expect_that(access(rich_dense, "sam_data"), is_a("sample_data"))
206-
expect_that(access(rich_sparse, "sam_data"), is_a("sample_data"))
207+
expect_is(access(rich_dense, "sam_data"), ("sample_data"))
208+
expect_is(access(rich_sparse, "sam_data"), ("sample_data"))
207209

208210
# taxonomyTable
209-
expect_that(access(rich_dense, "tax_table"), is_a("taxonomyTable"))
210-
expect_that(access(rich_sparse, "tax_table"), is_a("taxonomyTable"))
211+
expect_is(access(rich_dense, "tax_table"), ("taxonomyTable"))
212+
expect_is(access(rich_sparse, "tax_table"), ("taxonomyTable"))
211213

212214
# otu_table
213-
expect_that(access(rich_dense, "otu_table"), is_a("otu_table"))
214-
expect_that(access(rich_sparse, "otu_table"), is_a("otu_table"))
215+
expect_is(access(rich_dense, "otu_table"), ("otu_table"))
216+
expect_is(access(rich_sparse, "otu_table"), ("otu_table"))
215217
})
216218

217-
test_that("The different types of biom files yield phyloseq objects",{
219+
test_that("The different types of biom files yield phyloseq objects", {
218220
rich_dense = import_biom(rich_dense_biom, treefilename, refseqfilename, parseFunction=parse_taxonomy_greengenes)
219221
rich_sparse = import_biom(rich_sparse_biom, treefilename, refseqfilename, parseFunction=parse_taxonomy_greengenes)
220222
min_dense = import_biom(min_dense_biom, treefilename, refseqfilename, parseFunction=parse_taxonomy_greengenes)
221223
min_sparse = import_biom(min_sparse_biom, treefilename, refseqfilename, parseFunction=parse_taxonomy_greengenes)
222224

223-
expect_that(rich_dense, is_a("phyloseq"))
224-
expect_that(rich_sparse, is_a("phyloseq"))
225-
expect_that(min_dense, is_a("phyloseq"))
226-
expect_that(min_sparse, is_a("phyloseq"))
225+
expect_is(rich_dense, ("phyloseq"))
226+
expect_is(rich_sparse, ("phyloseq"))
227+
expect_is(min_dense, ("phyloseq"))
228+
expect_is(min_sparse, ("phyloseq"))
227229

228-
expect_that(ntaxa(rich_dense), equals(5L))
229-
expect_that(ntaxa(rich_sparse), equals(5L))
230-
expect_that(ntaxa(min_dense), equals(5L))
231-
expect_that(ntaxa(min_sparse), equals(5L))
230+
expect_equal(ntaxa(rich_dense), (5L))
231+
expect_equal(ntaxa(rich_sparse), (5L))
232+
expect_equal(ntaxa(min_dense), (5L))
233+
expect_equal(ntaxa(min_sparse), (5L))
232234

233235
# # Component classes
234236
# sample_data
235-
expect_that(access(rich_dense, "sam_data"), is_a("sample_data"))
236-
expect_that(access(rich_sparse, "sam_data"), is_a("sample_data"))
237-
expect_that(access(min_dense, "sam_data"), is_a("NULL"))
238-
expect_that(access(min_sparse, "sam_data"), is_a("NULL"))
237+
expect_is(access(rich_dense, "sam_data"), ("sample_data"))
238+
expect_is(access(rich_sparse, "sam_data"), ("sample_data"))
239+
expect_is(access(min_dense, "sam_data"), ("NULL"))
240+
expect_is(access(min_sparse, "sam_data"), ("NULL"))
239241

240242
# taxonomyTable
241-
expect_that(access(rich_dense, "tax_table"), is_a("taxonomyTable"))
242-
expect_that(access(rich_sparse, "tax_table"), is_a("taxonomyTable"))
243-
expect_that(access(min_dense, "tax_table"), is_a("NULL"))
244-
expect_that(access(min_sparse, "tax_table"), is_a("NULL"))
243+
expect_is(access(rich_dense, "tax_table"), ("taxonomyTable"))
244+
expect_is(access(rich_sparse, "tax_table"), ("taxonomyTable"))
245+
expect_is(access(min_dense, "tax_table"), ("NULL"))
246+
expect_is(access(min_sparse, "tax_table"), ("NULL"))
245247

246248
# phylo tree
247-
expect_that(access(rich_dense, "phy_tree"), is_a("phylo"))
248-
expect_that(access(rich_sparse, "phy_tree"), is_a("phylo"))
249-
expect_that(access(min_dense, "phy_tree"), is_a("phylo"))
250-
expect_that(access(min_sparse, "phy_tree"), is_a("phylo"))
249+
expect_is(access(rich_dense, "phy_tree"), ("phylo"))
250+
expect_is(access(rich_sparse, "phy_tree"), ("phylo"))
251+
expect_is(access(min_dense, "phy_tree"), ("phylo"))
252+
expect_is(access(min_sparse, "phy_tree"), ("phylo"))
251253

252254
# reference sequences
253-
expect_that(inherits(access(rich_dense, "refseq"), "XStringSet"), is_true())
254-
expect_that(inherits(access(rich_sparse, "refseq"), "XStringSet"), is_true())
255-
expect_that(inherits(access(min_dense, "refseq"), "XStringSet"), is_true())
256-
expect_that(inherits(access(min_sparse, "refseq"), "XStringSet"), is_true())
257-
expect_that(access(rich_dense, "refseq"), is_a("DNAStringSet"))
258-
expect_that(access(rich_sparse, "refseq"), is_a("DNAStringSet"))
259-
expect_that(access(min_dense, "refseq"), is_a("DNAStringSet"))
260-
expect_that(access(min_sparse, "refseq"), is_a("DNAStringSet"))
255+
expect_true(inherits(access(rich_dense, "refseq"), "XStringSet"))
256+
expect_true(inherits(access(rich_sparse, "refseq"), "XStringSet"))
257+
expect_true(inherits(access(min_dense, "refseq"), "XStringSet"))
258+
expect_true(inherits(access(min_sparse, "refseq"), "XStringSet"))
259+
expect_is(access(rich_dense, "refseq"), ("DNAStringSet"))
260+
expect_is(access(rich_sparse, "refseq"), ("DNAStringSet"))
261+
expect_is(access(min_dense, "refseq"), ("DNAStringSet"))
262+
expect_is(access(min_sparse, "refseq"), ("DNAStringSet"))
261263

262264
# otu_table
263-
expect_that(access(rich_dense, "otu_table"), is_a("otu_table"))
264-
expect_that(access(rich_sparse, "otu_table"), is_a("otu_table"))
265-
expect_that(access(min_dense, "otu_table"), is_a("otu_table"))
266-
expect_that(access(min_sparse, "otu_table"), is_a("otu_table"))
265+
expect_is(access(rich_dense, "otu_table"), ("otu_table"))
266+
expect_is(access(rich_sparse, "otu_table"), ("otu_table"))
267+
expect_is(access(min_dense, "otu_table"), ("otu_table"))
268+
expect_is(access(min_sparse, "otu_table"), ("otu_table"))
267269

268270
# Compare values in the otu_table. For some reason the otu_tables are not identical
269271
# one position is plus-two, another is minus-two
270272
combrich <- c(access(rich_dense, "otu_table"), access(rich_sparse, "otu_table"))
271-
expect_that(sum(diff(combrich, length(access(rich_dense, "otu_table")))), is_equivalent_to(0))
272-
expect_that(max(diff(combrich, length(access(rich_dense, "otu_table")))), is_equivalent_to(2))
273-
expect_that(min(diff(combrich, length(access(rich_dense, "otu_table")))), is_equivalent_to(-2))
273+
expect_equivalent(sum(diff(combrich, length(access(rich_dense, "otu_table")))), (0))
274+
expect_equivalent(max(diff(combrich, length(access(rich_dense, "otu_table")))), (2))
275+
expect_equivalent(min(diff(combrich, length(access(rich_dense, "otu_table")))), (-2))
274276
combmin <- c(access(min_dense, "otu_table"), access(min_sparse, "otu_table"))
275-
expect_that(sum(diff(combmin, length(access(min_dense, "otu_table")))), is_equivalent_to(0))
276-
expect_that(max(diff(combmin, length(access(min_dense, "otu_table")))), is_equivalent_to(2))
277-
expect_that(min(diff(combmin, length(access(min_dense, "otu_table")))), is_equivalent_to(-2))
277+
expect_equivalent(sum(diff(combmin, length(access(min_dense, "otu_table")))), (0))
278+
expect_equivalent(max(diff(combmin, length(access(min_dense, "otu_table")))), (2))
279+
expect_equivalent(min(diff(combmin, length(access(min_dense, "otu_table")))), (-2))
278280

279-
expect_that(access(min_dense, "otu_table"), is_equivalent_to(access(rich_dense, "otu_table")))
280-
expect_that(access(min_sparse, "otu_table"), is_equivalent_to(access(rich_sparse, "otu_table")))
281+
expect_equivalent(access(min_dense, "otu_table"), (access(rich_dense, "otu_table")))
282+
expect_equivalent(access(min_sparse, "otu_table"), (access(rich_sparse, "otu_table")))
281283

282284
# Compare values in the sample_data
283-
expect_that(access(rich_dense, "sam_data"), is_equivalent_to(access(rich_sparse, "sam_data")))
285+
expect_equivalent(access(rich_dense, "sam_data"), (access(rich_sparse, "sam_data")))
284286

285287
# Compare values in the taxonomyTable
286-
expect_that(access(rich_dense, "tax_table"), is_equivalent_to(access(rich_sparse, "tax_table")))
288+
expect_equivalent(access(rich_dense, "tax_table"), (access(rich_sparse, "tax_table")))
287289

288290
})
289291

290292
test_that("the import_biom and import(\"biom\", ) syntax give same result", {
291293
x1 <- import_biom(rich_dense_biom, parseFunction=parse_taxonomy_greengenes)
292294
x2 <- import("biom", BIOMfilename=rich_dense_biom, parseFunction=parse_taxonomy_greengenes)
293-
expect_that(x1, is_equivalent_to(x2))
295+
expect_equivalent(x1, x2)
294296
})
295297
################################################################################
296298
# read_tree tests
297299
test_that("The read_tree function works as expected:", {
298300
GPNewick <- read_tree(system.file("extdata", "GP_tree_rand_short.newick.gz", package="phyloseq"))
299301
expect_that(GPNewick, is_a("phylo"))
300-
expect_that(ntaxa(GPNewick), equals(length(GPNewick$tip.label)))
301-
expect_that(ntaxa(GPNewick), equals(500))
302-
expect_that(GPNewick$Nnode, equals(499))
303-
expect_that(taxa_names(GPNewick), is_equivalent_to(GPNewick$tip.label))
302+
expect_equal(ntaxa(GPNewick), length(GPNewick$tip.label))
303+
expect_equal(ntaxa(GPNewick), 500L)
304+
expect_equal(GPNewick$Nnode, 499L)
305+
expect_equivalent(taxa_names(GPNewick), GPNewick$tip.label)
304306
# Now read a nexus tree...
305307
# Some error-handling expectations
306308
expect_that(read_tree("alskflsakjsfskfhas.akshfaksj"), gives_warning()) # file not exist

0 commit comments

Comments
 (0)