Browse code

remove 'yieldSize' from most functions to simplify interface

- additional misc. tidy


git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/Streamer@68656 bc3139a8-67e5-0310-9ffc-ced21a209358

Martin Morgan authored on 21/08/2012 00:42:59
Showing 40 changed files

... ...
@@ -1,7 +1,7 @@
1 1
 Package: Streamer
2 2
 Type: Package
3 3
 Title: Enabling stream processing of large files
4
-Version: 1.3.2
4
+Version: 1.3.3
5 5
 Date: 2010-10-13
6 6
 Author: Martin Morgan, Nishant Gopalakrishnan
7 7
 Maintainer: Martin Morgan <mtmorgan@fhcrc.org>
8 8
deleted file mode 100644
... ...
@@ -1,41 +0,0 @@
1
-.BufferInt <- setRefClass("BufferInt",
2
-    fields=list(
3
-        length="function",
4
-        append="function",
5
-        subset="function"))
6
-
7
-.BufferInt$methods(
8
-    initialize=function(length=.Primitive("length"),
9
-                        append=.Primitive("c"), 
10
-                        subset=.Primitive("["))
11
-    {
12
-        "initialize 'BufferInt'"
13
-        .self$length <- length
14
-        .self$append <- append
15
-        .self$subset <- subset
16
-        .self
17
-    })
18
-
19
-BufferInt <- function(length=.Primitive("length"), append=.Primitive("c"),
20
-                     subset=.Primitive("["))
21
-{
22
-    .BufferInt$new(length=length, append=append, subset=subset)
23
-}
24
-
25
-
26
-setGeneric("BufferInterface",
27
-    function(object) standardGeneric("BufferInterface"))
28
-
29
-setMethod("BufferInterface", signature = signature(object = "ANY"),
30
-    function(object) BufferInt())
31
-
32
-setMethod("BufferInterface", signature = signature(object = "data.frame"),
33
-    function(object)
34
-{
35
-    BufferInt(length=nrow, append=rbind, subset=function(x, i) { 
36
-        as.data.frame(sapply(x, .Primitive("["), i))
37
-    })
38
-})
39
-
40
-
41
-
... ...
@@ -10,12 +10,9 @@
10 10
         parser = rawParserFactory(), ...)
11 11
     {
12 12
         "initialize ConnectionProducer"
13
-        callSuper(...)
14
-        if (verbose) msg(".ConnectionProducer$initialize")
13
+        callSuper(..., reader=reader, parser=parser)
15 14
         if (!missing(con))
16 15
             .self$con <- con
17
-        .self$reader <- reader
18
-        .self$parser <- parser
19 16
         .self
20 17
     },
21 18
     reset = function()
... ...
@@ -1,15 +1,11 @@
1 1
 .Consumer <- setRefClass("Consumer",
2 2
     contains="Streamer",
3
-    fields = list(
4
-        inputPipe="ANY", 
5
-        .records="ANY",
6
-        .bufferInt="BufferInt",
7
-        .bufFun="logical"),     
3
+    fields = list(inputPipe = "ANY"),
8 4
     methods = list(
9 5
     initialize = function(..., inputPipe)
10 6
     {
11 7
         "initialize 'Consumer'"
12
-        callSuper(..., .bufferInt=BufferInt(), .bufFun=FALSE)
8
+        callSuper(...)
13 9
         if (verbose) msg("Consumer$initialize")
14 10
         if (!missing(inputPipe))
15 11
             .self$inputPipe <- inputPipe
... ...
@@ -40,43 +36,13 @@
40 36
     {    
41 37
         "delegate yield() to inputPipe"
42 38
         if (verbose) msg("Consumer$yield()")
43
-        .fill()
44
-        idx <- seq_len(min(yieldSize, .self$.bufferInt$length(.records)))
45
-        records <- .self$.bufferInt$subset(.records,idx)
46
-        .self$.records <- .self$.bufferInt$subset(.records,-idx)
47
-        records
39
+        inputPipe$yield()
48 40
     },
49 41
     status = function() 
50 42
     {
51 43
         "report status of 'Consumer'"
52 44
         if (verbose) msg("Consumer$status()")
53
-        c(recLength=.self$.bufferInt$length(.records), inputs=inputs(),
54
-          callSuper())
55
-    },
56
-    .fill = function() {
57
-        "fill stream with yieldSize records, if available"
58
-        if(verbose) msg("Consumer$.fill()")
59
-        if(!.self$.bufFun)
60
-        {
61
-            input <- inputPipe$yield()
62
-            .self$.records <- new(class(input))
63
-            .self$.bufferInt <- BufferInterface(input)
64
-            .add(input)
65
-            .self$.bufFun <- TRUE
66
-        }
67
-        while ( .self$.bufferInt$length(.records) < yieldSize &&
68
-               0 != length(input<- inputPipe$yield())) 
69
-        {
70
-            .add(input)
71
-        }
72
-        .self
73
-    },
74
-    .add = function(input)
75
-    { 
76
-        ".add (incomplete) 'input'"
77
-        if (verbose) msg("Consumer$.add()")
78
-        .self$.records <- .self$.bufferInt$append(.records, input)
79
-        .self    
45
+        c(inputs=inputs(), callSuper())
80 46
     },
81 47
     show = function() 
82 48
     {
... ...
@@ -2,16 +2,13 @@
2 2
     contains = "Consumer",
3 3
     fields = list(
4 4
       probability = "numeric",
5
+      sampledSize = "integer",
5 6
       .buffer = "ANY"),
6 7
     methods = list(
7
-    initialize = function(..., probability)
8
+    initialize = function(...)
8 9
     {
9 10
         "initialize Downsample"
10
-        callSuper(...)
11
-        if (verbose) msg("Downsample$initialize")
12
-        .self$probability <- probability
13
-        .self$.buffer <- list()
14
-        .self
11
+        callSuper(..., .buffer=list())
15 12
     },
16 13
     .sample = function(x)
17 14
     {
... ...
@@ -22,12 +19,12 @@
22 19
     },
23 20
     yield = function()
24 21
     {
25
-        "sample records with 'probability' until 'yieldSize' retrieved"
22
+        "sample records with 'probability' until 'sampledSize' retrieved"
26 23
         if (verbose) msg("Downsample$yield()")
27
-        while (length(.buffer) < yieldSize &&
24
+        while (length(.buffer) < sampledSize &&
28 25
                0L != length(res <- callSuper()))
29 26
             .self$.buffer <- c(.buffer, .sample(res))
30
-        idx <- seq_len(min(length(.buffer), yieldSize))
27
+        idx <- seq_len(min(length(.buffer), sampledSize))
31 28
         result <- .buffer[idx]
32 29
         .self$.buffer <- .buffer[-idx]
33 30
         result
... ...
@@ -49,14 +46,15 @@
49 46
     show = function()
50 47
     {
51 48
         callSuper()
52
-        txt <- sprintf("probability: %.2f; yieldSize: %d",
53
-                       probability, yieldSize)
49
+        txt <- sprintf("probability: %.2f; sampledSize: %d",
50
+                       probability, sampledSize)
54 51
         cat(txt, "\n")
55 52
     }))
56 53
 
57 54
 Downsample <-
58
-    function(probability = 0.1, ..., yieldSize = 1e6, verbose=FALSE)
55
+    function(probability = 0.1, sampledSize = 1e6, ...)
59 56
 {
60
-    .Downsample$new(probability=probability, ...,
61
-                    yieldSize=yieldSize, verbose=verbose)
57
+    sampledSize <- as.integer(sampledSize)
58
+    .Downsample$new(probability=probability, sampledSize=sampledSize,
59
+                    ...)
62 60
 }
... ...
@@ -3,13 +3,6 @@
3 3
                 fields=list(.upstream="ANY"))
4 4
 
5 5
 .ParallelConnector$methods(
6
-    initialize = function(...)
7
-    {
8
-        "Initialize the fields of the ParallelConnector class"
9
-        callSuper(...)
10
-        if (verbose) msg(".ParallelConnector$initialize()")   
11
-        .self
12
-    },
13 6
     yield = function() 
14 7
    {  
15 8
         "Read data from childProcess"
... ...
@@ -27,8 +20,6 @@
27 20
         }
28 21
     })
29 22
 
30
-ParallelConnector <- function(..., yieldSize=1e6, verbose = FALSE) 
31
-{
32
-    .ParallelConnector$new(..., yieldSize=yieldSize, verbose = verbose)
33
-}
23
+ParallelConnector <- function(...)
24
+    .ParallelConnector$new(...)
34 25
 
... ...
@@ -36,18 +36,15 @@ rawParserFactory <-
36 36
 .RawInput <- setRefClass("RawInput",
37 37
     contains="ConnectionProducer",
38 38
     fields = list(
39
-        .buffer = "raw", .records = "list", .parsedRecords = "integer"
39
+      yieldSize = "integer",
40
+      .buffer = "raw", .records = "list", .parsedRecords = "integer"
40 41
     ))
41 42
 
42 43
 .RawInput$methods(
43 44
     initialize = function(...)
44 45
     {
45 46
         "initialize RawInput"
46
-        callSuper(...)
47
-        if (verbose) msg(".RawInput$initialize()")
48
-        .self$.records <- list()
49
-        .self$.parsedRecords <- 0L
50
-        .self
47
+        callSuper(..., .records=list(), .parsedRecords=0L)
51 48
     },
52 49
     reset = function()
53 50
     {
... ...
@@ -124,14 +121,12 @@ rawParserFactory <-
124 121
     
125 122
 
126 123
 RawInput <-
127
-    function(con, yieldSize = 1e6, 
128
-             reader=rawReaderFactory(),
129
-             parser=rawParserFactory(),
130
-             ..., verbose=FALSE)
124
+    function(con, yieldSize = 1e6, reader=rawReaderFactory(),
125
+             parser=rawParserFactory(), ...)
131 126
 {
132 127
     if (!is(con, "connection"))
133 128
         con <- file(con, "rb")
134
-    .RawInput$new(con=con, 
135
-         reader=reader, parser=parser, ...,
136
-         yieldSize=yieldSize, verbose=verbose)
129
+    yieldSize <- as.integer(yieldSize)
130
+    .RawInput$new(con=con, yieldSize=yieldSize, reader=reader,
131
+                  parser=parser, ...)
137 132
 }
... ...
@@ -1,19 +1,19 @@
1 1
 .Seq <- setRefClass("Seq",
2 2
     fields = list(
3
-      from="numeric", to="numeric", by="numeric"),
3
+      from="numeric", to="numeric", by="numeric", length.out="integer"),
4 4
     contains="Producer",
5 5
     methods = list(
6 6
       yield = function() {
7 7
           if ((from - to) * by > 0)
8 8
               return(integer())
9
-          s <- seq(from, by=by, length.out=yieldSize + 1L)
9
+          s <- seq(from, by=by, length.out=length.out + 1L)
10 10
           .self$from <- s[length(s)]
11 11
           s <- s[-length(s)]
12 12
           s[s <= to]
13 13
       },
14 14
       show = function() {
15 15
           cat("from:", from, "\nto:", to, "\nby:", by,
16
-              "\nlength.out:", yieldSize, "\n")
16
+              "\nlength.out:", length.out, "\n")
17 17
       }))
18 18
 
19 19
 Seq <-
... ...
@@ -31,5 +31,5 @@ Seq <-
31 31
     if (from > to)
32 32
         stop("'from' must be less than or equal to 'to'")
33 33
     length.out <- as.integer(length.out)
34
-    .Seq$new(from=from, to=to, by=by, yieldSize=length.out, ...)
34
+    .Seq$new(from=from, to=to, by=by, length.out=length.out, ...)
35 35
 }
... ...
@@ -31,7 +31,7 @@
31 31
         }
32 32
         x
33 33
     }, list(x, ...), right=TRUE)
