BiocGenerics/DESCRIPTION0000644000175200017520000000327314136065374015654 0ustar00biocbuildbiocbuildPackage: BiocGenerics Title: S4 generic functions used in Bioconductor Description: The package defines many S4 generic functions used in Bioconductor. biocViews: Infrastructure URL: https://bioconductor.org/packages/BiocGenerics BugReports: https://github.com/Bioconductor/BiocGenerics/issues Version: 0.40.0 License: Artistic-2.0 Author: The Bioconductor Dev Team Maintainer: Bioconductor Package Maintainer Depends: R (>= 4.0.0), methods, utils, graphics, stats Imports: methods, utils, graphics, stats Suggests: Biobase, S4Vectors, IRanges, GenomicRanges, DelayedArray, Biostrings, Rsamtools, AnnotationDbi, affy, affyPLM, DESeq2, flowClust, MSnbase, annotate, RUnit Collate: S3-classes-as-S4-classes.R utils.R normarg-utils.R replaceSlots.R append.R as.data.frame.R as.list.R as.vector.R cbind.R colSums.R do.call.R duplicated.R eval.R Extremes.R funprog.R get.R grep.R is.unsorted.R lapply.R mapply.R match.R mean.R nrow.R order.R paste.R rank.R rep.R row_colnames.R sets.R sort.R start.R subset.R t.R table.R tapply.R unique.R unlist.R unsplit.R relist.R var.R which.R which.min.R boxplot.R image.R density.R IQR.R mad.R residuals.R weights.R xtabs.R annotation.R combine.R dbconn.R dge.R dims.R fileName.R normalize.R Ontology.R organism_species.R path.R plotMA.R plotPCA.R score.R strand.R toTable.R type.R updateObject.R testPackage.R zzz.R git_url: https://git.bioconductor.org/packages/BiocGenerics git_branch: RELEASE_3_14 git_last_commit: 0bc1e0e git_last_commit_date: 2021-10-26 Date/Publication: 2021-10-26 NeedsCompilation: no Packaged: 2021-10-26 20:54:20 UTC; biocbuild BiocGenerics/NAMESPACE0000644000175200017520000001071514136047726015365 0ustar00biocbuildbiocbuildimport(methods) import(utils) import(graphics) import(stats) exportClasses( ## from R/S3-classes-as-S4-classes.R: connection, file, url, gzfile, bzfile, unz, pipe, fifo, sockconn, terminal, textConnection, gzcon, character_OR_connection, AsIs, #table, xtabs, dist ) ### ========================================================================== ### Export functions defined in base R and explicitly promoted to generics in ### the BiocGenerics package ### -------------------------------------------------------------------------- ### Generics for functions defined in package base: export( ## from R/append.R: append, ## from R/as.data.frame.R: as.data.frame, ## from R/as.list.R: as.list, ## from R/as.vector.R: as.vector, ## from R/cbind.R: rbind, cbind, ## from R/colSums.R: colSums, rowSums, colMeans, rowMeans, ## from R/do.call.R: do.call, ## from R/duplicated.R: duplicated, anyDuplicated, ## from R/eval.R: eval, evalq, ## from R/Extremes.R: pmax, pmin, pmax.int, pmin.int, ## from R/funprog.R: Reduce, Filter, Find, Map, Position, ## from R/get.R: get, mget, ## from R/grepl.R: grep, grepl, ## from R/is.unsorted.R: is.unsorted, ## from R/lapply.R: lapply, sapply, ## from R/mapply.R: mapply, ## from R/match.R: match, "%in%", ## from R/mean.R: mean, ## from R/nrow.R: nrow, ncol, NROW, NCOL, ## from R/order.R: order, ## from R/paste.R: paste, ## from R/rank.R: rank, ## from R/rep.R: rep.int, ## from R/row_colnames.R: rownames, "rownames<-", colnames, "colnames<-", ## from R/sets.R: union, intersect, setdiff, ## from R/sort.R: sort, ## from R/start.R: start, "start<-", end, "end<-", width, "width<-", pos, ## from R/subset.R: subset, ## from R/t.R: t, ## from R/table.R: table, ## from R/tapply.R: tapply, ## from R/unique.R: unique, ## from R/unlist.R: unlist, ## from R/unsplit.R: unsplit, ## from R/which.R: which, ## from R/which.min.R: which.min, which.max ) ### Generics for functions defined in package utils: export( ## from R/relist.R: relist ) ### Generics for functions defined in package graphics: export( ## from R/boxplot.R: boxplot, ## from R/image.R: image ) ### Generics for functions defined in package stats: export( ## from R/density.R: density, ## from R/IQR.R: IQR, ## from R/mad.R: mad, ## from R/residuals.R: residuals, ## from R/var.R: var, sd, ## from R/weights.R: weights, ## from R/xtabs.R: xtabs ) ### ========================================================================== ### Export Bioconductor specific generics and their methods ### -------------------------------------------------------------------------- export( ## from R/annotation.R: annotation, "annotation<-", ## from R/combine.R: combine, ## from R/dbconn.R: dbconn, dbfile, ## from R/dims.R: dims, nrows, ncols, ## from R/fileName.R: fileName, ## from R/normalize.R: normalize, ## from R/Ontology.R: Ontology, ## from R/organism_species.R: organism, "organism<-", species, "species<-", ## from R/path.R: path, "path<-", basename, "basename<-", dirname, "dirname<-", ## from R/plotMA.R: plotMA, ## from R/plotPCA.R: plotPCA, ## from R/score.R: score, "score<-", ## from R/strand.R: strand, "strand<-", invertStrand, ## from R/toTable.R: toTable, ## from R/type.R: type, "type<-", ## from R/updateObject.R: updateObject, updateObjectFromSlots, getObjectSlots ) exportMethods( ## from R/combine.R: combine, ## from R/updateObject.R: updateObject, ## from R/dge.R: counts, "counts<-", design, "design<-", dispTable, "dispTable<-", sizeFactors, "sizeFactors<-", conditions, "conditions<-", estimateSizeFactors, estimateDispersions, plotDispEsts, plotMA, plotPCA, ## from R/strand.R: invertStrand ) ### ========================================================================== ### Export non-generic functions ### -------------------------------------------------------------------------- export( ## from R/strand.R: unstrand ) BiocGenerics/R/0000755000175200017520000000000014136047726014343 5ustar00biocbuildbiocbuildBiocGenerics/R/Extremes.R0000644000175200017520000000165414136047726016270 0ustar00biocbuildbiocbuild### ========================================================================= ### The pmax(), pmin(), pmax.int() and pmin.int() generics ### ------------------------------------------------------------------------- ### ### Need to explicitly define those generics otherwise the implicit generics ### in package "base" would dispatch on 'na.rm'. ### ### Note that dispatching on '...' is supported starting with R 2.8.0 only. ### setGeneric() cannot be used on "max" and "min": ### > setGeneric("max", signature="...") ### Error in setGeneric("max", signature = "...") : ### ‘max’ is a primitive function; methods can be defined, but the ### generic function is implicit, and cannot be changed. #setGeneric("max", signature="...") #setGeneric("min", signature="...") setGeneric("pmax", signature="...") setGeneric("pmin", signature="...") setGeneric("pmax.int", signature="...") setGeneric("pmin.int", signature="...") BiocGenerics/R/IQR.R0000644000175200017520000000033014136047726015115 0ustar00biocbuildbiocbuild### ========================================================================= ### The IQR() generic ### ------------------------------------------------------------------------- ### setGeneric("IQR", signature="x") BiocGenerics/R/Ontology.R0000644000175200017520000000037614136047726016306 0ustar00biocbuildbiocbuild### ========================================================================= ### The Ontology() generic ### ------------------------------------------------------------------------- setGeneric("Ontology", function(object) standardGeneric("Ontology")) BiocGenerics/R/S3-classes-as-S4-classes.R0000644000175200017520000000225214136047726020727 0ustar00biocbuildbiocbuild### ========================================================================= ### S3 classes as S4 classes ### ------------------------------------------------------------------------- ### ### We register some old-style (aka S3) classes as formally defined (aka S4) ### classes. This allows S4 methods defined in Bioconductor packages to use ### them in their signatures. Note that dispatch still works without this ### registration but causes 'R CMD INSTALL' to (gently) complain. ### connection class and subclasses .connectionClasses <- c("file", "url", "gzfile", "bzfile", "unz", "pipe", "fifo", "sockconn", "terminal", "textConnection", "gzcon") apply(cbind(.connectionClasses, "connection"), 1, setOldClass, where = environment()) setClassUnion("character_OR_connection", c("character", "connection")) ### others setOldClass("AsIs") #setOldClass("xtabs", "table") # this seems to cause problems when installing # IRanges: # Warning: replacing previous import # ‘.__C__table’ when loading ‘BiocGenerics’ setOldClass("dist") BiocGenerics/R/annotation.R0000644000175200017520000000060514136047726016641 0ustar00biocbuildbiocbuild### ========================================================================= ### The annotation() and `annotation<-`() generics ### ------------------------------------------------------------------------- setGeneric("annotation", function(object, ...) standardGeneric("annotation") ) setGeneric("annotation<-", function(object, ..., value) standardGeneric("annotation<-") ) BiocGenerics/R/append.R0000644000175200017520000000071114136047726015734 0ustar00biocbuildbiocbuild### ========================================================================= ### The append() generic ### ------------------------------------------------------------------------- ### ### Need to explicitly define this generic otherwise the implicit generic in ### package "base" would dispatch on ('x', 'values', 'after'). Here we set ### dispatch on the first two args (the 'x' and 'values' args) only! setGeneric("append", signature=c("x", "values")) BiocGenerics/R/as.data.frame.R0000644000175200017520000000042714136047726017075 0ustar00biocbuildbiocbuild### ========================================================================= ### The as.data.frame() generic ### ------------------------------------------------------------------------- ### ### base::as.data.frame is an S3 generic. setGeneric("as.data.frame", signature="x") BiocGenerics/R/as.list.R0000644000175200017520000000036614136047726016050 0ustar00biocbuildbiocbuild### ========================================================================= ### The as.list() generic ### ------------------------------------------------------------------------- ### ### base::as.list is an S3 generic. setGeneric("as.list") BiocGenerics/R/as.vector.R0000644000175200017520000000064214136047726016374 0ustar00biocbuildbiocbuild### ========================================================================= ### The as.vector() generic ### ------------------------------------------------------------------------- ### ### Need to explicitly define this generic otherwise the implicit generic in ### package "base" would dispatch on ('x', 'mode'). Here we set dispatch on ### the 1st arg (the 'x' arg) only! setGeneric("as.vector", signature="x") BiocGenerics/R/boxplot.R0000644000175200017520000000037214136047726016157 0ustar00biocbuildbiocbuild### ========================================================================= ### The boxplot() generic ### ------------------------------------------------------------------------- ### ### graphics::boxplot is an S3 generic. setGeneric("boxplot") BiocGenerics/R/cbind.R0000644000175200017520000000075014136047726015547 0ustar00biocbuildbiocbuild### ========================================================================= ### The cbind() and rbind() generics ### ------------------------------------------------------------------------- ### ### Need to explicitly define those generics otherwise the implicit generics ### in package "base" would dispatch on 'deparse.level'. ### ### Note that dispatching on '...' is supported starting with R 2.8.0 only. setGeneric("cbind", signature="...") setGeneric("rbind", signature="...") BiocGenerics/R/colSums.R0000644000175200017520000000044314136047726016114 0ustar00biocbuildbiocbuild### ========================================================================= ### Row-level and column-level summary ### ------------------------------------------------------------------------- ### setGeneric("colSums") setGeneric("rowSums") setGeneric("colMeans") setGeneric("rowMeans") BiocGenerics/R/combine.R0000644000175200017520000001467114136047726016113 0ustar00biocbuildbiocbuild### ========================================================================= ### The combine() generic ### ------------------------------------------------------------------------- ### ### A "combine" default method + methods for some standard types are ### also provided. ### setGeneric("combine", function(x, y, ...) { if (length(list(...)) > 0L) { combine(x, do.call(combine, list(y, ...))) } else { standardGeneric("combine") } } ) setMethod("combine", c("ANY", "missing"), function(x, y, ...) x) setMethod("combine", c("data.frame", "data.frame"), function(x, y, ...) { if (all(dim(x) == 0L) && all(dim(y) == 0L)) return(x) else if (all(dim(x) == 0L)) return(y) else if (all(dim(y) == 0L)) return(x) uniqueRows <- unique(c(row.names(x), row.names(y))) uniqueCols <- unique(c(names(x), names(y))) sharedCols <- intersect(names(x), names(y)) ## check possible to combine alleq <- function(x, y) { res <- all.equal(x, y, check.attributes=FALSE) if (!is.logical(res)) { warning(res) FALSE } else TRUE } sharedRows <- intersect(row.names(x), row.names(y)) ok <- sapply(sharedCols, function(nm) { if (!all(class(x[[nm]]) == class(y[[nm]]))) return(FALSE) switch(class(x[[nm]])[[1L]], factor={ if (!alleq(levels(x[[nm]]), levels(y[[nm]]))) { warning("data frame column '", nm, "' levels not all.equal", call.=FALSE) TRUE } else if (!alleq(x[sharedRows, nm, drop=FALSE], y[sharedRows, nm, drop=FALSE])) { warning("data frame column '", nm, "' shared rows not all equal", call.=FALSE) FALSE } else TRUE }, ## ordered and non-factor columns need to ## satisfy the following identity; it seems ## possible that ordered could be treated ## differently, but these have not been ## encountered. ordered=, if (!alleq(x[sharedRows, nm, drop=FALSE], y[sharedRows, nm, drop=FALSE])) { warning("data frame column '", nm, "' shared rows not all equal") FALSE } else TRUE) }) if (!all(ok)) stop("data.frames contain conflicting data:", "\n\tnon-conforming colname(s): ", paste(sharedCols[!ok], collapse=", ")) ## x or y with zero rows -- make palatable to merge, but drop ## before return if (length(uniqueRows) == 0L) { x <- x["tmp",,drop=FALSE] y <- y["tmp",,drop=FALSE] } else if (nrow(x) == 0L) { x <- x[row.names(y),,drop=FALSE] row.names(x) <- row.names(y) } else if (nrow(y) == 0L) { y <- y[row.names(x),,drop=FALSE] row.names(y) <- row.names(x) } ## make colnames of merged data robust if (length(uniqueCols) > 0L) extLength <- max(nchar(sub(".*\\.", "", uniqueCols))) + 1L else extLength <- 1L extX <- paste(c(".", rep("x", extLength)), collapse="") extY <- paste(c(".", rep("y", extLength)), collapse="") z <- merge(x, y, by="row.names", all=TRUE, suffixes=c(extX, extY)) ## shared cols for (nm in sharedCols) { nmx <- paste(nm, extX, sep="") nmy <- paste(nm, extY, sep="") z[[nm]] <- switch(class(z[[nmx]])[[1]], AsIs=I(ifelse(is.na(z[[nmx]]), z[[nmy]], z[[nmx]])), factor={ col <- ifelse(is.na(z[[nmx]]), as.character(z[[nmy]]), as.character(z[[nmx]])) if (!identical(levels(z[[nmx]]), levels(z[[nmy]]))) factor(col) else factor(col, levels=levels(z[[nmx]])) }, { col <- ifelse(is.na(z[[nmx]]), z[[nmy]], z[[nmx]]) class(col) <- class(z[[nmx]]) col }) } ## tidy row.names(z) <- if (is.integer(attr(x, "row.names")) && is.integer(attr(y, "row.names"))) as.integer(z$Row.names) else z$Row.names z$Row.names <- NULL z[uniqueRows, uniqueCols, drop=FALSE] } ) setMethod("combine", c("matrix", "matrix"), function(x, y, ...) { if (length(y) == 0L) return(x) else if (length(x) == 0L) return(y) if (mode(x) != mode(y)) stop("matrix modes ", mode(x), ", ", mode(y), " differ") if (typeof(x) != typeof(y)) warning("matrix typeof ", typeof(x), ", ", typeof(y), " differ") xdim <- dimnames(x) ydim <- dimnames(y) if (is.null(xdim) || is.null(ydim) || any(sapply(xdim, is.null)) || any(sapply(ydim, is.null))) stop("matricies must have dimnames for 'combine'") sharedRows <- intersect(xdim[[1L]], ydim[[1L]]) sharedCols <- intersect(xdim[[2L]], ydim[[2L]]) ok <- all.equal(x[sharedRows, sharedCols], y[sharedRows, sharedCols]) if (!isTRUE(ok)) stop("matrix shared row and column elements differ: ", ok) unionRows <- union(xdim[[1L]], ydim[[1L]]) unionCols <- union(xdim[[2L]], ydim[[2L]]) m <- matrix(new(class(as.vector(x))), nrow=length(unionRows), ncol=length(unionCols), dimnames=list(unionRows, unionCols)) m[rownames(x), colnames(x)] <- x m[rownames(y), colnames(y)] <- y m } ) BiocGenerics/R/dbconn.R0000644000175200017520000000050114136047726015725 0ustar00biocbuildbiocbuild### ========================================================================= ### The dbconn() and dbfile() generics ### ------------------------------------------------------------------------- ### setGeneric("dbconn", function(x) standardGeneric("dbconn")) setGeneric("dbfile", function(x) standardGeneric("dbfile")) BiocGenerics/R/density.R0000644000175200017520000000036714136047726016153 0ustar00biocbuildbiocbuild### ========================================================================= ### The density() generic ### ------------------------------------------------------------------------- ### ### stats::density is an S3 generic. setGeneric("density") BiocGenerics/R/dge.R0000644000175200017520000000236614136047726015234 0ustar00biocbuildbiocbuild# Currently, these are for DESeq and DEXSeq. Could be extended to a more general # infrastructure for count datasets. setGeneric("counts", function(object, ...) standardGeneric("counts")) setGeneric("counts<-", function(object, ..., value) standardGeneric("counts<-")) setGeneric("dispTable", function(object, ...) standardGeneric("dispTable")) setGeneric("dispTable<-", function(object, ..., value) standardGeneric("dispTable<-")) setGeneric("sizeFactors", function(object, ...) standardGeneric("sizeFactors")) setGeneric("sizeFactors<-", function(object, ..., value) standardGeneric("sizeFactors<-")) setGeneric("conditions", function(object, ...) standardGeneric("conditions")) setGeneric("conditions<-", function(object, ..., value) standardGeneric("conditions<-")) setGeneric("design", function(object, ...) standardGeneric("design")) setGeneric("design<-", function(object, ..., value) standardGeneric("design<-")) setGeneric("estimateSizeFactors", function(object, ...) standardGeneric("estimateSizeFactors")) setGeneric("estimateDispersions", function(object, ...) standardGeneric("estimateDispersions")) setGeneric("plotDispEsts", function(object, ...) standardGeneric("plotDispEsts")) BiocGenerics/R/dims.R0000644000175200017520000000075114136047726015425 0ustar00biocbuildbiocbuild### ========================================================================= ### The dims(), nrows() and ncols() generics ### ------------------------------------------------------------------------- ### setGeneric("dims", signature="x", function(x, use.names=TRUE) standardGeneric("dims") ) setGeneric("nrows", signature="x", function(x, use.names=TRUE) standardGeneric("nrows") ) setGeneric("ncols", signature="x", function(x, use.names=TRUE) standardGeneric("ncols") ) BiocGenerics/R/do.call.R0000644000175200017520000000065014136047726016003 0ustar00biocbuildbiocbuild### ========================================================================= ### The do.call() generic ### ------------------------------------------------------------------------- ### Need to explicitly define this generic otherwise the implicit generic in ### package "base" would dispatch on all its arguments. Here we set dispatch ### on the 1st and 2nd args only! setGeneric("do.call", signature=c("what", "args")) BiocGenerics/R/duplicated.R0000644000175200017520000000076114136047726016610 0ustar00biocbuildbiocbuild### ========================================================================= ### The duplicated() and anyDuplicated() generics ### ------------------------------------------------------------------------- ### ### Need to explicitly define those generics otherwise the implicit generics ### in package "base" would dispatch on ('x', 'incomparables'). Here we set ### dispatch on the 1st arg (the 'x' arg) only! setGeneric("duplicated", signature="x") setGeneric("anyDuplicated", signature="x") BiocGenerics/R/eval.R0000644000175200017520000000161714136047726015422 0ustar00biocbuildbiocbuild### ========================================================================= ### The eval() generic ### ------------------------------------------------------------------------- ### ### Need to explicitly define this generic otherwise the implicit generic in ### package "base" would dispatch on all its arguments. Here we set dispatch ### on the first two args (the 'expr' and 'envir' args) only! setGeneric("eval", signature=c("expr", "envir"), function(expr, envir=parent.frame(), enclos=if (is.list(envir) || is.pairlist(envir)) parent.frame() else baseenv()) { force(envir) force(enclos) standardGeneric("eval") } ) evalq <- function(expr, envir = parent.frame(), enclos = if (is.list(envir) || is.pairlist(envir)) parent.frame() else baseenv()) eval(substitute(expr), envir, enclos) BiocGenerics/R/fileName.R0000644000175200017520000000040314136047726016203 0ustar00biocbuildbiocbuild### ========================================================================= ### The fileName() generic ### ------------------------------------------------------------------------- setGeneric("fileName", function(object, ...) standardGeneric("fileName")) BiocGenerics/R/funprog.R0000644000175200017520000000126614136047726016153 0ustar00biocbuildbiocbuild### ========================================================================= ### The Reduce(), Filter(), Find(), Map() and Position() generics ### ------------------------------------------------------------------------- ### ### Need to explicitly define those generics otherwise the implicit generics ### in package "base" would dispatch on all their arguments. Here we set ### dispatch on the 2nd arg (the 'x' or '...' arg) only! setGeneric("Reduce", signature="x") setGeneric("Filter", signature="x") setGeneric("Find", signature="x") ### Note that dispatching on '...' is supported starting with R 2.8.0 only. setGeneric("Map", signature="...") setGeneric("Position", signature="x") BiocGenerics/R/get.R0000644000175200017520000000106614136047726015250 0ustar00biocbuildbiocbuild### ========================================================================= ### The get() and mget() generics ### ------------------------------------------------------------------------- ### ### Need to explicitly define those generics otherwise the implicit generics ### in package "base" would dispatch on all their arguments. Here we set ### dispatch on the first 3 args ('x', 'pos', 'envir') for get(), and on the ### first 2 args ('x', 'envir') for mget(). setGeneric("get", signature=c("x", "pos", "envir")) setGeneric("mget", signature=c("x", "envir")) BiocGenerics/R/grep.R0000644000175200017520000000076414136047726015432 0ustar00biocbuildbiocbuild### ========================================================================= ### The grep() and grepl() generics ### ------------------------------------------------------------------------- ### ### Need to explicitly define those generics otherwise the implicit generics ### in package "base" would dispatch on all their arguments. Here we set ### dispatch on the first 2 args ('pattern', 'x'). setGeneric("grep", signature = c("pattern", "x")) setGeneric("grepl", signature = c("pattern", "x")) BiocGenerics/R/image.R0000644000175200017520000000036414136047726015553 0ustar00biocbuildbiocbuild### ========================================================================= ### The image() generic ### ------------------------------------------------------------------------- ### ### graphics::image is an S3 generic. setGeneric("image") BiocGenerics/R/is.unsorted.R0000644000175200017520000000133414136047726016744 0ustar00biocbuildbiocbuild### ========================================================================= ### The is.unsorted() generic ### ------------------------------------------------------------------------- ### base::is.unsorted() doesn't have the ellipsis. We add it to the generic ### function defined below so methods can support additional arguments (e.g. ### the 'ignore.strand' argument for the method for GenomicRanges objects). .is.unsorted.useAsDefault <- function(x, na.rm=FALSE, strictly=FALSE, ...) base::is.unsorted(x, na.rm=na.rm, strictly=strictly, ...) setGeneric("is.unsorted", signature="x", function(x, na.rm=FALSE, strictly=FALSE, ...) standardGeneric("is.unsorted"), useAsDefault=.is.unsorted.useAsDefault ) BiocGenerics/R/lapply.R0000644000175200017520000000073014136047726015767 0ustar00biocbuildbiocbuild### ========================================================================= ### The lapply() and sapply() generics ### ------------------------------------------------------------------------- ### ### Need to explicitly define those generics otherwise the implicit generics ### in package "base" would dispatch on all their arguments. Here we set ### dispatch on the 1st arg (the 'X' arg) only! setGeneric("lapply", signature="X") setGeneric("sapply", signature="X") BiocGenerics/R/mad.R0000644000175200017520000000036714136047726015235 0ustar00biocbuildbiocbuild### ========================================================================= ### The mad() generic ### ------------------------------------------------------------------------- ### ### Dispatches only on 'x' ### setGeneric("mad", signature="x") BiocGenerics/R/mapply.R0000644000175200017520000000076414136047726015777 0ustar00biocbuildbiocbuild### ========================================================================= ### The mapply() generic ### ------------------------------------------------------------------------- ### ### Need to explicitly define this generic otherwise the implicit generic in ### package "base" would dispatch on all its arguments. Here we set dispatch ### on the 2nd arg (the '...' arg) only! ### ### Note that dispatching on '...' is supported starting with R 2.8.0 only. setGeneric("mapply", signature="...") BiocGenerics/R/match.R0000644000175200017520000000143214136047726015562 0ustar00biocbuildbiocbuild### ========================================================================= ### The match() generic ### ------------------------------------------------------------------------- ### ### base::match() doesn't have the ... argument. We add it to the generic ### function defined here. We also set dispatch on the first two args (the ### 'x' and 'table' args) only! .match.useAsDefault <- function(x, table, nomatch=NA_integer_, incomparables=NULL, ...) base::match(x, table, nomatch=nomatch, incomparables=incomparables, ...) setGeneric("match", signature=c("x", "table"), function(x, table, nomatch=NA_integer_, incomparables=NULL, ...) standardGeneric("match"), useAsDefault=.match.useAsDefault ) setGeneric("%in%", function(x, table) standardGeneric("%in%")) BiocGenerics/R/mean.R0000644000175200017520000000031314136047726015403 0ustar00biocbuildbiocbuild### ------------------------------------------------------------------------- ### The mean() generic ### ------------------------------------------------------------------------- ### setGeneric("mean") BiocGenerics/R/normalize.R0000644000175200017520000000041414136047726016465 0ustar00biocbuildbiocbuild### ========================================================================= ### The normalize() generic ### ------------------------------------------------------------------------- setGeneric("normalize", function(object, ...) standardGeneric("normalize") ) BiocGenerics/R/normarg-utils.R0000644000175200017520000000307614136047726017277 0ustar00biocbuildbiocbuild### ========================================================================= ### Utility functions for checking/fixing user-supplied arguments ### ------------------------------------------------------------------------- ### NOTE: The stuff in this file (not exported) is a copy/paste of some of ### the functions in S4Vectors but it doesn't really belong to BiocGenerics. ### It seems that the only reason for having it duplicated here is that it's ### used by the stuff in the update-utils.R file. However the stuff in ### update-utils.R doesn't really belong to BiocGenerics either! ### ### TODO: This stuff would need to be moved to a more appropriate place (when ### we have one), and then we should get rid of the duplication between the ### functions below and the same functions in S4Vectors. ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ### For checking only. ### isTRUEorFALSE <- function(x) { is.logical(x) && length(x) == 1L && !is.na(x) } ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ### Handling variadic calls ### extraArgsAsList <- function(.valid.argnames, ...) { args <- list(...) argnames <- names(args) if (length(args) != 0L && (is.null(argnames) || any(argnames %in% c("", NA)))) stop("all extra arguments must be named") if (!is.null(.valid.argnames) && !all(argnames %in% .valid.argnames)) stop("valid extra argument names are ", paste("'", .valid.argnames, "'", sep="", collapse=", ")) if (anyDuplicated(argnames)) stop("argument names must be unique") args } BiocGenerics/R/nrow.R0000644000175200017520000000056614136047726015462 0ustar00biocbuildbiocbuild### ========================================================================= ### The nrow(), ncol(), NROW() and NCOL() generics ### ------------------------------------------------------------------------- ### The corresponding functions are standard functions defined in the base ### package. setGeneric("nrow") setGeneric("ncol") setGeneric("NROW") setGeneric("NCOL") BiocGenerics/R/order.R0000644000175200017520000000070614136047726015604 0ustar00biocbuildbiocbuild### ========================================================================= ### The order() generic ### ------------------------------------------------------------------------- ### ### Need to explicitly define this generic otherwise the implicit generic in ### package "base" would dispatch on ('na.last', 'decreasing', 'method'). ### ### Note that dispatching on '...' is supported starting with R 2.8.0 only. setGeneric("order", signature="...") BiocGenerics/R/organism_species.R0000644000175200017520000000110314136047726020013 0ustar00biocbuildbiocbuild### ========================================================================= ### The organism(), `organism<-`(), species(), and `species<-`() generics ### ------------------------------------------------------------------------- setGeneric("organism", function(object) standardGeneric("organism")) setGeneric("organism<-", signature="object", function(object, value) standardGeneric("organism<-") ) setGeneric("species", function(object) standardGeneric("species")) setGeneric("species<-", signature="object", function(object, value) standardGeneric("species<-") ) BiocGenerics/R/paste.R0000644000175200017520000000066614136047726015612 0ustar00biocbuildbiocbuild### ========================================================================= ### The paste() generic ### ------------------------------------------------------------------------- ### ### Need to explicitly define this generic otherwise the implicit generic in ### package "base" would dispatch on ('sep', 'collapse'). ### ### Note that dispatching on '...' is supported starting with R 2.8.0 only. setGeneric("paste", signature="...") BiocGenerics/R/path.R0000644000175200017520000001071414136047726015425 0ustar00biocbuildbiocbuild### ========================================================================= ### The path(), basename(), and dirname() getters/setters ### ------------------------------------------------------------------------- ### ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ### path() getter and setter ### setGeneric("path", function(object, ...) standardGeneric("path")) setGeneric("path<-", signature="object", function(object, ..., value) standardGeneric("path<-") ) ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ### basename() and dirname() getters and setters ### ### The basename() and dirname() functions defined in the base package ### only take 1 argument. We add the ... argument to the generic functions ### defined here so they can be called with additional arguments. ### .basename.useAsDefault <- function(path, ...) base::basename(path, ...) setGeneric("basename", function(path, ...) standardGeneric("basename"), useAsDefault=.basename.useAsDefault ) setGeneric("basename<-", signature="path", function(path, ..., value) standardGeneric("basename<-") ) .dirname.useAsDefault <- function(path, ...) base::dirname(path, ...) setGeneric("dirname", function(path, ...) standardGeneric("dirname"), useAsDefault=.dirname.useAsDefault ) setGeneric("dirname<-", signature="path", function(path, ..., value) standardGeneric("dirname<-") ) ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ### Default basename() and dirname() getters ### ### The purpose of these methods is to make the basename() and dirname() ### getters work out-of-the-box on any object for which the path() ### getter works. ### setMethod("basename", "ANY", function(path, ...) { ## If 'path' inherits from character (e.g. 'path' is a glue object ## as returned by something like 'glue::glue("some/path")'), we must ## return 'base::basename(path)'. ## See https://github.com/Bioconductor/BiocGenerics/issues/10 if (is.character(path) || !is.object(path)) { ## We intentionally pass ... to cause failure if additional ## arguments were supplied. base::basename(path, ...) } else { base::basename(path(path, ...)) } } ) setMethod("dirname", "ANY", function(path, ...) { ## If 'path' inherits from character (e.g. 'path' is a glue object ## as returned by something like 'glue::glue("some/path")'), we must ## return 'base::dirname(path)'. if (is.character(path) || !is.object(path)) { ## We intentionally pass ... to cause failure if additional ## arguments were supplied. base::dirname(path, ...) } else { base::dirname(path(path, ...)) } } ) ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ### Default basename() and dirname() setters ### ### The purpose of these replacement methods is to make the basename() and ### dirname() setters work out-of-the-box on any object for which the path() ### getter and setter work. ### setReplaceMethod("basename", "character", function(path, ..., value) { if (length(list(...)) != 0L) { dots <- match.call(expand.dots=FALSE)[[3L]] stop(unused_arguments_msg(dots)) } path_len <- length(path) path <- setNames(file.path(dirname(path), value), names(path)) if (length(path) != path_len) stop("number of supplied basenames is incompatible ", "with number of paths") path } ) setReplaceMethod("basename", "ANY", function(path, ..., value) { ppath <- path(path) basename(ppath, ...) <- value path(path) <- ppath path } ) setReplaceMethod("dirname", "character", function(path, ..., value) { if (length(list(...)) != 0L) { dots <- match.call(expand.dots=FALSE)[[3L]] stop(unused_arguments_msg(dots)) } path_len <- length(path) path <- setNames(file.path(value, basename(path)), names(path)) if (length(path) != path_len) stop("number of supplied dirnames is incompatible ", "with number of paths") path } ) setReplaceMethod("dirname", "ANY", function(path, ..., value) { ppath <- path(path) dirname(ppath, ...) <- value path(path) <- ppath path } ) BiocGenerics/R/plotMA.R0000644000175200017520000000102514136047726015660 0ustar00biocbuildbiocbuildsetGeneric("plotMA", function(object, ...) { standardGeneric("plotMA") }) setMethod("plotMA", signature="ANY", definition = function(object, ...) { msg = sprintf("Error from the generic function 'plotMA' defined in package 'BiocGenerics': no S4 method definition for argument '%s' of class '%s' was found. Did you perhaps mean calling the function 'plotMA' from another package, e.g. 'limma'? In that case, please use the syntax 'limma::plotMA'.", deparse(substitute(object)), class(object)) stop(msg) }) BiocGenerics/R/plotPCA.R0000644000175200017520000000012014136047726015761 0ustar00biocbuildbiocbuildsetGeneric("plotPCA", function(object, ...) { standardGeneric("plotPCA") }) BiocGenerics/R/rank.R0000644000175200017520000000146714136047726015431 0ustar00biocbuildbiocbuild### ========================================================================= ### The rank() generic ### ------------------------------------------------------------------------- ### ### base::rank() doesn't have the ellipsis. We add it to the generic ### function defined below so methods can support additional arguments (e.g. ### the 'ignore.strand' argument for the method for GenomicRanges objects). .is.rank.useAsDefault <- function(x, na.last=TRUE, ties.method=c("average", "first", "last", "random", "max", "min"), ...) { base::rank(x, na.last=na.last, ties.method=ties.method, ...) } setGeneric("rank", signature="x", function(x, na.last=TRUE, ties.method=c("average", "first", "last", "random", "max", "min"), ...) standardGeneric("rank"), useAsDefault=.is.rank.useAsDefault ) BiocGenerics/R/relist.R0000644000175200017520000000036414136047726015773 0ustar00biocbuildbiocbuild### ========================================================================= ### The relist() generic ### ------------------------------------------------------------------------- ### ### utils::relist is an S3 generic. setGeneric("relist") BiocGenerics/R/rep.R0000644000175200017520000000031614136047726015254 0ustar00biocbuildbiocbuild### ========================================================================= ### The rep.int() generic ### ------------------------------------------------------------------------- setGeneric("rep.int") BiocGenerics/R/replaceSlots.R0000644000175200017520000000516414136047726017134 0ustar00biocbuildbiocbuild### ========================================================================= ### Efficient multiple slots replacement of an S4 object ### ------------------------------------------------------------------------- ### ### From a caller point of views, replacement of the slots should feel atomic ### i.e. the object gets validated only after all the slots have been replaced. ### ### NOTE: The stuff in this file (not exported) doesn't really belong to ### BiocGenerics. ### ### TODO: This stuff would need to be moved to a more appropriate place (when ### we have one). ### unsafe_replaceSlots <- function(object, ..., .slotList=list()) { ## This function is no longer 'unsafe', in that it does not do ## in-place modification via `slot<-()`; see ## https://github.com/Bioconductor/BiocGenerics/pull/1 slots <- c(list(...), .slotList) slots_names <- names(slots) ## This is too slow. See further down for a much faster way to check ## that the supplied slots exist. #invalid_idx <- which(!(slots_names %in% slotNames(object))) #if (length(invalid_idx) != 0L) { # in1string <- paste0(slots_names[invalid_idx], collapse=", ") # stop(wmsg("invalid slot(s) for ", class(object), " instance: ", # in1string)) #} for (i in seq_along(slots)) { slot_name <- slots_names[[i]] if (slot_name == "mcols") slot_name <- "elementMetadata" ## Even if we won't make any use of 'old_slot_val', this is a very ## efficient way to check that the supplied slot exists. ## We need to check this because the slot() setter won't raise an error ## in case of invalid slot name when used with 'check=FALSE'. It will ## silently be a no-op! old_slot_val <- slot(object, slot_name) # check slot existence slot_val <- slots[[i]] ## Too risky! identical() is not reliable enough e.g. with objects ## that contain external pointers. For example, DNAStringSet("A") ## and DNAStringSet("T") are considered to be identical! identical() ## would first need to be fixed. #if (identical(old_slot_val, slot_val)) # next slot(object, slot_name, check=FALSE) <- slot_val } object } ### replaceSlots() is essentially a more efficient initialize(), especially ### when called with 'check=FALSE'. replaceSlots <- function(object, ..., check=TRUE) { if (!isTRUEorFALSE(check)) stop("'check' must be TRUE or FALSE") object <- unsafe_replaceSlots(object, ...) if (check) validObject(object) object } updateS4 <- function(...) { .Defunct("replaceSlots") } BiocGenerics/R/residuals.R0000644000175200017520000000037514136047726016466 0ustar00biocbuildbiocbuild### ========================================================================= ### The residuals() generic ### ------------------------------------------------------------------------- ### ### stats::residuals is an S3 generic. setGeneric("residuals") BiocGenerics/R/row_colnames.R0000644000175200017520000000065614136047726017165 0ustar00biocbuildbiocbuild### ========================================================================= ### The rownames() and colnames() generics ### ------------------------------------------------------------------------- ### ### Dispatch on the 1st arg (the 'x' arg) only! setGeneric("rownames", signature="x") setGeneric("rownames<-") ### Dispatch on the 1st arg (the 'x' arg) only! setGeneric("colnames", signature="x") setGeneric("colnames<-") BiocGenerics/R/score.R0000644000175200017520000000054514136047726015605 0ustar00biocbuildbiocbuild### ========================================================================= ### The score() and `score<-`() generics ### ------------------------------------------------------------------------- setGeneric("score", function(x, ...) standardGeneric("score")) setGeneric("score<-", signature="x", function(x, ..., value) standardGeneric("score<-") ) BiocGenerics/R/sets.R0000644000175200017520000000204614136047726015446 0ustar00biocbuildbiocbuild### ========================================================================= ### The union(), intersect() and setdiff() generics ### ------------------------------------------------------------------------- ### ### The default methods (defined in the base package) only take 2 arguments. ### We add the ... argument to the generic functions defined here so they can ### be called with an arbitrary number of effective arguments. See the \note ### section in ?BiocGenerics::union for the motivations. .union.useAsDefault <- function(x, y, ...) base::union(x, y, ...) .intersect.useAsDefault <- function(x, y, ...) base::intersect(x, y, ...) .setdiff.useAsDefault <- function(x, y, ...) base::setdiff(x, y, ...) setGeneric("union", function(x, y, ...) standardGeneric("union"), useAsDefault=.union.useAsDefault ) setGeneric("intersect", function(x, y, ...) standardGeneric("intersect"), useAsDefault=.intersect.useAsDefault ) setGeneric("setdiff", function(x, y, ...) standardGeneric("setdiff"), useAsDefault=.setdiff.useAsDefault ) BiocGenerics/R/sort.R0000644000175200017520000000037414136047726015461 0ustar00biocbuildbiocbuild### ========================================================================= ### The sort() generic ### ------------------------------------------------------------------------- ### ### base::sort is an S3 generic. setGeneric("sort", signature="x") BiocGenerics/R/start.R0000644000175200017520000000135514136047726015627 0ustar00biocbuildbiocbuild### ========================================================================= ### The start(), end(), width(), and pos() generic getters and setters ### ------------------------------------------------------------------------- ### ### stats::start and stats::end are S3 generics. ### setGeneric("start") setGeneric("start<-", signature="x", function(x, ..., value) standardGeneric("start<-") ) setGeneric("end") setGeneric("end<-", signature="x", function(x, ..., value) standardGeneric("end<-") ) setGeneric("width", function(x) standardGeneric("width")) setGeneric("width<-", signature="x", function(x, ..., value) standardGeneric("width<-") ) ### No pos() setter for now. setGeneric("pos", function(x) standardGeneric("pos")) BiocGenerics/R/strand.R0000644000175200017520000000111714136047726015761 0ustar00biocbuildbiocbuild### ========================================================================= ### The strand() and `strand<-`() generics ### ------------------------------------------------------------------------- setGeneric("strand", function(x, ...) standardGeneric("strand")) setGeneric("strand<-", function(x, ..., value) standardGeneric("strand<-")) unstrand <- function(x) { strand(x) <- "*" x } setGeneric("invertStrand", function(x) standardGeneric("invertStrand")) setMethod("invertStrand", "ANY", function(x) { strand(x) <- invertStrand(strand(x)) x } ) BiocGenerics/R/subset.R0000644000175200017520000000036314136047726015775 0ustar00biocbuildbiocbuild### ========================================================================= ### The subset() generic ### ------------------------------------------------------------------------- ### ### base::subset is an S3 generic. setGeneric("subset") BiocGenerics/R/t.R0000644000175200017520000000030514136047726014727 0ustar00biocbuildbiocbuild### ------------------------------------------------------------------------- ### The t() generic ### ------------------------------------------------------------------------- ### setGeneric("t") BiocGenerics/R/table.R0000644000175200017520000000203714136047726015557 0ustar00biocbuildbiocbuild### ========================================================================= ### The table() generic ### ------------------------------------------------------------------------- ### base::table() has a broken signature (list.names() is a function ### defined *inside* the body of base::table() so the default value for the ### 'dnn' arg is an expression that cannot be evaluated *outside* the ### base::table environment, this is poor design), we cannot keep all the ### extra arguments in the table() generic (those extra arguments are ugly ### and nobody uses them anyway). #setGeneric("table", signature="...", # function(..., exclude = if (useNA == "no") c(NA, NaN), # useNA = c("no", "ifany", "always"), # dnn = list.names(...), # deparse.level = 1) # standardGeneric("table") #) ### So we use this instead. .table.useAsDefault <- function(...) base::table(...) setGeneric("table", signature="...", function(...) standardGeneric("table"), useAsDefault=.table.useAsDefault ) BiocGenerics/R/tapply.R0000644000175200017520000000064714136047726016006 0ustar00biocbuildbiocbuild### ========================================================================= ### The tapply() generic ### ------------------------------------------------------------------------- ### ### Need to explicitly define this generic otherwise the implicit generic in ### package "base" would dispatch on all its arguments. Here we set dispatch ### on the 1st and 2nd args only! setGeneric("tapply", signature=c("X", "INDEX")) BiocGenerics/R/testPackage.R0000644000175200017520000000644714136047726016734 0ustar00biocbuildbiocbuild### packageRoot <- function(path) { hasDescription <- function(path) { file.exists(file.path(path, "DESCRIPTION")) } isRoot <- function(path) { identical(path, dirname(path)) } while (!hasDescription(path) && !isRoot(path)) { path <- dirname(path) } if (isRoot(path)) { NULL } else { path } } packageInfo <- function(path) { as.data.frame(read.dcf(file.path(path, "DESCRIPTION")), stringsAsFactors=FALSE) } testPackage <- function(pkgname = NULL, subdir="unitTests", pattern="^test_.*\\.R$", path = getwd()) { .failure_details <- function(result) { res <- result[[1L]] if (res$nFail > 0 || res$nErr > 0) { Filter(function(x) length(x) > 0, lapply(res$sourceFileResults, function(fileRes) { names(Filter(function(x) x$kind != "success", fileRes)) })) } else list() } if (is.null(pkgname)) { root <- packageRoot(path) if (is.null(root)) stop("could not infer package root directory") pkgname0 <- packageInfo(root)$Package if (is.null(pkgname)) { pkgname <- pkgname0 } else if (!identical(pkgname, pkgname0)) { stop("'pkgname' and inferred DESCRIPTION 'Package' differ") } } else { root <- system.file(package=pkgname) } library(pkgname, character.only = TRUE, quietly=TRUE) dir <- file.path(root, subdir) if (!file.exists(dir)) { # try inst/subdir dir <- file.path(root, "inst", subdir) } if (!file.exists(dir)) { stop("unable to find unit tests, no subdir ", sQuote(subdir)) } ## If we only load RUnit's namespace without attaching the package to ## the search path, then many tests in many packages will fail with ## errors like: could not find function "checkIdentical" #if (!requireNamespace("RUnit", quietly=TRUE)) # stop("Couldn't load the RUnit package. You need to ", # "install it before\n you can use testPackage().") library("RUnit", quietly=TRUE) RUnit_opts <- getOption("RUnit", list()) RUnit_opts$verbose <- 0L RUnit_opts$silent <- TRUE RUnit_opts$verbose_fail_msg <- TRUE oopt <- options(RUnit = RUnit_opts) on.exit(options(oopt)) suite <- RUnit::defineTestSuite(name=paste(pkgname, "RUnit Tests"), dirs=dir, testFileRegexp=pattern, rngKind="default", rngNormalKind="default") result <- RUnit::runTestSuite(suite) cat("\n\n") RUnit::printTextProtocol(result, showDetails=FALSE) if (length(details <- .failure_details(result)) > 0) { cat("\nTest files with failing tests\n") for (i in seq_along(details)) { cat("\n ", basename(names(details)[[i]]), "\n") for (j in seq_along(details[[i]])) { cat(" ", details[[i]][[j]], "\n") } } cat("\n\n") stop("unit tests failed for package ", pkgname) } result } BiocGenerics/R/toTable.R0000644000175200017520000000037314136047726016063 0ustar00biocbuildbiocbuild### ========================================================================= ### The toTable() generic ### ------------------------------------------------------------------------- setGeneric("toTable", function(x, ...) standardGeneric("toTable")) BiocGenerics/R/type.R0000644000175200017520000000050014136047726015442 0ustar00biocbuildbiocbuild### ========================================================================= ### The type() getter and setter ### ------------------------------------------------------------------------- ### setGeneric("type", function(x) standardGeneric("type")) setGeneric("type<-", function(x, value) standardGeneric("type<-")) BiocGenerics/R/unique.R0000644000175200017520000000064514136047726016001 0ustar00biocbuildbiocbuild### ========================================================================= ### The unique() generic ### ------------------------------------------------------------------------- ### ### Need to explicitly define this generic otherwise the implicit generic in ### package "base" would dispatch on ('x', 'incomparables'). Here we set ### dispatch on the 1st arg (the 'x' arg) only! setGeneric("unique", signature="x") BiocGenerics/R/unlist.R0000644000175200017520000000040214136047726016000 0ustar00biocbuildbiocbuild### ========================================================================= ### The unlist() generic ### ------------------------------------------------------------------------- ### ### base::unlist is an S3 generic. setGeneric("unlist", signature="x") BiocGenerics/R/unsplit.R0000644000175200017520000000055314136047726016167 0ustar00biocbuildbiocbuild### ========================================================================= ### The unsplit() generic ### ------------------------------------------------------------------------- ### ### unsplit should not dispatch on 'drop' setGeneric("unsplit", function (value, f, drop = FALSE) standardGeneric("unsplit"), signature=c("value", "f")) BiocGenerics/R/updateObject.R0000644000175200017520000002164714136047726017111 0ustar00biocbuildbiocbuild### ========================================================================= ### The updateObject() generic and related utilities ### ------------------------------------------------------------------------- ### ### An "updateObject" default method + methods for some standard types are ### also provided. ### ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ### Utilities. ### updateObjectFrom_errf <- function(..., verbose=FALSE) { function(err) { if (verbose) message(..., ":\n ", conditionMessage(err), "\n trying next method...") NULL } } getObjectSlots <- function(object) # object, rather than class defn, slots { if (!is.object(object) || isVirtualClass(class(object))) return(NULL) value <- attributes(object) value$class <- NULL if (is(object, "vector")) { .Data <- as.vector(object) attr(.Data, "class") <- NULL attrNames <- c("comment", "dim", "dimnames", "names", "row.names", "tsp") for (nm in names(value)[names(value) %in% attrNames]) attr(.Data, nm) <- value[[nm]] value <- value[!names(value) %in% attrNames] value$.Data <- .Data } value } updateObjectFromSlots <- function(object, objclass=class(object), ..., verbose=FALSE) { if (is(object, "environment")) { if (verbose) message("returning original object of class 'environment'") return(object) } classSlots <- slotNames(objclass) if (is.null(classSlots)) { if (verbose) message("definition of '", objclass, "' has no slots; ", "returning original object") return(object) } if (verbose) message("updateObjectFromSlots(object = '", class(object), "' class = '", objclass, "')") objectSlots <- getObjectSlots(object) ## de-mangle and remove NULL nulls <- sapply(names(objectSlots), function(slt) is.null(slot(object, slt))) objectSlots[nulls] <- NULL joint <- intersect(names(objectSlots), classSlots) toUpdate <- joint[joint!=".Data"] objectSlots[toUpdate] <- lapply(objectSlots[toUpdate], updateObject, ..., verbose=verbose) toDrop <- which(!names(objectSlots) %in% classSlots) if (length(toDrop) > 0L) { warning("dropping slot(s) '", paste(names(objectSlots)[toDrop], collapse="', '"), "' from object = '", class(object), "'") objectSlots <- objectSlots[-toDrop] } ## ad-hoc methods for creating new instances res <- NULL if (is.null(res)) { if (verbose) message("heuristic updateObjectFromSlots, method 1") res <- tryCatch({ do.call(new, c(objclass, objectSlots[joint])) }, error=updateObjectFrom_errf( "'new(\"", objclass, "\", ...)' from slots failed", verbose=verbose)) } if (is.null(res)) { if (verbose) message("heuristic updateObjectFromSlots, method 2") res <- tryCatch({ obj <- do.call(new, list(objclass)) for (slt in joint) slot(obj, slt) <- updateObject(objectSlots[[slt]], ..., verbose=verbose) obj }, error=updateObjectFrom_errf( "failed to add slots to 'new(\"", objclass, "\", ...)'", verbose=verbose)) } if (is.null(res)) stop("could not updateObject to class '", objclass, "'", "\nconsider defining an 'updateObject' method for class '", class(object), "'") res } getObjectFields <- function(object) { value <- object$.refClassDef@fieldClasses for (field in names(value)) value[[field]] <- object$field(field) value } updateObjectFromFields <- function(object, objclass=class(object), ..., verbose=FALSE) { if (verbose) message("updateObjectFromFields(object = '", class(object), "' objclass = '", objclass, "')") classFields <- names(getRefClass(objclass)$fields()) if (is.null(classFields)) { if (verbose) message("definition of '", objclass, "' has no fields; ", "regurning original object") return(object) } objectFields <- getObjectFields(object) toUpdate <- joint <- intersect(names(objectFields), classFields) objectFields[toUpdate] <- lapply(objectFields[toUpdate], updateObject, ..., verbose=verbose) toDrop <- which(!names(objectFields) %in% classFields) if (length(toDrop) > 0L) { warning("dropping fields(s) '", paste(names(objectFields)[toDrop], collapse="', '"), "' from object = '", class(object), "'") objectFields <- objectFields[-toDrop] } ## ad-hoc methods for creating new instances if (verbose) message("heuristic updateObjectFromFields, method 1") res <- tryCatch({ do.call(new, c(objclass, objectFields[joint])) }, error = updateObjectFrom_errf( "'new(\"", objclass, "\", ...' from slots failed", verbose=verbose) ) if (is.null(res)) stop("could not updateObject to class '", objclass, "'", "\nconsider defining an 'updateObject' method for class '", class(object), "'") res } ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ### updateObject() ### ### TODO: Would be cleaner if 'check' was a formal argument. setGeneric("updateObject", signature="object", function(object, ..., verbose=FALSE) { if (!isTRUEorFALSE(verbose)) stop("'verbose' must be TRUE or FALSE") result <- standardGeneric("updateObject") check <- list(...)$check if (is.null(check)) { check <- TRUE } else if (!isTRUEorFALSE(check)) { stop("'check' must be TRUE or FALSE") } if (check) { if (verbose) message("[updateObject] Validating the updated object ... ", appendLF=FALSE) validObject(result) if (verbose) message("OK") } result } ) setMethod("updateObject", "ANY", function(object, ..., verbose=FALSE) { if (verbose) message("updateObject(object=\"ANY\") default for object ", "of class '", class(object), "'") if (length(getObjectSlots(object)) > 0L && !any(class(object) %in% c("data.frame", "factor"))) { updateObjectFromSlots(object, ..., verbose=verbose) } else { object } } ) setMethod("updateObject", "list", function(object, ..., verbose=FALSE) { if (verbose) message("updateObject(object = 'list')") if ("class" %in% names(attributes(object))) callNextMethod() # old-style S4 else { result <- lapply(object, updateObject, ..., verbose=verbose) attributes(result) <- attributes(object) result } } ) setMethod("updateObject", "environment", function(object, ..., verbose=FALSE) { if (verbose) message("updateObject(object = 'environment')") envLocked <- environmentIsLocked(object) if (verbose) { if (envLocked) warning("updateObject duplicating locked environment") else warning("updateObject modifying environment") } env <- if (envLocked) new.env() else object lapply(ls(object, all.names=TRUE), function(elt) { # side-effect! bindingLocked <- bindingIsLocked(elt, object) if (!envLocked && bindingLocked) stop("updateObject object = 'environment' ", "cannot modify locked binding '", elt, "'") else { env[[elt]] <<- updateObject(object[[elt]], ..., verbose=verbose) if (bindingLocked) lockBinding(elt, env) } NULL }) attributes(env) <- attributes(object) if (envLocked) lockEnvironment(env) env } ) setMethod("updateObject", "formula", function(object, ..., verbose=FALSE) { if (verbose) ## object@.Environment could be too general, e.g,. R_GlobalEnv message("updateObject(object = 'formula'); ignoring .Environment") object }) setMethod("updateObject", "envRefClass", function(object, ..., verbose=FALSE) { msg <- sprintf("updateObject(object= '%s')", class(object)) if (verbose) message(msg) updateObjectFromFields(object, ..., verbose=verbose) }) BiocGenerics/R/utils.R0000644000175200017520000000142114136047726015624 0ustar00biocbuildbiocbuild### ========================================================================= ### Miscellaneous low-level utils ### ------------------------------------------------------------------------- ### ### Like toString() but also injects names(x) in the returned string. ### For example with: ### x <- alist(b = 99, 98:96, zz) ### to_string(x) returns: ### "b = 99, 98:96, zz" to_string <- function(x) { x_names <- names(x) x <- as.character(x) if (!is.null(x_names)) { x_names <- paste0(x_names, ifelse(x_names == "", "", " = ")) x <- paste0(x_names, x) } paste(x, collapse=", ") } unused_arguments_msg <- function(dots) { msg <- "unused argument" if (length(dots) >= 2L) msg <- c(msg, "s") c(msg, " (", to_string(dots), ")") } BiocGenerics/R/var.R0000644000175200017520000000047414136047726015263 0ustar00biocbuildbiocbuild### ========================================================================= ### The var() and sd() generics ### ------------------------------------------------------------------------- ### ### Dispatches only on 'x' (and 'y' for var) ### setGeneric("var", signature=c("x", "y")) setGeneric("sd", signature="x") BiocGenerics/R/weights.R0000644000175200017520000000036714136047726016146 0ustar00biocbuildbiocbuild### ========================================================================= ### The weights() generic ### ------------------------------------------------------------------------- ### ### stats::weights is an S3 generic. setGeneric("weights") BiocGenerics/R/which.R0000644000175200017520000000031614136047726015570 0ustar00biocbuildbiocbuild### ========================================================================= ### The which() generic ### ------------------------------------------------------------------------- ### setGeneric("which") BiocGenerics/R/which.min.R0000644000175200017520000000211514136047726016351 0ustar00biocbuildbiocbuild### ========================================================================= ### The which.min() and which.max() generics ### ------------------------------------------------------------------------- ### ### Michael, June 2016 (commit 860cce0ec85b94ebca190802be95e61c4f469d6b): ### ### The default methods (defined in the base package) only take 1 argument. ### We add the ... argument to the generic functions defined here so they ### can be called with an arbitrary number of effective arguments. This was ### motivated by the desire to optionally return global subscripts from ### methods on List. ### These generics are slated to be internalized in base R. When that ### happens, these calls will effectively be no-ops. .which.min.useAsDefault <- function(x, ...) base::which.min(x, ...) .which.max.useAsDefault <- function(x, ...) base::which.max(x, ...) setGeneric("which.min", function(x, ...) standardGeneric("which.min"), useAsDefault=.which.min.useAsDefault ) setGeneric("which.max", function(x, ...) standardGeneric("which.max"), useAsDefault=.which.max.useAsDefault ) BiocGenerics/R/xtabs.R0000644000175200017520000000064514136047726015614 0ustar00biocbuildbiocbuild### ========================================================================= ### The xtabs() generic ### ------------------------------------------------------------------------- ### ### Need to explicitly define this generic otherwise the implicit generic in ### package "stats" would dispatch on all its arguments. Here we set dispatch ### on the 2nd arg (the 'data' arg) only! setGeneric("xtabs", signature="data") BiocGenerics/R/zzz.R0000644000175200017520000000006114136047726015320 0ustar00biocbuildbiocbuild.test <- function() testPackage("BiocGenerics") BiocGenerics/README.md0000644000175200017520000000066414136047726015427 0ustar00biocbuildbiocbuild[](https://bioconductor.org/) **BiocGenerics** is an R/Bioconductor package that defines many S4 generic functions used in Bioconductor. See https://bioconductor.org/packages/BiocGenerics for more information including how to install the release version of the package (please refrain from installing directly from GitHub). BiocGenerics/TODO0000644000175200017520000000445014136047726014635 0ustar00biocbuildbiocbuildo Functions defined in base R that would need to be explicitly promoted to generics in the BiocGenerics package (currently they are implicitly made generics by the IRanges package): From package base: - split(): implicit generic dispatches on (x, f, drop). Explicit generic should dispatch on (x, f) only. - which(): implicit generic dispatches on (x, arr.ind, useNames). Explicit generic should dispatch on (x) only. - ifelse(): implicit generic dispatches on (test, yes, no). Explicit generic should dispatch on (test) only. - nchar(): implicit generic dispatches on (x, type, allowNA). Explicit generic should dispatch on (x) only. - substr(): implicit generic dispatches on (x, start, stop). Explicit generic should dispatch on (x) only. - substring(): implicit generic dispatches on (text, first, last). Explicit generic should dispatch on (text) only. - chartr(): implicit generic dispatches on (old, new, x). Explicit generic should dispatch on (x) only. - sub(), gsub(): implicit generics dispatch on (pattern, replacement, x, ignore.case, perl, fixed, useBytes). Explicit generics should dispatch on (x) only. - range(): - by(): From package stats: - var(): implicit generic dispatches on (x, y, na.rm, use). Explicit generic should dispatch on (x, y) only. - cov(): implicit generic dispatches on (x, y, use, method). Explicit generic should dispatch on (x, y) only. - cor(): implicit generic dispatches on (x, y, use, method). Explicit generic should dispatch on (x, y) only. - sd(): implicit generic dispatches on (x, na.rm). Explicit generic should dispatch on (x) only. - median(): implicit generic dispatches on (x, na.rm). Explicit generic should dispatch on (x) only. - mad(): implicit generic dispatches on (x, center, constant, na.rm, low, high). Explicit generic should dispatch on (x) only. - IQR(): implicit generic dispatches on (x, na.rm, type). Explicit generic should dispatch on (x) only. - smoothEnds(): implicit generic dispatches on (y, k). Explicit generic should dispatch on (y) only. - runmed(): implicit generic dispatches on (x, k, endrule, algorithm, print.level). Explicit generic should dispatch on (x) only. BiocGenerics/inst/0000755000175200017520000000000014136047726015117 5ustar00biocbuildbiocbuildBiocGenerics/inst/CITATION0000644000175200017520000000165614136047726016264 0ustar00biocbuildbiocbuildcitEntry(entry="Article", author = "Huber, W. and Carey, V. J. and Gentleman, R. and Anders, S. and Carlson, M. and Carvalho, B. S. and Bravo, H. C. and Davis, S. and Gatto, L. and Girke, T. and Gottardo, R. and Hahne, F. and Hansen, K. D. and Irizarry, R. A. and Lawrence, M. and Love, M. I. and MacDonald, J. and Obenchain, V. and {Ole\'s}, A. K. and {Pag\`es}, H. and Reyes, A. and Shannon, P. and Smyth, G. K. and Tenenbaum, D. and Waldron, L. and Morgan, M. ", title = "{O}rchestrating high-throughput genomic analysis with {B}ioconductor", journal = "Nature Methods", year = "2015", volume = "12", number = "2", pages = "115--121", url = "http://www.nature.com/nmeth/journal/v12/n2/full/nmeth.3252.html", textVersion = paste( "Orchestrating high-throughput genomic analysis with Bioconductor.", "W. Huber, V.J. Carey, R. Gentleman, ..., M. Morgan", "Nature Methods, 2015:12, 115.") ) BiocGenerics/inst/unitTests/0000755000175200017520000000000014136047726017121 5ustar00biocbuildbiocbuildBiocGenerics/inst/unitTests/test_Extremes.R0000644000175200017520000000072014136047726022076 0ustar00biocbuildbiocbuild test_ellipsis_forwarding_for_Extremes <- function() { for (FUN in c("pmax", "pmin", "pmax.int", "pmin.int")) { FUN <- match.fun(FUN) FUN_wrapper <- function(x, ...) FUN(x, ...) x <- c(1:3, NA) y <- c(NA, 3:1) checkIdentical(FUN(x, y), FUN_wrapper(x, y)) checkIdentical(FUN(x, y, na.rm=FALSE), FUN_wrapper(x, y, na.rm=FALSE)) checkIdentical(FUN(x, y, na.rm=TRUE), FUN_wrapper(x, y, na.rm=TRUE)) } } BiocGenerics/inst/unitTests/test_combine.R0000644000175200017520000002063514136047726021725 0ustar00biocbuildbiocbuild### checkDataFramesEqual <- function(obj1, obj2) { checkTrue(identical(row.names(obj1), row.names(obj2))) checkTrue(identical(colnames(obj1), colnames(obj2))) checkTrue(all(sapply(colnames(obj1), function(nm) identical(obj1[[nm]], obj2[[nm]])))) } test_combine_df <- function() { ## no warnings x <- data.frame(x=1:5,y=letters[1:5], row.names=letters[1:5]) y <- data.frame(z=3:7,y=letters[c(3:5,1:2)], row.names=letters[3:7]) z <- combine(x,y) checkDataFramesEqual(x, z[1:5, colnames(x)]) checkDataFramesEqual(y, z[3:7, colnames(y)]) x <- data.frame(x=1:2, y=letters[1:2], row.names=letters[1:2]) y <- data.frame(z=2:3, y=letters[2:3], row.names=letters[2:3]) z <- combine(x,y) checkDataFramesEqual(x, z[1:2, colnames(x)]) checkDataFramesEqual(y, z[2:3, colnames(y)]) ## an error -- content mismatch x <- data.frame(x=1:3, y=letters[1:3], row.names=letters[1:3]) y <- data.frame(z=2:4, y=letters[1:3], row.names=letters[2:4]) checkException(suppressWarnings(combine(x,y)), silent=TRUE) ## a warning -- level coercion oldw <- options("warn") options(warn=2) on.exit(options(oldw)) x <- data.frame(x=1:2, y=letters[1:2], row.names=letters[1:2], stringsAsFactors=TRUE) y <- data.frame(z=2:3, y=letters[2:3], row.names=letters[2:3], stringsAsFactors=TRUE) checkException(combine(x,y), silent=TRUE) options(oldw) checkDataFramesEqual(suppressWarnings(combine(x,y)), data.frame(x=c(1:2, NA), y=letters[1:3], z=c(NA, 2:3), row.names=letters[1:3], stringsAsFactors=TRUE)) } test_combine_df_preserveNumericRows <- function() { dfA <- data.frame(label=rep("x", 2), row.names=1:2) dfB <- data.frame(label=rep("x", 3), row.names=3:5) dfAB <- combine(dfA, dfB) ## preserve integer row names if possible checkEquals(1:5, attr(dfAB, "row.names")) ## silently coerce row.names to character dfC <- data.frame(label=rep("x", 2), row.names=as.character(3:4)) dfAC <- combine(dfA, dfC) checkEquals(as.character(1:4), attr(dfAC, "row.names")) } test_combine_df_NoRow <- function() { x <- data.frame(x=1,y=letters[1])[FALSE,] y <- data.frame(z=1,y=letters[1])[FALSE,] z <- combine(x,x) checkTrue(identical(dim(z), as.integer(c(0,2)))) x <- data.frame(x=1,y=letters[1])[FALSE,] y <- data.frame(z=1,y=letters[1]) z <- combine(x,y) checkTrue(identical(dim(z), as.integer(c(1,3)))) checkTrue(is.na(z$x)) z <- combine(y,x) checkTrue(identical(dim(z), as.integer(c(1,3)))) checkTrue(is.na(z$x)) } test_combine_df_OneRow <- function() { x <- data.frame(x=1,y=letters[1], row.names=letters[1]) y <- data.frame(z=3,y=letters[1], row.names=letters[2]) z <- combine(x,y) checkTrue(identical(dim(z), as.integer(c(2,3)))) checkTrue(z$x[[1]]==1) checkTrue(all(is.na(z$x[[2]]), is.na(z$z[[1]]))) z <- combine(x,data.frame()) checkTrue(identical(dim(z), as.integer(c(1,2)))) checkTrue(all(z[,1:2]==x[,1:2])) z <- combine(data.frame(),x) checkTrue(identical(dim(z), as.integer(c(1,2)))) checkTrue(all(z[,1:2]==x[,1:2])) } test_combine_df_NoCol <- function() { ## row.names obj1 <- data.frame(numeric(20), row.names=letters[1:20])[,FALSE] obj <- combine(obj1, obj1) checkTrue(identical(obj, obj1)) ## no row.names -- fails because row.names not recoverable from data.frame? obj1 <- data.frame(numeric(20))[,FALSE] obj <- combine(obj1, obj1) checkTrue(all(dim(obj)==dim(obj1))) } test_combine_df_NoCommonCols <- function() { x <- data.frame(x=1:5, row.names=letters[1:5]) y <- data.frame(y=3:7, row.names=letters[3:7]) z <- combine(x,y) checkTrue(all(dim(z)==as.integer(c(7,2)))) checkTrue(all(z[1:5,"x"]==x[,"x"])) checkTrue(all(z[3:7,"y"]==y[,"y"])) checkTrue(all(which(is.na(z))==6:9)) } test_combine_df_Empty <- function() { z <- combine(data.frame(), data.frame()) checkTrue(identical(dim(z), as.integer(c(0,0)))) x <- data.frame(x=1,y=letters[1], row.names=letters[1]) z <- combine(x,data.frame()) checkTrue(identical(dim(z), as.integer(c(1,2)))) checkTrue(identical(z["a",1:2], x["a",1:2])) z <- combine(data.frame(), x) checkTrue(identical(dim(z), as.integer(c(1,2)))) checkTrue(identical(z["a",1:2], x["a",1:2])) } test_combine_df_AsIs <- function() { x <- data.frame(x=I(1:5),y=I(letters[1:5]), row.names=letters[1:5]) y <- data.frame(z=I(3:7),y=I(letters[3:7]), row.names=letters[3:7]) z <- combine(x,y) checkTrue(all(sapply(z, class)=="AsIs")) } test_combine_df_ColNamesSuffix <- function() { obj1 <- data.frame(a=1:5, a.x=letters[1:5]) obj2 <- data.frame(a=1:5, a.y=LETTERS[1:5], b=5:1) obj <- combine(obj1, obj2) checkDataFramesEqual(obj, data.frame(a=1:5, a.x=letters[1:5], a.y=LETTERS[1:5], b=5:1)) } test_combine_3df <- function() { ## data.frame's are tricky, because c(df, list(...)) unlists df x <- data.frame(x=1:5, y=factor(letters[1:5], levels=letters[1:8]), row.names=letters[1:5]) y <- data.frame(z=3:7, y=factor(letters[3:7], levels=letters[1:8]), row.names=letters[3:7]) w <- data.frame(w=4:8, y=factor(letters[4:8], levels=letters[1:8]), row.names=letters[4:8]) res <- combine(w, x, y) e <- data.frame(w=c(4:8, rep(NA, 3)), y=factor(c(letters[c(4:8, 1:3)])), x=c(4:5, rep(NA, 3), 1:3), z=as.integer(c(4:7, rep(NA, 3), 3)), row.names=letters[c(4:8, 1:3)]) checkIdentical(e, res) } test_combine_df_POSIXct <- function() { ## class(x) can have length > 1 as in Sys.time() t0 <- Sys.time() df1 <- data.frame(i = 1:3, t = rep(t0, 3), row.names=letters[1:3]) df2 <- data.frame(i = 1:3, t = c(t0, t0 + 500, t0 + 1000), row.names=c("a", "d", "e")) e <- data.frame(i = c(1L, 2L, 3L, 2L, 3L), t = c(t0, t0, t0, t0 + 500, t0 + 1000), row.names=c("a", "b", "c", "d", "e")) res <- combine(df1, df2) checkIdentical(e, res) } test_combine_df_WithNamedArgs <- function() { x <- data.frame(x=1:5, y=factor(letters[1:5], levels=letters[1:8]), row.names=letters[1:5]) y <- data.frame(z=3:7, y=factor(letters[3:7], levels=letters[1:8]), row.names=letters[3:7]) w <- data.frame(w=4:8, y=factor(letters[4:8], levels=letters[1:8]), row.names=letters[4:8]) checkIdentical(combine(w, y, x), combine(w, x, y=y)) checkIdentical(combine(w, y, x), combine(w, y=y, x)) checkIdentical(combine(x, y, w), combine(w, y=y, x=x)) checkIdentical(combine(x, y, w), combine(y=y, x=x, w)) } test_combine_mat <- function() { ## dimnames m <- matrix(1:20, nrow=5, dimnames=list(LETTERS[1:5], letters[1:4])) checkEquals(m, combine(m, m)) checkEquals(m, combine(m[1:3,], m[4:5,])) checkEquals(m, combine(m[,1:3], m[,4, drop=FALSE])) ## overlap checkEquals(m, combine(m[1:3,], m[3:5,])) checkEquals(m, combine(m[,1:3], m[,3:4])) checkEquals(matrix(c(1:3, NA, NA, 6:8, NA, NA, 11:15, NA, NA, 18:20), nrow=5, dimnames=list(LETTERS[1:5], letters[1:4])), combine(m[1:3,1:3], m[3:5, 3:4])) ## row reordering checkEquals(m[c(1,3,5,2,4),], combine(m[c(1,3,5),], m[c(2,4),])) ## Exceptions checkException(combine(m, matrix(0, nrow=5, ncol=4)), silent=TRUE) # types differ checkException(combine(m, matrix(0L, nrow=5, ncol=4)), silent=TRUE) # attributes differ m1 <- matrix(1:20, nrow=5) checkException(combine(m, m1), silent=TRUE) # dimnames required } test_combine_mat_DifferentModes <- function() { m <- matrix(1:20, nrow=5, dimnames=list(LETTERS[1:5], letters[1:4])) n <- matrix(as.numeric(1:20), nrow=5, dimnames=list(LETTERS[1:5], letters[1:4])) res <- combine(m, n) # modes coerced to same checkEquals("numeric", mode(res)) n <- matrix(as.character(1:20), nrow=5, dimnames=list(LETTERS[1:5], letters[1:4])) checkException(combine(m, n)) # modes differ } BiocGenerics/inst/unitTests/test_mapply.R0000644000175200017520000000123714136047726021610 0ustar00biocbuildbiocbuild test_ellipsis_forwarding_for_mapply <- function() { mapply_wrapper <- function(FUN, x, ...) mapply(FUN, x, ...) x <- list(a=1:3, 1:2) y <- list(104:105, B=103) target <- mapply(append, x, y) checkIdentical(target, mapply_wrapper(append, x, y)) MoreArgs <- list(after=0) target <- mapply(append, x, y, MoreArgs=MoreArgs) current <- mapply_wrapper(append, x, y, MoreArgs=MoreArgs) checkIdentical(target, current) MoreArgs <- list(after=2) target <- mapply(append, x, y, MoreArgs=MoreArgs, USE.NAMES=FALSE) current <- mapply_wrapper(append, x, y, MoreArgs=MoreArgs, USE.NAMES=FALSE) checkIdentical(target, current) } BiocGenerics/inst/unitTests/test_order.R0000644000175200017520000000077514136047726021427 0ustar00biocbuildbiocbuild test_ellipsis_forwarding_for_order <- function() { x <- list(c(NA,11:13), c(21:22,NA)) target <- lapply(x, base::order) checkIdentical(target, lapply(x, order)) target <- lapply(x, base::order, na.last=TRUE) checkIdentical(target, lapply(x, order, na.last=TRUE)) target <- lapply(x, base::order, na.last=FALSE) checkIdentical(target, lapply(x, order, na.last=FALSE)) target <- lapply(x, base::order, na.last=NA) checkIdentical(target, lapply(x, order, na.last=NA)) } BiocGenerics/inst/unitTests/test_paste.R0000644000175200017520000000042714136047726021422 0ustar00biocbuildbiocbuild test_ellipsis_forwarding_for_paste <- function() { x <- list(letters, LETTERS) target <- sapply(x, base::paste) checkIdentical(target, sapply(x, paste)) target <- sapply(x, base::paste, collapse="") checkIdentical(target, sapply(x, paste, collapse="")) } BiocGenerics/inst/unitTests/test_updateObject.R0000644000175200017520000000663014136047726022721 0ustar00biocbuildbiocbuild### test_updateObject_list <- function() { setClass("A", representation(x="numeric"), prototype(x=1:10), where=.GlobalEnv) a <- new("A") l <- list(a,a) checkTrue(identical(l, updateObject(l))) setMethod("updateObject", "A", function(object, ..., verbose=FALSE) { if (verbose) message("updateObject object = 'A'") object@x <- -object@x object }, where=.GlobalEnv) obj <- updateObject(l) checkTrue(identical(lapply(l, function(elt) { elt@x <- -elt@x; elt }), obj)) removeMethod("updateObject", "A", where=.GlobalEnv) removeClass("A", where=.GlobalEnv) } test_updateObject_env <- function() { opts <- options() options(warn=-1) e <- new.env() e$x=1 e$.x=1 obj <- updateObject(e) checkTrue(identical(e,obj)) # modifies environment lockEnvironment(e) obj <- updateObject(e) # copies environment checkTrue(identical(lapply(ls(e, all=TRUE), function(x) x), lapply(ls(obj, all=TRUE), function(x) x))) checkTrue(!identical(e, obj)) # different environments e <- new.env() e$x=1 e$.x=1 lockBinding("x", e) checkException(updateObject(e), silent=TRUE) lockEnvironment(e) obj <- updateObject(e) checkTrue(TRUE==bindingIsLocked("x", obj)) # R bug, 14 May, 2006, fixed checkTrue(FALSE==bindingIsLocked(".x", obj)) options(opts) } test_updateObject_defaults <- function() { x <- 1:10 checkTrue(identical(x, updateObject(x))) } test_updateObject_S4 <- function() { setClass("A", representation=representation( x="numeric"), prototype=list(x=1:5), where=.GlobalEnv) .__a__ <- new("A") setClass("A", representation=representation( x="numeric", y="character"), where=.GlobalEnv) checkException(validObject(.__a__), silent=TRUE) # now out-of-date .__a__@x <- 1:5 a <- updateObject(.__a__) checkTrue(validObject(a)) checkIdentical(1:5, a@x) removeClass("A", where=.GlobalEnv) } test_updateObject_setClass <- function() { setClass("A", representation(x="numeric"), prototype=prototype(x=1:10), where=.GlobalEnv) a <- new("A") checkTrue(identical(a,updateObject(a))) removeClass("A", where=.GlobalEnv) } test_updateObject_refClass <- function() { cls <- ".__test_updateObject_refClassA" .A <- setRefClass(cls, fields=list(x="numeric", y="numeric"), where=.GlobalEnv) a <- .A() checkTrue(all.equal(a, updateObject(a))) a <- .A(x=1:5, y=5:1) checkTrue(all.equal(a, updateObject(a))) .A <- setRefClass(cls, fields=list(x="numeric", y="numeric", z="numeric"), where=.GlobalEnv) checkTrue(all.equal(.A(x=1:5, y=5:1, z=numeric()), updateObject(a))) .A <- setRefClass(cls, fields=list(x="numeric")) warn <- FALSE value <- withCallingHandlers(updateObject(a), warning=function(w) { txt <- "dropping fields(s) 'y' from object = '.__test_updateObject_refClassA'" warn <<- identical(txt, conditionMessage(w)) invokeRestart("muffleWarning") }) checkTrue(warn) checkTrue(all.equal(.A(x=1:5), value)) removeClass(cls, where=.GlobalEnv) } BiocGenerics/man/0000755000175200017520000000000014136047726014715 5ustar00biocbuildbiocbuildBiocGenerics/man/BiocGenerics-package.Rd0000644000175200017520000002106014136047726021130 0ustar00biocbuildbiocbuild\name{BiocGenerics-package} \alias{BiocGenerics-package} \alias{BiocGenerics} \docType{package} \title{S4 generic functions for Bioconductor} \description{ S4 generic functions needed by many Bioconductor packages. } \details{ We divide the generic functions defined in the \pkg{BiocGenerics} package in 2 categories: (1) functions already defined in base R and explicitly promoted to generics in BiocGenerics, and (2) Bioconductor specific generics. \subsection{(1) Functions defined in base R and explicitly promoted to generics in the \pkg{BiocGenerics} package}{ Generics for functions defined in package \pkg{base}: \itemize{ \item \code{BiocGenerics::\link[BiocGenerics]{append}} \item \code{BiocGenerics::\link[BiocGenerics]{as.data.frame}} \item \code{BiocGenerics::\link[BiocGenerics]{as.list}} \item \code{BiocGenerics::\link[BiocGenerics]{as.vector}} \item \code{BiocGenerics::\link[BiocGenerics]{rbind}}, \code{BiocGenerics::\link[BiocGenerics]{cbind}} \item \code{BiocGenerics::\link[BiocGenerics]{colSums}}, \code{BiocGenerics::\link[BiocGenerics]{rowSums}}, \code{BiocGenerics::\link[BiocGenerics]{colMeans}}, \code{BiocGenerics::\link[BiocGenerics]{rowMeans}} \item \code{BiocGenerics::\link[BiocGenerics]{do.call}} \item \code{BiocGenerics::\link[BiocGenerics]{duplicated}}, \code{BiocGenerics::\link[BiocGenerics]{anyDuplicated}} \item \code{BiocGenerics::\link[BiocGenerics]{eval}} \item Extremes: \code{BiocGenerics::\link[BiocGenerics]{pmax}}, \code{BiocGenerics::\link[BiocGenerics]{pmin}}, \code{BiocGenerics::\link[BiocGenerics]{pmax.int}}, \code{BiocGenerics::\link[BiocGenerics]{pmin.int}} \item funprog: \code{BiocGenerics::\link[BiocGenerics]{Reduce}}, \code{BiocGenerics::\link[BiocGenerics]{Filter}}, \code{BiocGenerics::\link[BiocGenerics]{Find}}, \code{BiocGenerics::\link[BiocGenerics]{Map}}, \code{BiocGenerics::\link[BiocGenerics]{Position}} \item \code{BiocGenerics::\link[BiocGenerics]{get}}, \code{BiocGenerics::\link[BiocGenerics]{mget}} \item \code{BiocGenerics::\link[BiocGenerics]{grep}}, \code{BiocGenerics::\link[BiocGenerics]{grepl}} \item \code{BiocGenerics::\link[BiocGenerics]{is.unsorted}} \item \code{BiocGenerics::\link[BiocGenerics]{lapply}}, \code{BiocGenerics::\link[BiocGenerics]{sapply}} \item \code{BiocGenerics::\link[BiocGenerics]{mapply}} \item \code{BiocGenerics::\link[BiocGenerics]{match}}, \code{BiocGenerics::\link[BiocGenerics]{\%in\%}} \item \code{BiocGenerics::\link[BiocGenerics]{nrow}}, \code{BiocGenerics::\link[BiocGenerics]{ncol}}, \code{BiocGenerics::\link[BiocGenerics]{NROW}}, \code{BiocGenerics::\link[BiocGenerics]{NCOL}} \item \code{BiocGenerics::\link[BiocGenerics]{order}} \item \code{BiocGenerics::\link[BiocGenerics]{paste}} \item \code{BiocGenerics::\link[BiocGenerics]{rank}} \item \code{BiocGenerics::\link[BiocGenerics]{rep.int}} \item \code{BiocGenerics::\link[BiocGenerics]{rownames}}, \code{BiocGenerics::\link[BiocGenerics]{rownames<-}}, \code{BiocGenerics::\link[BiocGenerics]{colnames}}, \code{BiocGenerics::\link[BiocGenerics]{colnames<-}} \item sets: \code{BiocGenerics::\link[BiocGenerics]{union}}, \code{BiocGenerics::\link[BiocGenerics]{intersect}}, \code{BiocGenerics::\link[BiocGenerics]{setdiff}} \item \code{BiocGenerics::\link[BiocGenerics]{sort}} \item \code{BiocGenerics::\link[BiocGenerics]{start}}, \code{BiocGenerics::\link[BiocGenerics]{start<-}}, \code{BiocGenerics::\link[BiocGenerics]{end}}, \code{BiocGenerics::\link[BiocGenerics]{end<-}}, \code{BiocGenerics::\link[BiocGenerics]{width}}, \code{BiocGenerics::\link[BiocGenerics]{width<-}}, \code{BiocGenerics::\link[BiocGenerics]{pos}} \item \code{BiocGenerics::\link[BiocGenerics]{subset}} \item \code{BiocGenerics::\link[BiocGenerics]{table}} \item \code{BiocGenerics::\link[BiocGenerics]{tapply}} \item \code{BiocGenerics::\link[BiocGenerics]{unique}} \item \code{BiocGenerics::\link[BiocGenerics]{unlist}} \item \code{BiocGenerics::\link[BiocGenerics]{unsplit}} \item \code{BiocGenerics::\link[BiocGenerics]{which}} \item \code{BiocGenerics::\link[BiocGenerics]{which.min}}, \code{BiocGenerics::\link[BiocGenerics]{which.max}} } Generics for functions defined in package \pkg{utils}: \itemize{ \item \code{BiocGenerics::\link[BiocGenerics]{relist}} } Generics for functions defined in package \pkg{graphics}: \itemize{ \item \code{BiocGenerics::\link[BiocGenerics]{boxplot}} \item \code{BiocGenerics::\link[BiocGenerics]{image}} } Generics for functions defined in package \pkg{stats}: \itemize{ \item \code{BiocGenerics::\link[BiocGenerics]{density}} \item \code{BiocGenerics::\link[BiocGenerics]{residuals}} \item \code{BiocGenerics::\link[BiocGenerics]{weights}} \item \code{BiocGenerics::\link[BiocGenerics]{xtabs}} } } \subsection{(2) Bioconductor specific generics}{ \itemize{ \item \code{\link[BiocGenerics]{annotation}}, \code{\link[BiocGenerics]{annotation<-}} \item \code{\link[BiocGenerics]{combine}} \item \code{\link[BiocGenerics]{dbconn}}, \code{\link[BiocGenerics]{dbfile}} \item \code{\link[BiocGenerics]{dims}}, \code{\link[BiocGenerics]{nrows}}, \code{\link[BiocGenerics]{ncols}}, \item \code{\link[BiocGenerics]{fileName}} \item \code{\link[BiocGenerics]{normalize}} \item \code{\link[BiocGenerics]{Ontology}} \item \code{\link[BiocGenerics]{organism}}, \code{\link[BiocGenerics]{organism<-}}, \code{\link[BiocGenerics]{species}}, \code{\link[BiocGenerics]{species<-}} \item \code{\link[BiocGenerics]{path}}, \code{\link[BiocGenerics]{path<-}}, \code{\link[BiocGenerics]{basename}}, \code{\link[BiocGenerics]{basename<-}}, \code{\link[BiocGenerics]{dirname}}, \code{\link[BiocGenerics]{dirname<-}} \item \code{\link[BiocGenerics]{plotMA}} \item \code{\link[BiocGenerics]{plotPCA}} \item \code{\link[BiocGenerics]{score}}, \code{\link[BiocGenerics]{score<-}} \item \code{\link[BiocGenerics]{strand}}, \code{\link[BiocGenerics]{strand<-}}, \code{\link[BiocGenerics]{invertStrand}} \item \code{\link[BiocGenerics]{toTable}} \item \code{\link[BiocGenerics]{type}}, \code{\link[BiocGenerics]{type<-}} \item \code{\link[BiocGenerics]{updateObject}} } } } \note{ More generics can be added on request by sending an email to the Bioc-devel mailing list: \url{http://bioconductor.org/help/mailing-list/} Things that should NOT be added to the \pkg{BiocGenerics} package: \itemize{ \item Internal generic primitive functions like \code{\link{length}}, \code{\link{dim}}, \code{`\link{dim<-}`}, etc... See \code{?\link{InternalMethods}} for the complete list. There are a few exceptions though, that is, the \pkg{BiocGenerics} package may actually redefine a few of those internal generic primitive functions as S4 generics when for example the signature of the internal generic primitive is not appropriate (this is the case for \code{BiocGenerics::\link[BiocGenerics]{cbind}}). \item S3 and S4 group generic functions like \code{\link{Math}}, \code{\link{Ops}}, etc... See \code{?\link{groupGeneric}} and \code{?\link{S4groupGeneric}} for the complete list. \item Generics already defined in the \pkg{stats4} package. } } \author{The Bioconductor Dev Team} \seealso{ \itemize{ \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \code{\link[methods]{setGeneric}} and \code{\link[methods]{setMethod}} for defining generics and methods. } } \examples{ ## List all the symbols defined in this package: ls('package:BiocGenerics') } \keyword{package} BiocGenerics/man/Extremes.Rd0000644000175200017520000000435114136047726017003 0ustar00biocbuildbiocbuild\name{Extremes} \alias{Extremes} \alias{pmax} \alias{pmin} \alias{pmax.int} \alias{pmin.int} \title{Maxima and minima} \description{ \code{pmax}, \code{pmin}, \code{pmax.int} and \code{pmin.int} return the parallel maxima and minima of the input values. NOTE: This man page is for the \code{pmax}, \code{pmin}, \code{pmax.int} and \code{pmin.int} \emph{S4 generic functions} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{pmax}} for the default methods (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically vector-like or matrix-like) not supported by the default methods. } \usage{ pmax(..., na.rm=FALSE) pmin(..., na.rm=FALSE) pmax.int(..., na.rm=FALSE) pmin.int(..., na.rm=FALSE) } \arguments{ \item{...}{ One or more vector-like or matrix-like objects. } \item{na.rm}{ See \code{?base::\link[base]{pmax}} for a description of this argument. } } \value{ See \code{?base::\link[base]{pmax}} for the value returned by the default methods. Specific methods defined in Bioconductor packages will typically return an object of the same class as the input objects. } \seealso{ \itemize{ \item \code{base::\link[base]{pmax}} for the default \code{pmax}, \code{pmin}, \code{pmax.int} and \code{pmin.int} methods. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{pmax,Rle-method} in the \pkg{S4Vectors} package for an example of a specific \code{pmax} method (defined for \link[S4Vectors]{Rle} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ pmax showMethods("pmax") selectMethod("pmax", "ANY") # the default method pmin showMethods("pmin") selectMethod("pmin", "ANY") # the default method pmax.int showMethods("pmax.int") selectMethod("pmax.int", "ANY") # the default method pmin.int showMethods("pmin.int") selectMethod("pmin.int", "ANY") # the default method } \keyword{methods} BiocGenerics/man/IQR.Rd0000644000175200017520000000253414136047726015643 0ustar00biocbuildbiocbuild\name{IQR} \alias{IQR} \title{The Interquartile Range} \description{ Compute the interquartile range for a vector. NOTE: This man page is for the \code{IQR} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?stats::\link[stats]{IQR}} for the default method (defined in the \pkg{stats} package). Bioconductor packages can define specific methods for objects not supported by the default method. } \usage{ IQR(x, na.rm = FALSE, type = 7) } \arguments{ \item{x, na.rm, type}{ See \code{?stats::\link[stats]{IQR}}. } } \value{ See \code{?stats::\link[stats]{IQR}} for the value returned by the default method. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default method. } \seealso{ \itemize{ \item \code{stats::\link[stats]{IQR}} for the default \code{IQR} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ IQR showMethods("IQR") selectMethod("IQR", "ANY") # the default method } \keyword{methods} BiocGenerics/man/Ontology.Rd0000644000175200017520000000172014136047726017016 0ustar00biocbuildbiocbuild\name{Ontology} \alias{Ontology} \title{Generic Ontology getter} \description{ Get the Ontology of an object. } \usage{ Ontology(object) } \arguments{ \item{object}{ An object with an Ontology. } } \seealso{ \itemize{ \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[AnnotationDbi]{Ontology,GOTerms-method} in the \pkg{AnnotationDbi} package for an example of a specific \code{Ontology} method (defined for \link[AnnotationDbi]{GOTerms} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ Ontology showMethods("Ontology") library(AnnotationDbi) showMethods("Ontology") selectMethod("Ontology", "GOTerms") } \keyword{methods} BiocGenerics/man/S3-classes-as-S4-classes.Rd0000644000175200017520000000234614136047726021451 0ustar00biocbuildbiocbuild\name{S3-classes-as-S4-classes} \alias{S3-classes-as-S4-classes} \alias{connection-class} \alias{file-class} \alias{url-class} \alias{gzfile-class} \alias{bzfile-class} \alias{unz-class} \alias{pipe-class} \alias{fifo-class} \alias{sockconn-class} \alias{terminal-class} \alias{textConnection-class} \alias{gzcon-class} \alias{character_OR_connection-class} \alias{AsIs-class} %\alias{table-class} %\alias{xtabs-class} \alias{dist-class} \title{S3 classes as S4 classes} \description{ Some old-style (aka S3) classes are turned into formally defined (aka S4) classes by the \pkg{BiocGenerics} package. This allows S4 methods defined in Bioconductor packages to use them in their signatures. } \details{ S3 classes currently turned into S4 classes: \itemize{ \item connection class and subclasses: \link{connection}, file, url, gzfile, bzfile, unz, pipe, fifo, sockconn, terminal, textConnection, gzcon. Addtitionally the character_OR_connection S4 class is defined as the union of classes character and connection. \item others: \link{AsIs}, \link{dist} } } \seealso{ \link{setOldClass} and \link{setClassUnion} in the \pkg{methods} package. } \keyword{classes} BiocGenerics/man/annotation.Rd0000644000175200017520000000230214136047726017353 0ustar00biocbuildbiocbuild\name{annotation} \alias{annotation} \alias{annotation<-} \title{Accessing annotation information} \description{ Get or set the annotation information contained in an object. } \usage{ annotation(object, ...) annotation(object, ...) <- value } \arguments{ \item{object}{ An object containing annotation information. } \item{...}{ Additional arguments, for use in specific methods. } \item{value}{ The annotation information to set on \code{object}. } } \seealso{ \itemize{ \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[Biobase]{annotation,eSet-method} in the \pkg{Biobase} package for an example of a specific \code{annotation} method (defined for \link[Biobase]{eSet} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ annotation showMethods("annotation") library(Biobase) showMethods("annotation") selectMethod("annotation", "eSet") } \keyword{methods} BiocGenerics/man/append.Rd0000644000175200017520000000377714136047726016471 0ustar00biocbuildbiocbuild\name{append} \alias{append} \title{Append elements to a vector-like object} \description{ Append (or insert) elements to (in) a vector-like object. NOTE: This man page is for the \code{append} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{append}} for the default method (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically vector-like or data-frame-like) not supported by the default method. } \usage{ append(x, values, after=length(x)) } \arguments{ \item{x}{ The vector-like object to be modified. } \item{values}{ The vector-like object containing the values to be appended to \code{x}. \code{values} would typically be of the same class as \code{x}, but not necessarily. } \item{after}{ A subscript, after which the values are to be appended. } } \value{ See \code{?base::\link[base]{append}} for the value returned by the default method. Specific methods defined in Bioconductor packages will typically return an object of the same class as \code{x} and of length \code{length(x) + length(values)}. } \seealso{ \itemize{ \item \code{base::\link[base]{append}} for the default \code{append} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{append,Vector,Vector-method} in the \pkg{S4Vectors} package for an example of a specific \code{append} method (defined for \link[S4Vectors]{Vector} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ append # note the dispatch on the 'x' and 'values' args only showMethods("append") selectMethod("append", c("ANY", "ANY")) # the default method } \keyword{methods} BiocGenerics/man/as.data.frame.Rd0000644000175200017520000000414314136047726017612 0ustar00biocbuildbiocbuild\name{as.data.frame} \alias{as.data.frame} \title{Coerce to a data frame} \description{ Generic function to coerce to a data frame, if possible. NOTE: This man page is for the \code{as.data.frame} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{as.data.frame}} for the default method (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects not supported by the default method. } \usage{ as.data.frame(x, row.names=NULL, optional=FALSE, ...) } \arguments{ \item{x}{ The object to coerce. } \item{row.names, optional, ...}{ See \code{?base::\link[base]{as.data.frame}} for a description of these arguments. } } \value{ An ordinary data frame. See \code{?base::\link[base]{as.data.frame}} for the value returned by the default method. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default method. } \seealso{ \itemize{ \item \code{base::\link[base]{as.data.frame}} for the default \code{as.data.frame} method. \item \code{\link[BiocGenerics]{toTable}} for an alternative to \code{as.data.frame}. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{as.data.frame,DataFrame-method} in the \pkg{S4Vectors} package, and \link[IRanges]{as.data.frame,IntegerRanges-method} in the \pkg{IRanges} package, for examples of specific \code{as.data.frame} methods (defined for \link[S4Vectors]{DataFrame} and \link[IRanges]{IntegerRanges} objects, respectively). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ as.data.frame # note the dispatch on the 'x' arg only showMethods("as.data.frame") selectMethod("as.data.frame", "ANY") # the default method } \keyword{methods} BiocGenerics/man/as.list.Rd0000644000175200017520000000302214136047726016556 0ustar00biocbuildbiocbuild\name{as.list} \alias{as.list} \title{Coerce to a list} \description{ Generic function to coerce to a list, if possible. NOTE: This man page is for the \code{as.list} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{as.list}} for the default method (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects not supported by the default method. } \usage{ as.list(x, ...) } \arguments{ \item{x}{ The object to coerce. } \item{...}{ Additional arguments, for use in specific methods. } } \value{ An ordinary list. } \seealso{ \itemize{ \item \code{base::\link[base]{as.list}} for the default \code{as.list} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{as.list,List-method} in the \pkg{S4Vectors} package for an example of a specific \code{as.list} method (defined for \link[S4Vectors]{List} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ as.list showMethods("as.list") selectMethod("as.list", "ANY") # the default method library(S4Vectors) showMethods("as.list") ## The as.list() method for List objects: selectMethod("as.list", "List") } \keyword{methods} BiocGenerics/man/as.vector.Rd0000644000175200017520000000402014136047726017104 0ustar00biocbuildbiocbuild\name{as.vector} \alias{as.vector} \title{Coerce an object into a vector} \description{ Attempt to coerce an object into a vector of the specified mode. If the mode is not specified, attempt to coerce to whichever vector mode is considered more appropriate for the class of the supplied object. NOTE: This man page is for the \code{as.vector} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{as.vector}} for the default method (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects not supported by the default method. } \usage{ as.vector(x, mode="any") } \arguments{ \item{x}{ The object to coerce. } \item{mode}{ See \code{?base::\link[base]{as.vector}} for a description of this argument. } } \value{ A vector. See \code{?base::\link[base]{as.vector}} for the value returned by the default method. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default method. } \seealso{ \itemize{ \item \code{base::\link[base]{as.vector}} for the default \code{as.vector} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{as.vector,Rle-method} and \link[IRanges]{as.vector,AtomicList-method} in the \pkg{S4Vectors} and \pkg{IRanges} packages, respectively, for examples of specific \code{as.vector} methods (defined for \link[S4Vectors]{Rle} and \link[IRanges]{AtomicList} objects, respectively). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ as.vector # note the dispatch on the 'x' arg only showMethods("as.vector") selectMethod("as.vector", "ANY") # the default method } \keyword{methods} BiocGenerics/man/boxplot.Rd0000644000175200017520000000331014136047726016670 0ustar00biocbuildbiocbuild\name{boxplot} \alias{boxplot} \title{Box plots} \description{ Produce box-and-whisker plot(s) of the given (grouped) values. NOTE: This man page is for the \code{boxplot} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?graphics::\link[graphics]{boxplot}} for the default method (defined in the \pkg{graphics} package). Bioconductor packages can define specific methods for objects not supported by the default method. } \usage{ boxplot(x, ...) } \arguments{ \item{x, ...}{ See \code{?graphics::\link[graphics]{boxplot}}. } } \value{ See \code{?graphics::\link[graphics]{boxplot}} for the value returned by the default method. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default method. } \seealso{ \itemize{ \item \code{graphics::\link[graphics]{boxplot}} for the default \code{boxplot} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[affy]{boxplot,AffyBatch-method} in the \pkg{affy} package for an example of a specific \code{boxplot} method (defined for \link[affy]{AffyBatch} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ boxplot showMethods("boxplot") selectMethod("boxplot", "ANY") # the default method library(affy) showMethods("boxplot") ## The boxplot() method for AffyBatch objects: selectMethod("boxplot", "AffyBatch") } \keyword{methods} BiocGenerics/man/cbind.Rd0000644000175200017520000000464214136047726016271 0ustar00biocbuildbiocbuild\name{cbind} \alias{rbind} \alias{cbind} \title{Combine objects by rows or columns} \description{ \code{rbind} and \code{cbind} take one or more objects and combine them by columns or rows, respectively. NOTE: This man page is for the \code{rbind} and \code{cbind} \emph{S4 generic functions} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{cbind}} for the default methods (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically vector-like or matrix-like) not supported by the default methods. } \usage{ rbind(..., deparse.level=1) cbind(..., deparse.level=1) } \arguments{ \item{...}{ One or more vector-like or matrix-like objects. These can be given as named arguments. } \item{deparse.level}{ See \code{?base::\link[base]{cbind}} for a description of this argument. } } \value{ See \code{?base::\link[base]{cbind}} for the value returned by the default methods. Specific methods defined in Bioconductor packages will typically return an object of the same class as the input objects. } \seealso{ \itemize{ \item \code{base::\link[base]{cbind}} for the default \code{rbind} and \code{cbind} methods. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{rbind,RectangularData-method} and \link[S4Vectors]{cbind,DataFrame-method} in the \pkg{S4Vectors} package for examples of specific \code{rbind} and \code{cbind} methods (defined for \link[S4Vectors]{RectangularData} derivatives and \link[S4Vectors]{DataFrame} objects, respectively). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ rbind # note the dispatch on the '...' arg only showMethods("rbind") selectMethod("rbind", "ANY") # the default method cbind # note the dispatch on the '...' arg only showMethods("cbind") selectMethod("cbind", "ANY") # the default method library(S4Vectors) showMethods("rbind") ## The rbind() method for RectangularData derivatives: selectMethod("rbind", "RectangularData") ## The cbind() method for DataFrame objects: selectMethod("cbind", "DataFrame") } \keyword{methods} BiocGenerics/man/colSums.Rd0000644000175200017520000000377414136047726016644 0ustar00biocbuildbiocbuild\name{colSums} \alias{rowSums} \alias{colSums} \alias{rowMeans} \alias{colMeans} \title{Form Row and Column Sums and Means} \description{ Form row and column sums and means for rectangular objects.. NOTE: This man page is for the \code{rowSums}, \code{colSums}, \code{rowMeans}, and \code{colMeans} \emph{S4 generic functions} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{colSums}} for the default methods (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically array-like) not supported by the default methods. } \usage{ colSums (x, na.rm=FALSE, dims=1, ...) rowSums (x, na.rm=FALSE, dims=1, ...) colMeans(x, na.rm=FALSE, dims=1, ...) rowMeans(x, na.rm=FALSE, dims=1, ...) } \arguments{ \item{x}{ A rectangular object, like a matrix or data frame. } \item{na.rm, dims}{ See \code{?base::\link[base]{colSums}} for a description of these arguments. } \item{...}{ Additional arguments, for use in specific methods. } } \value{ See \code{?base::\link[base]{colSums}} for the value returned by the default methods. } \seealso{ \itemize{ \item \code{base::\link[base]{colSums}} for the default \code{colSums}, \code{rowSums}, \code{colMeans}, and \code{colSums} methods. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[DelayedArray]{colSums,DelayedMatrix-method} in the \pkg{DelayedArray} package for an example of a specific \code{colSums} method (defined for \link[DelayedArray]{DelayedMatrix} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ colSums showMethods("colSums") selectMethod("colSums", "ANY") # the default method } \keyword{methods} BiocGenerics/man/combine.Rd0000644000175200017520000001332014136047726016617 0ustar00biocbuildbiocbuild\name{combine} \alias{combine} \alias{combine,ANY,missing-method} \alias{combine,data.frame,data.frame-method} \alias{combine,matrix,matrix-method} \title{Combining or merging different Bioconductor data structures} \description{ The \code{combine} generic function handles methods for combining or merging different Bioconductor data structures. It should, given an arbitrary number of arguments of the same class (possibly by inheritance), combine them into a single instance in a sensible way (some methods may only combine 2 objects, ignoring \code{...} in the argument list; because Bioconductor data structures are complicated, check carefully that \code{combine} does as you intend). } \usage{ combine(x, y, ...) } \arguments{ \item{x}{One of the values.} \item{y}{A second value.} \item{...}{Any other objects of the same class as \code{x} and \code{y}.} } \details{ There are two basic combine strategies. One is an intersection strategy. The returned value should only have rows (or columns) that are found in all input data objects. The union strategy says that the return value will have all rows (or columns) found in any one of the input data objects (in which case some indication of what to use for missing values will need to be provided). These functions and methods are currently under construction. Please let us know if there are features that you require. } \section{Methods}{ The following methods are defined in the \pkg{BiocGenerics} package: \describe{ \item{\code{combine(x=ANY, missing)}}{Return the first (x) argument unchanged.} \item{\code{combine(data.frame, data.frame)}}{Combines two \code{data.frame} objects so that the resulting \code{data.frame} contains all rows and columns of the original objects. Rows and columns in the returned value are unique, that is, a row or column represented in both arguments is represented only once in the result. To perform this operation, \code{combine} makes sure that data in shared rows and columns are identical in the two data.frames. Data differences in shared rows and columns usually cause an error. \code{combine} issues a warning when a column is a \code{\link{factor}} and the levels of the factor in the two data.frames are different.} \item{\code{combine(matrix, matrix)}}{Combined two \code{matrix} objects so that the resulting \code{matrix} contains all rows and columns of the original objects. Both matricies must have \code{dimnames}. Rows and columns in the returned value are unique, that is, a row or column represented in both arguments is represented only once in the result. To perform this operation, \code{combine} makes sure that data in shared rows and columns are all equal in the two matricies.} } Additional \code{combine} methods are defined in the \pkg{Biobase} package for \link[Biobase]{AnnotatedDataFrame}, \link[Biobase]{AssayData}, \link[Biobase]{MIAME}, and \link[Biobase]{eSet} objects. } \value{ A single value of the same class as the most specific common ancestor (in class terms) of the input values. This will contain the appropriate combination of the data in the input values. } \author{Biocore} \seealso{ \itemize{ \item \link[Biobase]{combine,AnnotatedDataFrame,AnnotatedDataFrame-method}, \link[Biobase]{combine,AssayData,AssayData-method}, \link[Biobase]{combine,MIAME,MIAME-method}, and \link[Biobase]{combine,eSet,eSet-method} in the \pkg{Biobase} package for additional \code{combine} methods. \item \code{\link{merge}} for merging two data frames (or data-frame-like) objects. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ combine showMethods("combine") selectMethod("combine", c("ANY", "missing")) selectMethod("combine", c("data.frame", "data.frame")) selectMethod("combine", c("matrix", "matrix")) ## --------------------------------------------------------------------- ## COMBINING TWO DATA FRAMES ## --------------------------------------------------------------------- x <- data.frame(x=1:5, y=factor(letters[1:5], levels=letters[1:8]), row.names=letters[1:5]) y <- data.frame(z=3:7, y=factor(letters[3:7], levels=letters[1:8]), row.names=letters[3:7]) combine(x,y) w <- data.frame(w=4:8, y=factor(letters[4:8], levels=letters[1:8]), row.names=letters[4:8]) combine(w, x, y) # y is converted to 'factor' with different levels df1 <- data.frame(x=1:5,y=letters[1:5], row.names=letters[1:5]) df2 <- data.frame(z=3:7,y=letters[3:7], row.names=letters[3:7]) try(combine(df1, df2)) # fails # solution 1: ensure identical levels y1 <- factor(letters[1:5], levels=letters[1:7]) y2 <- factor(letters[3:7], levels=letters[1:7]) df1 <- data.frame(x=1:5,y=y1, row.names=letters[1:5]) df2 <- data.frame(z=3:7,y=y2, row.names=letters[3:7]) combine(df1, df2) # solution 2: force column to be 'character' df1 <- data.frame(x=1:5,y=I(letters[1:5]), row.names=letters[1:5]) df2 <- data.frame(z=3:7,y=I(letters[3:7]), row.names=letters[3:7]) combine(df1, df2) ## --------------------------------------------------------------------- ## COMBINING TWO MATRICES ## --------------------------------------------------------------------- m <- matrix(1:20, nrow=5, dimnames=list(LETTERS[1:5], letters[1:4])) combine(m[1:3,], m[4:5,]) combine(m[1:3, 1:3], m[3:5, 3:4]) # overlap } \keyword{methods} BiocGenerics/man/dbconn.Rd0000644000175200017520000000235014136047726016447 0ustar00biocbuildbiocbuild\name{dbconn} \alias{dbconn} \alias{dbfile} \title{Accessing SQLite DB information} \description{ Get a connection object or file path for a SQLite DB } \usage{ dbconn(x) dbfile(x) } \arguments{ \item{x}{ An object with a SQLite connection. } } \value{ \code{dbconn} returns a connection object to the SQLite DB containing \code{x}'s data. \code{dbfile} returns a path (character string) to the SQLite DB (file) containing \code{x}'s data. } \seealso{ \itemize{ \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[AnnotationDbi]{dbconn,AnnotationDb-method} in the \pkg{AnnotationDbi} package for an example of a specific \code{dbconn} method (defined for \link[AnnotationDbi]{dbconn} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ dbconn showMethods("dbconn") dbfile showMethods("dbfile") library(AnnotationDbi) showMethods("dbconn") selectMethod("dbconn", "AnnotationDb") } \keyword{methods} BiocGenerics/man/density.Rd0000644000175200017520000000313414136047726016664 0ustar00biocbuildbiocbuild\name{density} \alias{density} \title{Kernel density estimation} \description{ The generic function \code{density} computes kernel density estimates. NOTE: This man page is for the \code{density} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?stats::\link[stats]{density}} for the default method (defined in the \pkg{stats} package). Bioconductor packages can define specific methods for objects not supported by the default method. } \usage{ density(x, ...) } \arguments{ \item{x, ...}{ See \code{?stats::\link[stats]{density}}. } } \value{ See \code{?stats::\link[stats]{density}} for the value returned by the default method. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default method. } \seealso{ \itemize{ \item \code{stats::\link[stats]{density}} for the default \code{density} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[flowClust]{density,flowClust-method} in the \pkg{flowClust} package for an example of a specific \code{density} method (defined for \link[flowClust]{flowClust} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ density showMethods("density") selectMethod("density", "ANY") # the default method } \keyword{methods} BiocGenerics/man/dge.Rd0000644000175200017520000000260514136047726015746 0ustar00biocbuildbiocbuild\name{dge} \alias{conditions} \alias{conditions<-} \alias{design} \alias{design<-} \alias{counts} \alias{counts<-} \alias{dispTable} \alias{dispTable<-} \alias{sizeFactors} \alias{sizeFactors<-} \alias{estimateSizeFactors} \alias{estimateDispersions} \alias{plotDispEsts} \title{Accessors and generic functions used in the context of count datasets} \description{These generic functions provide basic interfaces to operations on and data access to count datasets.} \usage{ counts(object, ...) counts(object, ...) <- value dispTable(object, ...) dispTable(object, ...) <- value sizeFactors(object, ...) sizeFactors(object, ...) <- value conditions(object, ...) conditions(object, ...) <- value design(object, ...) design(object, ...) <- value estimateSizeFactors(object, ...) estimateDispersions(object, ...) plotDispEsts(object, ...) } \arguments{ \item{object}{Object of class for which methods are defined, e.g., \code{CountDataSet}, \code{DESeqSummarizedExperiment} or \code{ExonCountSet}.} \item{value}{Value to be assigned to corresponding components of \code{object}; supported types depend on method implementation.} \item{...}{Further arguments, perhaps used by metohds} } \details{For the details, please consult the manual pages of the methods in the \pkg{DESeq}, \pkg{DESeq2}, and \pkg{DEXSeq} packages and the package vignettes.} \author{W. Huber, S. Anders} \keyword{manip} BiocGenerics/man/dims.Rd0000644000175200017520000000520114136047726016136 0ustar00biocbuildbiocbuild\name{dims} \alias{dims} \alias{nrows} \alias{ncols} \title{Get the dimensions of each element of a list-like object} \description{ Get the dimensions, number of rows, or number of columns, of each element of a list-like object. Note that these functions are the \emph{vectorized versions} of corresponding functions \code{dim()}, \code{nrow()}, and \code{ncol()}, in the same fashion that \code{lengths()} is the \emph{vectorized version} of \code{length}. } \usage{ dims(x, use.names=TRUE) nrows(x, use.names=TRUE) ncols(x, use.names=TRUE) } \arguments{ \item{x}{ List-like object (or environment) where all the list elements are expected to be array-like objects with the \emph{same number of dimensions}. } \item{use.names}{ Logical indicating if the names on \code{x} should be propagated to the returned matrix (as its rownames) or vector (as its names). } } \value{ For \code{dims()}: Typically a numeric matrix with one row per list element in \code{x} and one column per dimension in these list elements (they're all expected to have the same number of dimensions). The i-th row in the returned matrix is a vector containing the dimensions of the i-th list element in \code{x}. More formally: \preformatted{ dims(x)[i, ] is dim(x[[i]])} for any valid \code{i}. By default the names on \code{x}, if any, are propagated as the rownames of the returned matrix, unless \code{use.names} is set to \code{FALSE}. For \code{nrows()} or \code{ncols()}: A numeric vector with one element per list element in \code{x}. The i-th element in the returned vector is the number of rows (or columns) of the i-th list element in \code{x}. More formally: \preformatted{ nrows(x)[i] is nrow(x[[i]]) and ncols(x)[i] is ncol(x[[i]])} for any valid \code{i}. By default the names on \code{x}, if any, are propagated on the returned vector, unless \code{use.names} is set to \code{FALSE}. } \seealso{ \itemize{ \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[IRanges]{dims,DataFrameList-method} in the \pkg{IRanges} package for an example of a specific \code{dims} method (defined for \link[IRanges]{DataFrameList} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ dims showMethods("dims") library(IRanges) showMethods("dims") selectMethod("dims", "DataFrameList") } \keyword{methods} BiocGenerics/man/do.call.Rd0000644000175200017520000000432714136047726016526 0ustar00biocbuildbiocbuild\name{do.call} \alias{do.call} \title{Execute a function call} \description{ \code{do.call} constructs and executes a function call from a name or a function and a list of arguments to be passed to it. NOTE: This man page is for the \code{do.call} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{do.call}} for the default method (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects not supported by the default method. } \usage{ do.call(what, args, quote=FALSE, envir=parent.frame()) } \arguments{ \item{what}{ The default method expects either a function or a non-empty character string naming the function to be called. See \code{?base::\link[base]{do.call}} for the details. Specific methods can support other objects. Please refer to the documentation of a particular method for the details. } \item{args}{ The default method expects a \emph{list} of arguments to the function call (the \code{names} attribute of \code{args} gives the argument names). See \code{?base::\link[base]{do.call}} for the details. Specific methods can support other objects. Please refer to the documentation of a particular method for the details. } \item{quote, envir}{ See \code{?base::\link[base]{do.call}} for a description of these arguments. } } \value{ The result of the (evaluated) function call. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default method. } \seealso{ \itemize{ \item \code{base::\link[base]{do.call}} for the default \code{do.call} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ do.call # note the dispatch on the 'what' and 'args' args only showMethods("do.call") selectMethod("do.call", c("ANY", "ANY")) # the default method } \keyword{methods} BiocGenerics/man/duplicated.Rd0000644000175200017520000000537314136047726017332 0ustar00biocbuildbiocbuild\name{duplicated} \alias{duplicated} \alias{anyDuplicated} \title{Determine duplicate elements} \description{ Determines which elements of a vector-like or data-frame-like object are duplicates of elements with smaller subscripts, and returns a logical vector indicating which elements (rows) are duplicates. NOTE: This man page is for the \code{duplicated} and \code{anyDuplicated} \emph{S4 generic functions} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{duplicated}} for the default methods (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically vector-like or data-frame-like) not supported by the default method. } \usage{ duplicated(x, incomparables=FALSE, ...) anyDuplicated(x, incomparables=FALSE, ...) } \arguments{ \item{x}{ A vector-like or data-frame-like object. } \item{incomparables, ...}{ See \code{?base::\link[base]{duplicated}} for a description of these arguments. } } \value{ The default \code{duplicated} method (see \code{?base::\link[base]{duplicated}}) returns a logical vector of length N where N is: \itemize{ \item \code{length(x)} when \code{x} is a vector; \item \code{nrow(x)} when \code{x} is a data frame. } Specific \code{duplicated} methods defined in Bioconductor packages must also return a logical vector of the same length as \code{x} when \code{x} is a vector-like object, and a logical vector with one element for each row when \code{x} is a data-frame-like object. The default \code{anyDuplicated} method (see \code{?base::\link[base]{duplicated}}) returns a single non-negative integer and so must the specific \code{anyDuplicated} methods defined in Bioconductor packages. \code{anyDuplicated} should always behave consistently with \code{duplicated}. } \seealso{ \itemize{ \item \code{base::\link[base]{duplicated}} for the default \code{duplicated} and \code{anyDuplicated} methods. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{duplicated,Rle-method} in the \pkg{S4Vectors} package for an example of a specific \code{duplicated} method (defined for \link[S4Vectors]{Rle} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ duplicated showMethods("duplicated") selectMethod("duplicated", "ANY") # the default method anyDuplicated showMethods("anyDuplicated") selectMethod("anyDuplicated", "ANY") # the default method } \keyword{methods} BiocGenerics/man/eval.Rd0000644000175200017520000000452114136047726016135 0ustar00biocbuildbiocbuild\name{eval} \alias{eval} \title{Evaluate an (unevaluated) expression} \description{ \code{eval} evaluates an R expression in a specified environment. NOTE: This man page is for the \code{eval} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{eval}} for the default method (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects not supported by the default method. } \usage{ eval(expr, envir=parent.frame(), enclos=if (is.list(envir) || is.pairlist(envir)) parent.frame() else baseenv()) } \arguments{ \item{expr}{ An object to be evaluated. May be any object supported by the default method (see \code{?base::\link[base]{eval}}) or by the additional methods defined in Bioconductor packages. } \item{envir}{ The \emph{environment} in which \code{expr} is to be evaluated. May be any object supported by the default method (see \code{?base::\link[base]{eval}}) or by the additional methods defined in Bioconductor packages. } \item{enclos}{ See \code{?base::\link[base]{eval}} for a description of this argument. } } \value{ See \code{?base::\link[base]{eval}} for the value returned by the default method. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default method. } \seealso{ \itemize{ \item \code{base::\link[base]{eval}} for the default \code{eval} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[IRanges]{eval,expression,Vector-method} in the \pkg{IRanges} package for an example of a specific \code{eval} method (defined for when the \code{expr} and \code{envir} arguments are an \link[base]{expression} and a \link[S4Vectors]{Vector} object, respectively). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ eval # note the dispatch on 'expr' and 'envir' args only showMethods("eval") selectMethod("eval", c("ANY", "ANY")) # the default method } \keyword{methods} BiocGenerics/man/evalq.Rd0000644000175200017520000000232414136047726016315 0ustar00biocbuildbiocbuild\name{evalq} \alias{evalq} \title{Evaluate an (unevaluated) expression} \description{ \code{evalq} evaluates an R expression (the quoted form of its first argument) in a specified environment. NOTE: This man page is for the \code{evalq} wrapper defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{evalq}} for the function defined in the \pkg{base} package. This wrapper correctly delegates to the \code{eval} generic, rather than \code{base::\link[base]{eval}}. } \usage{ evalq(expr, envir=parent.frame(), enclos=if (is.list(envir) || is.pairlist(envir)) parent.frame() else baseenv()) } \arguments{ \item{expr}{ Quoted to form the expression that is evaluated. } \item{envir}{ The \emph{environment} in which \code{expr} is to be evaluated. May be any object supported by methods on the \code{\link{eval}} generic. } \item{enclos}{ See \code{?base::\link[base]{evalq}} for a description of this argument. } } \value{ See \code{?base::\link[base]{evalq}}. } \seealso{ \itemize{ \item \code{base::\link[base]{evalq}} for the base \code{evalq} function. } } \examples{ evalq # note just a copy of the original evalq } BiocGenerics/man/fileName.Rd0000644000175200017520000000201614136047726016723 0ustar00biocbuildbiocbuild\name{fileName} \alias{fileName} \title{Accessing the file name of an object} \description{ Get the file name of an object. } \usage{ fileName(object, ...) } \arguments{ \item{object}{ An object with a file name. } \item{...}{ Additional arguments, for use in specific methods. } } \seealso{ \itemize{ \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[MSnbase]{fileName,MSmap-method} in the \pkg{MSnbase} package for an example of a specific \code{fileName} method (defined for \link[MSnbase]{MSmap} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ fileName showMethods("fileName") library(MSnbase) showMethods("fileName") selectMethod("fileName", "MSmap") } \keyword{methods} BiocGenerics/man/funprog.Rd0000644000175200017520000000615514136047726016673 0ustar00biocbuildbiocbuild\name{funprog} \alias{funprog} \alias{Reduce} \alias{Filter} \alias{Find} \alias{Map} \alias{Position} \title{Common higher-order functions in functional programming languages} \description{ \code{Reduce} uses a binary function to successively combine the elements of a given list-like or vector-like object and a possibly given initial value. \code{Filter} extracts the elements of a list-like or vector-like object for which a predicate (logical) function gives true. \code{Find} and \code{Position} give the first or last such element and its position in the object, respectively. \code{Map} applies a function to the corresponding elements of given list-like or vector-like objects. NOTE: This man page is for the \code{Reduce}, \code{Filter}, \code{Find}, \code{Map} and \code{Position} \emph{S4 generic functions} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{Reduce}} for the default methods (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically list-like or vector-like) not supported by the default methods. } \usage{ Reduce(f, x, init, right=FALSE, accumulate=FALSE) Filter(f, x) Find(f, x, right=FALSE, nomatch=NULL) Map(f, ...) Position(f, x, right=FALSE, nomatch=NA_integer_) } \arguments{ \item{f, init, right, accumulate, nomatch}{ See \code{?base::\link[base]{Reduce}} for a description of these arguments. } \item{x}{ A list-like or vector-like object. } \item{...}{ One or more list-like or vector-like objects. } } \value{ See \code{?base::\link[base]{Reduce}} for the value returned by the default methods. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default methods. } \seealso{ \itemize{ \item \code{base::\link[base]{Reduce}} for the default \code{Reduce}, \code{Filter}, \code{Find}, \code{Map} and \code{Position} methods. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{Reduce,List-method} in the \pkg{S4Vectors} package for an example of a specific \code{Reduce} method (defined for \link[S4Vectors]{List} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ Reduce # note the dispatch on the 'x' arg only showMethods("Reduce") selectMethod("Reduce", "ANY") # the default method Filter # note the dispatch on the 'x' arg only showMethods("Filter") selectMethod("Filter", "ANY") # the default method Find # note the dispatch on the 'x' arg only showMethods("Find") selectMethod("Find", "ANY") # the default method Map # note the dispatch on the '...' arg only showMethods("Map") selectMethod("Map", "ANY") # the default method Position # note the dispatch on the 'x' arg only showMethods("Position") selectMethod("Position", "ANY") # the default method } \keyword{methods} BiocGenerics/man/get.Rd0000644000175200017520000000476414136047726015776 0ustar00biocbuildbiocbuild\name{get} \alias{get} \alias{mget} \title{Return the value of a named object} \description{ Search for an object with a given name and return it. NOTE: This man page is for the \code{get} and \code{mget} \emph{S4 generic functions} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{get}} for the default methods (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (list-like or environment-like) not supported by the default methods. } \usage{ get(x, pos=-1, envir=as.environment(pos), mode="any", inherits=TRUE) mget(x, envir, mode="any", ifnotfound, inherits=FALSE) } \arguments{ \item{x}{ For \code{get}: A variable name (or, more generally speaking, a \emph{key}), given as a single string. For \code{mget}: A vector of variable names (or \emph{keys}). } \item{envir}{ Where to look for the key(s). Typically a list-like or environment-like object. } \item{pos, mode, inherits, ifnotfound}{ See \code{?base::\link[base]{get}} for a description of these arguments. } } \details{ See \code{?base::\link[base]{get}} for details about the default methods. } \value{ For \code{get}: The value corresponding to the specified key. For \code{mget}: The list of values corresponding to the specified keys. The returned list must have one element per key, and in the same order as in \code{x}. See \code{?base::\link[base]{get}} for the value returned by the default methods. } \seealso{ \itemize{ \item \code{base::\link[base]{get}} for the default \code{get} and \code{mget} methods. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[AnnotationDbi]{get,ANY,Bimap,missing-method} in the \pkg{AnnotationDbi} package for an example of a specific \code{get} method (defined for \link[AnnotationDbi]{Bimap} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ get # note the dispatch on the 'x', 'pos' and 'envir' args only showMethods("get") selectMethod("get", c("ANY", "ANY", "ANY")) # the default method mget # note the dispatch on the 'x' and 'envir' args only showMethods("mget") selectMethod("mget", c("ANY", "ANY")) # the default method } \keyword{methods} BiocGenerics/man/grep.Rd0000644000175200017520000000365414136047726016151 0ustar00biocbuildbiocbuild\name{grep} \alias{grep} \alias{grepl} \title{Pattern Matching and Replacement} \description{ Search for matches to argument 'pattern' within each element of a character vector. NOTE: This man page is for the \code{grep} and \code{grepl} \emph{S4 generic functions} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{grep}} for the default methods (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects not supported by the default method. } \usage{ grep(pattern, x, ignore.case = FALSE, perl = FALSE, value = FALSE, fixed = FALSE, useBytes = FALSE, invert = FALSE) grepl(pattern, x, ignore.case = FALSE, perl = FALSE, fixed = FALSE, useBytes = FALSE) } \arguments{ \item{pattern}{ The pattern for searching in \code{x}, such as a regular expression. } \item{x}{ The character vector (in the general sense) to search. } \item{ignore.case, perl, value, fixed, useBytes, invert}{ See \code{?base::\link[base]{grep}} for a description of these arguments. } } \value{ See \code{?base::\link[base]{grep}} for the value returned by the default method. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default method. } \seealso{ \itemize{ \item \code{base::\link[base]{grep}} for the default \code{grep} and \code{grepl} methods. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ grep # note the dispatch on 'pattern' and 'x' args only showMethods("grep") selectMethod("grep", "ANY") # the default method } \keyword{methods} BiocGenerics/man/image.Rd0000644000175200017520000000342514136047726016272 0ustar00biocbuildbiocbuild\name{image} \alias{image} \title{Display a color image} \description{ Creates a grid of colored or gray-scale rectangles with colors corresponding to the values in \code{z}. This can be used to display three-dimensional or spatial data aka \emph{images}. NOTE: This man page is for the \code{image} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?graphics::\link[graphics]{image}} for the default method (defined in the \pkg{graphics} package). Bioconductor packages can define specific methods for objects not supported by the default method. } \usage{ image(x, ...) } \arguments{ \item{x, ...}{ See \code{?graphics::\link[graphics]{image}}. } } \details{ See \code{?graphics::\link[graphics]{image}} for the details. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default method. } \seealso{ \itemize{ \item \code{graphics::\link[graphics]{image}} for the default \code{image} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[affy]{image,AffyBatch-method} in the \pkg{affy} package for an example of a specific \code{image} method (defined for \link[affy]{AffyBatch} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ image showMethods("image") selectMethod("image", "ANY") # the default method library(affy) showMethods("image") ## The image() method for AffyBatch objects: selectMethod("image", "AffyBatch") } \keyword{methods} BiocGenerics/man/is.unsorted.Rd0000644000175200017520000000456614136047726017474 0ustar00biocbuildbiocbuild\name{is.unsorted} \alias{is.unsorted} \title{Test if a vector-like object is not sorted} \description{ Test if a vector-like object is not sorted, without the cost of sorting it. NOTE: This man page is for the \code{is.unsorted} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{is.unsorted}} for the default method (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically vector-like) not supported by the default method. } \usage{ is.unsorted(x, na.rm=FALSE, strictly=FALSE, ...) } \arguments{ \item{x}{ A vector-like object. } \item{na.rm, strictly}{ See \code{?base::\link[base]{is.unsorted}} for a description of these arguments. } \item{...}{ Additional arguments, for use in specific methods. Note that \code{base::\link[base]{is.unsorted}} (the default method) only takes the \code{x}, \code{na.rm}, and \code{strictly} arguments. } } \value{ See \code{?base::\link[base]{is.unsorted}} for the value returned by the default method. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default method. } \note{ TO DEVELOPERS: The \code{is.unsorted} method for specific vector-like objects should adhere to the same underlying order used by the \code{\link[BiocGenerics]{order}}, \code{\link[BiocGenerics]{sort}}, and \code{\link[BiocGenerics]{rank}} methods for the same objects. } \seealso{ \itemize{ \item \code{base::\link[base]{is.unsorted}} for the default \code{is.unsorted} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[GenomicRanges]{is.unsorted,GenomicRanges-method} in the \pkg{GenomicRanges} package for an example of a specific \code{is.unsorted} method (defined for \link[GenomicRanges]{GenomicRanges} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ is.unsorted # note the dispatch on the 'x' arg only showMethods("is.unsorted") selectMethod("is.unsorted", "ANY") # the default method } \keyword{methods} BiocGenerics/man/lapply.Rd0000644000175200017520000000477014136047726016515 0ustar00biocbuildbiocbuild\name{lapply} \alias{lapply} \alias{sapply} \title{Apply a function over a list-like or vector-like object} \description{ \code{lapply} returns a list of the same length as \code{X}, each element of which is the result of applying \code{FUN} to the corresponding element of \code{X}. \code{sapply} is a user-friendly version and wrapper of \code{lapply} by default returning a vector, matrix or, if \code{simplify="array"}, an array if appropriate, by applying \code{simplify2array()}. \code{sapply(x, f, simplify=FALSE, USE.NAMES=FALSE)} is the same as \code{lapply(x, f)}. NOTE: This man page is for the \code{lapply} and \code{sapply} \emph{S4 generic functions} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{lapply}} for the default methods (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically list-like or vector-like) not supported by the default methods. } \usage{ lapply(X, FUN, ...) sapply(X, FUN, ..., simplify=TRUE, USE.NAMES=TRUE) } \arguments{ \item{X}{ A list-like or vector-like object. } \item{FUN, ..., simplify, USE.NAMES}{ See \code{?base::\link[base]{lapply}} for a description of these arguments. } } \value{ See \code{?base::\link[base]{lapply}} for the value returned by the default methods. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default methods. In particular, \code{lapply} and \code{sapply(simplify=FALSE)} should always return a list. } \seealso{ \itemize{ \item \code{base::\link[base]{lapply}} for the default \code{lapply} and \code{sapply} methods. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{lapply,List-method} in the \pkg{S4Vectors} package for an example of a specific \code{lapply} method (defined for \link[S4Vectors]{List} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ lapply # note the dispatch on the 'X' arg only showMethods("lapply") selectMethod("lapply", "ANY") # the default method sapply # note the dispatch on the 'X' arg only showMethods("sapply") selectMethod("sapply", "ANY") # the default method } \keyword{methods} BiocGenerics/man/mad.Rd0000644000175200017520000000275314136047726015754 0ustar00biocbuildbiocbuild\name{mad} \alias{mad} \title{Median Absolute Deviation} \description{ Compute the median absolute deviation for a vector, dispatching only on the first argument, \code{x}. NOTE: This man page is for the \code{mad} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?stats::\link[stats]{mad}} for the default method (defined in the \pkg{stats} package). Bioconductor packages can define specific methods for objects not supported by the default method. } \usage{ mad(x, center = median(x), constant = 1.4826, na.rm = FALSE, low = FALSE, high = FALSE) } \arguments{ \item{x, center, constant, na.rm, low, high}{ See \code{?stats::\link[stats]{mad}}. } } \value{ See \code{?stats::\link[stats]{mad}} for the value returned by the default method. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default method. } \seealso{ \itemize{ \item \code{stats::\link[stats]{mad}} for the default \code{mad} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ mad showMethods("mad") selectMethod("mad", "ANY") # the default method } \keyword{methods} BiocGenerics/man/mapply.Rd0000644000175200017520000000363514136047726016515 0ustar00biocbuildbiocbuild\name{mapply} \alias{mapply} \title{Apply a function to multiple list-like or vector-like arguments} \description{ \code{mapply} is a multivariate version of \code{\link[BiocGenerics]{sapply}}. \code{mapply} applies \code{FUN} to the first elements of each \code{...} argument, the second elements, the third elements, and so on. Arguments are recycled if necessary. NOTE: This man page is for the \code{mapply} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{mapply}} for the default method (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically list-like or vector-like) not supported by the default methods. } \usage{ mapply(FUN, ..., MoreArgs=NULL, SIMPLIFY=TRUE, USE.NAMES=TRUE) } \arguments{ \item{FUN, MoreArgs, SIMPLIFY, USE.NAMES}{ See \code{?base::\link[base]{mapply}} for a description of these arguments. } \item{...}{ One or more list-like or vector-like objects of strictly positive length, or all of zero length. } } \value{ See \code{?base::\link[base]{mapply}} for the value returned by the default method. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default method. } \seealso{ \itemize{ \item \code{base::\link[base]{mapply}} for the default \code{mapply} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ mapply # note the dispatch on the '...' arg only showMethods("mapply") selectMethod("mapply", "ANY") # the default method } \keyword{methods} BiocGenerics/man/match.Rd0000644000175200017520000000530214136047726016300 0ustar00biocbuildbiocbuild\name{match} \alias{match} \alias{\%in\%} \title{Value matching} \description{ \code{match} returns a vector of the positions of (first) matches of its first argument in its second. \code{\%in\%} is a binary operator that returns a logical vector of the length of its left operand indicating if the elements in it have a match or not. NOTE: This man page is for the \code{match} and \code{\%in\%} \emph{S4 generic functions} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{match}} for the default methods (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically vector-like) not supported by the default methods. } \usage{ match(x, table, nomatch=NA_integer_, incomparables=NULL, ...) x \%in\% table } \arguments{ \item{x, table}{ Vector-like objects (typically of the same class, but not necessarily). } \item{nomatch, incomparables}{ See \code{?base::\link[base]{match}} for a description of these arguments. } \item{...}{ Additional arguments, for use in specific methods. } } \value{ The same as the default methods (see \code{?base::\link[base]{match}} for the value returned by the default methods). Specific methods defined in Bioconductor packages should behave as consistently as possible with the default methods. } \note{ The default \code{base::\link[base]{match}} method (defined in the \pkg{base} package) doesn't have the \code{...} argument. We've added it to the generic function defined in the \pkg{BiocGenerics} package in order to allow specific methods to support additional arguments if needed. } \seealso{ \itemize{ \item \code{base::\link[base]{match}} for the default \code{match} and \code{\%in\%} methods. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{match,Hits,Hits-method} and \link[S4Vectors]{\%in\%,Rle,ANY-method} in the \pkg{S4Vectors} package for examples of specific \code{match} and \code{\%in\%} methods (defined for \link[S4Vectors]{Hits} and \link[S4Vectors]{Rle} objects, respectively). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ match # note the dispatch on the 'x' and 'table' args only showMethods("match") selectMethod("match", c("ANY", "ANY")) # the default method `\%in\%` showMethods("\%in\%") selectMethod("\%in\%", c("ANY", "ANY")) # the default method } \keyword{methods} BiocGenerics/man/mean.Rd0000644000175200017520000000307214136047726016126 0ustar00biocbuildbiocbuild\name{mean} \alias{mean} \title{Arithmetic Mean} \description{ Generic function for the (trimmed) arithmetic mean. NOTE: This man page is for the \code{mean} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{mean}} for the default method (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically vector-like) not supported by the default method. } \usage{ mean(x, ...) } \arguments{ \item{x}{ typically a vector-like object } \item{...}{ see \code{\link[base]{mean}} } } \value{ See \code{?base::\link[base]{mean}} for the value returned by the default method. Specific methods defined in Bioconductor packages will typically return an object of the same class as the input object. } \seealso{ \itemize{ \item \code{base::\link[base]{mean}} for the default \code{mean} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{mean,Rle-method} in the \pkg{S4Vectors} package for an example of a specific \code{mean} method (defined for \link[S4Vectors]{Rle} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ mean showMethods("mean") selectMethod("mean", "ANY") # the default method } \keyword{methods} BiocGenerics/man/normalize.Rd0000644000175200017520000000277614136047726017220 0ustar00biocbuildbiocbuild\name{normalize} \alias{normalize} \title{Normalize an object} \description{ A generic function which normalizes an object containing microarray data or other data. Normalization is intended to remove from the intensity measures any systematic trends which arise from the microarray technology rather than from differences between the probes or between the target RNA samples hybridized to the arrays. } \usage{ normalize(object, ...) } \arguments{ \item{object}{ A data object, typically containing microarray data. } \item{...}{ Additional arguments, for use in specific methods. } } \value{ An object containing the normalized data. } \seealso{ \itemize{ \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[affy]{normalize,AffyBatch-method} in the \pkg{affy} package and \link[MSnbase]{normalize,MSnExp-method} in the \pkg{MSnbase} package for examples of specific \code{normalize} methods (defined for \link[affy]{AffyBatch} and \link[MSnbase]{MSnExp} objects, respectively). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ normalize showMethods("normalize") library(affy) showMethods("normalize") selectMethod("normalize", "AffyBatch") } \keyword{methods} BiocGenerics/man/nrow.Rd0000644000175200017520000000363614136047726016201 0ustar00biocbuildbiocbuild\name{nrow} \alias{nrow} \alias{ncol} \alias{NROW} \alias{NCOL} \title{The number of rows/columns of an array-like object} \description{ Return the number of rows or columns present in an array-like object. NOTE: This man page is for the \code{nrow}, \code{ncol}, \code{NROW} and \code{NCOL} \emph{S4 generic functions} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{nrow}} for the default methods (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically matrix- or array-like) not supported by the default methods. } \usage{ nrow(x) ncol(x) NROW(x) NCOL(x) } \arguments{ \item{x}{ A matrix- or array-like object. } } \value{ A single integer or \code{NULL}. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default methods. } \seealso{ \itemize{ \item \code{base::\link[base]{nrow}} for the default \code{nrow}, \code{ncol}, \code{NROW} and \code{NCOL} methods. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{nrow,DataFrame-method} in the \pkg{S4Vectors} package for an example of a specific \code{nrow} method (defined for \link[S4Vectors]{DataFrame} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ nrow showMethods("nrow") selectMethod("nrow", "ANY") # the default method ncol showMethods("ncol") selectMethod("ncol", "ANY") # the default method NROW showMethods("NROW") selectMethod("NROW", "ANY") # the default method NCOL showMethods("NCOL") selectMethod("NCOL", "ANY") # the default method } \keyword{methods} BiocGenerics/man/order.Rd0000644000175200017520000000577414136047726016334 0ustar00biocbuildbiocbuild\name{order} \alias{order} \title{Ordering permutation} \description{ \code{order} returns a permutation which rearranges its first argument into ascending or descending order, breaking ties by further arguments. NOTE: This man page is for the \code{order} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{order}} for the default method (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically vector-like) not supported by the default method. } \usage{ order(..., na.last=TRUE, decreasing=FALSE, method=c("auto", "shell", "radix")) } \arguments{ \item{...}{ One or more vector-like objects, all of the same length. } \item{na.last, decreasing, method}{ See \code{?base::\link[base]{order}} for a description of these arguments. } } \value{ The default method (see \code{?base::\link[base]{order}}) returns an integer vector of length N where N is the common length of the input objects. This integer vector represents a permutation of N elements and can be used to rearrange the first argument in \code{...} into ascending or descending order (by subsetting it). Specific methods defined in Bioconductor packages should also return an integer vector representing a permutation of N elements. } \note{ TO DEVELOPERS: Specific \code{order} methods should preferably be made "stable" for consistent behavior across platforms and consistency with \code{base::order()}. Note that C qsort() is \emph{not} "stable" so \code{order} methods that use qsort() at the C-level need to ultimately break ties by position, which can easily be done by adding a little extra code at the end of the comparison function passed to qsort(). \code{order(x, decreasing=TRUE)} is \emph{not} always equivalent to \code{rev(order(x))}. \code{\link[BiocGenerics]{order}}, \code{\link[BiocGenerics]{sort}}, and \code{\link[BiocGenerics]{rank}} methods for specific vector-like objects should adhere to the same underlying order that should be conceptually defined as a binary relation on the set of all possible vector values. For completeness, this binary relation should also be incarnated by a \link{<=} method. } \seealso{ \itemize{ \item \code{base::\link[base]{order}} for the default \code{order} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[IRanges]{order,IntegerRanges-method} in the \pkg{IRanges} package for an example of a specific \code{order} method (defined for \link[IRanges]{IntegerRanges} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ order showMethods("order") selectMethod("order", "ANY") # the default method } \keyword{methods} BiocGenerics/man/organism_species.Rd0000644000175200017520000000554714136047726020551 0ustar00biocbuildbiocbuild\name{organism_species} \alias{organism_species} \alias{organism} \alias{organism<-} \alias{species} \alias{species<-} \title{Organism and species accessors} \description{ Get or set the organism and/or species of an object. } \usage{ organism(object) organism(object) <- value species(object) species(object) <- value } \arguments{ \item{object}{ An object to get or set the organism or species of. } \item{value}{ The organism or species to set on \code{object}. } } \value{ \code{organism} should return the \emph{scientific name} (i.e. genus and species, or genus and species and subspecies) of the organism. Preferably in the format \code{"Genus species"} (e.g. \code{"Homo sapiens"}) or \code{"Genus species subspecies"} (e.g. \code{"Homo sapiens neanderthalensis"}). \code{species} should of course return the species of the organism. Unfortunately there is a long history of misuse of this accessor in Bioconductor so its usage is now discouraged (starting with BioC 3.1). } \note{ TO DEVELOPERS: \code{species} has been historically misused in many places in Bioconductor and is redundant with \code{organism}. So implementing the \code{species} accessor is now discouraged (starting with BioC 3.1). The \code{organism} accessor (returning the \emph{scientific name}) should be implemented instead. } \seealso{ \itemize{ \item \url{http://bioconductor.org/packages/release/BiocViews.html#___Organism} for browsing the annotation packages currently available in Bioconductor by organism. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[annotate]{organism,character-method} and \link[annotate]{organism,chromLocation-method} in the \pkg{annotate} package for examples of specific \code{organism} methods (defined for character and \link[annotate]{chromLocation} objects). \item \link[AnnotationDbi]{species,AnnotationDb-method} in the \pkg{AnnotationDbi} package for an example of a specific \code{species} method (defined for \link[AnnotationDbi]{AnnotationDb} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ ## organism() getter: organism showMethods("organism") library(annotate) showMethods("organism") selectMethod("organism", "character") selectMethod("organism", "chromLocation") ## organism() setter: `organism<-` showMethods("organism<-") ## species() getter: species showMethods("species") library(AnnotationDbi) selectMethod("species", "AnnotationDb") ## species() setter: `species<-` showMethods("species<-") } \keyword{methods} BiocGenerics/man/paste.Rd0000644000175200017520000000341714136047726016325 0ustar00biocbuildbiocbuild\name{paste} \alias{paste} \title{Concatenate strings} \description{ \code{paste} concatenates vectors of strings or vector-like objects containing strings. NOTE: This man page is for the \code{paste} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{paste}} for the default method (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically vector-like objects containing strings) not supported by the default method. } \usage{ paste(..., sep=" ", collapse=NULL, recycle0=FALSE) } \arguments{ \item{...}{ One or more vector-like objects containing strings. } \item{sep, collapse, recycle0}{ See \code{?base::\link[base]{paste}} for a description of these arguments. } } \value{ See \code{?base::\link[base]{paste}} for the value returned by the default method. Specific methods defined in Bioconductor packages will typically return an object of the same class as the input objects. } \seealso{ \itemize{ \item \code{base::\link[base]{paste}} for the default \code{paste} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{paste,Rle-method} in the \pkg{S4Vectors} package for an example of a specific \code{paste} method (defined for \link[S4Vectors]{Rle} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ paste showMethods("paste") selectMethod("paste", "ANY") # the default method } \keyword{methods} BiocGenerics/man/path.Rd0000644000175200017520000001070414136047726016142 0ustar00biocbuildbiocbuild\name{path} \alias{path} \alias{path<-} \alias{basename} \alias{basename<-} \alias{dirname} \alias{dirname<-} \alias{basename,ANY-method} \alias{dirname,ANY-method} \alias{basename<-,character-method} \alias{basename<-,ANY-method} \alias{dirname<-,character-method} \alias{dirname<-,ANY-method} \title{Accessing the path of an object} \description{ Get or set the path of an object. } \usage{ path(object, ...) path(object, ...) <- value basename(path, ...) basename(path, ...) <- value dirname(path, ...) dirname(path, ...) <- value ## The purpose of the following methods is to make the basename() and ## dirname() getters work out-of-the-box on any object for which the ## path() getter works. \S4method{basename}{ANY}(path, ...) \S4method{dirname}{ANY}(path, ...) ## The purpose of the following replacement methods is to make the ## basename() and dirname() setters work out-of-the-box on any object ## for which the path() getter and setter work. \S4method{basename}{character}(path, ...) <- value \S4method{basename}{ANY}(path, ...) <- value \S4method{dirname}{character}(path, ...) <- value \S4method{dirname}{ANY}(path, ...) <- value } \arguments{ \item{object}{ An object containing paths. Even though it will typically contain a single path, \code{object} can actually contain an arbitrary number of paths. } \item{...}{ Additional arguments, for use in specific methods. } \item{value}{ For \code{path<-}, the paths to set on \code{object}. For \code{basename<-} or \code{dirname<-}, the basenames or dirnames to set on \code{path}. } \item{path}{ A character vector \emph{or an object containing paths}. } } \value{ A character vector for \code{path(object)}, \code{basename(path)}, and \code{dirname(path)}. Typically of length 1 but not necessarily. Possibly with names on it for \code{path(object)}. } \seealso{ \itemize{ \item \code{base::\link[base]{basename}} for the functions the \code{basename} and \code{dirname} generics are based on. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[Rsamtools]{path,RsamtoolsFile-method} in the \pkg{Rsamtools} package for an example of a specific \code{path} method (defined for \link[Rsamtools]{RsamtoolsFile} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ ## --------------------------------------------------------------------- ## GENERIC FUNCTIONS AND DEFAULT METHODS ## --------------------------------------------------------------------- path showMethods("path") `path<-` showMethods("path<-") basename showMethods("basename") `basename<-` showMethods("basename<-") dirname showMethods("dirname") `dirname` showMethods("dirname<-") ## Default basename() and dirname() getters: selectMethod("basename", "ANY") selectMethod("dirname", "ANY") ## Default basename() and dirname() setters: selectMethod("basename<-", "character") selectMethod("basename<-", "ANY") selectMethod("dirname<-", "character") selectMethod("dirname<-", "ANY") ## --------------------------------------------------------------------- ## OBJECTS CONTAINING PATHS ## --------------------------------------------------------------------- ## Let's define a simple class to represent objects that contain paths: setClass("A", slots=c(stuff="ANY", path="character")) a <- new("A", stuff=runif(5), path=c(one="path/to/file1", two="path/to/file2")) ## path() getter: setMethod("path", "A", function(object) object@path) path(a) ## Because the path() getter works on 'a', now the basename() and ## dirname() getters also work: basename(a) dirname(a) ## path() setter: setReplaceMethod("path", "A", function(object, ..., value) { if (length(list(...)) != 0L) { dots <- match.call(expand.dots=FALSE)[[3L]] stop(BiocGenerics:::unused_arguments_msg(dots)) } object@path <- value object } ) a <- new("A", stuff=runif(5)) path(a) <- c(one="path/to/file1", two="path/to/file2") path(a) ## Because the path() getter and setter work on 'a', now the basename() ## and dirname() setters also work: basename(a) <- toupper(basename(a)) path(a) dirname(a) <- "~/MyDataFiles" path(a) } \keyword{methods} BiocGenerics/man/plotMA.Rd0000644000175200017520000000244414136047726016404 0ustar00biocbuildbiocbuild\name{plotMA} \alias{plotMA} \alias{plotMA,ANY-method} \title{MA-plot: plot differences versus averages for high-throughput data} \description{ A generic function which produces an MA-plot for an object containing microarray, RNA-Seq or other data. } \usage{ plotMA(object, ...) } \arguments{ \item{object}{ A data object, typically containing count values from an RNA-Seq experiment or microarray intensity values. } \item{...}{ Additional arguments, for use in specific methods. } } \value{ Undefined. The function exists for its side effect, producing a plot. } \seealso{ \itemize{ \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \code{\link[limma]{plotMA}} in the \pkg{limma} package for a function with the same name that is not dispatched through this generic function. \item \code{\link{BiocGenerics}} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ showMethods("plotMA") suppressWarnings( if(require("DESeq2")) example("plotMA", package="DESeq2", local=TRUE) ) } \keyword{methods} BiocGenerics/man/plotPCA.Rd0000644000175200017520000000217414136047726016512 0ustar00biocbuildbiocbuild\name{plotPCA} \alias{plotPCA} \alias{plotPCA,ANY-method} \title{PCA-plot: Principal Component Analysis plot} \description{ A generic function which produces a PCA-plot. } \usage{ plotPCA(object, ...) } \arguments{ \item{object}{ A data object, typically containing gene expression information. } \item{...}{ Additional arguments, for use in specific methods. } } \value{ Undefined. The function exists for its side effect, producing a plot. } \seealso{ \itemize{ \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \code{\link[DESeq2]{plotPCA}} in the \pkg{DESeq2} package for an example method that uses this generic. \item \code{\link{BiocGenerics}} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ showMethods("plotPCA") suppressWarnings( if(require("DESeq2")) example("plotPCA", package="DESeq2", local=TRUE) ) } \keyword{methods} BiocGenerics/man/rank.Rd0000644000175200017520000000504114136047726016137 0ustar00biocbuildbiocbuild\name{rank} \alias{rank} \title{Ranks the values in a vector-like object} \description{ Returns the ranks of the values in a vector-like object. Ties (i.e., equal values) and missing values can be handled in several ways. NOTE: This man page is for the \code{rank} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{rank}} for the default method (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects not supported by the default method. } \usage{ rank(x, na.last=TRUE, ties.method=c("average", "first", "last", "random", "max", "min"), ...) } \arguments{ \item{x}{ A vector-like object. } \item{na.last, ties.method}{ See \code{?base::\link[base]{rank}} for a description of these arguments. } \item{...}{ Additional arguments, for use in specific methods. Note that \code{base::\link[base]{rank}} (the default method) only takes the \code{x}, \code{na.last}, and \code{ties.method} arguments. } } \value{ See \code{?base::\link[base]{rank}} for the value returned by the default method. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default method. } \note{ TO DEVELOPERS: See note in \code{?BiocGenerics::\link[BiocGenerics]{order}} about "stable" order. \code{\link[BiocGenerics]{order}}, \code{\link[BiocGenerics]{sort}}, and \code{\link[BiocGenerics]{rank}} methods for specific vector-like objects should adhere to the same underlying order that should be conceptually defined as a binary relation on the set of all possible vector values. For completeness, this binary relation should also be incarnated by a \link{<=} method. } \seealso{ \itemize{ \item \code{base::\link[base]{rank}} for the default \code{rank} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{rank,Vector-method} in the \pkg{S4Vectors} package for an example of a specific \code{rank} method (defined for \link[S4Vectors]{Vector} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ rank # note the dispatch on the 'x' arg only showMethods("rank") selectMethod("rank", "ANY") # the default method } \keyword{methods} BiocGenerics/man/relist.Rd0000644000175200017520000000333214136047726016507 0ustar00biocbuildbiocbuild\name{relist} \alias{relist} \title{Re-listing an unlist()ed object} \description{ \code{relist} is a generic function with a few methods in order to allow easy inversion of \code{unlist(x)}. NOTE: This man page is for the \code{relist} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?utils::\link[utils]{relist}} for the default method (defined in the \pkg{utils} package). Bioconductor packages can define specific methods for objects not supported by the default method. } \usage{ relist(flesh, skeleton) } \arguments{ \item{flesh}{ A vector-like object. } \item{skeleton}{ A list-like object. Only the "shape" (i.e. the lengths of the individual list elements) of \code{skeleton} matters. Its exact content is ignored. } } \value{ A list-like object with the same "shape" as \code{skeleton} and that would give \code{flesh} back if unlist()ed. } \seealso{ \itemize{ \item \code{utils::\link[utils]{relist}} for the default \code{relist} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[IRanges]{relist,ANY,List-method} in the \pkg{IRanges} package for an example of a specific \code{relist} method (defined for when \code{skeleton} is a \link[S4Vectors]{List} object). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ relist showMethods("relist") selectMethod("relist", c("ANY", "ANY")) # the default method } \keyword{methods} BiocGenerics/man/rep.Rd0000644000175200017520000000335714136047726016002 0ustar00biocbuildbiocbuild\name{rep} \alias{rep.int} \title{Replicate elements of a vector-like object} \description{ \code{rep.int} replicates the elements in \code{x}. NOTE: This man page is for the \code{rep.int} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{rep.int}} for the default method (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically vector-like) not supported by the default method. } \usage{ rep.int(x, times) } \arguments{ \item{x}{ The object to replicate (typically vector-like). } \item{times}{ See \code{?base::\link[base]{rep.int}} for a description of this argument. } } \value{ See \code{?base::\link[base]{rep.int}} for the value returned by the default method. Specific methods defined in Bioconductor packages will typically return an object of the same class as the input object. } \seealso{ \itemize{ \item \code{base::\link[base]{rep.int}} for the default \code{rep.int}, \code{intersect}, and \code{setdiff} methods. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{rep.int,Rle-method} in the \pkg{S4Vectors} package for an example of a specific \code{rep.int} method (defined for \link[S4Vectors]{Rle} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ rep.int showMethods("rep.int") selectMethod("rep.int", "ANY") # the default method } \keyword{methods} BiocGenerics/man/residuals.Rd0000644000175200017520000000277614136047726017213 0ustar00biocbuildbiocbuild\name{residuals} \alias{residuals} \title{Extract model residuals} \description{ \code{residuals} is a generic function which extracts model residuals from objects returned by modeling functions. NOTE: This man page is for the \code{residuals} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?stats::\link[stats]{residuals}} for the default method (defined in the \pkg{stats} package). Bioconductor packages can define specific methods for objects not supported by the default method. } \usage{ residuals(object, ...) } \arguments{ \item{object, ...}{ See \code{?stats::\link[stats]{residuals}}. } } \value{ Residuals extracted from the object \code{object}. } \seealso{ \itemize{ \item \code{stats::\link[stats]{residuals}} for the default \code{residuals} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[affyPLM]{residuals,PLMset-method} in the \pkg{affyPLM} package for an example of a specific \code{residuals} method (defined for \link[affyPLM]{PLMset} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ residuals showMethods("residuals") selectMethod("residuals", "ANY") # the default method } \keyword{methods} BiocGenerics/man/row_colnames.Rd0000644000175200017520000000545214136047726017702 0ustar00biocbuildbiocbuild\name{row+colnames} \alias{row+colnames} \alias{rownames} \alias{rownames<-} \alias{colnames} \alias{colnames<-} \title{Row and column names} \description{ Get or set the row or column names of a matrix-like object. NOTE: This man page is for the \code{rownames}, \code{`rownames<-`}, \code{colnames}, and \code{`colnames<-`} \emph{S4 generic functions} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{rownames}} for the default methods (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically matrix-like) not supported by the default methods. } \usage{ rownames(x, do.NULL=TRUE, prefix="row") rownames(x) <- value colnames(x, do.NULL=TRUE, prefix="col") colnames(x) <- value } \arguments{ \item{x}{ A matrix-like object. } \item{do.NULL, prefix}{ See \code{?base::\link[base]{rownames}} for a description of these arguments. } \item{value}{ Either \code{NULL} or a character vector equal of length equal to the appropriate dimension. } } \value{ The getters will return \code{NULL} or a character vector of length \code{\link{nrow}(x)} for \code{rownames} and length \code{\link{ncol}(x)} for \code{colnames(x)}. See \code{?base::\link[base]{rownames}} for more information about the default methods, including how the setters are expected to behave. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default methods. } \seealso{ \itemize{ \item \code{base::\link[base]{rownames}} for the default \code{rownames}, \code{`rownames<-`}, \code{colnames}, and \code{`colnames<-`} methods. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{rownames,DataFrame-method} in the \pkg{S4Vectors} package for an example of a specific \code{rownames} method (defined for \link[S4Vectors]{DataFrame} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ ## rownames() getter: rownames # note the dispatch on the 'x' arg only showMethods("rownames") selectMethod("rownames", "ANY") # the default method ## rownames() setter: `rownames<-` showMethods("rownames<-") selectMethod("rownames<-", "ANY") # the default method ## colnames() getter: colnames # note the dispatch on the 'x' arg only showMethods("colnames") selectMethod("colnames", "ANY") # the default method ## colnames() setter: `colnames<-` showMethods("colnames<-") selectMethod("colnames<-", "ANY") # the default method } \keyword{methods} BiocGenerics/man/score.Rd0000644000175200017520000000235514136047726016324 0ustar00biocbuildbiocbuild\name{score} \alias{score} \alias{score<-} \title{Score accessor} \description{ Get or set the score value contained in an object. } \usage{ score(x, ...) score(x, ...) <- value } \arguments{ \item{x}{ An object to get or set the score value of. } \item{...}{ Additional arguments, for use in specific methods. } \item{value}{ The score value to set on \code{x}. } } \seealso{ \itemize{ \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[GenomicRanges]{score,GenomicRanges-method} in the \pkg{GenomicRanges} package for an example of a specific \code{score} method (defined for \link[GenomicRanges]{GenomicRanges} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ score showMethods("score") `score<-` showMethods("score<-") library(GenomicRanges) showMethods("score") selectMethod("score", "GenomicRanges") showMethods("score<-") selectMethod("score<-", "GenomicRanges") } \keyword{methods} BiocGenerics/man/sets.Rd0000644000175200017520000000610214136047726016161 0ustar00biocbuildbiocbuild\name{sets} \alias{sets} \alias{union} \alias{intersect} \alias{setdiff} \title{Set operations} \description{ Performs \emph{set} union, intersection and (asymmetric!) difference on two vector-like objects. NOTE: This man page is for the \code{union}, \code{intersect} and \code{setdiff} \emph{S4 generic functions} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{union}} for the default methods (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically vector-like) not supported by the default methods. } \usage{ union(x, y, ...) intersect(x, y, ...) setdiff(x, y, ...) } \arguments{ \item{x, y}{ Vector-like objects (typically of the same class, but not necessarily). } \item{...}{ Additional arguments, for use in specific methods. } } \value{ See \code{?base::\link[base]{union}} for the value returned by the default methods. Specific methods defined in Bioconductor packages will typically return an object of the same class as the input objects. } \note{ The default methods (defined in the \pkg{base} package) only take 2 arguments. We've added the \code{...} argument to the generic functions defined in the \pkg{BiocGenerics} package so they can be called with an arbitrary number of effective arguments. For \code{union} or \code{intersect}, this typically allows Bioconductor packages to define methods that compute the union or intersection of more than 2 objects. However, for \code{setdiff}, which is conceptually a binary operation, this typically allows methods to add extra arguments for controlling/altering the behavior of the operation. Like for example the \code{ignore.strand} argument supported by the \code{setdiff} method for \link[GenomicRanges]{GenomicRanges} objects (defined in the \pkg{GenomicRanges} package). (Note that the \code{union} and \code{intersect} methods for those objects also support the \code{ignore.strand} argument.) } \seealso{ \itemize{ \item \code{base::\link[base]{union}} for the default \code{union}, \code{intersect}, and \code{setdiff} methods. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[GenomicRanges]{union,GenomicRanges,GenomicRanges-method} in the \pkg{GenomicRanges} package for examples of specific \code{union}, \code{intersect}, and \code{setdiff} methods (defined for \link[GenomicRanges]{GenomicRanges} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ union showMethods("union") selectMethod("union", c("ANY", "ANY")) # the default method intersect showMethods("intersect") selectMethod("intersect", c("ANY", "ANY")) # the default method setdiff showMethods("setdiff") selectMethod("setdiff", c("ANY", "ANY")) # the default method } \keyword{methods} BiocGenerics/man/sort.Rd0000644000175200017520000000425314136047726016177 0ustar00biocbuildbiocbuild\name{sort} \alias{sort} \title{Sorting a vector-like object} \description{ Sort a vector-like object into ascending or descending order. NOTE: This man page is for the \code{sort} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{sort}} for the default method (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects not supported by the default method. } \usage{ sort(x, decreasing=FALSE, ...) } \arguments{ \item{x}{ A vector-like object. } \item{decreasing, ...}{ See \code{?base::\link[base]{sort}} for a description of these arguments. } } \value{ See \code{?base::\link[base]{sort}} for the value returned by the default method. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default method. } \note{ TO DEVELOPERS: See note in \code{?BiocGenerics::\link[BiocGenerics]{order}} about "stable" order. \code{\link[BiocGenerics]{order}}, \code{\link[BiocGenerics]{sort}}, and \code{\link[BiocGenerics]{rank}} methods for specific vector-like objects should adhere to the same underlying order that should be conceptually defined as a binary relation on the set of all possible vector values. For completeness, this binary relation should also be incarnated by a \link{<=} method. } \seealso{ \itemize{ \item \code{base::\link[base]{sort}} for the default \code{sort} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{sort,Vector-method} in the \pkg{S4Vectors} package for an example of a specific \code{sort} method (defined for \link[S4Vectors]{Vector} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ sort # note the dispatch on the 'x' arg only showMethods("sort") selectMethod("sort", "ANY") # the default method } \keyword{methods} BiocGenerics/man/start.Rd0000644000175200017520000000602214136047726016341 0ustar00biocbuildbiocbuild\name{start} \alias{start} \alias{start<-} \alias{end} \alias{end<-} \alias{width} \alias{width<-} \alias{pos} \title{The start(), end(), width(), and pos() generic getters and setters} \description{ Get or set the start, end, width, or single positions stored in an object. NOTE: This man page is for the \code{start}, \code{`start<-`}, \code{end}, \code{`end<-`}, \code{width}, \code{`width<-`}, and \code{pos} \emph{S4 generic functions} defined in the \pkg{BiocGenerics} package. See \code{?stats::\link[stats]{start}} for the \code{start} and \code{end} S3 generics defined in the \pkg{stats} package. } \usage{ start(x, ...) start(x, ...) <- value end(x, ...) end(x, ...) <- value width(x) width(x, ...) <- value pos(x) } \arguments{ \item{x}{ For the \code{start()}, \code{end()}, and \code{width()} getters/setters: an object containing start, end, and width values. For the \code{pos{}} getter: an object containing single positions. } \item{...}{ Additional arguments, for use in specific methods. } \item{value}{ The start, end, or width values to set on \code{x}. } } \value{ See specific methods defined in Bioconductor packages. } \seealso{ \itemize{ \item \code{stats::\link[stats]{start}} in the \pkg{stats} package for the \code{start} and \code{end} S3 generics. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[IRanges]{start,IRanges-method} in the \pkg{IRanges} package for examples of specific \code{start}, \code{end}, and \code{width} methods (defined for \link[IRanges]{IRanges} objects). \item \link[IRanges]{pos,UnstitchedIPos-method} in the \pkg{IRanges} package for an example of a specific \code{pos} method (defined for \link[IRanges]{UnstitchedIPos} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ ## start() getter: start showMethods("start") library(IRanges) showMethods("start") selectMethod("start", "IRanges") # start() getter for IRanges objects ## start() setter: `start<-` showMethods("start<-") selectMethod("start<-", "IRanges") # start() setter for IRanges objects ## end() getter: end showMethods("end") selectMethod("end", "IRanges") # end() getter for IRanges objects ## end() setter: `end<-` showMethods("end<-") selectMethod("end<-", "IRanges") # end() setter for IRanges objects ## width() getter: width showMethods("width") selectMethod("width", "IRanges") # width() getter for IRanges objects ## width() setter: `width<-` showMethods("width<-") selectMethod("width<-", "IRanges") # width() setter for IRanges objects ## pos() getter: pos showMethods("pos") selectMethod("pos", "UnstitchedIPos") # pos() getter for UnstitchedIPos # objects } \keyword{methods} BiocGenerics/man/strand.Rd0000644000175200017520000000520714136047726016503 0ustar00biocbuildbiocbuild\name{strand} \alias{strand} \alias{strand<-} \alias{unstrand} \alias{invertStrand} \alias{invertStrand,ANY-method} \title{Accessing strand information} \description{ Get or set the strand information contained in an object. } \usage{ strand(x, ...) strand(x, ...) <- value unstrand(x) invertStrand(x) \S4method{invertStrand}{ANY}(x) } \arguments{ \item{x}{ An object containing strand information. } \item{...}{ Additional arguments, for use in specific methods. } \item{value}{ The strand information to set on \code{x}. } } \details{ All the \code{strand} methods defined in the \pkg{GenomicRanges} package use the same set of 3 values (called the "standard strand levels") to specify the strand of a genomic location: \code{+}, \code{-}, and \code{*}. \code{*} is used when the exact strand of the location is unknown, or irrelevant, or when the "feature" at that location belongs to both strands. Note that \code{unstrand} is not a generic function, just a convenience wrapper to the generic \code{strand()} setter (\code{strand<-}) that does: \preformatted{ strand(x) <- "*" x } The default method for \code{invertStrand} does: \preformatted{ strand(x) <- invertStrand(strand(x)) x } } \value{ If \code{x} is a vector-like object, \code{strand(x)} will typically return a vector-like object \emph{parallel} to \code{x}, that is, an object of the same length as \code{x} where the i-th element describes the strand of the i-th element in \code{x}. \code{unstrand(x)} and \code{invertStrand(x)} return a copy of \code{x} with the strand set to \code{"*"} for \code{unstrand} or inverted for \code{invertStrand} (i.e. \code{"+"} and \code{"-"} switched, and \code{"*"} untouched). } \seealso{ \itemize{ \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[GenomicRanges]{strand,GRanges-method} in the \pkg{GenomicRanges} package for an example of a specific \code{strand} method (defined for \link[GenomicRanges]{GRanges} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ strand showMethods("strand") `strand<-` showMethods("strand<-") unstrand invertStrand showMethods("invertStrand") selectMethod("invertStrand", "ANY") # the default method library(GenomicRanges) showMethods("strand") selectMethod("strand", "missing") strand() showMethods("strand<-") } \keyword{methods} BiocGenerics/man/subset.Rd0000644000175200017520000000362014136047726016512 0ustar00biocbuildbiocbuild\name{subset} \alias{subset} \title{Subsetting vector-like, matrix-like and data-frame-like objects} \description{ Return subsets of vector-like, matrix-like or data-frame-like objects which meet conditions. NOTE: This man page is for the \code{subset} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{subset}} for the \code{subset} S3 generic defined in the \pkg{base} package. } \usage{ subset(x, ...) } \arguments{ \item{x}{ A vector-like, matrix-like or data-frame-like object to be subsetted. } \item{...}{ Additional arguments (e.g. \code{subset}, \code{select}, \code{drop}), for use in specific methods. See \code{?base::\link[base]{subset}} for more information. } } \value{ An object similar to \code{x} containing just the selected elements (for a vector-like object), or the selected rows and columns (for a matrix-like or data-frame-like object). } \seealso{ \itemize{ \item \code{base::\link[base]{subset}} in the \pkg{base} package for the \code{subset} S3 generic. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{subset,RectangularData-method} in the \pkg{S4Vectors} package for an example of a specific \code{subset} method (defined for \link[S4Vectors]{RectangularData} derivatives). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ subset showMethods("subset") selectMethod("subset", "ANY") # the default method library(S4Vectors) showMethods("subset") ## The subset() method for RectangularData derivatives: selectMethod("subset", "RectangularData") } \keyword{methods} BiocGenerics/man/t.Rd0000644000175200017520000000301514136047726015446 0ustar00biocbuildbiocbuild\name{t} \alias{t} \title{Matrix Transpose} \description{ Given a rectangular object \code{x}, \code{t} returns the transpose of \code{x}. NOTE: This man page is for the \code{t} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{t}} for the default method (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically array-like) not supported by the default method. } \usage{ t(x) } \arguments{ \item{x}{ a rectangular object, like a matrix or data frame } } \value{ See \code{?base::\link[base]{t}} for the value returned by the default method. Specific methods defined in Bioconductor packages will typically return an object of the same class as the input object. } \seealso{ \itemize{ \item \code{base::\link[base]{t}} for the default \code{t} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{t,Hits-method} in the \pkg{S4Vectors} package for an example of a specific \code{t} method (defined for \link[S4Vectors]{Hits} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ t showMethods("t") selectMethod("t", "ANY") # the default method } \keyword{methods} BiocGenerics/man/table.Rd0000644000175200017520000000333514136047726016277 0ustar00biocbuildbiocbuild\name{table} \alias{table} \title{Cross tabulation and table creation} \description{ \code{table} uses the cross-classifying factors to build a contingency table of the counts at each combination of factor levels. NOTE: This man page is for the \code{table} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{table}} for the default method (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects not supported by the default method. } \usage{ table(...) } \arguments{ \item{...}{ One or more objects which can be interpreted as factors (including character strings), or a list (or data frame) whose components can be so interpreted. } } \value{ See \code{?base::\link[base]{table}} for the value returned by the default method. Specific methods defined in Bioconductor packages should also return the type of object returned by the default method. } \seealso{ \itemize{ \item \code{base::\link[base]{table}} for the default \code{table} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{table,Rle-method} in the \pkg{S4Vectors} package for an example of a specific \code{table} method (defined for \link[S4Vectors]{Rle} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ table showMethods("table") selectMethod("table", "ANY") # the default method } \keyword{methods} BiocGenerics/man/tapply.Rd0000644000175200017520000000500314136047726016513 0ustar00biocbuildbiocbuild\name{tapply} \alias{tapply} \title{Apply a function over a ragged array} \description{ \code{tapply} applies a function to each cell of a ragged array, that is to each (non-empty) group of values given by a unique combination of the levels of certain factors. NOTE: This man page is for the \code{tapply} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{tapply}} for the default method (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically list-like or vector-like) not supported by the default method. } \usage{ tapply(X, INDEX, FUN=NULL, ..., default=NA, simplify=TRUE) } \arguments{ \item{X}{ The default method expects an atomic object, typically a vector. See \code{?base::\link[base]{tapply}} for the details. Specific methods can support other objects (typically list-like or vector-like). Please refer to the documentation of a particular method for the details. } \item{INDEX}{ The default method expects a list of one or more factors, each of same length as \code{X}. See \code{?base::\link[base]{tapply}} for the details. Specific methods can support other objects (typically list-like). Please refer to the documentation of a particular method for the details. } \item{FUN, ..., default, simplify}{ See \code{?base::\link[base]{tapply}} for a description of these arguments. } } \value{ See \code{?base::\link[base]{tapply}} for the value returned by the default method. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default method. } \seealso{ \itemize{ \item \code{base::\link[base]{tapply}} for the default \code{tapply} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[IRanges]{tapply,Vector,ANY-method} in the \pkg{IRanges} package for an example of a specific \code{tapply} method (defined for \link[S4Vectors]{Vector} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ tapply # note the dispatch on the 'X' and 'INDEX' args only showMethods("tapply") selectMethod("tapply", c("ANY", "ANY")) # the default method } \keyword{methods} BiocGenerics/man/testPackage.Rd0000644000175200017520000000473614136047726017451 0ustar00biocbuildbiocbuild\name{testPackage} \alias{testPackage} \title{Run RUnit package unit tests} \description{ \code{testPackage} helps developers implement unit tests using the \pkg{RUnit} testing conventions. } \usage{ testPackage(pkgname=NULL, subdir="unitTests", pattern="^test_.*\\\\.R$", path=getwd()) } \arguments{ \item{pkgname}{ The name of the package whose installed unit tests are to be run. A missing or NULL value implies that the \code{testPackage} command will look for tests within the package source directory indicated by \code{path}. } \item{subdir}{ A character(1) vector providing the subdirectory in which unit tests are located. The directory is searched first in the (installed or source) package root, or in a subdirectory \code{inst/} below the root. } \item{pattern}{ A character(1) regular expression describing the file names to be evaluated; typically used to restrict tests to a subset of all test files. } \item{path}{ A character(1) directory path indicating, when \code{pkgname} is missing or NULL, where unit tests will be searched. \code{path} can be any location at or below the package root. } } \details{ This function is not exported from the package namespace, and must be invoked using triple colons, \code{BiocGenerics:::testPackage()}; it is provided primarily for the convenience of developers. When invoked with missing or NULL \code{pkgname} argument, the function assumes that it has been invoked from within the package source tree (or that the source tree is located above \code{path}), and finds unit tests in \code{subdir="unitTests"} in either the base or \code{inst/} directories at the root of the package source tree. This mode is useful when developing unit tests, since the package does not have to be re-installed to run an updated test. When invoked with \code{pkgname} set to the name of an installed package, unit tests are searched for in the installed package directory. } \value{ The function returns the result of \code{RUnit::runTestSuite} invoked on the unit tests specified in the function call. } \seealso{ \url{http://bioconductor.org/developers/how-to/unitTesting-guidelines/} } \examples{ ## Run unit tests found in the library location where ## BiocGenerics is installed BiocGenerics:::testPackage("BiocGenerics") \dontrun{## Run unit tests for the package whose source tree implied ## by getwd() BiocGenerics:::testPackage() } } \keyword{methods} BiocGenerics/man/toTable.Rd0000644000175200017520000000242414136047726016600 0ustar00biocbuildbiocbuild\name{toTable} \alias{toTable} \title{An alternative to as.data.frame()} \description{ \code{toTable()} is an \emph{S4 generic function} provided as an alternative to \code{\link[BiocGenerics]{as.data.frame}()}. } \usage{ toTable(x, ...) } \arguments{ \item{x}{ The object to turn into a data frame. } \item{...}{ Additional arguments, for use in specific methods. } } \value{ A data frame. } \seealso{ \itemize{ \item The \code{\link[BiocGenerics]{as.data.frame}} \emph{S4 generic} defined in the \pkg{BiocGenerics} package. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[AnnotationDbi]{toTable,Bimap-method} in the \pkg{AnnotationDbi} package for an example of a specific \code{toTable} method (defined for \link[AnnotationDbi]{Bimap} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ toTable showMethods("toTable") library(AnnotationDbi) showMethods("toTable") selectMethod("toTable", "Bimap") } \keyword{methods} BiocGenerics/man/type.Rd0000644000175200017520000000412114136047726016163 0ustar00biocbuildbiocbuild\name{type} \alias{type} \alias{type<-} \title{Accessing the type of an object} \description{ Get or set the \emph{type} of an object. Note that \code{type} and \code{type<-} are defined as \emph{S4 generic functions} and what \emph{type} means exactly (and what \code{type()} returns) depends on the objects for which \code{type} and/or \code{type<-} methods are defined. } \usage{ type(x) type(x) <- value } \arguments{ \item{x}{ Any object for which the \code{type()} getter or setter is defined. Note that objects will either: not support the getter or setter at all, or support only the getter, or support the getter and setter. } \item{value}{ The type to set on \code{x} (assuming \code{x} supports the \code{type()} setter). \code{value} is typically (but not necessarily) expected to be a single string (i.e. a character vector of length 1). } } \value{ \code{type(x)} returns the type of \code{x}, typically (but not necessarily) as a single string (i.e. as a character vector of length 1). } \seealso{ \itemize{ \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[DelayedArray]{type,ANY-method} in the \pkg{DelayedArray} package for the default \code{type} method. \item \link[Biostrings]{type,PairwiseAlignments-method} in the \pkg{Biostrings} package for an example of a specific \code{type} method (defined for \link[Biostrings]{PairwiseAlignments} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ type showMethods("type") `type<-` showMethods("type<-") library(DelayedArray) showMethods("type") selectMethod("type", "ANY") # the default "type" method library(Biostrings) showMethods("type") ## The type() method for PairwiseAlignments objects: selectMethod("type", "PairwiseAlignments") } \keyword{methods} BiocGenerics/man/unique.Rd0000644000175200017520000000407614136047726016521 0ustar00biocbuildbiocbuild\name{unique} \alias{unique} \title{Extract unique elements} \description{ \code{unique} returns an object of the same class as \code{x} (typically a vector-like, data-frame-like, or array-like object) but with duplicate elements/rows removed. NOTE: This man page is for the \code{unique} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{unique}} for the default method (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically vector-like or data-frame-like) not supported by the default method. } \usage{ unique(x, incomparables=FALSE, ...) } \arguments{ \item{x}{ A vector-like, data-frame-like, or array-like object. } \item{incomparables, ...}{ See \code{?base::\link[base]{unique}} for a description of these arguments. } } \value{ See \code{?base::\link[base]{unique}} for the value returned by the default method. Specific methods defined in Bioconductor packages will typically return an object of the same class as the input object. \code{unique} should always behave consistently with \code{BiocGenerics::\link[BiocGenerics]{duplicated}}. } \seealso{ \itemize{ \item \code{base::\link[base]{unique}} for the default \code{unique} method. \item \code{BiocGenerics::\link[BiocGenerics]{duplicated}} for determining duplicate elements. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{unique,Rle-method} in the \pkg{S4Vectors} package for an example of a specific \code{unique} method (defined for \link[S4Vectors]{Rle} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ unique showMethods("unique") selectMethod("unique", "ANY") # the default method } \keyword{methods} BiocGenerics/man/unlist.Rd0000644000175200017520000000362414136047726016527 0ustar00biocbuildbiocbuild\name{unlist} \alias{unlist} \title{Flatten list-like objects} \description{ Given a list-like object \code{x}, \code{unlist} produces a vector-like object obtained by concatenating (conceptually thru \code{\link{c}}) all the top-level elements in \code{x} (each of them being expected to be a vector-like object, typically). NOTE: This man page is for the \code{unlist} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{unlist}} for the default method (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects not supported by the default method. } \usage{ unlist(x, recursive=TRUE, use.names=TRUE) } \arguments{ \item{x}{ A list-like object. } \item{recursive, use.names}{ See \code{?base::\link[base]{unlist}} for a description of these arguments. } } \value{ See \code{?base::\link[base]{unlist}} for the value returned by the default method. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default method. } \seealso{ \itemize{ \item \code{base::\link[base]{unlist}} for the default \code{unlist} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{unlist,List-method} in the \pkg{S4Vectors} package for an example of a specific \code{unlist} method (defined for \link[S4Vectors]{List} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ unlist # note the dispatch on the 'x' arg only showMethods("unlist") selectMethod("unlist", "ANY") # the default method } \keyword{methods} BiocGenerics/man/unsplit.Rd0000644000175200017520000000372614136047726016712 0ustar00biocbuildbiocbuild\name{unsplit} \alias{unsplit} \title{Unsplit a list-like object} \description{ Given a list-like object \code{value} and grouping \code{f}, \code{unsplit} produces a vector-like object \code{x} by conceptually reversing the split operation \code{value <- split(x, f)}. NOTE: This man page is for the \code{unsplit} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{unsplit}} for the default method (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects not supported by the default method. } \usage{ unsplit(value, f, drop=FALSE) } \arguments{ \item{value}{ A list-like object. } \item{f}{ A factor or other grouping object that corresponds to the \code{f} symbol in \code{value <- split(x, f)}. } \item{drop}{ See \code{?base::\link[base]{unsplit}} for a description of this argument. } } \value{ See \code{?base::\link[base]{unsplit}} for the value returned by the default method. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default method. } \seealso{ \itemize{ \item \code{base::\link[base]{unsplit}} for the default \code{unsplit} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[IRanges]{unsplit,List-method} in the \pkg{IRanges} package for an example of a specific \code{unsplit} method (defined for \link[S4Vectors]{List} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ unsplit # note the dispatch on the 'value' and 'f' args only showMethods("unsplit") selectMethod("unsplit", "ANY") # the default method } \keyword{methods} BiocGenerics/man/updateObject.Rd0000644000175200017520000001330314136047726017615 0ustar00biocbuildbiocbuild\name{updateObject} \alias{updateObject} \alias{updateObject,ANY-method} \alias{updateObject,list-method} \alias{updateObject,environment-method} \alias{updateObject,formula-method} \alias{updateObject,envRefClass-method} \alias{updateObjectFromSlots} \alias{getObjectSlots} \title{Update an object to its current class definition} \description{ \code{updateObject} is a generic function that returns an instance of \code{object} updated to its current class definition. } \usage{ updateObject(object, ..., verbose=FALSE) ## Related utilities: updateObjectFromSlots(object, objclass=class(object), ..., verbose=FALSE) getObjectSlots(object) } \arguments{ \item{object}{ Object to be updated for \code{updateObject} and \code{updateObjectFromSlots}. Object for slot information to be extracted from for \code{getObjectSlots}. } \item{...}{ Additional arguments, for use in specific \code{updateObject} methods. } \item{verbose}{ \code{TRUE} or \code{FALSE}, indicating whether information about the update should be reported. Use \code{\link[base]{message}} to report this information. } \item{objclass}{ Optional character string naming the class of the object to be created. } } \details{ Updating objects is primarily useful when an object has been serialized (e.g., stored to disk) for some time (e.g., months), and the class definition has in the mean time changed. Because of the changed class definition, the serialized instance is no longer valid. \code{updateObject} requires that the class of the returned object be the same as the class of the argument \code{object}, and that the object is valid (see \code{\link[methods]{validObject}}). By default, \code{updateObject} has the following behaviors: \describe{ \item{\code{updateObject(ANY, \dots, verbose=FALSE)}}{ By default, \code{updateObject} uses heuristic methods to determine whether the object should be the `new' S4 type (introduced in R 2.4.0), but is not. If the heuristics indicate an update is required, the \code{updateObjectFromSlots} function tries to update the object. The default method returns the original S4 object or the successfully updated object, or issues an error if an update is required but not possible. The optional named argument \code{verbose} causes a message to be printed describing the action. Arguments \code{\dots} are passed to \code{updateObjectFromSlots}. } \item{\code{updateObject(list, \dots, verbose=FALSE)}}{ Visit each element in \code{list}, applying \code{updateObject(list[[elt]], \dots, verbose=verbose)}. } \item{\code{updateObject(environment, \dots, verbose=FALSE)}}{ Visit each element in \code{environment}, applying \code{updateObject(environment[[elt]], \dots, verbose=verbose)} } \item{\code{updateObject(formula, \dots, verbose=FALSE)}}{ Do nothing; the environment of the formula may be too general (e.g., \code{R_GlobalEnv}) to attempt an update. } \item{\code{updateObject(envRefClass, \dots, verbose=FALSE)}}{ Attempt to update objects from fields using a strategy like \code{updateObjectFromSlots} Method 1. } } \code{updateObjectFromSlots(object, objclass=class(object), \dots, verbose=FALSE)} is a utility function that identifies the intersection of slots defined in the \code{object} instance and \code{objclass} definition. Under Method 1, the corresponding elements in \code{object} are then updated (with \code{updateObject(elt, \dots, verbose=verbose)}) and used as arguments to a call to \code{new(class, \dots)}, with \code{\dots} replaced by slots from the original object. If this fails, then Method 2 tries \code{new(class)} and assigns slots of \code{object} to the newly created instance. \code{getObjectSlots(object)} extracts the slot names and contents from \code{object}. This is useful when \code{object} was created by a class definition that is no longer current, and hence the contents of \code{object} cannot be determined by accessing known slots. } \value{ \code{updateObject} returns a valid instance of \code{object}. \code{updateObjectFromSlots} returns an instance of class \code{objclass}. \code{getObjectSlots} returns a list of named elements, with each element corresponding to a slot in \code{object}. } \seealso{ \itemize{ \item \code{\link[Biobase]{updateObjectTo}} in the \pkg{Biobase} package for updating an object to the class definition of a template (might be useful for updating a virtual superclass). \item \code{\link[methods]{validObject}} for testing the validity of an object. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ updateObject showMethods("updateObject") selectMethod("updateObject", "ANY") # the default method library(Biobase) ## update object, same class data(sample.ExpressionSet) obj <- updateObject(sample.ExpressionSet) setClass("UpdtA", representation(x="numeric"), contains="data.frame") setMethod("updateObject", "UpdtA", function(object, ..., verbose=FALSE) { if (verbose) message("updateObject object = 'A'") object <- callNextMethod() object@x <- -object@x object } ) a <- new("UpdtA", x=1:10) ## See steps involved updateObject(a) removeMethod("updateObject", "UpdtA") removeClass("UpdtA") } \keyword{methods} BiocGenerics/man/var.Rd0000644000175200017520000000322614136047726015777 0ustar00biocbuildbiocbuild\name{var} \alias{var} \alias{sd} \title{Variance and Standard Deviation} \description{ \code{var} and \code{sd} compute the variance and standard deviation of a vector \code{x}. NOTE: This man page is for the \code{var} and \code{sd}, \emph{S4 generic functions} defined in the \pkg{BiocGenerics} package. See \code{?stats::\link[stats]{var}} and \code{?stats::\link[stats]{sd}} for the default methods (defined in the \pkg{stats} package). Bioconductor packages can define specific methods for objects (typically array-like) not supported by the default method. } \usage{ var(x, y = NULL, na.rm = FALSE, use) sd(x, na.rm = FALSE) } \arguments{ \item{x}{ a vector-like object } \item{y}{ a vector-like object, or \code{NULL} } \item{na.rm, use}{see \link[stats]{var}} } \value{ See \code{?stats::\link[stats]{var}} and \code{?stats::\link[stats]{sd}} for the value returned by the default methods. Specific methods defined in Bioconductor packages will typically return an object of the same class as the input object. } \seealso{ \itemize{ \item \code{stats::\link[stats]{var}} and \code{stats::\link[stats]{sd}} for the default methods. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ var showMethods("var") selectMethod("var", "ANY") # the default method } \keyword{methods} BiocGenerics/man/weights.Rd0000644000175200017520000000326414136047726016663 0ustar00biocbuildbiocbuild\name{weights} \alias{weights} \title{Extract model weights} \description{ \code{weights} is a generic function which extracts fitting weights from objects returned by modeling functions. NOTE: This man page is for the \code{weights} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?stats::\link[stats]{weights}} for the default method (defined in the \pkg{stats} package). Bioconductor packages can define specific methods for objects not supported by the default method. } \usage{ weights(object, ...) } \arguments{ \item{object, ...}{ See \code{?stats::\link[stats]{weights}}. } } \value{ Weights extracted from the object \code{object}. See \code{?stats::\link[stats]{weights}} for the value returned by the default method. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default method. } \seealso{ \itemize{ \item \code{stats::\link[stats]{weights}} for the default \code{weights} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[affyPLM]{weights,PLMset-method} in the \pkg{affyPLM} package for an example of a specific \code{weights} method (defined for \link[affyPLM]{PLMset} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ weights showMethods("weights") selectMethod("weights", "ANY") # the default method } \keyword{methods} BiocGenerics/man/which.Rd0000644000175200017520000000402214136047726016304 0ustar00biocbuildbiocbuild\name{which} \alias{which} \title{Which values in an object are considered TRUE?} \description{ Give the indices of the values in a vector-, array-, or list-like object that are considered \code{TRUE}, allowing for array indices in the case of an array-like object. NOTE: This man page is for the \code{which} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{which}} for the default method (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically vector-, array-, or list-like) not supported by the default methods. } \usage{ which(x, arr.ind=FALSE, useNames=TRUE) } \arguments{ \item{x}{ An object, typically with a vector-, array-, or list-like semantic. } \item{arr.ind, useNames}{ See \code{?base::\link[base]{which}} for a description of these arguments. } } \value{ See \code{?base::\link[base]{which}} for the value returned by the default method. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default method. } \seealso{ \itemize{ \item \code{base::\link[base]{which}} for the default \code{which} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[DelayedArray]{which,DelayedArray-method} in the \pkg{DelayedArray} package for an example of a specific \code{which} method (defined for \link[DelayedArray]{DelayedArray} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ which showMethods("which") selectMethod("which", "ANY") # the default method library(DelayedArray) showMethods("which") ## The which() method for DelayedArray objects: selectMethod("which", "DelayedArray") } \keyword{methods} BiocGenerics/man/which.min.Rd0000644000175200017520000000522514136047726017074 0ustar00biocbuildbiocbuild\name{which.min} \alias{which.min} \alias{which.max} \title{What's the index of the first min or max value in an object?} \description{ Determines the location (i.e. index) of the (first) minimum or maximum value in an object. NOTE: This man page is for the \code{which.min} and \code{which.max} \emph{S4 generic functions} defined in the \pkg{BiocGenerics} package. See \code{?base::\link[base]{which.min}} for the default methods (defined in the \pkg{base} package). Bioconductor packages can define specific methods for objects (typically vector-, array-, or list-like) not supported by the default methods. } \usage{ which.min(x, ...) which.max(x, ...) } \arguments{ \item{x}{ An object, typically with a vector-, array-, or list-like semantic. } \item{...}{ Additional arguments, for use in specific methods. } } \value{ See \code{?base::\link[base]{which.min}} for the value returned by the default methods. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default methods. } \note{ The default methods (defined in the \pkg{base} package) only take a single argument. We've added the \code{...} argument to the generic functions defined in the \pkg{BiocGenerics} package so they can be called with an arbitrary number of effective arguments. This typically allows methods to add extra arguments for controlling/altering the behavior of the operation. Like for example the \code{global} argument supported by the \code{which.max} method for \link[IRanges]{NumericList} objects (defined in the \pkg{IRanges} package). } \seealso{ \itemize{ \item \code{base::\link[base]{which.min}} for the default \code{which.min} and \code{which.max} methods. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[IRanges]{which.max,NumericList-method} in the \pkg{IRanges} package for an example of a specific \code{which.max} method (defined for \link[IRanges]{NumericList} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ which.min showMethods("which.min") selectMethod("which.min", "ANY") # the default method which.max showMethods("which.max") selectMethod("which.max", "ANY") # the default method library(IRanges) showMethods("which.max") ## The which.max() method for NumericList objects: selectMethod("which.max", "NumericList") } \keyword{methods} BiocGenerics/man/xtabs.Rd0000644000175200017520000000416014136047726016326 0ustar00biocbuildbiocbuild\name{xtabs} \alias{xtabs} \title{Cross tabulation} \description{ \code{xtabs} creates a contingency table (optionally a sparse matrix) from cross-classifying factors, usually contained in a data-frame-like object, using a formula interface. NOTE: This man page is for the \code{xtabs} \emph{S4 generic function} defined in the \pkg{BiocGenerics} package. See \code{?stats::\link[stats]{xtabs}} for the default method (defined in the \pkg{stats} package). Bioconductor packages can define specific methods for objects not supported by the default method. } \usage{ xtabs(formula=~., data=parent.frame(), subset, sparse=FALSE, na.action, addNA=FALSE, exclude=if(!addNA)c(NA, NaN), drop.unused.levels=FALSE) } \arguments{ \item{formula, subset, sparse, na.action, addNA, exclude, drop.unused.levels}{ See \code{?stats::\link[stats]{xtabs}} for a description of these arguments. } \item{data}{ A data-frame-like object. } } \value{ See \code{?stats::\link[stats]{xtabs}} for the value returned by the default method. Specific methods defined in Bioconductor packages should also return the type of object returned by the default method. } \seealso{ \itemize{ \item \code{stats::\link[stats]{xtabs}} for the default \code{xtabs} method. \item \code{\link[methods]{showMethods}} for displaying a summary of the methods defined for a given generic function. \item \code{\link[methods]{selectMethod}} for getting the definition of a specific method. \item \link[S4Vectors]{xtabs,DataFrame-method} in the \pkg{S4Vectors} package for an example of a specific \code{xtabs} method (defined for \link[S4Vectors]{DataFrame} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the \pkg{BiocGenerics} package. } } \examples{ xtabs # note the dispatch on the 'data' arg only showMethods("xtabs") selectMethod("xtabs", "ANY") # the default method library(S4Vectors) showMethods("xtabs") ## The xtabs() method for DataFrame objects: selectMethod("xtabs", "DataFrame") } \keyword{methods} BiocGenerics/tests/0000755000175200017520000000000014136047726015304 5ustar00biocbuildbiocbuildBiocGenerics/tests/run_unitTests.R0000644000175200017520000000013614136047726020315 0ustar00biocbuildbiocbuildrequire("BiocGenerics") || stop("unable to load BiocGenerics package") BiocGenerics:::.test()