| RaggedExperiment-class {RaggedExperiment} | R Documentation |
The RaggedExperiment class is a container for
storing range-based data, including but not limited to copy
number data, and mutation data. It can store a collection of
GRanges objects, as it is derived from the
GenomicRangesList.
RaggedExperiment(..., colData = DataFrame())
## S4 method for signature 'RaggedExperiment'
rowRanges(x, ...)
## S4 method for signature 'RaggedExperiment'
dim(x)
## S4 method for signature 'RaggedExperiment'
dimnames(x)
## S4 replacement method for signature 'RaggedExperiment,list'
dimnames(x) <- value
## S4 method for signature 'RaggedExperiment'
colData(x, ...)
## S4 replacement method for signature 'RaggedExperiment,DataFrame'
colData(x) <- value
## S4 method for signature 'RaggedExperiment,missing'
assay(x, i, ...)
## S4 method for signature 'RaggedExperiment,ANY'
assay(x, i, ..., withDimnames = TRUE)
## S4 method for signature 'RaggedExperiment'
assays(x, ..., withDimnames = TRUE)
## S4 method for signature 'RaggedExperiment'
assayNames(x, ...)
## S4 method for signature 'RaggedExperiment'
show(object)
## S4 method for signature 'RaggedExperiment,ANY,ANY,ANY'
x[i, j, ..., drop = TRUE]
## S4 method for signature 'RaggedExperiment,Vector'
overlapsAny(query, subject, maxgap = 0L,
minoverlap = 1L, type = c("any", "start", "end", "within", "equal"), ...)
## S4 method for signature 'RaggedExperiment,Vector'
subsetByOverlaps(x, ranges, maxgap = -1L,
minoverlap = 0L, type = c("any", "start", "end", "within", "equal"),
invert = FALSE, ...)
... |
Constructor: GRanges, list of GRanges, or GRangesList OR assay: Additional arguments for assay. See details for more information. |
colData |
A |
x |
A RaggedExperiment object. |
value |
A |
i |
logical(1), integer(1), or character(1) indicating the
assay to be reported. For |
withDimnames |
logical (default TRUE) whether to use dimension names in the resulting object |
object |
A RaggedExperiment object. |
j |
integer(), character(), or logical() index selecting columns from RaggedExperiment |
drop |
logical (default TRUE) whether to drop empty samples |
query |
A RaggedExperiment instance. |
subject |
Each of them can be a Ranges, Views, RangesList,
or ViewsList object.
In addition, if If If both arguments are list-like objects with names, each list element from the 2nd argument is paired with the list element from the 1st argument with the matching name, if any. Otherwise, list elements are paired by position. The overlap is then computed between the pairs as described below. If |
maxgap |
A single integer >= -1. If If |
minoverlap |
A single non-negative integer. Only ranges with a minimum of When |
type |
By default, any overlap is accepted. By specifying the The |
ranges |
Each of them can be a Ranges, Views, RangesList,
or ViewsList object.
In addition, if If If both arguments are list-like objects with names, each list element from the 2nd argument is paired with the list element from the 1st argument with the matching name, if any. Otherwise, list elements are paired by position. The overlap is then computed between the pairs as described below. If |
invert |
If |
constructor returns a RaggedExperiment object
'rowRanges' returns a GRanges object
summarizing ranges corresponding to assay() rows.
'assays' returns a SimpleList
overlapsAny returns a logical vector of length equal
to the number of rows in the query; TRUE when the
copy number region overlaps the subject.
subsetByOverlaps returns a RaggedExperiment containing
only copy number regions overlapping subject.
rowRanges: rowRanges accessor
dim: get dimensions (number of sample-specific row
ranges by number of samples)
dimnames: get row (sample-specific) range names
and sample names
dimnames<-: set row (sample-specific) range names
and sample names
colData: get column data
colData<-: change the colData
assay: assay missing method uses first metadata column
assay: assay numeric method.
assays: assays
assayNames: names in each assay
show: show method
[: Subset a RaggedExperiment object
overlapsAny: Determine whether copy number ranges
defined by query overlap ranges of subject.
subsetByOverlaps: Subset the RaggedExperiment to contain only
copy number ranges overlapping ranges of subject.
RaggedExperiment(..., colData=DataFrame()): Creates a
RaggedExperiment object using multiple GRanges objects or a list
of GRanges objects. Additional column data may be provided
as a DataFrame object.
In the following, 'x' represents a RaggedExperiment object:
x[i, j]: Get ranges or elements (i and j,
respectively) with optional metadata columns where i or j
can be missing, an NA-free logical, numeric, or character vector.
Coercion possible from
RangedRaggedAssay to
RaggedExperiment. Here object represents a
RangedRaggedAssay: as(object, "RaggedExperiment")
## Create an empty RaggedExperiment instance
re0 <- RaggedExperiment()
re0
## Create a couple of GRanges objects with row ranges names
sample1 <- GRanges(
c(a = "chr1:1-10:-", b = "chr1:11-18:+"),
score = 1:2)
sample2 <- GRanges(
c(c = "chr2:1-10:-", d = "chr2:11-18:+"),
score = 3:4)
## Include column data
colDat <- DataFrame(id = 1:2)
## Create a RaggedExperiment object from a couple of GRanges
re1 <- RaggedExperiment(sample1=sample1, sample2=sample2, colData = colDat)
re1
## With list of GRanges
lgr <- list(sample1 = sample1, sample2 = sample2)
## Create a RaggedExperiment from a list of GRanges
re2 <- RaggedExperiment(lgr, colData = colDat)
grl <- GRangesList(sample1 = sample1, sample2 = sample2)
## Create a RaggedExperiment from a GRangesList
re3 <- RaggedExperiment(grl, colData = colDat)
## Subset a RaggedExperiment
assay(re3[c(1, 3),])
subsetByOverlaps(re3, GRanges("chr1:1-5")) # by ranges