##############################################################################
##############################################################################
## General rules that works:
# For non-standard generics: 1st comes export, then setGeneric, setGeneric with
# <-, empty lines, then comes export again, then generic function (here
# pheno.PAC), export, and finally comes setMethod.
#
# Non-standard generics (e.g. pheno, overview) works with "object" in
# functions, standard generics (e.g. nrow, rownames) need to have "x" in
# functions.
#
##############################################################################
##############################################################################
# Non-standard generics PAC
#
#------------------------------------------------------------------------------
#------------------------------------------------------------------------------
#' pheno(PAC)
#'
#' Access sample information in a PAC-object
#'
#' @rdname pheno
#' @family PAC methods
#' @param object A S4 PAC-object containing Pheno, Anno and Counts tables. Can
#' be generated by the 'PAC generation' family of functions, for example see
#' ?make_counts.
#' @param value Data.frame having the same row names as column names in Counts
#' (sample IDs).
#'
#' @docType methods
#' @aliases pheno, pheno, pheno<-
#' @return The Pheno data.frame table from a S4 PAC-object
#' @return Updated S4 PAC-object.
#' @examples
#'
#' load(system.file("extdata", "drosophila_sRNA_pac_filt_anno.Rdata",
#' package = "seqpac", mustWork = TRUE))
#'
#' # extra fuctionality with s4 PAC-object:
#' names(pac)
#' length(pac)
#' nrow(pac)
#' ncol(pac)
#' rownames(pac)
#' colnames(pac)
#' pheno(pac)
#' head(anno(pac))
#' head(counts(pac))
#' head(norm(pac)$cpm)
#'
#'
#' @export
setGeneric("pheno", function(object){standardGeneric("pheno")})
setGeneric("pheno<-", function(object, value){standardGeneric("pheno<-")})
pheno.PAC <- function(object){ object@Pheno }
#' @rdname pheno
#' @export
setMethod("pheno", methods::signature(object="PAC"), pheno.PAC)
#' @rdname pheno
#' @export
setReplaceMethod("pheno", methods::signature(object="PAC", value="data.frame"),
function( object, value ) {
object@Pheno <- value
methods::validObject(object)
object
})
#-----------------------------------------------------------------------------
#-----------------------------------------------------------------------------
#' anno(PAC)
#'
#' Access the annotation table in S4 PAC
#'
#' @rdname anno
#' @family PAC methods
#' @param object A S4 PAC-object containing Pheno, Anno and Counts tables. Can
#' be generated by the 'PAC generation' family of functions, for example see
#' ?make_counts.
#' @param value Data.frame having the same row names as row names in Counts
#' (sequences).
#' @docType methods
#' @aliases anno, anno, anno<-
#'
#' @return The Anno data.frame table from a PAC-object.
#' @return Updated S4 PAC-object.
#' @examples
#'
#' load(system.file("extdata", "drosophila_sRNA_pac_filt_anno.Rdata",
#' package = "seqpac", mustWork = TRUE))
#'
#' # extra fuctionality with s4 PAC-object:
#' names(pac)
#' length(pac)
#' nrow(pac)
#' ncol(pac)
#' rownames(pac)
#' colnames(pac)
#' pheno(pac)
#' head(anno(pac))
#' head(counts(pac))
#' head(norm(pac)$cpm)
#'
#' @export
#'
setGeneric("anno", function(object){standardGeneric("anno")})
setGeneric("anno<-", function(object, value){standardGeneric("anno<-")})
anno.PAC <- function(object){ object@Anno }
#' @rdname anno
#' @export
setMethod("anno", methods::signature(object="PAC"), anno.PAC)
#' @rdname anno
#' @export
setReplaceMethod("anno", methods::signature(object="PAC", value="data.frame"),
function( object, value ) {
object@Anno <- value
methods::validObject(object)
object
})
#------------------------------------------------------------------------------
#------------------------------------------------------------------------------
#' counts(PAC)
#'
#' Access the raw counts table in S4 PAC
#'
#' @rdname counts
#' @family PAC methods
#' @param object A S4 PAC-object containing Pheno, Anno and Counts tables. Can
#' be generated by the 'PAC generation' family of functions, for example see
#' ?make_counts.
#' @param value Data.frame having the same column names as row names in Pheno
#' (sample ID) and row names as row names in Anno (sequences).
#' @docType methods
#' @aliases counts, counts, counts<-
#' @return The Counts data frame table from a PAC-object.
#' @return Updated S4 PAC-object.
#'
#' @examples
#'
#' load(system.file("extdata", "drosophila_sRNA_pac_filt_anno.Rdata",
#' package = "seqpac", mustWork = TRUE))
#'
#' # extra fuctionality with s4 PAC-object:
#' names(pac)
#' length(pac)
#' nrow(pac)
#' ncol(pac)
#' rownames(pac)
#' colnames(pac)
#' pheno(pac)
#' head(anno(pac))
#' head(counts(pac))
#' head(norm(pac)$cpm)
#'
#'
#' @export
setGeneric("counts", function(object){standardGeneric("counts")})
setGeneric("counts<-", function(object, value){standardGeneric("counts<-")})
counts.PAC <- function(object){ object@Counts }
#' @rdname counts
#' @export
setMethod("counts", methods::signature(object="PAC"), counts.PAC)
#' @rdname counts
#' @export
setReplaceMethod("counts", methods::signature(object="PAC", value="data.frame"),
function( object, value ) {
object@Counts <- value
methods::validObject(object)
object
})
#------------------------------------------------------------------------------
#------------------------------------------------------------------------------
#' norm(PAC)
#'
#' Access the norm list with normalized table in S4 PAC
#'
#' @rdname norm
#' @family PAC methods
#' @param object A S4 PAC-object containing a norm list ('folder') with
#' normalized data.frames. Can be generated by the PAC_norm function.
#' @param value List of data.frames having the same column names as row names in
#' Pheno (sample ID) and row names as row names in Anno (sequences.)
#' @docType methods
#' @aliases norm, norm, norm<-
#' @return The list of normalized tables (data.frames) from a PAC-object.
#' @return Updated S4 PAC-object.
#' @examples
#'
#' load(system.file("extdata", "drosophila_sRNA_pac_filt_anno.Rdata",
#' package = "seqpac", mustWork = TRUE))
#'
#' # extra fuctionality with s4 PAC-object:
#' names(pac)
#' length(pac)
#' nrow(pac)
#' ncol(pac)
#' rownames(pac)
#' colnames(pac)
#' pheno(pac)
#' head(anno(pac))
#' head(counts(pac))
#' head(norm(pac)$cpm)
#'
#' @export
setGeneric("norm", function(object){standardGeneric("norm")})
setGeneric("norm<-", function(object, value){standardGeneric("norm<-")})
norm.PAC <- function(object){ object@norm }
#' @rdname norm
#' @export
setMethod("norm", methods::signature(object="PAC"), norm.PAC)
#' @rdname norm
#' @export
setReplaceMethod("norm", methods::signature(object="PAC", value="list"),
function( object, value ) {
object@norm <- value
methods::validObject(object)
object
})
#------------------------------------------------------------------------------
#------------------------------------------------------------------------------
#' summary(PAC)
#'
#' Access the summary list with summarized tables in S4 PAC
#'
#' @rdname summary
#' @family PAC methods
#' @param object A S4 PAC-object containing a summary list ('folder') with
#' normalized data.frames. Can be generated by the PAC_summary function.
#' @param value List of data.frames having the same row names as row names in
#' Anno (sequences).
#' @aliases summary, summary, summary<-
#' @return The list of summary tables (data.frames) from a PAC-object.
#' @return Updated S4 PAC-object.
#' @examples
#'
#' load(system.file("extdata", "drosophila_sRNA_pac_filt_anno.Rdata",
#' package = "seqpac", mustWork = TRUE))
#'
#' # extra fuctionality with s4 PAC-object:
#' names(pac)
#' length(pac)
#' nrow(pac)
#' ncol(pac)
#' rownames(pac)
#' colnames(pac)
#' pheno(pac)
#' head(anno(pac))
#' head(counts(pac))
#' head(norm(pac)$cpm)
#'
#' @export
setGeneric("summary", function(object){standardGeneric("summary")})
setGeneric("summary<-", function(object, value){standardGeneric("summary<-")})
summary.PAC <- function(object){ object@summary }
#' @rdname summary
#' @export
setMethod("summary", "PAC", summary.PAC)
#' @rdname summary
#' @export
setReplaceMethod("summary", methods::signature(object="PAC", value="list"),
function( object, value ) {
object@summary <- value
methods::validObject(object)
object
})
#------------------------------------------------------------------------------
#------------------------------------------------------------------------------
# Standard methods PAC
#------------------------------------------------------------------------------
#------------------------------------------------------------------------------
# Special case show
#
#' show(PAC)
#'
#' Overview (show method) of a S4 PAC
#'
#' @rdname show
#' @family PAC methods
#' @param object A S4 object of class PAC.
# @aliases show, show
#' @return Simple statistical overview of a PAC-object.
#' @importFrom methods as new setMethod
#' @examples
#'
#' load(system.file("extdata", "drosophila_sRNA_pac_filt_anno.Rdata",
#' package = "seqpac", mustWork = TRUE))
#'
#' # extra fuctionality with s4 PAC-object:
#' names(pac)
#' length(pac)
#' nrow(pac)
#' ncol(pac)
#' rownames(pac)
#' colnames(pac)
#' pheno(pac)
#' head(anno(pac))
#' head(counts(pac))
#' head(norm(pac)$cpm)
#'
#' @export
show.PAC <- function(object) {
pac <- as(object, "list")
cat("PAC object with: \n")
cat(" ", nrow(pac$Pheno), "samples\n")
cat(" ",nrow(pac$Anno), "sequences\n")
avg <- round(mean(colSums(pac$Counts)), digits=0)
mn <- round(min(colSums(pac$Counts)), digits=0)
mx <- round(max(colSums(pac$Counts)), digits=0)
mx_seq <- round(max(rowMeans(pac$Counts)), digits=0)
mn_seq <- round(min(rowMeans(pac$Counts)), digits=0)
cat(paste0(" mean total counts: ", avg, " (min:", mn, "/max:", mx, ")\n"))
cat(" best sequence:", mx_seq, "mean counts\n")
cat(" worst sequence:", mn_seq, "mean counts\n")
if("norm" %in% names(object)){
cat("normalized tables:", length(pac$norm),"\n")
cat(names(pac$norm),"\n")
}
if("summary" %in% names(object)){
cat("summarized tables:", length(pac$summary),"\n")
cat(names(pac$summary),"\n")
}
}
setMethod("show", signature(object="PAC"), show.PAC)
#------------------------------------------------------------------------------
# Important!!!, standard method definitions must have x and not object
# Object works well with non-standard.
#
names.PAC <- function(x){ names(as(x, "list")) }
#' @rdname names
#' @family PAC methods
#' @param x A S4 object of class PAC.
#' @return The names of the content in a PAC-object.
#' @examples
#'
#' load(system.file("extdata", "drosophila_sRNA_pac_filt_anno.Rdata",
#' package = "seqpac", mustWork = TRUE))
#'
#' # extra fuctionality with s4 PAC-object:
#' names(pac)
#' length(pac)
#' nrow(pac)
#' ncol(pac)
#' rownames(pac)
#' colnames(pac)
#' pheno(pac)
#' head(anno(pac))
#' head(counts(pac))
#' head(norm(pac)$cpm)
#'
#' @export
setMethod("names", "PAC", names.PAC)
#------------------------------------------------------------------------------
rownames.PAC <- function(x){ rownames(x@Counts) }
#' sequence names
#' @rdname rownames
#' @param x A S4 object of class PAC.
#' @return The sequences (row names) held by the Counts/Anno tables of a
#' PAC-object.
#' @examples
#'
#' load(system.file("extdata", "drosophila_sRNA_pac_filt_anno.Rdata",
#' package = "seqpac", mustWork = TRUE))
#'
#' # extra fuctionality with s4 PAC-object:
#' names(pac)
#' length(pac)
#' nrow(pac)
#' ncol(pac)
#' rownames(pac)
#' colnames(pac)
#' pheno(pac)
#' head(anno(pac))
#' head(counts(pac))
#' head(norm(pac)$cpm)
#'
#' @export
setMethod("rownames", "PAC", rownames.PAC)
#------------------------------------------------------------------------------
colnames.PAC <- function(x){colnames(x@Counts)}
#' sample names
#'
#' @rdname colnames
#' @param x A S4 object of class PAC.
#' @return The sample names held by the Counts table (column names) and the
#' Pheno table (row names) of a PAC-object.
#' @examples
#'
#' load(system.file("extdata", "drosophila_sRNA_pac_filt_anno.Rdata",
#' package = "seqpac", mustWork = TRUE))
#'
#' # extra fuctionality with s4 PAC-object:
#' names(pac)
#' length(pac)
#' nrow(pac)
#' ncol(pac)
#' rownames(pac)
#' colnames(pac)
#' pheno(pac)
#' head(anno(pac))
#' head(counts(pac))
#' head(norm(pac)$cpm)
#'
#' @export
setMethod("colnames", "PAC", colnames.PAC)
#------------------------------------------------------------------------------
length.PAC <- function(x){ length(as(x, "list")) }
#' number of objects in PAC
#' @rdname length
#' @param x A S4 object of class PAC.
#' @return The number of items in a PAC-object.
#' @examples
#'
#' load(system.file("extdata", "drosophila_sRNA_pac_filt_anno.Rdata",
#' package = "seqpac", mustWork = TRUE))
#'
#' # extra functionality with s4 PAC-object:
#' names(pac)
#' length(pac)
#' nrow(pac)
#' ncol(pac)
#' rownames(pac)
#' colnames(pac)
#' pheno(pac)
#' head(anno(pac))
#' head(counts(pac))
#' head(norm(pac)$cpm)
#'
#' @export
setMethod("length", "PAC", length.PAC)
#------------------------------------------------------------------------------
ncol.PAC <- function(x){ ncol(x@Counts) }
#' number of samples
#' @rdname ncol
#' @param x A S4 object of class PAC.
#' @return The number of samples in a PAC-object.
#' @examples
#'
#' load(system.file("extdata", "drosophila_sRNA_pac_filt_anno.Rdata",
#' package = "seqpac", mustWork = TRUE))
#'
#' # extra fuctionality with s4 PAC-object:
#' names(pac)
#' length(pac)
#' nrow(pac)
#' ncol(pac)
#' rownames(pac)
#' colnames(pac)
#' pheno(pac)
#' head(anno(pac))
#' head(counts(pac))
#' head(norm(pac)$cpm)
#'
#' @export
setMethod("ncol", "PAC", ncol.PAC)
#------------------------------------------------------------------------------
nrow.PAC <- function(x){ nrow(x@Counts) }
#' number of sequences
#' @rdname nrow
#' @param x A S4 object of class PAC.
#' @return The number of sequences in a PAC-object.
#' @examples
#'
#' load(system.file("extdata", "drosophila_sRNA_pac_filt_anno.Rdata",
#' package = "seqpac", mustWork = TRUE))
#'
#' # extra fuctionality with s4 PAC-object:
#' names(pac)
#' length(pac)
#' nrow(pac)
#' ncol(pac)
#' rownames(pac)
#' colnames(pac)
#' pheno(pac)
#' head(anno(pac))
#' head(counts(pac))
#' head(norm(pac)$cpm)
#'
#' @export
setMethod("nrow", "PAC", nrow.PAC)
###############################################################################
###############################################################################
# Non-standard generics reanno
#------------------------------------------------------------------------------
#' overview(reanno)
#'
#' Access the overview table in a S4 reanno object
#'
#' @rdname overview
#' @family reanno methods
#' @param object A S4 reanno-object containing an overview table.
#' @param value Tibble data.frame with the same property as the Overview table
#' of the reanno object, e.g. having the same names in seq column as row names
#' (sequences) in the original PAC-object used to generate the reanno object.
#' See examples and ?make_reanno for details.
#' @aliases overview, overview, overview<-
#'
#' @return The overview table of a reanno-object as a tibble data.frame (class
#' tbl_df, tbl, data.frame).
#' @return Updated reanno-object.
#' @examples
#' #########################################################
#' ##### Create a reanno object
#'
#' ## First load a PAC- object
#'
#' load(system.file("extdata", "drosophila_sRNA_pac_filt_anno.Rdata",
#' package = "seqpac", mustWork = TRUE))
#' anno(pac) <- anno(pac)[,1, drop = FALSE]
#'
#'
#' ## Then specify paths to fasta references
#' # If you are having problem see the vignette small RNA guide for more info.
#'
#' trna_path <- system.file("extdata/trna", "tRNA.fa",
#' package = "seqpac", mustWork = TRUE)
#' rrna_path <- system.file("extdata/rrna", "rRNA.fa",
#' package = "seqpac", mustWork = TRUE)
#'
#' ref_paths <- list(trna= trna_path, rrna= rrna_path)
#'
#' ## Add output path of your choice.
#' # Here we use the R temporary folder depending on platform
#'if(grepl("windows", .Platform$OS.type)){
#' output <- paste0(tempdir(), "\\seqpac\\test")
#'}else{
#' output <- paste0(tempdir(), "/seqpac/test")}
#'
#' ## Make sure it is empty (otherwise you will be prompted for a question)
#' out_fls <- list.files(output, recursive=TRUE)
#' closeAllConnections()
#' suppressWarnings(file.remove(paste(output, out_fls, sep="/")))
#'
#' ## Then map your PAC-object against the fasta references
#' map_reanno(pac, ref_paths=ref_paths, output_path=output,
#' type="internal", mismatches=2, import="biotype",
#' threads=2, keep_temp=FALSE)
#'
#' ## Then generate a reanno-object of the temporary bowtie-files
#' reanno_object <- make_reanno(output, PAC=pac, mis_fasta_check = TRUE)
#'
#'## Accessing content and S4/S3 conversion:
#' names(reanno_object)
#' overview(reanno_object)
#' full(reanno_object)
#' rownames(reanno_object)
#' length(reanno_object)
#' nrow(reanno_object)
#' reanno_s3 <- as(reanno_object, "list")
#' reanno_s4 <- as.reanno(reanno_s3)
#'
#' @export
setGeneric("overview", function(object){standardGeneric("overview")})
setGeneric("overview<-", function(object, value){standardGeneric("overview<-")})
overview.reanno <- function(object){ object@Overview }
#' @rdname overview
#' @export
setMethod("overview", "reanno", overview.reanno)
#' @rdname overview
#' @export
setReplaceMethod("overview", methods::signature(object="reanno",
value="data.frame"),
function( object, value ) {
object@Overview <- value
methods::validObject(object)
object
})
#-----------------------------------------------------------------------------
#' full(reanno)
#'
#' Access the multilevel list of imported data.frames in a S4 reanno object
#'
#' @rdname full
#' @family reanno methods
#' @param object A S4 reanno-object containing an Full_anno list.
#' @param value List of tibble data.frames with the same property as the
#' Full_anno list of tibble data.frames in the reanno object, e.g. having the
#' same names in seq column as row names (sequences) in the original
#' PAC-object used to generate the reanno object. See examples and
#' ?make_reanno for details.
#' @aliases full, full, full<-
#' @return All the results that were imported into the reanno-object returned as
#' a list of tibble data.frames (class tbl_df, tbl, data.frame).
#' @return Updated S4 reanno-object.
#' @examples
#' #########################################################
#' ##### Create a reanno object
#'
#' ## First load a PAC- object
#'
#' load(system.file("extdata", "drosophila_sRNA_pac_filt_anno.Rdata",
#' package = "seqpac", mustWork = TRUE))
#' anno(pac) <- anno(pac)[,1, drop = FALSE]
#'
#'
#' ## Then specify paths to fasta references
#' # If you are having problem see the vignette small RNA guide for more info.
#'
#' trna_path <- system.file("extdata/trna", "tRNA.fa",
#' package = "seqpac", mustWork = TRUE)
#' rrna_path <- system.file("extdata/rrna", "rRNA.fa",
#' package = "seqpac", mustWork = TRUE)
#'
#' ref_paths <- list(trna= trna_path, rrna= rrna_path)
#'
#' ## Add output path of your choice.
#' # Here we use the R temporary folder depending on platform
#'if(grepl("windows", .Platform$OS.type)){
#' output <- paste0(tempdir(), "\\seqpac\\test")
#'}else{
#' output <- paste0(tempdir(), "/seqpac/test")}
#'
#' ## Make sure it is empty (otherwise you will be prompted for a question)
#' out_fls <- list.files(output, recursive=TRUE)
#' closeAllConnections()
#' suppressWarnings(file.remove(paste(output, out_fls, sep="/")))
#'
#' ## Then map your PAC-object against the fasta references
#' map_reanno(pac, ref_paths=ref_paths, output_path=output,
#' type="internal", mismatches=2, import="biotype",
#' threads=2, keep_temp=FALSE)
#'
#' ## Then generate a reanno-object of the temporary bowtie-files
#' reanno_object <- make_reanno(output, PAC=pac, mis_fasta_check = TRUE)
#'
#'## Accessing content and S4/S3 conversion:
#' names(reanno_object)
#' overview(reanno_object)
#' full(reanno_object)
#' rownames(reanno_object)
#' length(reanno_object)
#' nrow(reanno_object)
#' reanno_s3 <- as(reanno_object, "list")
#' reanno_s4 <- as.reanno(reanno_s3)
#' @export
setGeneric("full", function(object){standardGeneric("full")})
setGeneric("full<-", function(object, value){standardGeneric("full<-")})
full.reanno <- function(object){object@Full_anno}
#' @rdname full
#' @export
setMethod("full", "reanno", full.reanno)
#' @rdname full
#' @export
setReplaceMethod("full", methods::signature(object="reanno", value="list"),
function( object, value ) {
object@Full_anno <- value
methods::validObject(object)
object
})
#-----------------------------------------------------------------------------
#-----------------------------------------------------------------------------
# Standard methods reanno
#-----------------------------------------------------------------------------
#-----------------------------------------------------------------------------
# Important!!!, standard method definitions must have "x" and not "object"
# Object works well with non-standard.
#
names.reanno <- function(x){ names(as(x, "list"))}
#' names of objects in reanno
#' @rdname names
#' @return Names of the items in the reanno-object.
#' @examples
#' #########################################################
#' ##### Create a reanno object
#'
#' ## First load a PAC- object
#'
#' load(system.file("extdata", "drosophila_sRNA_pac_filt_anno.Rdata",
#' package = "seqpac", mustWork = TRUE))
#' anno(pac) <- anno(pac)[,1, drop = FALSE]
#'
#'
#' ## Then specify paths to fasta references
#' # If you are having problem see the vignette small RNA guide for more info.
#'
#' trna_path <- system.file("extdata/trna", "tRNA.fa",
#' package = "seqpac", mustWork = TRUE)
#' rrna_path <- system.file("extdata/rrna", "rRNA.fa",
#' package = "seqpac", mustWork = TRUE)
#'
#' ref_paths <- list(trna= trna_path, rrna= rrna_path)
#'
#' ## Add output path of your choice.
#' # Here we use the R temporary folder depending on platform
#'if(grepl("windows", .Platform$OS.type)){
#' output <- paste0(tempdir(), "\\seqpac\\test")
#'}else{
#' output <- paste0(tempdir(), "/seqpac/test")}
#'
#' ## Make sure it is empty (otherwise you will be prompted for a question)
#' out_fls <- list.files(output, recursive=TRUE)
#' closeAllConnections()
#' suppressWarnings(file.remove(paste(output, out_fls, sep="/")))
#'
#' ## Then map your PAC-object against the fasta references
#' map_reanno(pac, ref_paths=ref_paths, output_path=output,
#' type="internal", mismatches=2, import="biotype",
#' threads=2, keep_temp=FALSE)
#'
#' ## Then generate a reanno-object of the temporary bowtie-files
#' reanno_object <- make_reanno(output, PAC=pac, mis_fasta_check = TRUE)
#'
#'## Accessing content and S4/S3 conversion:
#' names(reanno_object)
#' overview(reanno_object)
#' full(reanno_object)
#' rownames(reanno_object)
#' length(reanno_object)
#' nrow(reanno_object)
#' reanno_s3 <- as(reanno_object, "list")
#' reanno_s4 <- as.reanno(reanno_s3)
#' @export
setMethod("names", "reanno", names.reanno)
#------------------------------------------------------------------------------
rownames.reanno <- function(x){ dplyr::pull(x@Overview[1])}
#' sequences in reanno
#' @rdname rownames
#' @return Sequences in the reanno-object.
#' @export
setMethod("rownames", "reanno", rownames.reanno)
#------------------------------------------------------------------------------
length.reanno <- function(x){ length(as(x, "list")) }
#' length of reanno object
#' @rdname length
#' @return Number of items in the reanno-object.
#' @export
setMethod("length", "reanno", length.reanno)
#------------------------------------------------------------------------------
nrow.reanno <- function(x){ nrow(x@Overview) }
#' number of sequences
#' @rdname nrow
#' @return Number of sequences in the reanno-object.
#' @export
setMethod("nrow", "reanno", nrow.reanno)
Add the following code to your website.
For more information on customizing the embed code, read Embedding Snippets.