BiocGenerics/DESCRIPTION0000644000126300012640000000216412227143057016205 0ustar00biocbuildphs_compbioPackage: BiocGenerics Title: Generic functions for Bioconductor Description: S4 generic functions needed by many Bioconductor packages. Version: 0.8.0 Author: The Bioconductor Dev Team Maintainer: Bioconductor Package Maintainer biocViews: Infrastructure Depends: methods, graphics, stats, parallel Imports: methods, graphics, stats, parallel Suggests: Biobase, IRanges, GenomicRanges, AnnotationDbi, oligoClasses, oligo, affyPLM, flowClust, affy, RUnit, DESeq2 License: Artistic-2.0 Collate: S3-classes-as-S4-classes.R append.R as.data.frame.R as.vector.R cbind.R dge.R plotMA.R duplicated.R eval.R Extremes.R funprog.R get.R is.unsorted.R lapply.R mapply.R match.R nrow.R order.R paste.R rank.R rep.R row_colnames.R sets.R sort.R table.R tapply.R unique.R unlist.R boxplot.R image.R density.R residuals.R weights.R xtabs.R clusterApply.R annotation.R combine.R normalize.R normarg-utils.R show-utils.R strand.R updateObject.R update.R testPackage.R test_BiocGenerics_package.R zzz.R Packaged: 2013-10-15 04:35:59 UTC; biocbuild BiocGenerics/NAMESPACE0000644000126300012640000000621512227065015015714 0ustar00biocbuildphs_compbioimport(methods) import(graphics) import(stats) import(parallel) exportClasses( ## from R/S3-classes-as-S4-classes.R: connection, file, url, gzfile, bzfile, unz, pipe, fifo, sockconn, terminal, textConnection, gzcon, characterORconnection, AsIs #table, xtabs ) ### ========================================================================== ### 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.vector.R: as.vector, ## from R/cbind.R: cbind, rbind, ## 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/is.unsorted.R: is.unsorted, ## from R/lapply.R: lapply, sapply, ## from R/mapply.R: mapply, ## from R/match.R: match, ## 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, colnames, ## from R/sets.R: union, intersect, setdiff, ## from R/sort.R: sort, ## from R/table.R: table, ## from R/tapply.R: tapply, ## from R/unique.R: unique, ## from R/unlist.R: unlist ) ### 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/residuals.R: residuals, ## from R/weights.R: weights, ## from R/xtabs.R: xtabs ) ### Generics for functions defined in package parallel: export( ## from R/clusterApply.R: clusterCall, clusterApply, clusterApplyLB, clusterEvalQ, clusterExport, clusterMap, clusterSplit, parLapply, parSapply, parApply, parRapply, parCapply, parLapplyLB, parSapplyLB ) ### ========================================================================== ### Bioconductor specific generics and their methods ### -------------------------------------------------------------------------- export( ## from R/annotation.R: annotation, "annotation<-", ## from R/combine.R: combine, ## from R/normalize.R: normalize, ## from R/strand.R: strand, "strand<-", ## 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 ) BiocGenerics/R/0000755000126300012640000000000012227065012014667 5ustar00biocbuildphs_compbioBiocGenerics/R/Extremes.R0000644000126300012640000000165412227065012016614 0ustar00biocbuildphs_compbio### ========================================================================= ### 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/S3-classes-as-S4-classes.R0000644000126300012640000000222312227065012021251 0ustar00biocbuildphs_compbio### ========================================================================= ### 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("characterORconnection", 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’ BiocGenerics/R/annotation.R0000644000126300012640000000060512227065012017165 0ustar00biocbuildphs_compbio### ========================================================================= ### The annotation() and `annotation<-`() generics ### ------------------------------------------------------------------------- setGeneric("annotation", function(object, ...) standardGeneric("annotation") ) setGeneric("annotation<-", function(object, ..., value) standardGeneric("annotation<-") ) BiocGenerics/R/append.R0000644000126300012640000000071112227065012016260 0ustar00biocbuildphs_compbio### ========================================================================= ### 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.R0000644000126300012640000000042712227065012017421 0ustar00biocbuildphs_compbio### ========================================================================= ### The as.data.frame() generic ### ------------------------------------------------------------------------- ### ### base::as.data.frame is an S3 generic. setGeneric("as.data.frame", signature="x") BiocGenerics/R/as.vector.R0000644000126300012640000000064212227065012016720 0ustar00biocbuildphs_compbio### ========================================================================= ### 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.R0000644000126300012640000000037212227065012016503 0ustar00biocbuildphs_compbio### ========================================================================= ### The boxplot() generic ### ------------------------------------------------------------------------- ### ### graphics::boxplot is an S3 generic. setGeneric("boxplot") BiocGenerics/R/cbind.R0000644000126300012640000000075012227065012016073 0ustar00biocbuildphs_compbio### ========================================================================= ### 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/clusterApply.R0000644000126300012640000000174212227065012017505 0ustar00biocbuildphs_compbio### ========================================================================= ### The clusterApply() and related generics ### ------------------------------------------------------------------------- ### The corresponding functions are ordinary functions defined in the ### parallel package. setGeneric("clusterCall", signature="cl") setGeneric("clusterApply", signature=c("cl", "x")) setGeneric("clusterApplyLB", signature=c("cl", "x")) setGeneric("clusterEvalQ", signature="cl") setGeneric("clusterExport", signature="cl") setGeneric("clusterMap", signature="cl") setGeneric("clusterSplit") # dispatch on all arguments ('cl' and 'seq') setGeneric("parLapply", signature=c("cl", "X")) setGeneric("parSapply", signature=c("cl", "X")) setGeneric("parApply", signature=c("cl", "X")) setGeneric("parRapply", signature=c("cl", "x")) setGeneric("parCapply", signature=c("cl", "x")) setGeneric("parLapplyLB", signature=c("cl", "X")) setGeneric("parSapplyLB", signature=c("cl", "X")) BiocGenerics/R/combine.R0000644000126300012640000001467112227065012016437 0ustar00biocbuildphs_compbio### ========================================================================= ### 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/density.R0000644000126300012640000000036712227065012016477 0ustar00biocbuildphs_compbio### ========================================================================= ### The density() generic ### ------------------------------------------------------------------------- ### ### stats::density is an S3 generic. setGeneric("density") BiocGenerics/R/dge.R0000644000126300012640000000236612227065012015560 0ustar00biocbuildphs_compbio# 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/duplicated.R0000644000126300012640000000076112227065012017134 0ustar00biocbuildphs_compbio### ========================================================================= ### 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.R0000644000126300012640000000161712227065012015746 0ustar00biocbuildphs_compbio### ========================================================================= ### 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/funprog.R0000644000126300012640000000126612227065012016477 0ustar00biocbuildphs_compbio### ========================================================================= ### 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.R0000644000126300012640000000106612227065012015574 0ustar00biocbuildphs_compbio### ========================================================================= ### 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/image.R0000644000126300012640000000036412227065012016077 0ustar00biocbuildphs_compbio### ========================================================================= ### The image() generic ### ------------------------------------------------------------------------- ### ### graphics::image is an S3 generic. setGeneric("image") BiocGenerics/R/is.unsorted.R0000644000126300012640000000052412227065012017270 0ustar00biocbuildphs_compbio### ========================================================================= ### The is.unsorted() generic ### ------------------------------------------------------------------------- setGeneric("is.unsorted", function(x, na.rm = FALSE, strictly = FALSE) standardGeneric("is.unsorted"), signature = "x") BiocGenerics/R/lapply.R0000644000126300012640000000073012227065012016313 0ustar00biocbuildphs_compbio### ========================================================================= ### 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/mapply.R0000644000126300012640000000076412227065012016323 0ustar00biocbuildphs_compbio### ========================================================================= ### 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.R0000644000126300012640000000133212227065012016105 0ustar00biocbuildphs_compbio### ========================================================================= ### 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 ) BiocGenerics/R/normalize.R0000644000126300012640000000041412227065012017011 0ustar00biocbuildphs_compbio### ========================================================================= ### The normalize() generic ### ------------------------------------------------------------------------- setGeneric("normalize", function(object, ...) standardGeneric("normalize") ) BiocGenerics/R/normarg-utils.R0000644000126300012640000000177112227065012017623 0ustar00biocbuildphs_compbio### ========================================================================= ### Utility functions for checking/fixing user-supplied arguments ### ------------------------------------------------------------------------- ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ### 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.R0000644000126300012640000000056612227065012016006 0ustar00biocbuildphs_compbio### ========================================================================= ### 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.R0000644000126300012640000000067412227065012016134 0ustar00biocbuildphs_compbio### ========================================================================= ### The order() generic ### ------------------------------------------------------------------------- ### ### Need to explicitly define this generic otherwise the implicit generic in ### package "base" would dispatch on ('na.last', 'decreasing'). ### ### Note that dispatching on '...' is supported starting with R 2.8.0 only. setGeneric("order", signature="...") BiocGenerics/R/paste.R0000644000126300012640000000066612227065012016136 0ustar00biocbuildphs_compbio### ========================================================================= ### 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/plotMA.R0000644000126300012640000000102512227065012016204 0ustar00biocbuildphs_compbiosetGeneric("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/rank.R0000644000126300012640000000033312227065012015744 0ustar00biocbuildphs_compbio### ========================================================================= ### The rank() generic ### ------------------------------------------------------------------------- ### setGeneric("rank", signature="x") BiocGenerics/R/rep.R0000644000126300012640000000244412227065012015604 0ustar00biocbuildphs_compbio### ========================================================================= ### The rep() and rep.int() generics ### ------------------------------------------------------------------------- ### Actually, rep() seems to be already a generic function (that's what the ### man page claims) but the reality is confusing. On a fresh R session (this ### is with R-2.14.0): ### ### > isGeneric("rep") ### [1] FALSE ### > showMethods("rep") ### Function: rep (package base) ### ### > isGeneric("rep") ### [1] TRUE ### #setGeneric("rep") ### A more natural (and cleaner) thing to do for this generic would be to ### use the same arguments as base::rep.int() (i.e. 'x', 'times') but then ### 'R CMD check' would get confused and think that we are trying to define ### an S3 method for base::rep and would complain (observed with R <= 2.12): ### ### * checking S3 generic/method consistency ... WARNING ### rep: ### function(x, ...) ### rep.int: ### function(x, times) ### ### so we use the arguments of base::rep() (i.e. 'x', '...') just to make ### 'R CMD check' happy :-) ... Kind of an ugly/silly hack though :-( .rep.int.useAsDefault <- function(x, ...) base::rep.int(x, ...) setGeneric("rep.int", function(x, ...) standardGeneric("rep.int"), useAsDefault=.rep.int.useAsDefault ) BiocGenerics/R/residuals.R0000644000126300012640000000037512227065012017012 0ustar00biocbuildphs_compbio### ========================================================================= ### The residuals() generic ### ------------------------------------------------------------------------- ### ### stats::residuals is an S3 generic. setGeneric("residuals") BiocGenerics/R/row_colnames.R0000644000126300012640000000074312227065012017506 0ustar00biocbuildphs_compbio### ========================================================================= ### The rownames() and colnames() generics ### ------------------------------------------------------------------------- ### ### Need to explicitly define those generics otherwise the implicit generics ### in package "base" would dispatch on 'do.NULL' and 'prefix'. Here we set ### dispatch on the 1st arg (the 'x' arg) only! setGeneric("rownames", signature="x") setGeneric("colnames", signature="x") BiocGenerics/R/sets.R0000644000126300012640000000204612227065012015772 0ustar00biocbuildphs_compbio### ========================================================================= ### 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/show-utils.R0000644000126300012640000000356212227065012017136 0ustar00biocbuildphs_compbio### ========================================================================= ### Utilities for showing object components in a systematic way ### ------------------------------------------------------------------------- ### labeledLine <- function(label, els, count = TRUE, labelSep = ":", sep = " ", ellipsis = "...") { if (count) label <- paste(label, "(", length(els), ")", sep = "") label <- paste(label, labelSep, sep, sep = "") width <- getOption("width") - nchar(label) line <- ellipsize(els, width, sep, ellipsis) paste(label, line, "\n", sep = "") } ellipsize <- function(obj, width = getOption("width"), sep = " ", ellipsis = "...") { if (length(obj) > 2 * width) obj <- c(head(obj, width), tail(obj, width)) str <- encodeString(obj) ## get order selectSome() would print half <- seq_len(ceiling(length(obj) / 2)) ind <- as.vector(rbind(half, length(obj) - half + 1)) nc <- cumsum(nchar(str[ind]) + nchar(sep)) - nchar(sep) last <- findInterval(width, nc) if (length(obj) > last) { ## make sure ellipsis fits while (last && (nc[last] + nchar(sep)*2^(last>1) + nchar(ellipsis)) > width) last <- last - 1L if (last == 0) ## have to truncate the first element str <- paste(substring(str[1L], 1, width - nchar(ellipsis)), ellipsis, sep = "") else if (last == 1) ## can only show the first str <- c(str[1L], "...") else str <- selectSome(str, last + 1L) } paste(str, collapse = sep) } ## taken directly from Biobase selectSome <- function(obj, maxToShow = 5) { len <- length(obj) if (maxToShow < 3) maxToShow <- 3 if (len > maxToShow) { maxToShow <- maxToShow - 1 bot <- ceiling(maxToShow/2) top <- len - (maxToShow - bot - 1) nms <- obj[c(1:bot, top:len)] c(as.character(nms[1:bot]), "...", as.character(nms[-c(1:bot)])) } else { obj } } BiocGenerics/R/sort.R0000644000126300012640000000037412227065012016005 0ustar00biocbuildphs_compbio### ========================================================================= ### The sort() generic ### ------------------------------------------------------------------------- ### ### base::sort is an S3 generic. setGeneric("sort", signature="x") BiocGenerics/R/strand.R0000644000126300012640000000052712227065012016311 0ustar00biocbuildphs_compbio### ========================================================================= ### The strand() and `strand<-`() generics ### ------------------------------------------------------------------------- setGeneric("strand", function(x, ...) standardGeneric("strand")) setGeneric("strand<-", function(x, ..., value) standardGeneric("strand<-")) BiocGenerics/R/table.R0000644000126300012640000000203712227065012016103 0ustar00biocbuildphs_compbio### ========================================================================= ### 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.R0000644000126300012640000000064712227065012016332 0ustar00biocbuildphs_compbio### ========================================================================= ### 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.R0000644000126300012640000000342412227065012017250 0ustar00biocbuildphs_compbio### testPackage <- function(pkgname, subdir="unitTests", pattern="^test_.*\\.R$") { .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() } require(pkgname, quietly=TRUE, character.only=TRUE) || stop("package '", pkgname, "' not found") dir <- system.file(subdir, package=pkgname) if (nchar(dir) == 0L) stop("unable to find unit tests, no '", subdir, "' dir") require("RUnit", quietly=TRUE) || stop("RUnit package not found") RUnit_opts <- getOption("RUnit", list()) RUnit_opts$verbose <- 0L RUnit_opts$silent <- TRUE RUnit_opts$verbose_fail_msg <- TRUE options(RUnit = RUnit_opts) suite <- defineTestSuite(name=paste(pkgname, "RUnit Tests"), dirs=dir, testFileRegexp=pattern, rngKind="default", rngNormalKind="default") result <- runTestSuite(suite) cat("\n\n") 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/test_BiocGenerics_package.R0000644000126300012640000000006012227065012022054 0ustar00biocbuildphs_compbio.test <- function() testPackage("BiocGenerics") BiocGenerics/R/unique.R0000644000126300012640000000064512227065012016325 0ustar00biocbuildphs_compbio### ========================================================================= ### 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.R0000644000126300012640000000040212227065012016324 0ustar00biocbuildphs_compbio### ========================================================================= ### The unlist() generic ### ------------------------------------------------------------------------- ### ### base::unlist is an S3 generic. setGeneric("unlist", signature="x") BiocGenerics/R/update.R0000644000126300012640000000254612227065012016303 0ustar00biocbuildphs_compbio### ========================================================================= ### Efficient update behavior for S4 objects ### ------------------------------------------------------------------------- ### ### 'updateS4' is essentially a more efficient initialize for (value) S4 objects. unsafe_updateS4 <- function(object, ..., .slotList = list()) { valid_argnames <- slotNames(object) args <- extraArgsAsList(valid_argnames, ...) firstTime <- TRUE listUpdate <- function(object, l) { for (nm in names(l)) { ## 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() needs ## to be fixed first. ##if (identical(slot(object, nm), l[[nm]])) ## next if (firstTime) { ## Triggers a copy. slot(object, nm, check=FALSE) <- l[[nm]] firstTime <<- FALSE } else { ## In-place modification (i.e. no copy). `slot<-`(object, nm, check=FALSE, l[[nm]]) } } object } listUpdate(listUpdate(object, args), .slotList) } updateS4 <- function(object, ..., check = TRUE) { if (!isTRUEorFALSE(check)) stop("'check' must be TRUE or FALSE") object <- unsafe_updateS4(object, ...) if (check) { validObject(object) } object } BiocGenerics/R/updateObject.R0000644000126300012640000001406412227065012017430 0ustar00biocbuildphs_compbio### ========================================================================= ### The updateObject() generic and related utilities ### ------------------------------------------------------------------------- ### ### An "updateObject" default method + methods for some standard types are ### also provided. ### ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ### Utilities. ### 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) } errf <- function(...) { function(err) { if (verbose) message(..., ":\n ", conditionMessage(err), "\n trying next method...") NULL } } 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=errf("'new(\"", objclass, "\", ...)' from slots failed")) } 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=errf("failed to add slots to 'new(\"", objclass, "\", ...)'")) } if (is.null(res)) stop("could not updateObject to class '", objclass, "'", "\nconsider defining an 'updateObject' method for class '", class(object), "'") res } ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ### updateObject() ### setGeneric("updateObject", signature="object", function(object, ..., verbose=FALSE) { result <- standardGeneric("updateObject") validObject(result) 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"))) { 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 } ) BiocGenerics/R/weights.R0000644000126300012640000000036712227065012016472 0ustar00biocbuildphs_compbio### ========================================================================= ### The weights() generic ### ------------------------------------------------------------------------- ### ### stats::weights is an S3 generic. setGeneric("weights") BiocGenerics/R/xtabs.R0000644000126300012640000000064512227065012016140 0ustar00biocbuildphs_compbio### ========================================================================= ### 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.R0000644000126300012640000000000512227065012015642 0ustar00biocbuildphs_compbio### BiocGenerics/TODO0000644000126300012640000000504312227065015015163 0ustar00biocbuildphs_compbioo 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: - is.unsorted(): implicit generic dispatches on (x, na.rm, strictly). Explicit generic should dispatch on (x) only. - 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. o Move all the generics for count datasets defined in Biobase (and used by the DESeq and DEXSeq packages) to BiocGenerics. BiocGenerics/inst/0000755000126300012640000000000012227065015015446 5ustar00biocbuildphs_compbioBiocGenerics/inst/unitTests/0000755000126300012640000000000012227065015017450 5ustar00biocbuildphs_compbioBiocGenerics/inst/unitTests/test_combine.R0000644000126300012640000002005112227065015022244 0ustar00biocbuildphs_compbio### 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)]) ## 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]) y <- data.frame(z=2:3, y=letters[2:3], row.names=letters[2:3]) 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])) } 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=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_updateObject.R0000644000126300012640000000473312227065015023252 0ustar00biocbuildphs_compbio### 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) } BiocGenerics/man/0000755000126300012640000000000012227065015015244 5ustar00biocbuildphs_compbioBiocGenerics/man/BiocGenerics-package.Rd0000644000126300012640000001527012227065015021465 0ustar00biocbuildphs_compbio\name{BiocGenerics-package} \alias{BiocGenerics-package} \alias{BiocGenerics} \docType{package} \title{Generic functions for Bioconductor} \description{ S4 generic functions needed by many Bioconductor packages. } \details{ We divide the generic functions defined in the 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 BiocGenerics package}{ Generics for functions defined in package base: \itemize{ \item \code{BiocGenerics::\link[BiocGenerics]{append}} \item \code{BiocGenerics::\link[BiocGenerics]{as.data.frame}} \item \code{BiocGenerics::\link[BiocGenerics]{as.vector}} \item \code{BiocGenerics::\link[BiocGenerics]{cbind}}, \code{BiocGenerics::\link[BiocGenerics]{rbind}} \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]{lapply}}, \code{BiocGenerics::\link[BiocGenerics]{sapply}} \item \code{BiocGenerics::\link[BiocGenerics]{mapply}} \item \code{BiocGenerics::\link[BiocGenerics]{match}} \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]{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]{table}} \item \code{BiocGenerics::\link[BiocGenerics]{tapply}} \item \code{BiocGenerics::\link[BiocGenerics]{unique}} \item \code{BiocGenerics::\link[BiocGenerics]{unlist}} } Generics for functions defined in package graphics: \itemize{ \item \code{BiocGenerics::\link[BiocGenerics]{boxplot}} \item \code{BiocGenerics::\link[BiocGenerics]{image}} } Generics for functions defined in package 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}} } Generics for functions defined in package parallel: \itemize{ \item \code{BiocGenerics::\link[BiocGenerics]{clusterCall}}, \code{BiocGenerics::\link[BiocGenerics]{clusterApply}}, \code{BiocGenerics::\link[BiocGenerics]{clusterApplyLB}}, \code{BiocGenerics::\link[BiocGenerics]{clusterEvalQ}}, \code{BiocGenerics::\link[BiocGenerics]{clusterExport}}, \code{BiocGenerics::\link[BiocGenerics]{clusterMap}}, \code{BiocGenerics::\link[BiocGenerics]{clusterSplit}}, \code{BiocGenerics::\link[BiocGenerics]{parLapply}}, \code{BiocGenerics::\link[BiocGenerics]{parSapply}}, \code{BiocGenerics::\link[BiocGenerics]{parApply}}, \code{BiocGenerics::\link[BiocGenerics]{parRapply}}, \code{BiocGenerics::\link[BiocGenerics]{parCapply}}, \code{BiocGenerics::\link[BiocGenerics]{parLapplyLB}}, \code{BiocGenerics::\link[BiocGenerics]{parSapplyLB}} } } \subsection{(2) Bioconductor specific generics}{ \itemize{ \item \code{\link[BiocGenerics]{annotation}}, \code{\link[BiocGenerics]{annotation<-}} \item \code{\link[BiocGenerics]{combine}} \item \code{\link[BiocGenerics]{normalize}} \item \code{\link[BiocGenerics]{strand}}, \code{\link[BiocGenerics]{strand<-}} \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 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 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 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.Rd0000644000126300012640000000431312227065015017330 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?base::\link[base]{pmax}} for the default methods (defined in the 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[IRanges]{pmax,Rle-method} in the IRanges package for an example of a specific \code{pmax} method (defined for \link[IRanges]{Rle} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the 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/S3-classes-as-S4-classes.Rd0000644000126300012640000000225012227065015021772 0ustar00biocbuildphs_compbio\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{characterORconnection-class} \alias{AsIs-class} %\alias{table-class} %\alias{xtabs-class} \title{S3 classes as S4 classes} \description{ Some old-style (aka S3) classes are turned into formally defined (aka S4) classes by the 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: connection, file, url, gzfile, bzfile, unz, pipe, fifo, sockconn, terminal, textConnection, gzcon. Addtitionally the characterORconnection S4 class is defined as the union of classes character and connection. \item others: AsIs } } \seealso{ \link{setOldClass} and \link{setClassUnion} in the methods package. } \keyword{classes} BiocGenerics/man/annotation.Rd0000644000126300012640000000226612227065015017713 0ustar00biocbuildphs_compbio\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 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 BiocGenerics package. } } \examples{ annotation showMethods("annotation") library(Biobase) showMethods("annotation") selectMethod("annotation", "eSet") } \keyword{methods} BiocGenerics/man/append.Rd0000644000126300012640000000374112227065015017007 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?base::\link[base]{append}} for the default method (defined in the 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[IRanges]{append,Vector,Vector-method} in the IRanges package for an example of a specific \code{append} method (defined for \link[IRanges]{Vector} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the 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.Rd0000644000126300012640000000364312227065015020145 0ustar00biocbuildphs_compbio\name{as.data.frame} \alias{as.data.frame} \title{Coerce an object into a data frame} \description{ 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 BiocGenerics package. See \code{?base::\link[base]{as.data.frame}} for the default method (defined in the 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{ A 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[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]{as.data.frame,Ranges-method} and \link[IRanges]{as.data.frame,DataFrame-method} in the IRanges package for examples of specific \code{as.data.frame} methods (defined for \link[IRanges]{Ranges} and \link[IRanges]{DataFrame} objects, respectively). \item \link{BiocGenerics} for a summary of all the generics defined in the 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.vector.Rd0000644000126300012640000000372012227065015017441 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?base::\link[base]{as.vector}} for the default method (defined in the 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[IRanges]{as.vector,Rle-method} and \link[IRanges]{as.vector,AtomicList-method} in the IRanges package for examples of specific \code{as.vector} methods (defined for \link[IRanges]{Rle} and \link[IRanges]{AtomicList} objects, respectively). \item \link{BiocGenerics} for a summary of all the generics defined in the 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.Rd0000644000126300012640000000310212227065015017216 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?graphics::\link[graphics]{boxplot}} for the default method (defined in the 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[oligo]{boxplot,FeatureSet-method} in the oligo package for an example of a specific \code{boxplot} method (defined for \link[oligoClasses]{FeatureSet} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the BiocGenerics package. } } \examples{ boxplot showMethods("boxplot") selectMethod("boxplot", "ANY") # the default method } \keyword{methods} BiocGenerics/man/cbind.Rd0000644000126300012640000000402612227065015016614 0ustar00biocbuildphs_compbio\name{cbind} \alias{cbind} \alias{rbind} \title{Combine objects by rows or columns} \description{ \code{cbind} and \code{rbind} take one or more objects and combine them by columns or rows, respectively. NOTE: This man page is for the \code{cbind} and \code{rbind} \emph{S4 generic functions} defined in the BiocGenerics package. See \code{?base::\link[base]{cbind}} for the default methods (defined in the base package). Bioconductor packages can define specific methods for objects (typically vector-like or matrix-like) not supported by the default methods. } \usage{ cbind(..., deparse.level=1) rbind(..., 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{cbind} and \code{rbind} 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]{cbind,DataFrame-method} in the IRanges package for an example of a specific \code{cbind} method (defined for \link[IRanges]{DataFrame} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the BiocGenerics package. } } \examples{ cbind # note the dispatch on the '...' arg only showMethods("cbind") selectMethod("cbind", "ANY") # the default method rbind # note the dispatch on the '...' arg only showMethods("rbind") selectMethod("rbind", "ANY") # the default method } \keyword{methods} BiocGenerics/man/clusterApply.Rd0000644000126300012640000001211212227065015020217 0ustar00biocbuildphs_compbio\name{clusterApply} \alias{clusterCall} \alias{clusterApply} \alias{clusterApplyLB} \alias{clusterEvalQ} \alias{clusterExport} \alias{clusterMap} \alias{clusterSplit} \alias{parLapply} \alias{parSapply} \alias{parApply} \alias{parRapply} \alias{parCapply} \alias{parLapplyLB} \alias{parSapplyLB} \title{Apply operations using clusters} \description{ These functions provide several ways to parallelize computations using a cluster. NOTE: This man page is for the \code{clusterCall}, \code{clusterApply}, \code{clusterApplyLB}, \code{clusterEvalQ}, \code{clusterExport}, \code{clusterMap}, \code{clusterSplit}, \code{parLapply}, \code{parSapply}, \code{parApply}, \code{parRapply}, \code{parCapply}, \code{parLapplyLB}, and \code{parSapplyLB} \emph{S4 generic functions} defined in the BiocGenerics package. See \code{?parallel::\link[parallel]{clusterApply}} for the default methods (defined in the parallel package). Bioconductor packages can define specific methods for cluster-like objects not supported by the default methods. } \usage{ clusterCall(cl=NULL, fun, ...) clusterApply(cl=NULL, x, fun, ...) clusterApplyLB(cl=NULL, x, fun, ...) clusterEvalQ(cl=NULL, expr) clusterExport(cl=NULL, varlist, envir=.GlobalEnv) clusterMap(cl=NULL, fun, ..., MoreArgs=NULL, RECYCLE=TRUE, SIMPLIFY=FALSE, USE.NAMES=TRUE, .scheduling=c("static", "dynamic")) clusterSplit(cl=NULL, seq) parLapply(cl=NULL, X, fun, ...) parSapply(cl=NULL, X, FUN, ..., simplify=TRUE, USE.NAMES=TRUE) parApply(cl=NULL, X, MARGIN, FUN, ...) parRapply(cl=NULL, x, FUN, ...) parCapply(cl=NULL, x, FUN, ...) parLapplyLB(cl=NULL, X, fun, ...) parSapplyLB(cl=NULL, X, FUN, ..., simplify=TRUE, USE.NAMES=TRUE) } \arguments{ \item{cl}{ A cluster-like object. } \item{x}{ A vector-like object for \code{clusterApply} and \code{clusterApplyLB}. A matrix-like object for \code{parRapply} and \code{parCapply}. } \item{seq}{ Vector-like object to split. } \item{X}{ A vector-like object for \code{parLapply}, \code{parSapply}, \code{parLapplyLB}, and \code{parSapplyLB}. An array-like object for \code{parApply}. } \item{fun, ..., expr, varlist, envir, MoreArgs, RECYCLE, SIMPLIFY, USE.NAMES, .scheduling, FUN, simplify, MARGIN}{ See \code{?parallel::\link[parallel]{clusterApply}} for a description of these arguments. } } \value{ See \code{?parallel::\link[parallel]{clusterApply}} for the value returned by the default methods. Specific methods defined in Bioconductor packages should behave like the default methods. } \seealso{ \itemize{ \item \code{parallel::\link[parallel]{clusterApply}} 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 BiocGenerics package. } } \examples{ clusterCall # note the dispatch on the 'cl' arg only showMethods("clusterCall") selectMethod("clusterCall", "ANY") # the default method clusterApply # note the dispatch on the 'cl' and 'x' args only showMethods("clusterApply") selectMethod("clusterApply", c("ANY", "ANY")) # the default method clusterApplyLB # note the dispatch on the 'cl' and 'x' args only showMethods("clusterApplyLB") selectMethod("clusterApplyLB", c("ANY", "ANY")) # the default method clusterEvalQ # note the dispatch on the 'cl' arg only showMethods("clusterEvalQ") selectMethod("clusterEvalQ", "ANY") # the default method clusterExport # note the dispatch on the 'cl' arg only showMethods("clusterExport") selectMethod("clusterExport", "ANY") # the default method clusterMap # note the dispatch on the 'cl' arg only showMethods("clusterMap") selectMethod("clusterMap", "ANY") # the default method clusterSplit showMethods("clusterSplit") selectMethod("clusterSplit", c("ANY", "ANY")) # the default method parLapply # note the dispatch on the 'cl' and 'X' args only showMethods("parLapply") selectMethod("parLapply", c("ANY", "ANY")) # the default method parSapply # note the dispatch on the 'cl' and 'X' args only showMethods("parSapply") selectMethod("parSapply", c("ANY", "ANY")) # the default method parApply # note the dispatch on the 'cl' and 'X' args only showMethods("parApply") selectMethod("parApply", c("ANY", "ANY")) # the default method parRapply # note the dispatch on the 'cl' and 'x' args only showMethods("parRapply") selectMethod("parRapply", c("ANY", "ANY")) # the default method parCapply # note the dispatch on the 'cl' and 'x' args only showMethods("parCapply") selectMethod("parCapply", c("ANY", "ANY")) # the default method parLapplyLB # note the dispatch on the 'cl' and 'X' args only showMethods("parLapplyLB") selectMethod("parLapplyLB", c("ANY", "ANY")) # the default method parSapplyLB # note the dispatch on the 'cl' and 'X' args only showMethods("parSapplyLB") selectMethod("parSapplyLB", c("ANY", "ANY")) # the default method } \keyword{methods} BiocGenerics/man/combine.Rd0000644000126300012640000001327012227065015017152 0ustar00biocbuildphs_compbio\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 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 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 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 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/density.Rd0000644000126300012640000000310412227065015017210 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?stats::\link[stats]{density}} for the default method (defined in the 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 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 BiocGenerics package. } } \examples{ density showMethods("density") selectMethod("density", "ANY") # the default method } \keyword{methods} BiocGenerics/man/dge.Rd0000644000126300012640000000261012227065015016271 0ustar00biocbuildphs_compbio\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 \code{DESeq}, \code{DESeq2}, and \code{DEXSeq} packages and the package vignettes.} \author{W. Huber, S. Anders} \keyword{manip} BiocGenerics/man/duplicated.Rd0000644000126300012640000000534312227065015017656 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?base::\link[base]{duplicated}} for the default methods (defined in the 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[IRanges]{duplicated,Ranges-method} in the IRanges package for an example of a specific \code{duplicated} method (defined for \link[IRanges]{Ranges} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the 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.Rd0000644000126300012640000000446312227065015016471 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?base::\link[base]{eval}} for the default method (defined in the 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,List-method} in the 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[IRanges]{List} object, respectively). \item \link{BiocGenerics} for a summary of all the generics defined in the 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.Rd0000644000126300012640000000231012227065015016637 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?base::\link[base]{evalq}} for the function defined in the 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/funprog.Rd0000644000126300012640000000611712227065015017220 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?base::\link[base]{Reduce}} for the default methods (defined in the 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[IRanges]{Reduce,List-method} in the IRanges package for an example of a specific \code{Reduce} method (defined for \link[IRanges]{List} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the 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.Rd0000644000126300012640000000473412227065015016322 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?base::\link[base]{get}} for the default methods (defined in the 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 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 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/image.Rd0000644000126300012640000000322512227065015016617 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?graphics::\link[graphics]{image}} for the default method (defined in the 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[oligo]{image,FeatureSet-method} in the oligo package for an example of a specific \code{image} method (defined for \link[oligoClasses]{FeatureSet} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the BiocGenerics package. } } \examples{ image showMethods("image") selectMethod("image", "ANY") # the default method } \keyword{methods} BiocGenerics/man/is.unsorted.Rd0000644000126300012640000000437212227065015020016 0ustar00biocbuildphs_compbio\name{is.unsorted} \alias{is.unsorted} \title{Test if an Object is Not Sorted} \description{ Test if an 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 BiocGenerics package. See \code{?base::\link[base]{is.unsorted}} for the default method (defined in the base package). Bioconductor packages can define specific methods for objects 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. } } \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 DEVELOPPERS: 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]{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[IRanges]{is.unsorted,Rle-method} in the IRanges package for an example of a specific \code{is.unsorted} method (defined for \link[IRanges]{Rle} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the 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.Rd0000644000126300012640000000473212227065015017042 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?base::\link[base]{lapply}} for the default methods (defined in the 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[IRanges]{lapply,List-method} in the IRanges package for an example of a specific \code{lapply} method (defined for \link[IRanges]{List} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the 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/mapply.Rd0000644000126300012640000000410212227065015017032 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?base::\link[base]{mapply}} for the default method (defined in the 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[IRanges]{mapply,List-method} in the IRanges package for an example of a specific \code{mapply} method (defined for \link[IRanges]{List} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the BiocGenerics package. } } \examples{ mapply # note the dispatch on the '...' arg only showMethods("mapply") selectMethod("mapply", "ANY") # the default method } \keyword{methods} BiocGenerics/man/match.Rd0000644000126300012640000000446712227065015016642 0ustar00biocbuildphs_compbio\name{match} \alias{match} \title{Value matching} \description{ \code{match} returns a vector of the positions of (first) matches of its first argument in its second. NOTE: This man page is for the \code{match} \emph{S4 generic function} defined in the BiocGenerics package. See \code{?base::\link[base]{match}} for the default method (defined in the base package). Bioconductor packages can define specific methods for objects (typically vector-like) not supported by the default method. } \usage{ match(x, table, nomatch=NA_integer_, incomparables=NULL, ...) } \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 method, that is, an integer vector of the same length as \code{x} giving the position in \code{table} of the first match if there is a match, otherwise \code{nomatch}. See \code{?base::\link[base]{match}} for more details. Specific methods defined in Bioconductor packages should behave as consistently as possible with the default method. } \note{ The default method (defined in the base package) doesn't have the \code{...} argument. We've added it to the generic function defined in the 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} 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]{match,Hits,Hits-method} in the IRanges package for an example of a specific \code{match} method (defined for \link[IRanges]{Hits} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the BiocGenerics package. } } \examples{ match # note the dispatch on the 'x' and 'table' args only showMethods("match") selectMethod("match", c("ANY", "ANY")) # the default method } \keyword{methods} BiocGenerics/man/normalize.Rd0000644000126300012640000000276512227065015017545 0ustar00biocbuildphs_compbio\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 affy package and \link[oligo]{normalize,FeatureSet-method} in the oligo package for examples of specific \code{normalize} methods (defined for \link[affy]{AffyBatch} and \link[oligoClasses]{FeatureSet} objects, respectively). \item \link{BiocGenerics} for a summary of all the generics defined in the BiocGenerics package. } } \examples{ normalize showMethods("normalize") library(affy) showMethods("normalize") selectMethod("normalize", "AffyBatch") } \keyword{methods} BiocGenerics/man/nrow.Rd0000644000126300012640000000357612227065015016533 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?base::\link[base]{nrow}} for the default methods (defined in the 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[IRanges]{nrow,DataFrame-method} in the IRanges package for an example of a specific \code{nrow} method (defined for \link[IRanges]{DataFrame} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the 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.Rd0000644000126300012640000000565312227065015016657 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?base::\link[base]{order}} for the default method (defined in the 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) } \arguments{ \item{...}{ One or more vector-like objects, all of the same length. } \item{na.last, decreasing}{ 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 DEVELOPPERS: 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,Ranges-method} in the IRanges package for an example of a specific \code{order} method (defined for \link[IRanges]{Ranges} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the BiocGenerics package. } } \examples{ order showMethods("order") selectMethod("order", "ANY") # the default method } \keyword{methods} BiocGenerics/man/paste.Rd0000644000126300012640000000332712227065015016654 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?base::\link[base]{paste}} for the default method (defined in the 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) } \arguments{ \item{...}{ One or more vector-like objects containing strings. } \item{sep, collapse}{ 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[IRanges]{paste,Rle-method} in the IRanges package for an example of a specific \code{paste} method (defined for \link[IRanges]{Rle} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the BiocGenerics package. } } \examples{ paste showMethods("paste") selectMethod("paste", "ANY") # the default method } \keyword{methods} BiocGenerics/man/plotMA.Rd0000644000126300012640000000242112227065015016726 0ustar00biocbuildphs_compbio\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 \code{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 BiocGenerics package. } } \examples{ showMethods("plotMA") suppressWarnings( if(require("DESeq2")) example("plotMA", package="DESeq2", local=TRUE) ) } \keyword{methods} BiocGenerics/man/rank.Rd0000644000126300012640000000442712227065015016475 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?base::\link[base]{rank}} for the default method (defined in the 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", "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. } } \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 DEVELOPPERS: 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[IRanges]{rank,Ranges-method} in the IRanges package for an example of a specific \code{rank} method (defined for \link[IRanges]{Ranges} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the BiocGenerics package. } } \examples{ rank # note the dispatch on the 'x' arg only showMethods("rank") selectMethod("rank", "ANY") # the default method } \keyword{methods} BiocGenerics/man/rep.Rd0000644000126300012640000000354212227065015016325 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?base::\link[base]{rep.int}} for the default method (defined in the base package). Bioconductor packages can define specific methods for objects (typically vector-like) not supported by the default method. } \usage{ ## Unlike the standard rep.int() function defined in base (default method), ## the generic function described here have a '...' argument (instead of ## 'times'). rep.int(x, ...) } \arguments{ \item{x}{ The object to replicate (typically vector-like). } \item{...}{ Additional arguments, for use in specific \code{rep.int} methods. } } \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[IRanges]{rep.int,Rle-method} in the IRanges package for an example of a specific \code{rep.int} method (defined for \link[IRanges]{Rle} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the BiocGenerics package. } } \examples{ rep.int showMethods("rep.int") selectMethod("rep.int", "ANY") # the default method } \keyword{methods} BiocGenerics/man/residuals.Rd0000644000126300012640000000274612227065015017537 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?stats::\link[stats]{residuals}} for the default method (defined in the 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 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 BiocGenerics package. } } \examples{ residuals showMethods("residuals") selectMethod("residuals", "ANY") # the default method } \keyword{methods} BiocGenerics/man/row_colnames.Rd0000644000126300012640000000416212227065015020226 0ustar00biocbuildphs_compbio\name{row+colnames} \alias{row+colnames} \alias{rownames} \alias{colnames} \title{Row and column names} \description{ Retrieve the row or column names of a matrix-like object. NOTE: This man page is for the \code{rownames} and \code{colnames} \emph{S4 generic functions} defined in the BiocGenerics package. See \code{?base::\link[base]{rownames}} for the default methods (defined in the 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") colnames(x, do.NULL=TRUE, prefix="col") } \arguments{ \item{x}{ A matrix-like object. } \item{do.NULL, prefix}{ See \code{?base::\link[base]{rownames}} for a description of these arguments. } } \value{ \code{NULL} or a character vector of length \code{\link{nrow}(x)} for \code{rownames} and \code{\link{ncol}(x)} for \code{colnames(x)}. See \code{?base::\link[base]{rownames}} for more information about 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]{rownames}} for the default \code{rownames} 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[IRanges]{rownames,DataFrame-method} in the IRanges package for an example of a specific \code{rownames} method (defined for \link[IRanges]{DataFrame} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the BiocGenerics package. } } \examples{ rownames # note the dispatch on the 'x' arg only showMethods("rownames") selectMethod("rownames", "ANY") # the default method colnames # note the dispatch on the 'x' arg only showMethods("colnames") selectMethod("colnames", "ANY") # the default method } \keyword{methods} BiocGenerics/man/sets.Rd0000644000126300012640000000572312227065015016520 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?base::\link[base]{union}} for the default methods (defined in the 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 base package) only take 2 arguments. We've added the \code{...} argument to the generic functions defined in the 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]{GRanges} objects (defined in the 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,GRanges,GRanges-method} in the GenomicRanges package for an example of a specific \code{union} method (defined for \link[GenomicRanges]{GRanges} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the 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.Rd0000644000126300012640000000421612227065015016525 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?base::\link[base]{sort}} for the default method (defined in the 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 DEVELOPPERS: 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[IRanges]{sort,Vector-method} in the IRanges package for an example of a specific \code{sort} method (defined for \link[IRanges]{Vector} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the BiocGenerics package. } } \examples{ sort # note the dispatch on the 'x' arg only showMethods("sort") selectMethod("sort", "ANY") # the default method } \keyword{methods} BiocGenerics/man/strand.Rd0000644000126300012640000000275612227065015017040 0ustar00biocbuildphs_compbio\name{strand} \alias{strand} \alias{strand<-} \title{Accessing strand information} \description{ Get or set the strand information contained in an object. } \usage{ strand(x, ...) strand(x, ...) <- value } \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}. } } \note{ All the \code{strand} methods defined in the GenomicRanges package use the same set of 3 values (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. } \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 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 BiocGenerics package. } } \examples{ strand showMethods("strand") library(GenomicRanges) showMethods("strand") selectMethod("strand", "missing") strand() } \keyword{methods} BiocGenerics/man/table.Rd0000644000126300012640000000327712227065015016633 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?base::\link[base]{table}} for the default method (defined in the 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[IRanges]{table,Rle-method} in the IRanges package for an example of a specific \code{table} method (defined for \link[IRanges]{Rle} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the BiocGenerics package. } } \examples{ table showMethods("table") selectMethod("table", "ANY") # the default method } \keyword{methods} BiocGenerics/man/tapply.Rd0000644000126300012640000000357112227065015017052 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?base::\link[base]{tapply}} for the default method (defined in the base package). Bioconductor packages can define specific methods for objects (typically list-like or vector-like) not supported by the default methods. } \usage{ tapply(X, INDEX, FUN=NULL, ..., simplify=TRUE) } \arguments{ \item{X}{ A list-like or vector-like object. } \item{INDEX, FUN, ..., 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-method} in the IRanges package for an example of a specific \code{tapply} method (defined for \link[IRanges]{Vector} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the BiocGenerics package. } } \examples{ tapply # note the dispatch on the 'X' arg only showMethods("tapply") selectMethod("tapply", "ANY") # the default method } \keyword{methods} BiocGenerics/man/unique.Rd0000644000126300012640000000404012227065015017037 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?base::\link[base]{unique}} for the default method (defined in the 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[IRanges]{unique,Rle-method} in the IRanges package for an example of a specific \code{unique} method (defined for \link[IRanges]{Rle} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the BiocGenerics package. } } \examples{ unique showMethods("unique") selectMethod("unique", "ANY") # the default method } \keyword{methods} BiocGenerics/man/unlist.Rd0000644000126300012640000000356612227065015017063 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?base::\link[base]{unlist}} for the default method (defined in the 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[IRanges]{unlist,List-method} in the IRanges package for an example of a specific \code{unlist} method (defined for \link[IRanges]{List} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the BiocGenerics package. } } \examples{ unlist # note the dispatch on the 'x' arg only showMethods("unlist") selectMethod("unlist", "ANY") # the default method } \keyword{methods} BiocGenerics/man/updateObject.Rd0000644000126300012640000001242512227065015020150 0ustar00biocbuildphs_compbio\name{updateObject} \alias{updateObject} \alias{updateObject,ANY-method} \alias{updateObject,list-method} \alias{updateObject,environment-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)} } } \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. 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, \code{updateObjectFromSlots} then 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 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 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/weights.Rd0000644000126300012640000000323412227065015017207 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?stats::\link[stats]{weights}} for the default method (defined in the 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 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 BiocGenerics package. } } \examples{ weights showMethods("weights") selectMethod("weights", "ANY") # the default method } \keyword{methods} BiocGenerics/man/xtabs.Rd0000644000126300012640000000366512227065015016666 0ustar00biocbuildphs_compbio\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 BiocGenerics package. See \code{?stats::\link[stats]{xtabs}} for the default method (defined in the 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, exclude=c(NA, NaN), drop.unused.levels=FALSE) } \arguments{ \item{formula, subset, sparse, na.action, 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[IRanges]{xtabs,DataTable-method} in the IRanges package for an example of a specific \code{xtabs} method (defined for \link[IRanges]{DataTable} objects). \item \link{BiocGenerics} for a summary of all the generics defined in the BiocGenerics package. } } \examples{ xtabs # note the dispatch on the 'data' arg only showMethods("xtabs") selectMethod("xtabs", "ANY") # the default method } \keyword{methods} BiocGenerics/tests/0000755000126300012640000000000012227065012015630 5ustar00biocbuildphs_compbioBiocGenerics/tests/BiocGenerics_unit_tests.R0000644000126300012640000000013612227065012022570 0ustar00biocbuildphs_compbiorequire("BiocGenerics") || stop("unable to load BiocGenerics package") BiocGenerics:::.test()