git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/Streamer@68644 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -16,12 +16,12 @@ Description: Large data files can be difficult to work with in R, |
16 | 16 |
License: Artistic-2.0 |
17 | 17 |
LazyLoad: yes |
18 | 18 |
Imports: methods, graph, parallel |
19 |
-Suggests: RUnit, Rsamtools (>= 1.5.53) |
|
19 |
+Suggests: BiocGenerics, RUnit, Rsamtools (>= 1.5.53) |
|
20 | 20 |
biocViews: Infrastructure, DataImport |
21 | 21 |
Collate: |
22 |
- generics.R OldClass.R Streamer.R |
|
23 |
- Producer.R BufferInterface.R Consumer.R Stream.R |
|
22 |
+ generics.R OldClass.R |
|
23 |
+ Streamer.R Producer.R Consumer.R Stream.R |
|
24 | 24 |
ConnectionProducer.R RawInput.R ValueInput.R Seq.R |
25 |
- Downsample.R Team.R Utility.R |
|
26 |
- runit_runner.R ParallelConnector.R |
|
27 |
- TConnector.R YConnector.R UserFunction-class.R zzz.R |
|
25 |
+ Downsample.R Team.R UserFunction-class.R Utility.R |
|
26 |
+ ParallelConnector.R TConnector.R YConnector.R |
|
27 |
+ zzz.R |
28 | 28 |
deleted file mode 100644 |
... | ... |
@@ -1,55 +0,0 @@ |
1 |
-.test <- function(dir, pattern = ".*_test\\.R$") |
|
2 |
-{ |
|
3 |
- .failure_details <- function(result) { |
|
4 |
- res <- result[[1L]] |
|
5 |
- if (res$nFail > 0 || res$nErr > 0) { |
|
6 |
- Filter(function(x) length(x) > 0, |
|
7 |
- lapply(res$sourceFileResults, |
|
8 |
- function(fileRes) { |
|
9 |
- names(Filter(function(x) x$kind != "success", |
|
10 |
- fileRes)) |
|
11 |
- })) |
|
12 |
- } else list() |
|
13 |
- } |
|
14 |
- |
|
15 |
- if (missing(dir)) { |
|
16 |
- dir <- system.file("unitTests", package="Streamer") |
|
17 |
- if (!nzchar(dir)) { |
|
18 |
- dir <- system.file("UnitTests", package="Streamer") |
|
19 |
- if (!nzchar(dir)) |
|
20 |
- stop("unable to find unit tests, no 'unitTests' dir") |
|
21 |
- } |
|
22 |
- } |
|
23 |
- |
|
24 |
- ## Run unit tests from the directory containing the test files. |
|
25 |
- ## This allows tests to refer to data files with relative paths |
|
26 |
- cwd <- getwd() |
|
27 |
- on.exit(setwd(cwd)) |
|
28 |
- setwd(dir) |
|
29 |
- |
|
30 |
- require("RUnit", quietly=TRUE) || stop("RUnit package not found") |
|
31 |
- RUnit_opts <- getOption("RUnit", list()) |
|
32 |
- RUnit_opts$verbose <- 0L |
|
33 |
- RUnit_opts$silent <- TRUE |
|
34 |
- RUnit_opts$verbose_fail_msg <- TRUE |
|
35 |
- options(RUnit = RUnit_opts) |
|
36 |
- suite <- defineTestSuite(name="Streamer RUnit Tests", dirs=getwd(), |
|
37 |
- testFileRegexp=pattern, |
|
38 |
- rngKind="default", |
|
39 |
- rngNormalKind="default") |
|
40 |
- result <- runTestSuite(suite) |
|
41 |
- cat("\n\n") |
|
42 |
- printTextProtocol(result, showDetails=FALSE) |
|
43 |
- if (length(details <- .failure_details(result)) >0) { |
|
44 |
- cat("\nTest files with failing tests\n") |
|
45 |
- for (i in seq_along(details)) { |
|
46 |
- cat("\n ", basename(names(details)[[i]]), "\n") |
|
47 |
- for (j in seq_along(details[[i]])) { |
|
48 |
- cat(" ", details[[i]][[j]], "\n") |
|
49 |
- } |
|
50 |
- } |
|
51 |
- cat("\n\n") |
|
52 |
- stop("unit tests failed for package Streamer") |
|
53 |
- } |
|
54 |
- result |
|
55 |
-} |