34
-    .Stream$new(inputPipe=inputPipe, yieldSize=x$yieldSize, verbose=verbose)
34
+    .Stream$new(inputPipe=inputPipe, verbose=verbose)
35 35
 }
36 36
 
37 37
 setMethod(length, "Stream",
... ...
@@ -1,16 +1,13 @@
1 1
 .Streamer <- setRefClass("Streamer",
2 2
     fields = list(
3
-      yieldSize="integer",
4 3
       verbose="logical",
5 4
       inUse="logical"))
6 5
 
7 6
 .Streamer$methods(
8
-    initialize = function(..., yieldSize=1e6, verbose=FALSE)
7
+    initialize = function(..., verbose=FALSE)
9 8
     {
10 9
         "initialize 'Streamer'"
11
-        if (verbose) msg("Streamer$initialize")
12
-        invisible(callSuper(..., yieldSize=as.integer(yieldSize),
13
-                            verbose=verbose, inUse=FALSE))
10
+        invisible(callSuper(..., verbose=verbose, inUse=FALSE))
14 11
     },
15 12
     msg = function(fmt, ...)
16 13
     {
... ...
@@ -34,7 +31,7 @@
34 31
     {
35 32
         "report status of Steamer"
36 33
         if (verbose) msg("Streamer$status()")
37
-        list(yieldSize=yieldSize, verbose=verbose, inUse=inUse)
34
+        list(verbose=verbose, inUse=inUse)
38 35
     },
39 36
     show = function()
40 37
     {
... ...
@@ -1,42 +1,28 @@
1
+## TOut
2
+
1 3
 .TOut <- setRefClass("TOut", 
2 4
     contains="Consumer",
3
-    fields=list(
4
-        .start="numeric"
5
-    ))
5
+    fields=list(.start = "numeric"))
6 6
 
7 7
 .TOut$methods(
8 8
     initialize =function(...) 
9 9
     {  
10 10
        "initialize TOut"
11
-        callSuper(...)
12
-        if (verbose) msg(".TOut$initialize()")
13
-        .self$.start <- 1L
14
-        .self
11
+        callSuper(..., .start = 1L)
15 12
     },
16 13
     yield = function() 
17
-    {  "Calls yield on the inputPipe"
18
-       if (verbose) msg(".TOut$yield()")
19
-       while(length(.self$inputPipe$.records) - .self$.start < yieldSize &&
20
-              0 != length(input <- .self$inputPipe$.fill()) )
21
-         .self$inputPipe$.add(input)
22
-       if( .self$.start + yieldSize  <= length(.self$inputPipe$.records))
23
-            width <-  .self$.start + yieldSize -1
24
-       else
25
-            width <- length(.self$inputPipe$.records) - .self$.start +1
26
-       if(width>0)
27
-            idx <- seq(.self$.start, .self$.start + width -1)
28
-       else  idx <- 0
29
-       .self$.start <- .self$.start + width
30
-       dat <- .self$inputPipe$.records[idx]
31
-       .self$inputPipe$.dump()
32
-       dat
14
+    {
15
+        "Calls yield on the inputPipe"
16
+        if (verbose) msg(".TOut$yield()")
17
+        inputPipe$.add(inputPipe$yield())
18
+        dat <- inputPipe$.records
19
+        inputPipe$.dump()
20
+        dat
33 21
     })
34 22
 
35
-TOut <- function( ..., yieldSize=1e6, verbose=FALSE) 
36
-{
37
-    .TOut$new(..., yieldSize=yieldSize, verbose=verbose)
23
+TOut <- function(...) .TOut$new(...)
38 24
 
39
-}
25
+## TConnector
40 26
 
41 27
 .TConnector <- setRefClass("TConnector", 
42 28
     contains = "Consumer",
... ...
@@ -49,16 +35,8 @@ TOut <- function( ..., yieldSize=1e6, verbose=FALSE)
49 35
     initialize = function(...) 
50 36
     {   
51 37
         "initialize TConnector"
52
-        callSuper(...)
53
-        if (verbose) msg("TConnector$initialize()")
54
-        .self$.tOuts <- list()
55
-        .self
38
+        callSuper(..., .tOuts = list())
56 39
     },   
57
-    .fill = function() 
58
-    {   "Fills the stream with yieldSize records"
59
-        if (verbose) msg("TConnector$.fill")
60
-        .self$inputPipe$yield()
61
-    },
62 40
     .add = function(input)
63 41
     { 
64 42
         ".add (incomplete) 'input'"
... ...
@@ -70,25 +48,15 @@ TOut <- function( ..., yieldSize=1e6, verbose=FALSE)
70 48
     {    
71 49
         "Clear .records that are used"
72 50
         if (verbose) msg("TConnector$.dump()")
73
-        mn <- min(sapply(.self$.tOuts, function(x) {
74
-                    x$.start
75
-               }))
76
-        if(mn !=1) {
77
-            len <- length(.self$.tOuts)
78
-            for(i in 1:len) 
79
-            {   
80
-              .self$.tOuts[[i]]$.start <-  .self$.tOuts[[i]]$.start - mn +1
81
-
82
-            }
83
-            .self$.records[seq_len(mn-1)] <- NULL
51
+        mn <- min(sapply(.tOuts, function(x) x$.start))
52
+        if (mn != 1L) {
53
+            for(i in seq_along(.tOuts))
54
+                .self$.tOuts[[i]]$.start <- .tOuts[[i]]$.start - mn +1L
55
+            .self$.records[seq_len(mn - 1L)] <- NULL
84 56
         }
85 57
         .self
86 58
    })
87 59
 
88
-                   
89
-
90
-TConnector <- function(..., yieldSize=1e6, verbose=FALSE) {
91
-    .TConnector$new(..., yieldSize=yieldSize, verbose=verbose)
92
-}
60
+TConnector <- function(...) .TConnector$new(...)
93 61
 
94 62
 
... ...
@@ -1,28 +1,23 @@
1 1
 .UserFunction <- 
2 2
     setRefClass("UserFunction",
3 3
         contains = "Consumer",
4
-        fields = list(
5
-            .fun= "function")) 
4
+        fields = list(FUN = "function")) 
6 5
  
7 6
 .UserFunction$methods(
8
-    initialize = function(..., fun)
7
+    initialize = function(..., FUN)
9 8
     {
10 9
         "initialize myCons"
11
-        callSuper(...)
12
-        if (.self$verbose)
13
-            .self$msg("myCons$initialize")
14
-        .self$.fun <- fun
15
-        .self
10
+        callSuper(..., FUN=FUN)
16 11
     },
17 12
     yield = function()
18 13
     {
19 14
         "yield data from UserFunction"
20 15
         if (verbose) msg("UserFunction$yield")
21
-        .self$.fun(callSuper())
16
+        FUN(callSuper())
22 17
     })
23 18
 
24
-UserFunction <- function(fun, ..., yieldSize = 1e6, verbose = FALSE)
19
+UserFunction <- function(FUN, ...)
25 20
 {
26
-    .UserFunction$new(fun=fun,..., yieldSize=yieldSize, verbose=verbose)
21
+    .UserFunction$new(FUN=FUN,...)
27 22
 }
28 23
 
... ...
@@ -15,11 +15,8 @@
15 15
          sapply(callSuper(), rawToChar)
16 16
     }))
17 17
 
18
-RawToChar <-
19
-    function(yieldSize=1e6, verbose=FALSE)
20
-{
21
-    .RawToChar$new(yieldSize=yieldSize, verbose=verbose)
22
-}
18
+RawToChar <- function(...)
19
+    .RawToChar$new(...)
23 20
 
24 21
 ## Rev
25 22
 
... ...
@@ -32,62 +29,64 @@ RawToChar <-
32 29
         sapply(callSuper(), rev)
33 30
     }))
