git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/Streamer@68630 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -23,20 +23,19 @@ BufferInt <- function(length=.Primitive("length"), append=.Primitive("c"), |
23 | 23 |
} |
24 | 24 |
|
25 | 25 |
|
26 |
-setGeneric("BufferInterface", function(object) standardGeneric("BufferInterface")) |
|
26 |
+setGeneric("BufferInterface", |
|
27 |
+ function(object) standardGeneric("BufferInterface")) |
|
27 | 28 |
|
28 | 29 |
setMethod("BufferInterface", signature = signature(object = "ANY"), |
29 |
- function(object) { |
|
30 |
- BufferInt() |
|
31 |
- }) |
|
30 |
+ function(object) BufferInt()) |
|
32 | 31 |
|
33 | 32 |
setMethod("BufferInterface", signature = signature(object = "data.frame"), |
34 |
- function(object) { |
|
35 |
- BufferInt(length=nrow, append=rbind, |
|
36 |
- subset=function(x, i){ |
|
37 |
- as.data.frame(sapply(x, .Primitive("["), i)) |
|
38 |
- }) |
|
39 |
- }) |
|
33 |
+ function(object) |
|
34 |
+{ |
|
35 |
+ BufferInt(length=nrow, append=rbind, subset=function(x, i) { |
|
36 |
+ as.data.frame(sapply(x, .Primitive("["), i)) |
|
37 |
+ }) |
|
38 |
+}) |
|
40 | 39 |
|
41 | 40 |
|
42 | 41 |
|
... | ... |
@@ -77,6 +77,15 @@ |
77 | 77 |
if (verbose) msg("Consumer$.add()") |
78 | 78 |
.self$.records <- .self$.bufferInt$append(.records, input) |
79 | 79 |
.self |
80 |
+ }, |
|
81 |
+ show = function() |
|
82 |
+ { |
|
83 |
+ callSuper() |
|
84 |
+ inp <- rev(inputs()) |
|
85 |
+ indx <- !inp %in%"TOut" |
|
86 |
+ inp <- paste(inp[indx], collapse=" => ") |
|
87 |
+ txt <- sprintf("stream: %s", inp) |
|
88 |
+ cat(strwrap(txt, exdent=2), sep="\n") |
|
80 | 89 |
}) |
81 | 90 |
|
82 | 91 |
setMethod(stream, "Consumer", |
... | ... |
@@ -84,14 +93,3 @@ setMethod(stream, "Consumer", |
84 | 93 |
{ |
85 | 94 |
.stream_set(x, ..., verbose=verbose) |
86 | 95 |
}) |
87 |
- |
|
88 |
-setMethod(show, "Consumer", |
|
89 |
- function(object) |
|
90 |
-{ |
|
91 |
- callNextMethod() |
|
92 |
- inp <- rev(object$inputs()) |
|
93 |
- indx = !inp %in%"TOut" |
|
94 |
- inp <- paste(inp[indx], collapse=" => ") |
|
95 |
- txt <- sprintf("stream: %s", inp) |
|
96 |
- cat(strwrap(txt, exdent=2), sep="\n") |
|
97 |
-}) |
... | ... |
@@ -45,21 +45,18 @@ |
45 | 45 |
"report status of 'Downsample'" |
46 | 46 |
if (verbose) msg("Downsample$status()") |
47 | 47 |
c(list(probability=probability), callSuper()) |
48 |
+ }, |
|
49 |
+ show = function() |
|
50 |
+ { |
|
51 |
+ callSuper() |
|
52 |
+ txt <- sprintf("probability: %.2f; yieldSize: %d", |
|
53 |
+ probability, yieldSize) |
|
54 |
+ cat(txt, "\n") |
|
48 | 55 |
})) |
49 | 56 |
|
50 | 57 |
Downsample <- |
51 |
- function(probability = 0.1, ..., yieldSize = 1e6, |
|
52 |
- verbose=FALSE) |
|
58 |
+ function(probability = 0.1, ..., yieldSize = 1e6, verbose=FALSE) |
|
53 | 59 |
{ |
54 | 60 |
.Downsample$new(probability=probability, ..., |
55 | 61 |
yieldSize=yieldSize, verbose=verbose) |
56 | 62 |
} |
57 |
- |
|
58 |
-setMethod(show, "Downsample", |
|
59 |
- function(object) |
|
60 |
-{ |
|
61 |
- callNextMethod() |
|
62 |
- txt <- sprintf("probability: %.2f; yieldSize: %d", |
|
63 |
- object$probability, object$yieldSize) |
|
64 |
- cat(txt, "\n") |
|
65 |
-}) |
... | ... |
@@ -111,6 +111,15 @@ rawParserFactory <- |
111 | 111 |
.recordLength = length(.records), |
112 | 112 |
.bufferLength = length(.buffer)), |
113 | 113 |
callSuper()) |
114 |
+ }, |
|
115 |
+ show = function() |
|
116 |
+ { |
|
117 |
+ callSuper() |
|
118 |
+ cat("file:", basename(summary(con)$description), "\n") |
|
119 |
+ s <- status() |
|
120 |
+ elts <- paste(names(s), s, sep="=", collapse=" ") |
|
121 |
+ txt <- sprintf("status: %s", elts) |
|
122 |
+ cat(strwrap(txt, exdent=2), sep="\n") |
|
114 | 123 |
}) |
115 | 124 |
|
116 | 125 |
|
... | ... |
@@ -126,14 +135,3 @@ RawInput <- |
126 | 135 |
reader=reader, parser=parser, ..., |
127 | 136 |
yieldSize=yieldSize, verbose=verbose) |
128 | 137 |
} |
129 |
- |
|
130 |
-setMethod(show, "RawInput", |
|
131 |
- function(object) |
|
132 |
-{ |
|
133 |
- callNextMethod() |
|
134 |
- cat("file:", basename(summary(object$con)$description), "\n") |
|
135 |
- s <- object$status() |
|
136 |
- elts <- paste(names(s), s, sep="=", collapse=" ") |
|
137 |
- txt <- sprintf("status: %s", elts) |
|
138 |
- cat(strwrap(txt, exdent=2), sep="\n") |
|
139 |
-}) |
... | ... |
@@ -35,6 +35,10 @@ |
35 | 35 |
"report status of Steamer" |
36 | 36 |
if (verbose) msg("Streamer$status()") |
37 | 37 |
list(yieldSize=yieldSize, verbose=verbose, inUse=inUse) |
38 |
+ }, |
|
39 |
+ show = function() |
|
40 |
+ { |
|
41 |
+ cat("class:", class(.self), "\n") |
|
38 | 42 |
}) |
39 | 43 |
|
40 | 44 |
setMethod(reset, "Streamer", function(x, ...) x$reset()) |
... | ... |
@@ -42,9 +46,3 @@ setMethod(reset, "Streamer", function(x, ...) x$reset()) |
42 | 46 |
setMethod(yield, "Streamer", function(x, ...) x$yield()) |
43 | 47 |
|
44 | 48 |
setMethod(status,"Streamer", function(x, ...) x$status()) |
45 |
- |
|
46 |
-setMethod(show, "Streamer", |
|
47 |
- function(object) |
|
48 |
-{ |
|
49 |
- cat("class:", class(object), "\n") |
|
50 |
-}) |
... | ... |
@@ -21,18 +21,17 @@ |
21 | 21 |
k$yield() |
22 | 22 |
}) |
23 | 23 |
do.call(.self$.fun, args) |
24 |
+ }, |
|
25 |
+ show = function() |
|
26 |
+ { |
|
27 |
+ callSuper() |
|
28 |
+ upstream <- paste(lapply(.upstream, "class"), collapse = " ,") |
|
29 |
+ upstream[!nzchar(upstream)] <- "uninitialized field" |
|
30 |
+ txt <- sprintf("upstream: %s", upstream) |
|
31 |
+ cat(strwrap(txt, exdent=2), sep="\n") |
|
24 | 32 |
}) |
25 | 33 |
|
26 | 34 |
YConnector <- function(fun, ..., yieldSize =1e6, verbose = FALSE) |
27 | 35 |
{ |
28 | 36 |
.YConnector$new(fun=fun, ..., yieldSize=yieldSize, verbose=verbose) |
29 | 37 |
} |
30 |
- |
|
31 |
-setMethod(show, "YConnector", |
|
32 |
- function(object) |
|
33 |
-{ |
|
34 |
- cat("class:", class(object), "\n") |
|
35 |
- upstream <- paste(lapply(object$.upstream, "class"), collapse = " ,") |
|
36 |
- txt <- sprintf("upstream: %s", if(upstream=="") "uninitialized field" else upstream) |
|
37 |
- cat(strwrap(txt, exdent=2), sep="\n") |
|
38 |
-}) |