Compute column/row sums of a matrix-like object, for groups of rows/columns
rowsum.Rd
rowsum()
computes column sums across rows of a numeric matrix-like
object for each level of a grouping variable.
colsum()
computes row sums across columns of a numeric matrix-like
object for each level of a grouping variable.
NOTE: This man page is for the rowsum
and colsum
S4 generic functions defined in the S4Arrays package.
See ?base::rowsum
for the default rowsum()
method (defined in the base package).
Bioconductor packages can define specific methods for objects
(typically matrix-like) not supported by the default methods.
Arguments
- x
A numeric matrix-like object.
- group, reorder, ...
See
?base::rowsum
for a description of these arguments.
Value
See ?base::rowsum
for the value returned
by the default method.
The default colsum()
method simply does
t(rowsum(t(x), group, reorder=reorder, ...))
.
Specific methods defined in Bioconductor packages should behave as consistently as possible with the default methods.
See also
base::rowsum
for the defaultrowsum
method.showMethods
for displaying a summary of the methods defined for a given generic function.selectMethod
for getting the definition of a specific method.rowsum,DelayedMatrix-method in the DelayedArray package for an example of a specific
rowsum
method (defined for DelayedMatrix objects).
Examples
rowsum # note the dispatch on the 'x' arg only
#> new("standardGeneric", .Data = function (x, group, reorder = TRUE,
#> ...)
#> standardGeneric("rowsum"), generic = "rowsum", package = "S4Arrays",
#> group = list(), valueClass = character(0), signature = "x",
#> default = new("derivedDefaultMethod", .Data = function (x,
#> group, reorder = TRUE, ...)
#> UseMethod("rowsum"), target = new("signature", .Data = "ANY",
#> names = "x", package = "methods"), defined = new("signature",
#> .Data = "ANY", names = "x", package = "methods"), generic = "rowsum"),
#> skeleton = (new("derivedDefaultMethod", .Data = function (x,
#> group, reorder = TRUE, ...)
#> UseMethod("rowsum"), target = new("signature", .Data = "ANY",
#> names = "x", package = "methods"), defined = new("signature",
#> .Data = "ANY", names = "x", package = "methods"), generic = "rowsum"))(x,
#> group, reorder, ...))
#> <bytecode: 0x55f5867809b0>
#> <environment: 0x55f58677d698>
#> attr(,"generic")
#> [1] "rowsum"
#> attr(,"generic")attr(,"package")
#> [1] "S4Arrays"
#> attr(,"package")
#> [1] "S4Arrays"
#> attr(,"group")
#> list()
#> attr(,"valueClass")
#> character(0)
#> attr(,"signature")
#> [1] "x"
#> attr(,"default")
#> Method Definition (Class "derivedDefaultMethod"):
#>
#> function (x, group, reorder = TRUE, ...)
#> UseMethod("rowsum")
#> <bytecode: 0x55f5867785c0>
#> <environment: namespace:base>
#>
#> Signatures:
#> x
#> target "ANY"
#> defined "ANY"
#> attr(,"skeleton")
#> (new("derivedDefaultMethod", .Data = function (x, group, reorder = TRUE,
#> ...)
#> UseMethod("rowsum"), target = new("signature", .Data = "ANY",
#> names = "x", package = "methods"), defined = new("signature",
#> .Data = "ANY", names = "x", package = "methods"), generic = "rowsum"))(x,
#> group, reorder, ...)
#> attr(,"class")
#> [1] "standardGeneric"
#> attr(,"class")attr(,"package")
#> [1] "methods"
showMethods("rowsum")
#> Function: rowsum (package S4Arrays)
#> x="ANY"
#> x="DelayedMatrix"
#> x="SparseMatrix"
#> x="dsparseMatrix"
#>
selectMethod("rowsum", "ANY") # the default rowsum() method
#> new("derivedDefaultMethod", .Data = function (x, group, reorder = TRUE,
#> ...)
#> UseMethod("rowsum"), target = new("signature", .Data = "ANY",
#> names = "x", package = "methods"), defined = new("signature",
#> .Data = "ANY", names = "x", package = "methods"), generic = "rowsum")
#> <bytecode: 0x55f5867842e8>
#> <environment: namespace:base>
#> attr(,"target")
#> An object of class “signature”
#> x
#> "ANY"
#> attr(,"defined")
#> An object of class “signature”
#> x
#> "ANY"
#> attr(,"generic")
#> [1] "rowsum"
#> attr(,"generic")attr(,"package")
#> [1] "base"
#> attr(,"class")
#> [1] "derivedDefaultMethod"
#> attr(,"class")attr(,"package")
#> [1] "methods"
colsum # note the dispatch on the 'x' arg only
#> new("standardGeneric", .Data = function (x, group, reorder = TRUE,
#> ...)
#> standardGeneric("colsum"), generic = "colsum", package = "S4Arrays",
#> group = list(), valueClass = character(0), signature = "x",
#> default = NULL, skeleton = (function (x, group, reorder = TRUE,
#> ...)
#> stop(gettextf("invalid call in method dispatch to '%s' (no default method)",
#> "colsum"), domain = NA))(x, group, reorder, ...))
#> <bytecode: 0x55f584883e68>
#> <environment: 0x55f58488bee8>
#> attr(,"generic")
#> [1] "colsum"
#> attr(,"generic")attr(,"package")
#> [1] "S4Arrays"
#> attr(,"package")
#> [1] "S4Arrays"
#> attr(,"group")
#> list()
#> attr(,"valueClass")
#> character(0)
#> attr(,"signature")
#> [1] "x"
#> attr(,"default")
#> `\001NULL\001`
#> attr(,"skeleton")
#> (function (x, group, reorder = TRUE, ...)
#> stop(gettextf("invalid call in method dispatch to '%s' (no default method)",
#> "colsum"), domain = NA))(x, group, reorder, ...)
#> attr(,"class")
#> [1] "standardGeneric"
#> attr(,"class")attr(,"package")
#> [1] "methods"
showMethods("colsum")
#> Function: colsum (package S4Arrays)
#> x="ANY"
#> x="DelayedMatrix"
#> x="SparseMatrix"
#> x="dsparseMatrix"
#> x="matrix"
#>
selectMethod("colsum", "ANY") # the default colsum() method
#> new("MethodDefinition", .Data = function (x, group, reorder = TRUE,
#> ...)
#> t(rowsum(t(x), group, reorder = reorder, ...)), target = new("signature",
#> .Data = "ANY", names = "x", package = "methods"), defined = new("signature",
#> .Data = "ANY", names = "x", package = "methods"), generic = "colsum")
#> <bytecode: 0x55f5848755e0>
#> <environment: namespace:S4Arrays>
#> attr(,"target")
#> An object of class “signature”
#> x
#> "ANY"
#> attr(,"defined")
#> An object of class “signature”
#> x
#> "ANY"
#> attr(,"generic")
#> [1] "colsum"
#> attr(,"generic")attr(,"package")
#> [1] "S4Arrays"
#> attr(,"class")
#> [1] "MethodDefinition"
#> attr(,"class")attr(,"package")
#> [1] "methods"
selectMethod("colsum", "matrix") # colsum() method for ordinary matrices
#> new("MethodDefinition", .Data = function (x, group, reorder = TRUE,
#> ...)
#> .fast_colsum(x, group, reorder = reorder, ...), target = new("signature",
#> .Data = "matrix", names = "x", package = "methods"), defined = new("signature",
#> .Data = "matrix", names = "x", package = "methods"), generic = "colsum")
#> <bytecode: 0x55f584875ea0>
#> <environment: namespace:S4Arrays>
#> attr(,"target")
#> An object of class “signature”
#> x
#> "matrix"
#> attr(,"defined")
#> An object of class “signature”
#> x
#> "matrix"
#> attr(,"generic")
#> [1] "colsum"
#> attr(,"generic")attr(,"package")
#> [1] "S4Arrays"
#> attr(,"class")
#> [1] "MethodDefinition"
#> attr(,"class")attr(,"package")
#> [1] "methods"