34 31
 
35
-Rev <-
36
-    function(yieldSize=1e6,verbose=FALSE)
37
-{
38
-    .Rev$new(yieldSize=yieldSize, verbose=verbose)
39
-}
32
+Rev <- function(...)
33
+    .Rev$new(...)
40 34
 
35
+## connect
41 36
 
42
-connect <- function(blocks, df) 
37
+connect <-
38
+    function(blocks, df) 
43 39
 {
44
-    use <- sapply(blocks, function(x) {
45
-        all(x$inUse)
46
-    })
40
+    inUse <- sapply(blocks, function(x) all(x$inUse))
47 41
     cls <- sapply(blocks, class)
48
-    if(any(use)) {
49
-        msg <- sprintf("%s : already in use in another stream",
50
-                       paste(cls[which(use)], sep = " ", collapse = ", "))
42
+    if (any(inUse)) {
43
+        msg <- sprintf("%s: already in use in another stream",
44
+                       paste(cls[which(inUse)], collapse = ", "))
51 45
         stop(msg)
52 46
     }
47
+
53 48
     len <- length(blocks)
54 49
     n <- nrow(df)
55
-    df <- cbind(df, "weight" =rep(1L, n))
56
-    g <- graphBAM(df,edgemode="directed")
57
-    outDeg <- degree(g)$outDegree
58
-    nms <- names(outDeg[outDeg==0])
59
-    for(i in 1:n) 
50
+    df$weight <- 1L
51
+    
52
+    for (i in seq_len(n)) 
60 53
     {
61
-        left <- blocks[[as.character(df$from[i])]]
62
-        right <- blocks[[as.character(df$to[i])]]
63
-        if(is(right, "YConnector")) {
64
-            right$.upstream[[as.character(df$from[i])]] <- left
65
-        }
66
-        if(is(left, "TConnector")) 
54
+        fromi <- as.character(df$from[i])
55
+        toi <- as.character(df$to[i])
56
+        left <- blocks[[fromi]]
57
+        right <- blocks[[toi]]
58
+        if (is(right, "YConnector"))
59
+            right$.upstream[[fromi]] <- left
60
+
61
+        if (is(left, "TConnector")) 
67 62
         {
68 63
             orig <- left$.tOuts 
69
-            temp <- TOut(yieldSize = left$yieldSize)
64
+            temp <- TOut()
70 65
             temp$inputPipe <- left
71 66
             right$inputPipe <- temp
72 67
             left$.tOuts <- c(left$.tOuts, temp)
73 68
         } else {
74 69
             right$inputPipe <- left
75
-
76 70
         }
77
-        if ( is(right, "ParallelConnector")) {
71
+        
72
+        if (is(right, "ParallelConnector")) {
78 73
             right$.upstream <- mcparallel(quote({
79 74
                 while(TRUE) {
80 75
                     prime <- yield(left)
81
-                    sendMaster(prime)
82
-        }}))
76
+                    parallel:::sendMaster(prime)
77
+                }}))
83 78
 
84 79
         }
85 80
     }
81
+    
82
+    nms <- local({
83
+        g <- graphBAM(df, edgemode="directed")
84
+        outDeg <- degree(g)$outDegree
85
+        names(outDeg[outDeg==0])
86
+    })
86 87
     s <- lapply(blocks[nms], stream)
