This changes the manual pages etc. so that the detail function and
generic can be moved to the Biostrings package.
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/ShortRead@49981 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,7 +1,7 @@ |
1 | 1 |
Package: ShortRead |
2 | 2 |
Type: Package |
3 | 3 |
Title: Classes and methods for high-throughput short-read sequencing data. |
4 |
-Version: 1.7.26 |
|
4 |
+Version: 1.7.27 |
|
5 | 5 |
Author: Martin Morgan, Michael Lawrence, Simon Anders |
6 | 6 |
Maintainer: Biocore Team c/o BioC user list <bioconductor@stat.math.ethz.ch> |
7 | 7 |
Description: Base classes, functions, and methods for representation of |
... | ... |
@@ -23,7 +23,7 @@ importFrom(GenomicRanges, strand) |
23 | 23 |
importFrom(Biostrings, BString, BStringSet, DNAString, DNAStringSet, |
24 | 24 |
compact, alphabetFrequency, alphabet, DNA_ALPHABET, |
25 | 25 |
quality, pairwiseAlignment, pattern, |
26 |
- trimLRPatterns, unaligned) |
|
26 |
+ trimLRPatterns, unaligned, detail) |
|
27 | 27 |
|
28 | 28 |
importFrom(hwriter, hwrite, hwriteImage) |
29 | 29 |
|
... | ... |
@@ -125,10 +125,6 @@ setGeneric("clean", function(object, ...) standardGeneric("clean")) |
125 | 125 |
setGeneric("srdistance", function(pattern, subject, ...) |
126 | 126 |
standardGeneric("srdistance"), signature=c("pattern", "subject")) |
127 | 127 |
|
128 |
-detail <- function(object, ...) show(object) |
|
129 |
- |
|
130 |
-setGeneric("detail") |
|
131 |
- |
|
132 | 128 |
setGeneric("alphabetScore", |
133 | 129 |
function(object, ...) standardGeneric("alphabetScore")) |
134 | 130 |
|
... | ... |
@@ -14,7 +14,7 @@ setMethod(show, |
14 | 14 |
}) |
15 | 15 |
|
16 | 16 |
setMethod(detail, |
17 |
- signature=signature(object=".ShortReadBase"), |
|
18 |
- function(object, ...) { |
|
19 |
- cat("class: ", class(object), "\n", sep="") |
|
17 |
+ signature=signature(x=".ShortReadBase"), |
|
18 |
+ function(x, ...) { |
|
19 |
+ cat("class: ", class(x), "\n", sep="") |
|
20 | 20 |
}) |
... | ... |
@@ -294,15 +294,15 @@ setMethod(show, "AlignedRead", function(object) { |
294 | 294 |
selectSome(varLabels(alignData(object))), "\n") |
295 | 295 |
}) |
296 | 296 |
|
297 |
-setMethod(detail, "AlignedRead", function(object, ...) { |
|
297 |
+setMethod(detail, "AlignedRead", function(x, ...) { |
|
298 | 298 |
callNextMethod() |
299 |
- cat("\nchromosome:", selectSome(chromosome(object)), "\n") |
|
300 |
- cat("position:", selectSome(position(object)), "\n") |
|
301 |
- cat("strand:", selectSome(strand(object)), "\n") |
|
299 |
+ cat("\nchromosome:", selectSome(chromosome(x)), "\n") |
|
300 |
+ cat("position:", selectSome(position(x)), "\n") |
|
301 |
+ cat("strand:", selectSome(strand(x)), "\n") |
|
302 | 302 |
cat("alignQuality:\n") |
303 |
- detail(alignQuality(object)) |
|
303 |
+ detail(alignQuality(x)) |
|
304 | 304 |
cat("\nalignData:\n") |
305 |
- show(alignData(object)) |
|
305 |
+ show(alignData(x)) |
|
306 | 306 |
}) |
307 | 307 |
|
308 | 308 |
## summary |
... | ... |
@@ -65,7 +65,7 @@ setMethod(show, "ExperimentPath", function(object) { |
65 | 65 |
for (slt in slts[slts!="basePath"]) catPath(slt) |
66 | 66 |
} |
67 | 67 |
|
68 |
-setMethod(detail, "ExperimentPath", function(object, ...) { |
|
68 |
+setMethod(detail, "ExperimentPath", function(x, ...) { |
|
69 | 69 |
callNextMethod() |
70 |
- cat("experimentPath:\n ", experimentPath(object), "\n", sep="") |
|
70 |
+ cat("experimentPath:\n ", experimentPath(x), "\n", sep="") |
|
71 | 71 |
}) |
... | ... |
@@ -31,10 +31,10 @@ setMethod(append, c("QualityScore", "QualityScore", "missing"), |
31 | 31 |
initialize(x, quality=append(quality(x), quality(values))) |
32 | 32 |
}) |
33 | 33 |
|
34 |
-setMethod(detail, "QualityScore", function(object) { |
|
34 |
+setMethod(detail, "QualityScore", function(x) { |
|
35 | 35 |
callNextMethod() |
36 | 36 |
cat("quality:\n") |
37 |
- print(quality(object)) |
|
37 |
+ print(quality(x)) |
|
38 | 38 |
}) |
39 | 39 |
|
40 | 40 |
## NumericQuality |
... | ... |
@@ -89,7 +89,7 @@ setMethod(show, "RochePath", function(object) { |
89 | 89 |
.show_additionalPathSlots(object) |
90 | 90 |
}) |
91 | 91 |
|
92 |
-setMethod(detail, "RochePath", function(object, ...) { |
|
92 |
+setMethod(detail, "RochePath", function(x, ...) { |
|
93 | 93 |
callNextMethod() |
94 |
- .detail_additionalPathSlots(object) |
|
94 |
+ .detail_additionalPathSlots(x) |
|
95 | 95 |
}) |
... | ... |
@@ -42,7 +42,7 @@ setMethod(lapply, "SRList", function(X, FUN, ...) { |
42 | 42 |
|
43 | 43 |
setMethod(show, "SRList", .SRList_show_class) |
44 | 44 |
|
45 |
-setMethod(detail, "SRList", function(object,...) { |
|
46 |
- .SRList_show_class(object) |
|
47 |
- .srlist(object) |
|
45 |
+setMethod(detail, "SRList", function(x,...) { |
|
46 |
+ .SRList_show_class(x) |
|
47 |
+ .srlist(x) |
|
48 | 48 |
}) |
... | ... |
@@ -58,12 +58,12 @@ setMethod(show, "SRSet", function(object) { |
58 | 58 |
sep="") |
59 | 59 |
}) |
60 | 60 |
|
61 |
-setMethod(detail, "SRSet", function(object, ...) { |
|
61 |
+setMethod(detail, "SRSet", function(x, ...) { |
|
62 | 62 |
callNextMethod() |
63 | 63 |
cat("\nsourcePath\n") |
64 |
- detail(sourcePath(object), ...) |
|
64 |
+ detail(sourcePath(x), ...) |
|
65 | 65 |
cat("\nphenoData\n") |
66 |
- pd <- phenoData(object) |
|
66 |
+ pd <- phenoData(x) |
|
67 | 67 |
cat("pData:\n") |
68 | 68 |
print(pData(pd)) |
69 | 69 |
cat("varMetadata:\n") |
... | ... |
@@ -32,7 +32,7 @@ setMethod(show, "SRVector", function(object) { |
32 | 32 |
cat("vclass: ", vclass(object), "\n", sep="") |
33 | 33 |
}) |
34 | 34 |
|
35 |
-setMethod(detail, "SRVector", function(object) { |
|
36 |
- .SRList_show_class(object) |
|
37 |
- show(unlist(.srlist(object))) |
|
35 |
+setMethod(detail, "SRVector", function(x) { |
|
36 |
+ .SRList_show_class(x) |
|
37 |
+ show(unlist(.srlist(x))) |
|
38 | 38 |
}) |
... | ... |
@@ -167,12 +167,12 @@ setMethod(show, "ShortRead", function(object) { |
167 | 167 |
cat("length:", length(object), "reads; width:", wd, "cycles\n") |
168 | 168 |
}) |
169 | 169 |
|
170 |
-setMethod(detail, "ShortRead", function(object, ...) { |
|
171 |
- cat("class: ", class(object), "\n") |
|
170 |
+setMethod(detail, "ShortRead", function(x, ...) { |
|
171 |
+ cat("class: ", class(x), "\n") |
|
172 | 172 |
cat("\nsread:\n") |
173 |
- show(sread(object)) |
|
173 |
+ show(sread(x)) |
|
174 | 174 |
cat("\nid:\n") |
175 |
- show(id(object)) |
|
175 |
+ show(id(x)) |
|
176 | 176 |
}) |
177 | 177 |
|
178 | 178 |
## summary |
... | ... |
@@ -213,9 +213,9 @@ setMethod(alphabetScore, "ShortReadQ", .forward_objq) |
213 | 213 |
|
214 | 214 |
## show |
215 | 215 |
|
216 |
-setMethod(detail, "ShortReadQ", function(object, ...) { |
|
216 |
+setMethod(detail, "ShortReadQ", function(x, ...) { |
|
217 | 217 |
callNextMethod() |
218 |
- detail(quality(object)) |
|
218 |
+ detail(quality(x)) |
|
219 | 219 |
}) |
220 | 220 |
|
221 | 221 |
## summary |
... | ... |
@@ -120,7 +120,7 @@ setMethod(show, "SolexaPath", function(object) { |
120 | 120 |
.show_additionalPathSlots(object) |
121 | 121 |
}) |
122 | 122 |
|
123 |
-setMethod(detail, "SolexaPath", function(object, ...) { |
|
123 |
+setMethod(detail, "SolexaPath", function(x, ...) { |
|
124 | 124 |
callNextMethod() |
125 |
- .detail_additionalPathSlots(object) |
|
125 |
+ .detail_additionalPathSlots(x) |
|
126 | 126 |
}) |
... | ... |
@@ -81,12 +81,12 @@ setMethod(show, "SolexaSet", function(object) { |
81 | 81 |
print(laneDescription(object)) |
82 | 82 |
}) |
83 | 83 |
|
84 |
-setMethod(detail, "SolexaSet", function(object, ...) { |
|
84 |
+setMethod(detail, "SolexaSet", function(x, ...) { |
|
85 | 85 |
callNextMethod() |
86 | 86 |
cat("\n") |
87 |
- detail(solexaPath(object), ...) |
|
87 |
+ detail(solexaPath(x), ...) |
|
88 | 88 |
cat("\nclass: AnnotatedDataFrame\n") |
89 |
- ld <- laneDescription(object) |
|
89 |
+ ld <- laneDescription(x) |
|
90 | 90 |
cat("pData:\n") |
91 | 91 |
print(pData(ld)) |
92 | 92 |
cat("varMetadata:\n") |
... | ... |
@@ -197,7 +197,7 @@ Class \code{"\linkS4class{.ShortReadBase}"}, by class "ShortReadQ", distance 3. |
197 | 197 |
\item{show}{\code{signature(object = "AlignedRead")}: provide a |
198 | 198 |
compact display of the \code{AlignedRead} content.} |
199 | 199 |
|
200 |
- \item{detail}{\code{signature(object = "AlignedRead")}: display |
|
200 |
+ \item{detail}{\code{signature(x = "AlignedRead")}: display |
|
201 | 201 |
\code{alignData} in more detail.} |
202 | 202 |
} |
203 | 203 |
} |
... | ... |
@@ -218,5 +218,9 @@ ltrim0 <- function(x) { |
218 | 218 |
Rle(runValue(x)[i], runLength(x)[i]) |
219 | 219 |
} |
220 | 220 |
endoapply(cvg, ltrim0) |
221 |
+## demonstration of show() and detail() methods |
|
222 |
+show(aln) |
|
223 |
+detail(aln) |
|
221 | 224 |
} |
225 |
+ |
|
222 | 226 |
\keyword{classes} |
... | ... |
@@ -51,8 +51,8 @@ |
51 | 51 |
\item{show}{\code{signature(object = "ExperimentPath")}: briefly |
52 | 52 |
summarize the file paths of \code{object}.} |
53 | 53 |
|
54 |
- \item{detail}{\code{signature(object = "ExperimentPath")}: summarize |
|
55 |
- file paths of \code{object}.} |
|
54 |
+ \item{detail}{\code{signature(x = "ExperimentPath")}: summarize |
|
55 |
+ file paths of \code{x}.} |
|
56 | 56 |
} |
57 | 57 |
} |
58 | 58 |
|
... | ... |
@@ -138,7 +138,7 @@ Class \code{"\linkS4class{.ShortReadBase}"}, by class ".Roche", distance 2. |
138 | 138 |
\item{show}{\code{signature(object = "RochePath")}: Briefly |
139 | 139 |
summarize the experiment path locations.} |
140 | 140 |
|
141 |
- \item{detail}{\code{signature(object = "RochePath")}: Provide |
|
141 |
+ \item{detail}{\code{signature(x = "RochePath")}: Provide |
|
142 | 142 |
additional detail on the Roche path. All file paths are presented |
143 | 143 |
in full.} |
144 | 144 |
} |
... | ... |
@@ -73,7 +73,7 @@ Class \code{"\linkS4class{.ShortReadBase}"}, directly. |
73 | 73 |
\item{show}{\code{signature(object = "SRSet")}: display the contents |
74 | 74 |
of this object.} |
75 | 75 |
|
76 |
- \item{detail}{\code{signature(object = "SRSet")}: provide more |
|
76 |
+ \item{detail}{\code{signature(x = "SRSet")}: provide more |
|
77 | 77 |
extensive information on the object.} |
78 | 78 |
} |
79 | 79 |
} |
... | ... |
@@ -181,7 +181,7 @@ |
181 | 181 |
informative summary of the object content, including the length of |
182 | 182 |
the list represented by \code{object}.} |
183 | 183 |
|
184 |
- \item{detail}{\code{signature(object = "SRList")}: display a more |
|
184 |
+ \item{detail}{\code{signature(x = "SRList")}: display a more |
|
185 | 185 |
extensive version of the object, as one might expect from printing |
186 | 186 |
a standard list in R.} |
187 | 187 |
|
... | ... |
@@ -196,7 +196,7 @@ |
196 | 196 |
informative summary of the object content, e.g., the vector class |
197 | 197 |
(\code{vclass}) and length.} |
198 | 198 |
|
199 |
- \item{detail}{\code{signature(object = "SRVector")}: display a more |
|
199 |
+ \item{detail}{\code{signature(x = "SRVector")}: display a more |
|
200 | 200 |
extensive version of the object, as one might expect from a |
201 | 201 |
printing a standard R list.} |
202 | 202 |
|
... | ... |
@@ -158,7 +158,7 @@ Class \code{"\linkS4class{.ShortReadBase}"}, directly. |
158 | 158 |
\item{show}{\code{signature(object = "ShortRead")}: provides a brief |
159 | 159 |
summary of the object, including its class, length and width.} |
160 | 160 |
|
161 |
- \item{detail}{\code{signature(object = "ShortRead")}: provides a |
|
161 |
+ \item{detail}{\code{signature(x = "ShortRead")}: provides a |
|
162 | 162 |
more extensive summary of this object, displaying the first and |
163 | 163 |
last entries of \code{sread} and \code{id}.} |
164 | 164 |
|
... | ... |
@@ -146,7 +146,7 @@ Class \code{"\linkS4class{.ShortReadBase}"}, by class "ShortRead", distance 2. |
146 | 146 |
\code{lane} to identify the object and returning an instance of |
147 | 147 |
\code{\linkS4class{ShortReadQQA}}. See \code{\link{qa}}} |
148 | 148 |
|
149 |
- \item{detail}{\code{signature(object = "ShortReadQ")}: display the |
|
149 |
+ \item{detail}{\code{signature(x = "ShortReadQ")}: display the |
|
150 | 150 |
first and last entries of each of \code{sread}, \code{id}, and |
151 | 151 |
\code{quality} entries of \code{object}.} |
152 | 152 |
} |
... | ... |
@@ -189,8 +189,8 @@ Class \code{"\linkS4class{.ShortReadBase}"}, by class ".Solexa", distance 2. |
189 | 189 |
\code{experimentPath} is given in full; the remaining paths are |
190 | 190 |
identified by their leading characters.} |
191 | 191 |
|
192 |
- \item{detail}{\code{signature(object = "SolexaPath")}: summarize |
|
193 |
- file paths of \code{object}. All file paths are presented in |
|
192 |
+ \item{detail}{\code{signature(x = "SolexaPath")}: summarize |
|
193 |
+ file paths of \code{x}. All file paths are presented in |
|
194 | 194 |
full.} |
195 | 195 |
} |
196 | 196 |
} |
... | ... |
@@ -69,7 +69,7 @@ Class \code{"\linkS4class{.ShortReadBase}"}, by class ".Solexa", distance 2. |
69 | 69 |
summarize the experiment path and lane description of the Solexa |
70 | 70 |
set. } |
71 | 71 |
|
72 |
- \item{detail}{\code{signature(object = "SolexaSet")}: Provide |
|
72 |
+ \item{detail}{\code{signature(x = "SolexaSet")}: Provide |
|
73 | 73 |
additional detail on the Solexa set, including the content of |
74 | 74 |
\code{solexaPath} and the \code{pData} and \code{varMetadata} of |
75 | 75 |
\code{laneDescription}.} |
76 | 76 |
deleted file mode 100644 |
... | ... |
@@ -1,42 +0,0 @@ |
1 |
-\name{detail} |
|
2 |
- |
|
3 |
-\alias{detail} |
|
4 |
- |
|
5 |
-\title{Show (display) detailed object content} |
|
6 |
- |
|
7 |
-\description{ |
|
8 |
- |
|
9 |
- This is a variant of \code{\link{show}}, offering a more detailed |
|
10 |
- display of object content. |
|
11 |
- |
|
12 |
-} |
|
13 |
-\usage{ |
|
14 |
- |
|
15 |
-detail(object, ...) |
|
16 |
- |
|
17 |
-} |
|
18 |
- |
|
19 |
-\arguments{ |
|
20 |
- |
|
21 |
- \item{object}{An object derived from class \code{ShortRead}. See help |
|
22 |
- pages for individual objects, e.g., |
|
23 |
- \code{\linkS4class{ShortReadQ}}. The default simply invokes |
|
24 |
- \code{\link{show}}.} |
|
25 |
- |
|
26 |
- \item{...}{Additional arguments. The default definition makes no use |
|
27 |
- of these arguments.} |
|
28 |
- |
|
29 |
-} |
|
30 |
-\value{ |
|
31 |
- |
|
32 |
- None; the function is invoked for its side effect (detailed display of |
|
33 |
- object content). |
|
34 |
- |
|
35 |
-} |
|
36 |
-\author{Martin Morgan} |
|
37 |
-\examples{ |
|
38 |
-sp <- SolexaPath(system.file('extdata', package='ShortRead')) |
|
39 |
-show(sp) |
|
40 |
-detail(sp) |
|
41 |
-} |
|
42 |
-\keyword{manip} |