87
-    for(i in 1:len) 
88
-    {
88
+    for (i in seq_len(len))
89 89
         blocks[[i]]$inUse <- TRUE
90
-    }
91 90
     s
92 91
 }
93 92
 
... ...
@@ -41,21 +41,15 @@ scanParserFactory <- concatenationParserFactory
41 41
 .ReadLinesInput <- setRefClass("ReadLinesInput",
42 42
     contains = "ConnectionProducer",
43 43
     fields = list(
44
+      yieldSize = "integer",
44 45
       .records = "character"))
45 46
 
46 47
 .ReadLinesInput$methods(
47
-    initialize = function(...)
48
-    {
49
-        "initialize 'ReadLinesInput'"
50
-        callSuper(...)
51
-        if (verbose) msg("ReadLinesInput$initialize()")
52
-        .self
53
-    },
54 48
     reset = function()
55 49
     {
56 50
         "reset ReadLinesInput"
57
-        callSuper()
58 51
         if (verbose) msg("ReadLinesInput$reset()")
52
+        callSuper()
59 53
         .self$.records <- character()
60 54
         .self$.parsedRecords <- 0L
61 55
         .self
... ...
@@ -93,15 +87,15 @@ scanParserFactory <- concatenationParserFactory
93 87
 
94 88
 ReadLinesInput <- 
95 89
     function(con, reader=readLinesReaderFactory(),
96
-             parser=readLinesParserFactory(), ...,
97
-             yieldSize=1e6, verbose=FALSE)
98
-    {
99
-        if (!is(con, "connection"))
100
-            con <- file(con, "r")
101
-        .ReadLinesInput$new(con=con, 
102
-                      reader=reader, parser=parser, ...,
103
-                      yieldSize=yieldSize, verbose=verbose)
104
-    }
90
+             parser=readLinesParserFactory(), 
91
+             yieldSize=1e6, ...)
92
+{
93
+    if (!is(con, "connection"))
94
+        con <- file(con, "r")
95
+    yieldSize <- as.integer(yieldSize)
96
+    .ReadLinesInput$new(con=con, reader=reader, parser=parser,
97
+                        yieldSize=yieldSize, ...)
98
+}
105 99
 
106 100
 
107 101
 
... ...
@@ -5,14 +5,11 @@
5 5
     
6 6
 .YConnector$methods(
7 7
     initialize = function(..., fun) 
8
-    {   "initialize YConnector"
9
-        callSuper(...)
10
-        if(verbose) msg(".YConnector$initialize")
11
-        .self$.upstream <- list()
8
+    {
9
+        "initialize YConnector"
12 10
         if(missing(fun))
13
-            .self$.fun <- function(){}
14
-        else .self$.fun <- fun
15
-        .self
11
+            fun <- function(...) as.list(...)
12
+        callSuper(..., .upstream=list(), .fun=fun)
16 13
     },
17 14
     yield = function() 
18 15
     {
... ...
@@ -25,13 +22,11 @@
25 22
     show = function()
26 23
     {
27 24
         callSuper()
28
-        upstream <- paste(lapply(.upstream, "class"), collapse = " ,")
25
+        upstream <- paste(sapply(.upstream, "class"), collapse = " ,")
29 26
         upstream[!nzchar(upstream)] <- "uninitialized field"
30 27
         txt <- sprintf("upstream: %s", upstream)
31 28
         cat(strwrap(txt, exdent=2), sep="\n")
32 29
     })
33 30
 
34
-YConnector <- function(fun, ...,  yieldSize =1e6, verbose = FALSE) 
35
-{
36
-    .YConnector$new(fun=fun, ..., yieldSize=yieldSize, verbose=verbose)
37
-}
31
+YConnector <- function(fun, ...)
32
+    .YConnector$new(fun=fun, ...)
... ...
@@ -7,9 +7,3 @@ setGeneric("reset", function(x, ...) standardGeneric("reset"))
7 7
 setGeneric("yield", function(x, ...) standardGeneric("yield"))
8 8
 
9 9
 setGeneric("status", function(x, ...) standardGeneric("status"))
10
-
11
-## Generic Functions for NetCDFFile class 
12
-
13
-setGeneric("precision", function(x, ...) standardGeneric("precision"))
14
-
15
-setGeneric("dimensions", function(x, ...) standardGeneric("dimensions"))
16 10
Binary files a/inst/doc/Streamer.Rnw and b/inst/doc/Streamer.Rnw differ
17 11
similarity index 84%
18 12
rename from inst/unitTests/test_BinaryInput.R
19 13
rename to inst/unitTests/test_RawInput.R
... ...
@@ -1,11 +1,7 @@
1
-test_recordReader <- function()
2
-{
3
-}
4
-
5
-test_binary_parse_count_records <- function()
1
+test_raw_parse_count_records <- function()
6 2
 {
7 3
     f <- function(...)
8
-        .Call(Streamer:::.binary_parse_count_records, ...)
4
+        .Call(Streamer:::.raw_parse_count_records, ...)
9 5
 
10 6
     sep <- charToRaw("\n")
11 7
 
... ...
@@ -32,9 +28,9 @@ test_binary_parse_count_records <- function()
32 28
     checkIdentical(1L, f(charToRaw("foo\nfoo\n"), sep))
33 29
 }
34 30
 
35
-test_binary_parse <- function()
31
+test_raw_parse <- function()
36 32
 {
37
-    f <- function(...) .Call(Streamer:::.binary_parse, ...)
33
+    f <- function(...) .Call(Streamer:::.raw_parse, ...)
38 34
 
39 35
     sep <- charToRaw("\n")
40 36
     trim <- sep
... ...
@@ -75,25 +71,25 @@ test_binary_parse <- function()
75 71
                    f(charToRaw("@foo\n@bar\n@"), sep, trim))
76 72
 }
77 73
 
78
-test_binaryParserFactory <- function()
74
+test_rawParserFactory <- function()
79 75
 {
80
-    checkException(binaryParserFactory("\n"),
76
+    checkException(rawParserFactory("\n"),
81 77
                    "'separator' must be 'raw()'", TRUE)
82
-    checkException(binaryParserFactory(trim="\n"),
78
+    checkException(rawParserFactory(trim="\n"),
83 79
                    "'trim' must be 'raw()'", TRUE)
84
-    checkException(binaryParserFactory(charToRaw("\n@"),
80
+    checkException(rawParserFactory(charToRaw("\n@"),
85 81
                                        charToRaw("@")),
86 82
                    "'trim' must equal separator[seq_along(trim)]",
87 83
                    TRUE)
88
-    checkException(binaryParserFactory(charToRaw("\n@"),
84
+    checkException(rawParserFactory(charToRaw("\n@"),
89 85
                                        charToRaw("\n@x")),
90 86
                    "'length(separator)' must be >= length(trim)",
91 87
                    TRUE)
92 88
 }
93 89
 
94
-test_binaryParser <- function()
90
+test_rawParser <- function()
95 91
 {
96
-    p <- binaryParserFactory()
92
+    p <- rawParserFactory()
97 93
     checkIdentical(list(), p(raw(), raw()))
98 94
 
99 95
     foo <- charToRaw("foo")
... ...
@@ -108,12 +104,12 @@ test_binaryParser <- function()
108 104
     checkIdentical(list(foo, foo), p(foo_n, foo))
109 105
 }
110 106
 
111
-test_BinaryInput <- function()
107
+test_RawInput <- function()
112 108
 {
113 109
     fl <- system.file("extdata", "s_1_sequence.txt", package="Streamer")
114 110
 
115 111
     ## default yield
116
-    s <- BinaryInput(fl)
112
+    s <- RawInput(fl)
117 113
     y <- yield(s)
118 114
     checkIdentical(1024L,length(y))
119 115
     checkIdentical(list(), yield(s))    # no more records
... ...
@@ -126,8 +122,8 @@ test_BinaryInput <- function()
126 122
     checkIdentical(list(), yield(s))
127 123
 
128 124
     ## yield w/ sep & trim arguments -- fastq records
129
-    parser <- binaryParserFactory(charToRaw("\n@"), charToRaw("\n"))
130
-    s <- BinaryInput(fl, parser=parser)
125
+    parser <- rawParserFactory(charToRaw("\n@"), charToRaw("\n"))
126
+    s <- RawInput(fl, parser=parser)
131 127
     y2 <- yield(s)
132 128
     checkIdentical(256L, length(y2))
133 129
     checkIdentical(sapply(y1, rawToChar),
... ...
@@ -1,9 +1,9 @@
1
-test_RevStream <-
1
+test_Rev <-
2 2
     function()
3 3
 {
4
-    checkTrue(validObject(RevStream()))
4
+    checkTrue(validObject(Rev()))
5 5
 
6 6
     fl <- system.file("extdata", "s_1_sequence.txt", package="Streamer")
7
-    s <- stream(RevStream(), BinaryInput(fl))
7
+    s <- stream(Rev(), RawInput(fl))
8 8
     res <- yield(s)
9 9
 }
10 10
deleted file mode 100644
... ...
@@ -1,76 +0,0 @@
1
-test_2D_Data_read <- function() {
2
-    file <- system.file("extdata", "NetCDFData.nc", package = "Streamer")
3
-    ncFile <- NetCDFFile(file)
4
-
5
-    vars <- names(dimensions(ncFile))
6
-    checkIdentical(vars, c( "2dIntData", "2dFloatData"))
7
-
8
-    current <- dimensions(ncFile)
9
-    target <- list(`2dIntData` = c(sampleDim=5L, snpDim=10L),
10
-                   `2dFloatData` = c(sampleDim=5L, snpDim=10L ))
11
-    checkIdentical(current, target)
12
-    
13
-    ncprod <- NetCDFInput(ncFile, "2dIntData")
14
-    current <- names(dimensions(ncprod))
15
-    checkIdentical(current, "2dIntData")
16
-    
17
-    slice <- c(sampleDim = 5, snpDim = 5)
18
-    ncprod <- NetCDFInput(ncFile, "2dIntData", slice)
19
-    current <- ncprod$slice
20
-    nms <-  c("sampleDim", "snpDim")
21
-    target <-  structure( c(5L, 5L), names = nms)
22
-    checkIdentical(current, target)
23
-
24
-    dat <- yield(ncprod)
25
-    current <- status(ncprod)
26
-    target <- structure(c(1L, 6L), names = c("sampleDim", "snpDim"))
27
-    checkEquals(target, current)
28
-   
29
-    reset(ncprod)
30
-    current <- status(ncprod)
31
-    target <- structure(c(1L, 1L), names = c("sampleDim", "snpDim"))
32
-    checkEquals(target, current)
33
-
34
-    current <- yield(ncprod)
35
-    target <- matrix(1:25, ncol = 5)
36
-    checkEquals(target ,current)
37
-   
38
-    current <- yield(ncprod)
39
-    target <- matrix(26:50, ncol = 5)
40
-    checkEquals(target ,current)
41
-
42
-    current <- yield(ncprod)
43
-    target <- matrix(numeric(0), 0, 0)
44
-    checkEquals(target ,current)
45
-  
46
-    slice <- c(sampleDim = 4, snpDim = 4)
47
-    ncprod <- NetCDFInput(ncFile, "2dIntData", slice)
48
-
49
-    current <- yield(ncprod)
50
-    target <- matrix(c(1:4, 6:9, 11:14, 16:19), ncol = 4)
51
-    checkEquals(target ,current)
52
-    
53
-    current <- yield(ncprod)
54
-    target <-  c(5,10, 15, 20)
55
-    checkEquals(target , as.numeric(current))
56
-    
57
-    current <- yield(ncprod)
58
-    target <- c(21:24, 26:29, 31:34, 36:39)
59
-    checkEquals(target , as.numeric(current))
60
-    current <- yield(ncprod)
61
-    target <-  c(25, 30, 35, 40)
62
-    checkEquals(target , as.numeric(current))
63
-
64
-    current <- yield(ncprod)
65
-    target <- matrix(c(41: 44, 46:49), ncol =2)
66
-    checkEquals(target ,current)
67
-    
68
-    current <- yield(ncprod)
69
-    target <- c(45, 50)
70
-    checkEquals(target , as.numeric(current))
71
-    
72
-    current <- yield(ncprod)
73
-    target <- matrix(numeric(0), 0, 0)
74
-    checkEquals(target ,current)
75
-}
76
-
77 0
deleted file mode 100644
... ...
@@ -1,68 +0,0 @@
1
-\name{BufferInt-class}
2
-\Rdversion{1.1}
3
-\docType{class}
4
-\alias{BufferInt-class}
5
-\alias{BufferInt}
6
-\alias{BufferInterface}
7
-\alias{BufferInterface,ANY-method}
8
-\alias{BufferInterface,data.frame-method}
9
-\alias{show,BufferInt-method}
10
-
11
-\title{Class "BufferInt"}
12
-
13
-\description{
14
-
15
- An internal reference class container used by the \code{Consumer}-class to
16
- store functions that operate on the records stored in the \code{.records} field 
17
- of the \code{Consumer}-class.  Operations performed on 
18
- the \code{.records} field by the \code{Consumer}-class include \code{length}, 
19
- \code{append}, \code{subset}.  
20
-
21
- Users have the options of modifying the behaviour of the above mentioned 
22
- operations for records of different data types by declaring an S4 
23
- method \code{BufferInterface} that returns an object of \code{BufferInt}-class.
24
-}
25
-
26
-\section{Constructors}{
27
-  Instances from this class are constructed with calls to \code{BufferInt}
28
-  constructor.
29
-}
30
-
31
-
32
-\section{Fields}{
33
-  \describe{
34
-    \item{\code{length}:}{Object of class \code{function} that returns the length
35
-        of the records.}
36
-    \item{\code{append}:}{Object of class \code{function} that appends records
37
-        together. This function is called when a new records is read and is to
38
-        be added to the existing buffer. }
39
-    \item{\code{subset}:}{Object of class \code{function} that subsets records.
40
-    This function is called when records have been yielded and are to be removed
41
-    from the buffer}
42
-  }
43
-}
44
-
45
-\section{Methods}{
46
-  Users have the option of controlling the beaviour of the functions
47
-  \code{length}, \code{append} and \code{subset} used to manipulate the
48
-  \code{.records} field of the \code{Consumer}-class by declaring a function
49
-  \code{BufferInterface}.
50
-  \describe{BufferInterface}{Returns an object of class \code{BufferInt} that
51
-      holds functions for manipulating the record of the \code{Consumer} class.
52
-  }  
53
-}
54
-
55
-\author{Nishant Gopalakrishnan \url{ngopalak@fhcrc.org}}
56
-
57
-\seealso{
58
-
59
-  \code{\link{Streamer-package}}, \code{\linkS4class{Consumer}-class}.
60
-
61
-}
62
-
63
-\examples{
64
-showClass("BufferInt")
65
-selectMethod("BufferInterface", "data.frame")
66
-}
67
-
68
-\keyword{classes}
... ...
@@ -7,20 +7,24 @@
7 7
 
8 8
 \description{
9 9
 
10
-  A virtual class containing components that are required to create a custom
11
-  \code{Producer}-class to read data from file connections. Users can inherit from
12
-  the \code{ConnectionProducer}-class to create their own \code{Producer}
13
-  classes that interact with files. Users are expected to pass in appropriate 
14
-  \code{reader} and \code{parser} functions for files when creating instances of
15
-  classes that inherit from \code{ConnectionProducer}-class.
10
+  A virtual class containing components that are required to create a
11
+  custom \code{Producer}-class to read data from file connections. Users
12
+  can inherit from the \code{ConnectionProducer}-class to create their
13
+  own \code{Producer} classes that interact with files. Users are
14
+  expected to pass in appropriate \code{reader} and \code{parser}
15
+  functions for files when creating instances of classes that inherit
16
+  from \code{ConnectionProducer}-class.
16 17
 
17 18
 }
18 19
 
19 20
 \section{Fields}{
20 21
   \describe{
21
-    The \code{ConnectionProducer} class inherits the fields \code{verbose}, \code{inUse}
22
-    and \code{yieldSize} fields from the \code{Streamer} class. Please refer to
23
-    the \code{\link{Streamer}} class for more details.
22
+
23
+    The \code{ConnectionProducer} class inherits the fields
24
+    \code{verbose} and \code{inUse} fields from the \code{Streamer}
25
+    class. Please refer to the \code{\link{Streamer}} class for more
26
+    details.
27
+
24 28
     \item{\code{con}:}{An object of class \code{connection}.}
25 29
     \item{\code{reader}:}{A function that reads data from a file
26 30
         connection}
... ...
@@ -30,14 +34,16 @@
30 34
 
31 35
 \section{Class-Based Methods}{
32 36
   \describe{
33
-    The \code{ConnectionProducer} class inherits the methods \code{initialize}, \code{msg},
34
-    \code{reset}, \code{status} and \code{yield} from the \code{Streamer}
35
-    virtual class. Please refer to the \code{\link{Streamer}} class for more
36
-    details.
37
+
38
+    The \code{ConnectionProducer} class inherits the methods
39
+    \code{initialize}, \code{msg}, \code{reset}, \code{status} and
40
+    \code{yield} from the \code{Streamer} virtual class. Please refer to
41
+    the \code{\link{Streamer}} class for more details.
37 42
   
38
-    Derived classes should implement an appropriate  \code{yield} method to 
39
-    return the contents of the current stream. The default method for the base 
40
-    virtual \code{Streamer} class returns a \code{list()} 
43
+    Derived classes should implement an appropriate \code{yield} method
44
+    to return the contents of the current stream. The default method for
45
+    the base virtual \code{Streamer} class returns a \code{list()}
46
+
41 47
   }
42 48
 }
43 49
 
... ...
@@ -29,15 +29,15 @@
29 29
 
30 30
 \section{Fields}{
31 31
   \describe{
32
+
32 33
     \item{\code{inputPipe}:}{Object of class \code{Streamer},
33
-      representing the \code{Producer} or \code{Consumer} connected up-stream to
34
-      it and from which records are yielded.}
35
-    \item{\code{.records}:}{Object of class\code{list} which is used as a
36
-        temporary buffer for storing records.}
34
+      representing the \code{Producer} or \code{Consumer} connected
35
+      up-stream to it and from which records are yielded.}
37 36
     
38
-    The \code{Consumer} class inherits the fields \code{yieldSize},
39
-    \code{verbose} and \code{inUse} from the virtual \code{Streamer} class.
40
-    Please refer to the \code{\link{Streamer}} class for more details.
37
+    The \code{Consumer} class inherits the fields \code{verbose} and
38
+    \code{inUse} from the virtual \code{Streamer} class.  Please refer
39
+    to the \code{\link{Streamer}} class for more details.
40
+
41 41
   }
42 42
 }
43 43
 
... ...
@@ -46,38 +46,37 @@
46 46
     \item{\code{initialize(..., inputPipe)}:}{A method to
47 47
       initialize the fields of the \code{Consumer} class.
48 48
       \describe{
49
-	\item{\code{inputPipe}:}{An object of class \code{Streamer} connected
50
-        up-stream to it. The class could be a  \code{Consumer} or \code{Producer}
51
-	  which yields data to the \code{Consumer} class.}
52
-	\item{\code{...}:}{Additonal arguments, currently unused.}
53
-	\item{\code{verbose}:}{A \code{logical(1)} instance indicating
54
-	  whether methods invoked on the class should be reported to the
55
-	  user.}
49
+	\item{\code{inputPipe}:}{An object of class \code{Streamer}
50
+          connected up-stream to it. The class could be a
51
+          \code{Consumer} or \code{Producer} which yields data to the
52
+          \code{Consumer} class.}
56 53
       }
57 54
     }
55
+
58 56
     \item{\code{reset()}:}{Return the result of delegating
59 57
       \code{reset()} to the object in the field \code{inputPipe}.}
58
+
60 59
     \item{\code{yield()}:}{Return the result of delegating
61 60
       \code{yield()} to the object in the field \code{inputPipe}.}
61
+
62 62
     \item{\code{inputs()}:}{Return a \code{character} vector
63 63
       representing up-stream components.}
64
-    \item{\code{status{}}:}{Reports the status of the \code{Consumer} class. A
65
-        \code{list} of the status of the length of the object in the \code{.records} 
66
-        field, the classes connected to the \code{inputPipe} field and the status of the fields
67
-        of the virtual class \code{Streamer} are returned.}
68
-    \item{\code{.fill()}:}{An internal method that fills the \code{.records}
69
-        field with \code{yieldSize} records if available.}
70
-    \item{\code{.add(input)}:}{An internal method that appends the value passed to the argument
71
-    \code{input} to the \code{.records} field.}
72
-    }
64
+
65
+    \item{\code{status{}}:}{Reports the status of the \code{Consumer}
66
+      class. A \code{list} of the status of the length of the object in
67
+      the \code{.records} field, the classes connected to the
68
+      \code{inputPipe} field and the status of the fields of the virtual
69
+      class \code{Streamer} are returned.}
70
+
71
+  }
73 72
 }
74 73
 
75 74
 \author{Martin Morgan \url{mtmorgan@fhcrc.org}}
76 75
 
77
-
78 76
 \seealso{
79 77
 
80
-  \code{\link{Streamer-package}}, \code{\linkS4class{Streamer}-class}, \code{\linkS4class{Producer}-class},
78
+  \code{\link{Streamer-package}}, \code{\linkS4class{Streamer}-class},
79
+  \code{\linkS4class{Producer}-class},
81 80
   \code{\linkS4class{Stream}-class}.
82 81
 
83 82
 }
... ...
@@ -18,7 +18,7 @@
18 18
 }
19 19
 
20 20
 \usage{
21
-Downsample(probability=0.1, ..., yieldSize=1e6, verbose=FALSE)
21
+Downsample(probability=0.1, sampledSize=1e6, ...)
22 22
 }
23 23
 
24 24
 \arguments{
... ...
@@ -26,48 +26,25 @@ Downsample(probability=0.1, ..., yieldSize=1e6, verbose=FALSE)
26 26
     probability with which a record should be retained.}
27 27
   \item{...}{Additional arguments, passed to the \code{$new} method of
28 28
     the underlying reference class. Currently unused.}
29
-  \item{yieldSize}{A \code{integer(1)} indicating the number of
30
-    records to yield.}
31
-  \item{verbose}{\code{logical(1)} indicating whether class methods
32
-    should report to the user.}
29
+  \item{sampledSize}{A \code{integer(1)} indicating the number of
30
+    records to return.}
33 31
 }
34 32
   
35 33
 \section{Fields}{
36 34
   \describe{
37
-    \item{\code{inputPipe}:}{Object of class \code{ANY}. The component
38
-      from which input is retrieved.}
39 35
     \item{\code{probability}:}{Object of class \code{numeric}. The
40 36
       probability of including a record in the \code{yield}.}
41
-    \item{\code{yieldSize}:}{Object of class \code{integer}
37
+    \item{\code{sampledSize}:}{Object of class \code{integer}
42 38
       storing the number of records to produced each time \code{yield}
43 39
       is invoked.}
44 40
     \item{\code{.buffer}:}{Object of class \code{ANY}, used internally
45 41
       to store read but not yet parsed records.}
46
-    \item{\code{verbose}:}{Object of class \code{logical}. Display
47
-      method invokation messages to the user.}
48 42
   }
49 43
 }
50 44
 
51 45
 \section{Class-Based Methods}{
52 46
   \describe{
53
-    \item{\code{initialize(..., probability, yieldSize,
54
-	verbose)}:}{Initialize the instance.
55
-      \describe{
56
-	\item{\code{probability}:}{The probability with which a record
57
-	  is included in the sample.}
58
-	\item{\code{yieldSize}:}{The number of records to return when
59
-	  \code{yield} is invoked.}
60
-	\item{\code{...}:}{Additional arguments, currently ignored.}
61
-	\item{\code{verbose}:}{Display method invokation messages to the
62
-	  user.}
63
-      }}
64
-    \item{\code{reset()}:}{Reset sample buffer and delegate \code{reset}
65
-      to \code{inputPipe}.}
66
-    \item{\code{yield()}:}{Continually invoke \code{yield} on
67
-      \code{inputPipe}, accumulating a random sample of
68
-      \code{yieldSize} records until the \code{yield} of
69
-      \code{inputPipe} has length 0. The result is a \code{list} of
70
-      length \code{yieldSize}.}
47
+    \item{\code{.sample(x)}:}{Sample from amongst the incoming records.}
71 48
   }
72 49
 }
73 50
 
... ...
@@ -7,21 +7,20 @@
7 7
 
8 8
 \description{
9 9
 
10
-  The \code{ParallelConnector} \code{\linkS4class{Consumer}}-class can be used
11
-  to parallelize the computations done by blocks directly connected to the 
12
-  \code{ParallelConnector} and all blocks down-stream to the
13
-  \code{ParallelConnector}. i.e Computations performed by the block directly 
14
-  connected  up-stream to the \code{ParallelConnector} and all blocks connected
15
-  down-stream to the \code{ParallelConnector} in a stream happen simultaneously.
10
+  The \code{ParallelConnector} \code{\linkS4class{Consumer}}-class can
11
+  be used to parallelize the computations done by blocks directly
12
+  connected to the \code{ParallelConnector} and all blocks down-stream
13
+  to the \code{ParallelConnector}. i.e Computations performed by the
14
+  block directly connected up-stream to the \code{ParallelConnector} and
15
+  all blocks connected down-stream to the \code{ParallelConnector} in a
16
+  stream happen simultaneously.
17
+
16 18
 }
17 19
 
18
-\usage{ParallelConnector(..., yieldSize=1e6, verbose=FALSE)}
20
+\usage{ParallelConnector(...)}
19 21
 
20 22
 \arguments{
21 23
   \item{...}{Additional arguments to be passed to the constructor.}
22
-  \item{yieldSize}{The number of records the input parser is to yield.}
23
-  \item{verbose}{\code{logical(1)} indicating whether class methods
24
-    should report to the user.}
25 24
 }
26 25
 
27 26
 \section{Constructors}{
... ...
@@ -57,4 +56,3 @@
57 56
 \examples{showClass("ParallelConnector")}
58 57
 
59 58
 \keyword{classes}
60
-
... ...
@@ -30,9 +30,11 @@
30 30
 
31 31
 \section{Fields}{
32 32
   \describe{
33
-    The \code{Producer} class inherits the fields \code{verbose}, \code{inUse}
34
-    and \code{yieldSize} fields from the \code{Streamer} class. Please refer to
33
+
34
+    The \code{Producer} class inherits the fields \code{verbose} and
35
+    \code{inUse} fields from the \code{Streamer} class. Please refer to
35 36
     the \code{\link{Streamer}} class for more details.
37
+
36 38
   }
37 39
 }
38 40
 
... ...
@@ -34,7 +34,7 @@
34 34
 
35 35
 \usage{
36 36
 RawInput(con, yieldSize = 1e+06, reader = rawReaderFactory(), 
37
-    parser = rawParserFactory(), ..., verbose = FALSE)
37
+    parser = rawParserFactory(), ...)
38 38
 rawReaderFactory(blockSize = 1e+06, what)
39 39
 rawParserFactory(separator = charToRaw("\n"), trim = separator)
40 40
 }
... ...
@@ -51,12 +51,12 @@ rawParserFactory(separator = charToRaw("\n"), trim = separator)
51 51
     parsing the \code{raw} vector \code{c(buf, bin)} into records.}
52 52
   \item{...}{Additional arguments, passed to the \code{$new} method of
53 53
     this class. Currently ignored.}
54
-  \item{verbose}{\code{logical(1)} indicating whether class methods
55
-    should report to the user.}
54
+
56 55
   % rawReaderFactory
57 56
   \item{blockSize}{The number of bytes to read at one time.}
58 57
   \item{what}{The type of data to read, as the argument to
59 58
     \code{\link{readBin}}.}
59
+
60 60
   % rawParserFactory
61 61
   \item{separator}{A \code{raw} vector indicating the unique sequence of
62 62
     bytes by which record starts are to be recognized. The parser
... ...
@@ -68,41 +68,40 @@ rawParserFactory(separator = charToRaw("\n"), trim = separator)
68 68
 
69 69
 \section{Fields}{
70 70
   \describe{
71
+
71 72
     \item{\code{con}:}{Object of class \code{connection}. An R
72 73
       \code{\link{connection}} opened in \dQuote{rb} mode from which
73 74
       data will be read.}
75
+
74 76
     \item{\code{blockSize}:}{Object of class \code{integer}. Size
75 77
       (e.g., number of raw bytes) input during each
76 78
       \code{\link{yield}}.}
79
+
77 80
     \item{\code{reader}:}{Object of class \code{function}. A function
78 81
       used to input \code{blockSize} elements. See
79 82
       \code{\link{rawReaderFactory}}.}
83
+
80 84
     \item{\code{parser}:}{Object of class \code{function}. A function
81 85
       used to parse raw input into records, e.g., breaking a
82 86
       \code{raw} vector on new lines \sQuote{\\n}. See
83 87
       \code{\link{rawParserFactory}}}
88
+
84 89
     \item{\code{.buffer}:}{Object of class \code{raw}. Contains read but
85 90
       not parsed raw stream data.}
91
+
86 92
     \item{\code{.records}:}{Object of class \code{list}. Parsed but not
87 93
       yet yield-ed records.}
94
+
88 95
     \item{\code{.parsedRecords}:}{Object of class \code{integer}. Total
89 96
       number of records parsed by the Producer.}
90
-    \item{\code{verbose}:}{Object of class \code{logical}. Should
91
-      progress be reported?}
97
+
92 98
   }
93 99
 }
94 100
 
95 101
 \section{Class-Based Methods}{
96 102
   \describe{
97
-    \item{\code{initialize(con, blockSize, reader, parser,
98
-	verbose)}:}{Called during object creation with values to
99
-      initialize fields.}
100 103
     \item{\code{reset()}:}{Remove buffer and current records, reset
101 104
       record counter, re-open \code{con}.}
102
-    \item{\code{status()}:}{Summarize status of stream.}
103
-    \item{\code{yield()}:}{Process stream to yield as many complete
104
-      records as are represented in the current \code{blockSize}
105
-      elements.}
106 105
   }
107 106
 }
108 107
 
... ...
@@ -13,37 +13,20 @@
13 13
 
14 14
 }
15 15
 
16
-\usage{RawToChar(yieldSize = 1e6,verbose = FALSE)}
16
+\usage{RawToChar(...)}
17 17
 
18 18
 \arguments{
19
-  \item{yieldSize}{A \code{integer(1)} indicating the number of
20
-      records to yield.}
21
-  \item{verbose}{\code{logical(1)} indicating whether class methods
22
-    should report to the user.}
19
+  \item{...}{Arguments passed to the \code{\linkS4class{Consumer}}-class
20
+    constructors.}
23 21
 }
24 22
 
25 23
 \section{Constructors}{
26 24
   Use \code{RawToChar} to construct instances of this class.
27 25
 }
28 26
 
29
-\section{Fields}{
30
-  \describe{
31
-    \item{\code{inputPipe}:}{Object of class \code{ANY}. The component
32
-      from which input is retrieved.}
33
-    \item{\code{yieldSize}:}{A \code{integer(1)} indicating the number of
34
-      records to yield.}
35
-     \item{\code{verbose}:}{Object of class \code{logical}. Display
36
-      method invokation messages to the user.}
37
-  }
38
-}
27
+\section{Fields}{There are no fields unique to this class.}
39 28
 
40
-\section{Methods}{
41
-  \describe{
42
-    \item{\code{yield()}:}{Convert the result of applying \code{yield}
43
-      to \code{inputPipe} (which must be a list of \code{raw}) into a
44
-      vector of \code{character}.}
45
-  }
46
-}
29
+\section{Methods}{There are no methods unique to this class.}
47 30
 
48 31
 \author{Martin Morgan \url{mtmorgan@fhcrc.org}}
49 32
 
... ...
@@ -15,24 +15,24 @@
15 15
 
16 16
 \description{
17 17
 
18
-  A \code{\linkS4class{Producer}}-class to interpret text files. Users interact 
19
-  with this class through the constructor \code{ReadLinesInput} and methods 
20
-  \code{\link{yield}}, \code{\link{reset}}, and \code{\link{stream}}.
18
+  A \code{\linkS4class{Producer}}-class to interpret text files. Users
19
+  interact with this class through the constructor \code{ReadLinesInput}
20
+  and methods \code{\link{yield}}, \code{\link{reset}}, and
21
+  \code{\link{stream}}.
21 22
 
22 23
   This class requires two helper functions; the \sQuote{factory} methods
23 24
   defined on this page can be used to supply these.
24 25
   \code{readLinesReaderFactory} creates a \sQuote{reader}, whose
25
-  responsibility it is to accept a connection and return a  \code{character} 
26
-  vector.  \code{readLinesParserFactory} creates  a \sQuote{parser}, 
27
-  responsible for parsing a buffer and vector of the
28
-  same type as produced by the reader into records. 
26
+  responsibility it is to accept a connection and return a
27
+  \code{character} vector.  \code{readLinesParserFactory} creates a
28
+  \sQuote{parser}, responsible for parsing a buffer and vector of the
29
+  same type as produced by the reader into records.
29 30
   
30 31
 }
31 32
 
32 33
 \usage{
33 34
 ReadLinesInput(con, reader = readLinesReaderFactory(), 
34
-    parser = readLinesParserFactory(), ..., yieldSize = 1e+06,
35
-    verbose = FALSE)
35
+    parser = readLinesParserFactory(), yieldSize = 1e+06, ...)
36 36
 readLinesReaderFactory(blockSize=1e+06, ...)
37 37
 scanReaderFactory(blockSize=1e06, ...)
38 38
 }
... ...
@@ -47,10 +47,10 @@ scanReaderFactory(blockSize=1e06, ...)
47 47
     reader function) that returns a vector of type \code{character}.}
48 48
   \item{parser}{A function of two arguments (\code{buf}, \code{bin}),
49 49
     parsing the \code{raw} vector \code{c(buf, bin)} into records.}
50
-  \item{verbose}{\code{logical(1)} indicating whether class methods
51
-    should report to the user.}
50
+
52 51
   % readLinesReaderFactory
53 52
   \item{blockSize}{The number of characters to read at one time.}
53
+
54 54
   \item{...}{Additional arugments.}
55 55
  }
56 56
 
... ...
@@ -14,36 +14,18 @@
14 14
 
15 15
 }
16 16
 
17
-\usage{Rev(yieldSize = 1e6, verbose=FALSE)}
17
+\usage{Rev(...)}
18 18
 
19 19
 \arguments{
20
-   \item{yieldSize}{A \code{integer(1)} indicating the number of
21
-      records to yield.}
22
-   \item{verbose}{\code{logical(1)} indicating whether class methods
23
-    should report to the user.}
20
+  \item{...}{Arguments passed to the \code{\linkS4class{Consumer}}-class
21
+    constructors.}
24 22
 }
25 23
 
26
-\section{Constructors}{
27
-  Use \code{Rev} to construct instances of this class.
28
-}
24
+\section{Constructors}{Use \code{Rev} to construct instances of this class.}
29 25
 
30
-\section{Fields}{
31
-  \describe{
32
-    \item{\code{inputPipe}:}{Object of class \code{ANY}. The component
33
-      from which input is retrieved.}
34
-    \item{\code{yieldSize}:}{A \code{integer(1)} indicating the number of
35
-      records to yield.}
36
-    \item{\code{verbose}:}{Object of class \code{logical}. Display
37
-      method invokation messages to the user.}
38
-  }
39
-}
26
+\section{Fields}{There are no fields unique to this class.}
40 27
 
41
-\section{Methods}{
42
-  \describe{
43
-    \item{\code{yield()}:}{Reverse the result of applyng \code{yield} to
44
-      \code{inputPipe}.}
45
-  }
46
-}
28
+\section{Methods}{There are no methods unique to this class.}
47 29
 
48 30
 \author{Martin Morgan \url{mtmorgan@fhcrc.org}}
49 31
 
... ...
@@ -20,8 +20,6 @@
20 20
 
21 21
 \section{Fields}{
22 22
   \describe{
23
-      \item{\code{yieldSize}:}{ An \code{integer} for the number of records
24
-          to be returned.}
25 23
       \item{\code{verbose}:}{A \code{logical(1)} instance indicating
26 24
       whether methods invoked on the class should be reported to the
27 25
       user.}
... ...
@@ -32,17 +30,23 @@
32 30
 
33 31
 \section{Class-Based Methods}{
34 32
   \describe{
33
+
35 34
     \item{\code{initialize(..., verbose = FALSE)}:}{Initialize
36
-      \code{Streamer}, setting \code{verbose}, \code{yieldSize} and \code{inUse}
37
-      fields, returning \code{.self} invisibly.}
35
+      \code{Streamer}, setting \code{verbose} and \code{inUse} fields,
36
+      returning \code{.self} invisibly.}
37
+
38 38
     \item{\code{msg(fmt, ...)}:}{Use \code{msg} to print
39 39
       \code{sprintf(fmt, ...)} messages to user.}
40
+
40 41
     \item{\code{reset()}:}{Reset \code{Streamer}; this default method is
41 42
       a no-op.}
43
+
42 44
     \item{\code{yield()}:}{Yield default value \code{list()}.}
43
-    \item{\code{status()}:}{Reports the status of the \code{Streamer} class.
44
-       A \code{list} of the status of \code{yieldSize}, \code{verbose} and 
45
+